Updated internal docs.

stopcriterion
Salvatore Filippone 5 years ago
parent 9d38bff674
commit bebdba6d61

@ -285,7 +285,7 @@ contains
!! The mapping is store in ILAGGR; for each local row index I,
!! ILAGGR(I) contains the index of the aggregate to which index I
!! will contribute, in global numbering.
!! Many aggregation produce a binary tentative prolongator, but some
!! Many aggregations produce a binary tentative prolongator, but some
!! do not, hence we also need the OP_PROL output.
!! AG_DATA is passed here just in case some of the
!! aggregators need it internally, most of them will ignore.

@ -56,6 +56,9 @@
! contains a SOLVER object: the SOLVER operates locally within the
! current process, whereas the SMOOTHER object accounts for (possible)
! interactions between processes.
! Some solvers (MUMPS and SuperLU_DIST) can also operate on the entire
! distributed matrix, in which case the smoother object essentially
! becomes transparent.
!
module mld_c_base_smoother_mod

@ -275,6 +275,18 @@ contains
end module mld_c_diag_solver
!
! Module: mld_c_l1_diag_solver_mod
!
! This module defines:
! - the mld_c_l1_diag_solver_type data structure containing the
! L1 diagonal solver.
! The solver is defined as a diagonal containing in each element the
! inverse of the sum of the absolute values of the matrix entries
! along the corresponding row.
! Combined with a Jacobi "smoother" generates
! what are commonly known as the L1-Jacobi iterations
!
module mld_c_l1_diag_solver

@ -48,7 +48,8 @@
! on the block diagonal). Combined with a Jacobi smoother will generate a
! hybrid-Gauss-Seidel solver, i.e. Gauss-Seidel within each process, Jacobi
! among the processes.
!
! With two objects as pre- and post-smoothers it is possible to build a
! Forward-Backward smoother, suitable for symmetric iterations.
!
module mld_c_gs_solver

@ -41,7 +41,7 @@
!
! Module: mld_c_ilu_fact_mod
!
! This module defines some interfaces used internally by the implementation if
! This module defines some interfaces used internally by the implementation of
! mld_c_ilu_solver, but not visible to the end user.
!
!

@ -51,7 +51,7 @@
! threshold base ILU(T,L)
! 3. The diagonal is stored separately, so strictly speaking this is
! an incomplete LDU factorization;
! 4. The application phase is shared;
! 4. The application phase is shared among all variants;
!
!
module mld_c_ilu_solver

@ -39,8 +39,7 @@
!
! Module: mld_inner_mod
!
! This module defines the interfaces to the real/complex, single/double
! precision versions of inner MLD2P4 routines.
! This module defines the interfaces to inner MLD2P4 routines.
! The interfaces of the user level routines are defined in mld_prec_mod.f90.
!
module mld_c_inner_mod

@ -44,10 +44,10 @@
! the mld_c_jac_smoother_type data structure containing the
! smoother for a Jacobi/block Jacobi smoother.
! The smoother stores in ND the block off-diagonal matrix.
! One special case is treated separately, when the solver is DIAG
! One special case is treated separately, when the solver is DIAG or L1-DIAG
! then the ND is the entire off-diagonal part of the matrix (including the
! main diagonal block), so that it becomes possible to implement
! pure Jacobi global solver.
! a pure Jacobi or L1-Jacobi global solver.
!
module mld_c_jac_smoother

@ -48,7 +48,7 @@
! - the mld_c_mumps_solver_type data structure containing the ingredients
! to interface with the MUMPS package.
! 1. The factorization can be either restricted to the diagonal block of the
! current image or distributed (and thus exact)
! current image or distributed (and thus exact).
!
module mld_c_mumps_solver
use mld_c_base_solver_mod

@ -39,7 +39,7 @@
!
! Module: mld_c_prec_mod
!
! This module defines the interfaces to the real/complex, single/double
! This module defines the user interfaces to the real/complex, single/double
! precision versions of the user-level MLD2P4 routines.
!
module mld_c_prec_mod

@ -61,24 +61,24 @@ module mld_c_prec_type
use psb_prec_mod, only : psb_cprec_type
!
! Type: mld_Tprec_type.
! Type: mld_cprec_type.
!
! This is the data type containing all the information about the multilevel
! preconditioner (here and in the following 'T' denotes 'd', 's', 'c' and
! 'z', according to the real/complex, single/double precision version of
! MLD2P4). It consists of an array of 'one-level' intermediate data structures
! of type mld_Tonelev_type, each containing the information needed to apply
! preconditioner ('d', 's', 'c' and 'z', according to the real/complex,
! single/double precision version of MLD2P4).
! It consists of an array of 'one-level' intermediate data structures
! of type mld_conelev_type, each containing the information needed to apply
! the smoothing and the coarse-space correction at a generic level. RT is the
! real data type, i.e. S for both S and C, and D for both D and Z.
!
! type mld_Tprec_type
! type(mld_Tonelev_type), allocatable :: precv(:)
! end type mld_Tprec_type
! type mld_cprec_type
! type(mld_conelev_type), allocatable :: precv(:)
! end type mld_cprec_type
!
! Note that the levels are numbered in increasing order starting from
! the finest one and the number of levels is given by size(precv(:)),
! and that is the id of the coarsest level.
! In the multigrid literature authors often number the levels in decreasing
! the level 1 as the finest one, and the number of levels is given by
! size(precv(:)) which is the id of the coarsest level.
! In the multigrid literature many authors number the levels in the opposite
! order, with level 0 being the id of the coarsest level.
!
!
@ -92,9 +92,9 @@ module mld_c_prec_type
!
integer(psb_ipk_) :: outer_sweeps = 1
!
! Coarse solver requires some tricky checks, and this needs we record the
! choice in the format given by the user, to keep track against what
! is put later in the multilevel array
! Coarse solver requires some tricky checks, and for this we need to
! record the choice in the format given by the user,
! to keep track against what is put later in the multilevel array
!
integer(psb_ipk_) :: coarse_solver = -1

@ -285,7 +285,7 @@ contains
!! The mapping is store in ILAGGR; for each local row index I,
!! ILAGGR(I) contains the index of the aggregate to which index I
!! will contribute, in global numbering.
!! Many aggregation produce a binary tentative prolongator, but some
!! Many aggregations produce a binary tentative prolongator, but some
!! do not, hence we also need the OP_PROL output.
!! AG_DATA is passed here just in case some of the
!! aggregators need it internally, most of them will ignore.

@ -56,6 +56,9 @@
! contains a SOLVER object: the SOLVER operates locally within the
! current process, whereas the SMOOTHER object accounts for (possible)
! interactions between processes.
! Some solvers (MUMPS and SuperLU_DIST) can also operate on the entire
! distributed matrix, in which case the smoother object essentially
! becomes transparent.
!
module mld_d_base_smoother_mod

@ -275,6 +275,18 @@ contains
end module mld_d_diag_solver
!
! Module: mld_d_l1_diag_solver_mod
!
! This module defines:
! - the mld_d_l1_diag_solver_type data structure containing the
! L1 diagonal solver.
! The solver is defined as a diagonal containing in each element the
! inverse of the sum of the absolute values of the matrix entries
! along the corresponding row.
! Combined with a Jacobi "smoother" generates
! what are commonly known as the L1-Jacobi iterations
!
module mld_d_l1_diag_solver

@ -48,7 +48,8 @@
! on the block diagonal). Combined with a Jacobi smoother will generate a
! hybrid-Gauss-Seidel solver, i.e. Gauss-Seidel within each process, Jacobi
! among the processes.
!
! With two objects as pre- and post-smoothers it is possible to build a
! Forward-Backward smoother, suitable for symmetric iterations.
!
module mld_d_gs_solver

@ -41,7 +41,7 @@
!
! Module: mld_d_ilu_fact_mod
!
! This module defines some interfaces used internally by the implementation if
! This module defines some interfaces used internally by the implementation of
! mld_d_ilu_solver, but not visible to the end user.
!
!

@ -51,7 +51,7 @@
! threshold base ILU(T,L)
! 3. The diagonal is stored separately, so strictly speaking this is
! an incomplete LDU factorization;
! 4. The application phase is shared;
! 4. The application phase is shared among all variants;
!
!
module mld_d_ilu_solver

@ -39,8 +39,7 @@
!
! Module: mld_inner_mod
!
! This module defines the interfaces to the real/complex, single/double
! precision versions of inner MLD2P4 routines.
! This module defines the interfaces to inner MLD2P4 routines.
! The interfaces of the user level routines are defined in mld_prec_mod.f90.
!
module mld_d_inner_mod

@ -44,10 +44,10 @@
! the mld_d_jac_smoother_type data structure containing the
! smoother for a Jacobi/block Jacobi smoother.
! The smoother stores in ND the block off-diagonal matrix.
! One special case is treated separately, when the solver is DIAG
! One special case is treated separately, when the solver is DIAG or L1-DIAG
! then the ND is the entire off-diagonal part of the matrix (including the
! main diagonal block), so that it becomes possible to implement
! pure Jacobi global solver.
! a pure Jacobi or L1-Jacobi global solver.
!
module mld_d_jac_smoother

@ -48,7 +48,7 @@
! - the mld_d_mumps_solver_type data structure containing the ingredients
! to interface with the MUMPS package.
! 1. The factorization can be either restricted to the diagonal block of the
! current image or distributed (and thus exact)
! current image or distributed (and thus exact).
!
module mld_d_mumps_solver
use mld_d_base_solver_mod

@ -39,7 +39,7 @@
!
! Module: mld_d_prec_mod
!
! This module defines the interfaces to the real/complex, single/double
! This module defines the user interfaces to the real/complex, single/double
! precision versions of the user-level MLD2P4 routines.
!
module mld_d_prec_mod

@ -61,24 +61,24 @@ module mld_d_prec_type
use psb_prec_mod, only : psb_dprec_type
!
! Type: mld_Tprec_type.
! Type: mld_dprec_type.
!
! This is the data type containing all the information about the multilevel
! preconditioner (here and in the following 'T' denotes 'd', 's', 'c' and
! 'z', according to the real/complex, single/double precision version of
! MLD2P4). It consists of an array of 'one-level' intermediate data structures
! of type mld_Tonelev_type, each containing the information needed to apply
! preconditioner ('d', 's', 'c' and 'z', according to the real/complex,
! single/double precision version of MLD2P4).
! It consists of an array of 'one-level' intermediate data structures
! of type mld_donelev_type, each containing the information needed to apply
! the smoothing and the coarse-space correction at a generic level. RT is the
! real data type, i.e. S for both S and C, and D for both D and Z.
!
! type mld_Tprec_type
! type(mld_Tonelev_type), allocatable :: precv(:)
! end type mld_Tprec_type
! type mld_dprec_type
! type(mld_donelev_type), allocatable :: precv(:)
! end type mld_dprec_type
!
! Note that the levels are numbered in increasing order starting from
! the finest one and the number of levels is given by size(precv(:)),
! and that is the id of the coarsest level.
! In the multigrid literature authors often number the levels in decreasing
! the level 1 as the finest one, and the number of levels is given by
! size(precv(:)) which is the id of the coarsest level.
! In the multigrid literature many authors number the levels in the opposite
! order, with level 0 being the id of the coarsest level.
!
!
@ -92,9 +92,9 @@ module mld_d_prec_type
!
integer(psb_ipk_) :: outer_sweeps = 1
!
! Coarse solver requires some tricky checks, and this needs we record the
! choice in the format given by the user, to keep track against what
! is put later in the multilevel array
! Coarse solver requires some tricky checks, and for this we need to
! record the choice in the format given by the user,
! to keep track against what is put later in the multilevel array
!
integer(psb_ipk_) :: coarse_solver = -1

@ -285,7 +285,7 @@ contains
!! The mapping is store in ILAGGR; for each local row index I,
!! ILAGGR(I) contains the index of the aggregate to which index I
!! will contribute, in global numbering.
!! Many aggregation produce a binary tentative prolongator, but some
!! Many aggregations produce a binary tentative prolongator, but some
!! do not, hence we also need the OP_PROL output.
!! AG_DATA is passed here just in case some of the
!! aggregators need it internally, most of them will ignore.

@ -56,6 +56,9 @@
! contains a SOLVER object: the SOLVER operates locally within the
! current process, whereas the SMOOTHER object accounts for (possible)
! interactions between processes.
! Some solvers (MUMPS and SuperLU_DIST) can also operate on the entire
! distributed matrix, in which case the smoother object essentially
! becomes transparent.
!
module mld_s_base_smoother_mod

@ -275,6 +275,18 @@ contains
end module mld_s_diag_solver
!
! Module: mld_s_l1_diag_solver_mod
!
! This module defines:
! - the mld_s_l1_diag_solver_type data structure containing the
! L1 diagonal solver.
! The solver is defined as a diagonal containing in each element the
! inverse of the sum of the absolute values of the matrix entries
! along the corresponding row.
! Combined with a Jacobi "smoother" generates
! what are commonly known as the L1-Jacobi iterations
!
module mld_s_l1_diag_solver

@ -48,7 +48,8 @@
! on the block diagonal). Combined with a Jacobi smoother will generate a
! hybrid-Gauss-Seidel solver, i.e. Gauss-Seidel within each process, Jacobi
! among the processes.
!
! With two objects as pre- and post-smoothers it is possible to build a
! Forward-Backward smoother, suitable for symmetric iterations.
!
module mld_s_gs_solver

@ -41,7 +41,7 @@
!
! Module: mld_s_ilu_fact_mod
!
! This module defines some interfaces used internally by the implementation if
! This module defines some interfaces used internally by the implementation of
! mld_s_ilu_solver, but not visible to the end user.
!
!

@ -51,7 +51,7 @@
! threshold base ILU(T,L)
! 3. The diagonal is stored separately, so strictly speaking this is
! an incomplete LDU factorization;
! 4. The application phase is shared;
! 4. The application phase is shared among all variants;
!
!
module mld_s_ilu_solver

@ -39,8 +39,7 @@
!
! Module: mld_inner_mod
!
! This module defines the interfaces to the real/complex, single/double
! precision versions of inner MLD2P4 routines.
! This module defines the interfaces to inner MLD2P4 routines.
! The interfaces of the user level routines are defined in mld_prec_mod.f90.
!
module mld_s_inner_mod

@ -44,10 +44,10 @@
! the mld_s_jac_smoother_type data structure containing the
! smoother for a Jacobi/block Jacobi smoother.
! The smoother stores in ND the block off-diagonal matrix.
! One special case is treated separately, when the solver is DIAG
! One special case is treated separately, when the solver is DIAG or L1-DIAG
! then the ND is the entire off-diagonal part of the matrix (including the
! main diagonal block), so that it becomes possible to implement
! pure Jacobi global solver.
! a pure Jacobi or L1-Jacobi global solver.
!
module mld_s_jac_smoother

@ -48,7 +48,7 @@
! - the mld_s_mumps_solver_type data structure containing the ingredients
! to interface with the MUMPS package.
! 1. The factorization can be either restricted to the diagonal block of the
! current image or distributed (and thus exact)
! current image or distributed (and thus exact).
!
module mld_s_mumps_solver
use mld_s_base_solver_mod

@ -39,7 +39,7 @@
!
! Module: mld_s_prec_mod
!
! This module defines the interfaces to the real/complex, single/double
! This module defines the user interfaces to the real/complex, single/double
! precision versions of the user-level MLD2P4 routines.
!
module mld_s_prec_mod

@ -61,24 +61,24 @@ module mld_s_prec_type
use psb_prec_mod, only : psb_sprec_type
!
! Type: mld_Tprec_type.
! Type: mld_sprec_type.
!
! This is the data type containing all the information about the multilevel
! preconditioner (here and in the following 'T' denotes 'd', 's', 'c' and
! 'z', according to the real/complex, single/double precision version of
! MLD2P4). It consists of an array of 'one-level' intermediate data structures
! of type mld_Tonelev_type, each containing the information needed to apply
! preconditioner ('d', 's', 'c' and 'z', according to the real/complex,
! single/double precision version of MLD2P4).
! It consists of an array of 'one-level' intermediate data structures
! of type mld_sonelev_type, each containing the information needed to apply
! the smoothing and the coarse-space correction at a generic level. RT is the
! real data type, i.e. S for both S and C, and D for both D and Z.
!
! type mld_Tprec_type
! type(mld_Tonelev_type), allocatable :: precv(:)
! end type mld_Tprec_type
! type mld_sprec_type
! type(mld_sonelev_type), allocatable :: precv(:)
! end type mld_sprec_type
!
! Note that the levels are numbered in increasing order starting from
! the finest one and the number of levels is given by size(precv(:)),
! and that is the id of the coarsest level.
! In the multigrid literature authors often number the levels in decreasing
! the level 1 as the finest one, and the number of levels is given by
! size(precv(:)) which is the id of the coarsest level.
! In the multigrid literature many authors number the levels in the opposite
! order, with level 0 being the id of the coarsest level.
!
!
@ -92,9 +92,9 @@ module mld_s_prec_type
!
integer(psb_ipk_) :: outer_sweeps = 1
!
! Coarse solver requires some tricky checks, and this needs we record the
! choice in the format given by the user, to keep track against what
! is put later in the multilevel array
! Coarse solver requires some tricky checks, and for this we need to
! record the choice in the format given by the user,
! to keep track against what is put later in the multilevel array
!
integer(psb_ipk_) :: coarse_solver = -1

@ -285,7 +285,7 @@ contains
!! The mapping is store in ILAGGR; for each local row index I,
!! ILAGGR(I) contains the index of the aggregate to which index I
!! will contribute, in global numbering.
!! Many aggregation produce a binary tentative prolongator, but some
!! Many aggregations produce a binary tentative prolongator, but some
!! do not, hence we also need the OP_PROL output.
!! AG_DATA is passed here just in case some of the
!! aggregators need it internally, most of them will ignore.

@ -56,6 +56,9 @@
! contains a SOLVER object: the SOLVER operates locally within the
! current process, whereas the SMOOTHER object accounts for (possible)
! interactions between processes.
! Some solvers (MUMPS and SuperLU_DIST) can also operate on the entire
! distributed matrix, in which case the smoother object essentially
! becomes transparent.
!
module mld_z_base_smoother_mod

@ -275,6 +275,18 @@ contains
end module mld_z_diag_solver
!
! Module: mld_z_l1_diag_solver_mod
!
! This module defines:
! - the mld_z_l1_diag_solver_type data structure containing the
! L1 diagonal solver.
! The solver is defined as a diagonal containing in each element the
! inverse of the sum of the absolute values of the matrix entries
! along the corresponding row.
! Combined with a Jacobi "smoother" generates
! what are commonly known as the L1-Jacobi iterations
!
module mld_z_l1_diag_solver

@ -48,7 +48,8 @@
! on the block diagonal). Combined with a Jacobi smoother will generate a
! hybrid-Gauss-Seidel solver, i.e. Gauss-Seidel within each process, Jacobi
! among the processes.
!
! With two objects as pre- and post-smoothers it is possible to build a
! Forward-Backward smoother, suitable for symmetric iterations.
!
module mld_z_gs_solver

@ -41,7 +41,7 @@
!
! Module: mld_z_ilu_fact_mod
!
! This module defines some interfaces used internally by the implementation if
! This module defines some interfaces used internally by the implementation of
! mld_z_ilu_solver, but not visible to the end user.
!
!

@ -51,7 +51,7 @@
! threshold base ILU(T,L)
! 3. The diagonal is stored separately, so strictly speaking this is
! an incomplete LDU factorization;
! 4. The application phase is shared;
! 4. The application phase is shared among all variants;
!
!
module mld_z_ilu_solver

@ -39,8 +39,7 @@
!
! Module: mld_inner_mod
!
! This module defines the interfaces to the real/complex, single/double
! precision versions of inner MLD2P4 routines.
! This module defines the interfaces to inner MLD2P4 routines.
! The interfaces of the user level routines are defined in mld_prec_mod.f90.
!
module mld_z_inner_mod

@ -44,10 +44,10 @@
! the mld_z_jac_smoother_type data structure containing the
! smoother for a Jacobi/block Jacobi smoother.
! The smoother stores in ND the block off-diagonal matrix.
! One special case is treated separately, when the solver is DIAG
! One special case is treated separately, when the solver is DIAG or L1-DIAG
! then the ND is the entire off-diagonal part of the matrix (including the
! main diagonal block), so that it becomes possible to implement
! pure Jacobi global solver.
! a pure Jacobi or L1-Jacobi global solver.
!
module mld_z_jac_smoother

@ -48,7 +48,7 @@
! - the mld_z_mumps_solver_type data structure containing the ingredients
! to interface with the MUMPS package.
! 1. The factorization can be either restricted to the diagonal block of the
! current image or distributed (and thus exact)
! current image or distributed (and thus exact).
!
module mld_z_mumps_solver
use mld_z_base_solver_mod

@ -39,7 +39,7 @@
!
! Module: mld_z_prec_mod
!
! This module defines the interfaces to the real/complex, single/double
! This module defines the user interfaces to the real/complex, single/double
! precision versions of the user-level MLD2P4 routines.
!
module mld_z_prec_mod

@ -61,24 +61,24 @@ module mld_z_prec_type
use psb_prec_mod, only : psb_zprec_type
!
! Type: mld_Tprec_type.
! Type: mld_zprec_type.
!
! This is the data type containing all the information about the multilevel
! preconditioner (here and in the following 'T' denotes 'd', 's', 'c' and
! 'z', according to the real/complex, single/double precision version of
! MLD2P4). It consists of an array of 'one-level' intermediate data structures
! of type mld_Tonelev_type, each containing the information needed to apply
! preconditioner ('d', 's', 'c' and 'z', according to the real/complex,
! single/double precision version of MLD2P4).
! It consists of an array of 'one-level' intermediate data structures
! of type mld_zonelev_type, each containing the information needed to apply
! the smoothing and the coarse-space correction at a generic level. RT is the
! real data type, i.e. S for both S and C, and D for both D and Z.
!
! type mld_Tprec_type
! type(mld_Tonelev_type), allocatable :: precv(:)
! end type mld_Tprec_type
! type mld_zprec_type
! type(mld_zonelev_type), allocatable :: precv(:)
! end type mld_zprec_type
!
! Note that the levels are numbered in increasing order starting from
! the finest one and the number of levels is given by size(precv(:)),
! and that is the id of the coarsest level.
! In the multigrid literature authors often number the levels in decreasing
! the level 1 as the finest one, and the number of levels is given by
! size(precv(:)) which is the id of the coarsest level.
! In the multigrid literature many authors number the levels in the opposite
! order, with level 0 being the id of the coarsest level.
!
!
@ -92,9 +92,9 @@ module mld_z_prec_type
!
integer(psb_ipk_) :: outer_sweeps = 1
!
! Coarse solver requires some tricky checks, and this needs we record the
! choice in the format given by the user, to keep track against what
! is put later in the multilevel array
! Coarse solver requires some tricky checks, and for this we need to
! record the choice in the format given by the user,
! to keep track against what is put later in the multilevel array
!
integer(psb_ipk_) :: coarse_solver = -1

Loading…
Cancel
Save