From fa1b5dcdea4f4a001e7b1d97048cb344d255f30b Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 16 Feb 2018 14:39:00 +0000 Subject: [PATCH 01/33] Fixed op_restr build for unsmoothed aggregation. --- mlprec/impl/mld_c_lev_aggrmat_asb.f90 | 2 +- mlprec/impl/mld_caggrmat_nosmth_asb.f90 | 39 +++++++++++++++++++------ mlprec/impl/mld_d_lev_aggrmat_asb.f90 | 2 +- mlprec/impl/mld_daggrmat_nosmth_asb.f90 | 39 +++++++++++++++++++------ mlprec/impl/mld_s_lev_aggrmat_asb.f90 | 2 +- mlprec/impl/mld_saggrmat_nosmth_asb.f90 | 39 +++++++++++++++++++------ mlprec/impl/mld_z_lev_aggrmat_asb.f90 | 2 +- mlprec/impl/mld_zaggrmat_nosmth_asb.f90 | 39 +++++++++++++++++++------ 8 files changed, 124 insertions(+), 40 deletions(-) diff --git a/mlprec/impl/mld_c_lev_aggrmat_asb.f90 b/mlprec/impl/mld_c_lev_aggrmat_asb.f90 index 78391efb..5aa1730e 100644 --- a/mlprec/impl/mld_c_lev_aggrmat_asb.f90 +++ b/mlprec/impl/mld_c_lev_aggrmat_asb.f90 @@ -101,7 +101,7 @@ subroutine mld_c_lev_aggrmat_asb(p,a,desc_a,ilaggr,nlaggr,op_prol,info) ! Local variables - character(len=20) :: name + character(len=24) :: name integer(psb_mpik_) :: ictxt, np, me integer(psb_ipk_) :: err_act type(psb_cspmat_type) :: ac, op_restr diff --git a/mlprec/impl/mld_caggrmat_nosmth_asb.f90 b/mlprec/impl/mld_caggrmat_nosmth_asb.f90 index a19b5539..bbf1f218 100644 --- a/mlprec/impl/mld_caggrmat_nosmth_asb.f90 +++ b/mlprec/impl/mld_caggrmat_nosmth_asb.f90 @@ -117,11 +117,11 @@ subroutine mld_caggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_re integer(psb_ipk_) :: ictxt,np,me, icomm, ndx, minfo character(len=20) :: name integer(psb_ipk_) :: ierr(5) - type(psb_c_coo_sparse_mat) :: ac_coo, acoo + type(psb_c_coo_sparse_mat) :: ac_coo, tmpcoo type(psb_c_csr_sparse_mat) :: acsr1, acsr2 integer(psb_ipk_) :: debug_level, debug_unit integer(psb_ipk_) :: nrow, nglob, ncol, ntaggr, nzl, ip, & - & naggr, nzt, naggrm1, i, k + & naggr, nzt, naggrm1, naggrp1, i, k name='mld_aggrmat_nosmth_asb' if(psb_get_errstatus().ne.0) return @@ -137,16 +137,37 @@ subroutine mld_caggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_re ncol = desc_a%get_local_cols() - naggr = nlaggr(me+1) - ntaggr = sum(nlaggr) - naggrm1=sum(nlaggr(1:me)) - - call acoo%allocate(ncol,ntaggr,ncol) + naggr = nlaggr(me+1) + ntaggr = sum(nlaggr) + naggrm1 = sum(nlaggr(1:me)) + naggrp1 = sum(nlaggr(1:me+1)) + + call op_prol%cp_to(tmpcoo) call op_prol%cscnv(info,type='csr',dupl=psb_dupl_add_) - if (info /= psb_success_) goto 9999 - call op_prol%transp(op_restr) + call tmpcoo%transp() + nzl = tmpcoo%get_nzeros() + i=0 + ! + ! Now we have to fix this. The only rows of tmpcoo/op_restr that are correct + ! are those corresponding to "local" aggregates, i.e. indices in ilaggr(:) + ! + do k=1, nzl + if ((naggrm1 < tmpcoo%ia(k)) .and.(tmpcoo%ia(k) <= naggrp1)) then + i = i+1 + tmpcoo%val(i) = tmpcoo%val(k) + tmpcoo%ia(i) = tmpcoo%ia(k) + tmpcoo%ja(i) = tmpcoo%ja(k) + end if + end do + call tmpcoo%set_nzeros(i) + ! call tmpcoo%trim() + call op_restr%mv_from(tmpcoo) + call op_restr%cscnv(info,type='csr',dupl=psb_dupl_add_) + + if (info /= psb_success_) goto 9999 + call a%cp_to(ac_coo) nzt = ac_coo%get_nzeros() diff --git a/mlprec/impl/mld_d_lev_aggrmat_asb.f90 b/mlprec/impl/mld_d_lev_aggrmat_asb.f90 index e5f969b6..98c579a6 100644 --- a/mlprec/impl/mld_d_lev_aggrmat_asb.f90 +++ b/mlprec/impl/mld_d_lev_aggrmat_asb.f90 @@ -101,7 +101,7 @@ subroutine mld_d_lev_aggrmat_asb(p,a,desc_a,ilaggr,nlaggr,op_prol,info) ! Local variables - character(len=20) :: name + character(len=24) :: name integer(psb_mpik_) :: ictxt, np, me integer(psb_ipk_) :: err_act type(psb_dspmat_type) :: ac, op_restr diff --git a/mlprec/impl/mld_daggrmat_nosmth_asb.f90 b/mlprec/impl/mld_daggrmat_nosmth_asb.f90 index 3d2d4309..8c507876 100644 --- a/mlprec/impl/mld_daggrmat_nosmth_asb.f90 +++ b/mlprec/impl/mld_daggrmat_nosmth_asb.f90 @@ -117,11 +117,11 @@ subroutine mld_daggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_re integer(psb_ipk_) :: ictxt,np,me, icomm, ndx, minfo character(len=20) :: name integer(psb_ipk_) :: ierr(5) - type(psb_d_coo_sparse_mat) :: ac_coo, acoo + type(psb_d_coo_sparse_mat) :: ac_coo, tmpcoo type(psb_d_csr_sparse_mat) :: acsr1, acsr2 integer(psb_ipk_) :: debug_level, debug_unit integer(psb_ipk_) :: nrow, nglob, ncol, ntaggr, nzl, ip, & - & naggr, nzt, naggrm1, i, k + & naggr, nzt, naggrm1, naggrp1, i, k name='mld_aggrmat_nosmth_asb' if(psb_get_errstatus().ne.0) return @@ -137,16 +137,37 @@ subroutine mld_daggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_re ncol = desc_a%get_local_cols() - naggr = nlaggr(me+1) - ntaggr = sum(nlaggr) - naggrm1=sum(nlaggr(1:me)) - - call acoo%allocate(ncol,ntaggr,ncol) + naggr = nlaggr(me+1) + ntaggr = sum(nlaggr) + naggrm1 = sum(nlaggr(1:me)) + naggrp1 = sum(nlaggr(1:me+1)) + + call op_prol%cp_to(tmpcoo) call op_prol%cscnv(info,type='csr',dupl=psb_dupl_add_) - if (info /= psb_success_) goto 9999 - call op_prol%transp(op_restr) + call tmpcoo%transp() + nzl = tmpcoo%get_nzeros() + i=0 + ! + ! Now we have to fix this. The only rows of tmpcoo/op_restr that are correct + ! are those corresponding to "local" aggregates, i.e. indices in ilaggr(:) + ! + do k=1, nzl + if ((naggrm1 < tmpcoo%ia(k)) .and.(tmpcoo%ia(k) <= naggrp1)) then + i = i+1 + tmpcoo%val(i) = tmpcoo%val(k) + tmpcoo%ia(i) = tmpcoo%ia(k) + tmpcoo%ja(i) = tmpcoo%ja(k) + end if + end do + call tmpcoo%set_nzeros(i) + ! call tmpcoo%trim() + call op_restr%mv_from(tmpcoo) + call op_restr%cscnv(info,type='csr',dupl=psb_dupl_add_) + + if (info /= psb_success_) goto 9999 + call a%cp_to(ac_coo) nzt = ac_coo%get_nzeros() diff --git a/mlprec/impl/mld_s_lev_aggrmat_asb.f90 b/mlprec/impl/mld_s_lev_aggrmat_asb.f90 index 93932d65..2433a1a0 100644 --- a/mlprec/impl/mld_s_lev_aggrmat_asb.f90 +++ b/mlprec/impl/mld_s_lev_aggrmat_asb.f90 @@ -101,7 +101,7 @@ subroutine mld_s_lev_aggrmat_asb(p,a,desc_a,ilaggr,nlaggr,op_prol,info) ! Local variables - character(len=20) :: name + character(len=24) :: name integer(psb_mpik_) :: ictxt, np, me integer(psb_ipk_) :: err_act type(psb_sspmat_type) :: ac, op_restr diff --git a/mlprec/impl/mld_saggrmat_nosmth_asb.f90 b/mlprec/impl/mld_saggrmat_nosmth_asb.f90 index 990d6f52..c4805080 100644 --- a/mlprec/impl/mld_saggrmat_nosmth_asb.f90 +++ b/mlprec/impl/mld_saggrmat_nosmth_asb.f90 @@ -117,11 +117,11 @@ subroutine mld_saggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_re integer(psb_ipk_) :: ictxt,np,me, icomm, ndx, minfo character(len=20) :: name integer(psb_ipk_) :: ierr(5) - type(psb_s_coo_sparse_mat) :: ac_coo, acoo + type(psb_s_coo_sparse_mat) :: ac_coo, tmpcoo type(psb_s_csr_sparse_mat) :: acsr1, acsr2 integer(psb_ipk_) :: debug_level, debug_unit integer(psb_ipk_) :: nrow, nglob, ncol, ntaggr, nzl, ip, & - & naggr, nzt, naggrm1, i, k + & naggr, nzt, naggrm1, naggrp1, i, k name='mld_aggrmat_nosmth_asb' if(psb_get_errstatus().ne.0) return @@ -137,16 +137,37 @@ subroutine mld_saggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_re ncol = desc_a%get_local_cols() - naggr = nlaggr(me+1) - ntaggr = sum(nlaggr) - naggrm1=sum(nlaggr(1:me)) - - call acoo%allocate(ncol,ntaggr,ncol) + naggr = nlaggr(me+1) + ntaggr = sum(nlaggr) + naggrm1 = sum(nlaggr(1:me)) + naggrp1 = sum(nlaggr(1:me+1)) + + call op_prol%cp_to(tmpcoo) call op_prol%cscnv(info,type='csr',dupl=psb_dupl_add_) - if (info /= psb_success_) goto 9999 - call op_prol%transp(op_restr) + call tmpcoo%transp() + nzl = tmpcoo%get_nzeros() + i=0 + ! + ! Now we have to fix this. The only rows of tmpcoo/op_restr that are correct + ! are those corresponding to "local" aggregates, i.e. indices in ilaggr(:) + ! + do k=1, nzl + if ((naggrm1 < tmpcoo%ia(k)) .and.(tmpcoo%ia(k) <= naggrp1)) then + i = i+1 + tmpcoo%val(i) = tmpcoo%val(k) + tmpcoo%ia(i) = tmpcoo%ia(k) + tmpcoo%ja(i) = tmpcoo%ja(k) + end if + end do + call tmpcoo%set_nzeros(i) + ! call tmpcoo%trim() + call op_restr%mv_from(tmpcoo) + call op_restr%cscnv(info,type='csr',dupl=psb_dupl_add_) + + if (info /= psb_success_) goto 9999 + call a%cp_to(ac_coo) nzt = ac_coo%get_nzeros() diff --git a/mlprec/impl/mld_z_lev_aggrmat_asb.f90 b/mlprec/impl/mld_z_lev_aggrmat_asb.f90 index f1bbee94..07cac52e 100644 --- a/mlprec/impl/mld_z_lev_aggrmat_asb.f90 +++ b/mlprec/impl/mld_z_lev_aggrmat_asb.f90 @@ -101,7 +101,7 @@ subroutine mld_z_lev_aggrmat_asb(p,a,desc_a,ilaggr,nlaggr,op_prol,info) ! Local variables - character(len=20) :: name + character(len=24) :: name integer(psb_mpik_) :: ictxt, np, me integer(psb_ipk_) :: err_act type(psb_zspmat_type) :: ac, op_restr diff --git a/mlprec/impl/mld_zaggrmat_nosmth_asb.f90 b/mlprec/impl/mld_zaggrmat_nosmth_asb.f90 index 5dfc77c1..8dde35d7 100644 --- a/mlprec/impl/mld_zaggrmat_nosmth_asb.f90 +++ b/mlprec/impl/mld_zaggrmat_nosmth_asb.f90 @@ -117,11 +117,11 @@ subroutine mld_zaggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_re integer(psb_ipk_) :: ictxt,np,me, icomm, ndx, minfo character(len=20) :: name integer(psb_ipk_) :: ierr(5) - type(psb_z_coo_sparse_mat) :: ac_coo, acoo + type(psb_z_coo_sparse_mat) :: ac_coo, tmpcoo type(psb_z_csr_sparse_mat) :: acsr1, acsr2 integer(psb_ipk_) :: debug_level, debug_unit integer(psb_ipk_) :: nrow, nglob, ncol, ntaggr, nzl, ip, & - & naggr, nzt, naggrm1, i, k + & naggr, nzt, naggrm1, naggrp1, i, k name='mld_aggrmat_nosmth_asb' if(psb_get_errstatus().ne.0) return @@ -137,16 +137,37 @@ subroutine mld_zaggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_re ncol = desc_a%get_local_cols() - naggr = nlaggr(me+1) - ntaggr = sum(nlaggr) - naggrm1=sum(nlaggr(1:me)) - - call acoo%allocate(ncol,ntaggr,ncol) + naggr = nlaggr(me+1) + ntaggr = sum(nlaggr) + naggrm1 = sum(nlaggr(1:me)) + naggrp1 = sum(nlaggr(1:me+1)) + + call op_prol%cp_to(tmpcoo) call op_prol%cscnv(info,type='csr',dupl=psb_dupl_add_) - if (info /= psb_success_) goto 9999 - call op_prol%transp(op_restr) + call tmpcoo%transp() + nzl = tmpcoo%get_nzeros() + i=0 + ! + ! Now we have to fix this. The only rows of tmpcoo/op_restr that are correct + ! are those corresponding to "local" aggregates, i.e. indices in ilaggr(:) + ! + do k=1, nzl + if ((naggrm1 < tmpcoo%ia(k)) .and.(tmpcoo%ia(k) <= naggrp1)) then + i = i+1 + tmpcoo%val(i) = tmpcoo%val(k) + tmpcoo%ia(i) = tmpcoo%ia(k) + tmpcoo%ja(i) = tmpcoo%ja(k) + end if + end do + call tmpcoo%set_nzeros(i) + ! call tmpcoo%trim() + call op_restr%mv_from(tmpcoo) + call op_restr%cscnv(info,type='csr',dupl=psb_dupl_add_) + + if (info /= psb_success_) goto 9999 + call a%cp_to(ac_coo) nzt = ac_coo%get_nzeros() From b76fb7cd69c2a1ed7758b7c3631700edfee35d68 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Sun, 18 Feb 2018 12:28:08 +0000 Subject: [PATCH 02/33] Put in new cartesian data partition from PSBLAS. Minor typo in Makefile. --- Makefile | 3 +- tests/pdegen/mld_d_pde2d.f90 | 167 ++++++++++++++++++++++++++++------- tests/pdegen/mld_d_pde3d.f90 | 151 ++++++++++++++++++++++++------- tests/pdegen/mld_s_pde2d.f90 | 167 ++++++++++++++++++++++++++++------- tests/pdegen/mld_s_pde3d.f90 | 151 ++++++++++++++++++++++++------- 5 files changed, 502 insertions(+), 137 deletions(-) diff --git a/Makefile b/Makefile index eb496629..f72d29d0 100644 --- a/Makefile +++ b/Makefile @@ -30,7 +30,8 @@ install: all /bin/cp -fr docs/*pdf docs/html $(INSTALL_DOCSDIR) $(SHELL) ./mkdir.sh $(INSTALL_DOCSDIR) && \ $(INSTALL_DATA) README LICENSE $(INSTALL_DOCSDIR) - $(SHELL) ./mkdir.sh $(INSTALL_SAMPLESDIR) && ./mkdir.sh $(INSTALL_SAMPLESDIR)/simple &&\ + $(SHELL) ./mkdir.sh $(INSTALL_SAMPLESDIR) && \ + ./mkdir.sh $(INSTALL_SAMPLESDIR)/simple &&\ ./mkdir.sh $(INSTALL_SAMPLESDIR)/advanced && \ (cd examples; /bin/cp -fr pdegen fileread $(INSTALL_SAMPLESDIR)/simple ) && \ (cd tests; /bin/cp -fr pdegen fileread $(INSTALL_SAMPLESDIR)/advanced ) diff --git a/tests/pdegen/mld_d_pde2d.f90 b/tests/pdegen/mld_d_pde2d.f90 index 67be3884..15ccd34a 100644 --- a/tests/pdegen/mld_d_pde2d.f90 +++ b/tests/pdegen/mld_d_pde2d.f90 @@ -56,10 +56,12 @@ ! ! Note that if b1=b2=c=0., the PDE is the Laplace equation. ! -! In this sample program the index space of the discretized -! computational domain is first numbered sequentially in a standard way, -! then the corresponding vector is distributed according to a BLOCK -! data distribution. +! There are three choices available for data distribution: +! 1. A simple BLOCK distribution +! 2. A ditribution based on arbitrary assignment of indices to processes, +! typically from a graph partitioner +! 3. A 2D distribution in which the unit square is partitioned +! into rectangles, each one assigned to a process. ! module mld_d_pde2d_mod use psb_base_mod, only : psb_dpk_, psb_ipk_, psb_desc_type,& @@ -94,8 +96,9 @@ contains ! the rhs. ! subroutine mld_d_gen_pde2d(ictxt,idim,a,bv,xv,desc_a,afmt,& - & a1,a2,b1,b2,c,g,info,f,amold,vmold,imold,nrl) + & a1,a2,b1,b2,c,g,info,f,amold,vmold,imold,partition,nrl,iv) use psb_base_mod + use psb_util_mod ! ! Discretizes the partial differential equation ! @@ -123,7 +126,7 @@ contains class(psb_d_base_sparse_mat), optional :: amold class(psb_d_base_vect_type), optional :: vmold class(psb_i_base_vect_type), optional :: imold - integer(psb_ipk_), optional :: nrl + integer(psb_ipk_), optional :: partition, nrl,iv(:) ! Local variables. @@ -132,9 +135,13 @@ contains type(psb_d_coo_sparse_mat) :: acoo type(psb_d_csr_sparse_mat) :: acsr real(psb_dpk_) :: zt(nb),x,y,z - integer(psb_ipk_) :: m,n,nnz,glob_row,nlr,i,ii,ib,k + integer(psb_ipk_) :: m,n,nnz,nr,nt,glob_row,nlr,i,j,ii,ib,k, partition_ integer(psb_ipk_) :: ix,iy,iz,ia,indx_owner - integer(psb_ipk_) :: np, iam, nr, nt + ! For 2D partition + integer(psb_ipk_) :: npx,npy,npdims(2),iamx,iamy,mynx,myny + integer(psb_ipk_), allocatable :: bndx(:),bndy(:) + ! Process grid + integer(psb_ipk_) :: np, iam integer(psb_ipk_) :: icoeff integer(psb_ipk_), allocatable :: irow(:),icol(:),myidx(:) real(psb_dpk_), allocatable :: val(:) @@ -164,6 +171,17 @@ contains sqdeltah = deltah*deltah deltah2 = 2.e0* deltah + if (present(partition)) then + if ((1<= partition).and.(partition <= 3)) then + partition_ = partition + else + write(*,*) 'Invalid partition choice ',partition,' defaulting to 3' + partition_ = 3 + end if + else + partition_ = 3 + end if + ! initialize array descriptor and sparse matrix storage. provide an ! estimate of the number of non zeroes @@ -172,32 +190,121 @@ contains nnz = ((n*7)/(np)) if(iam == psb_root_) write(psb_out_unit,'("Generating Matrix (size=",i0,")...")')n - if (present(nrl)) then - nr = nrl - else + select case(partition_) + case(1) + ! A BLOCK partition + if (present(nrl)) then + nr = nrl + else + ! + ! Using a simple BLOCK distribution. + ! + nt = (m+np-1)/np + nr = max(0,min(nt,m-(iam*nt))) + end if + + nt = nr + call psb_sum(ictxt,nt) + if (nt /= m) then + write(psb_err_unit,*) iam, 'Initialization error ',nr,nt,m + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + return + end if + ! - ! Using a simple BLOCK distribution. + ! First example of use of CDALL: specify for each process a number of + ! contiguous rows + ! + call psb_cdall(ictxt,desc_a,info,nl=nr) + myidx = desc_a%get_global_indices() + nlr = size(myidx) + + case(2) + ! A partition defined by the user through IV + + if (present(iv)) then + if (size(iv) /= m) then + write(psb_err_unit,*) iam, 'Initialization error: wrong IV size',size(iv),m + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + return + end if + else + write(psb_err_unit,*) iam, 'Initialization error: IV not present' + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + return + end if + ! - nt = (m+np-1)/np - nr = max(0,min(nt,m-(iam*nt))) - end if + ! Second example of use of CDALL: specify for each row the + ! process that owns it + ! + call psb_cdall(ictxt,desc_a,info,vg=iv) + myidx = desc_a%get_global_indices() + nlr = size(myidx) + + case(3) + ! A 2-dimensional partition + + ! A nifty MPI function will split the process list + npdims = 0 + call mpi_dims_create(np,2,npdims,info) + npx = npdims(1) + npy = npdims(2) + + allocate(bndx(0:npx),bndy(0:npy)) + ! We can reuse idx2ijk for process indices as well. + call idx2ijk(iamx,iamy,iam,npx,npy,base=0) + ! Now let's split the 2D square in rectangles + call dist1Didx(bndx,idim,npx) + mynx = bndx(iamx+1)-bndx(iamx) + call dist1Didx(bndy,idim,npy) + myny = bndy(iamy+1)-bndy(iamy) + + ! How many indices do I own? + nlr = mynx*myny + allocate(myidx(nlr)) + ! Now, let's generate the list of indices I own + nr = 0 + do i=bndx(iamx),bndx(iamx+1)-1 + do j=bndy(iamy),bndx(iamy+1)-1 + nr = nr + 1 + call ijk2idx(myidx(nr),i,j,idim,idim) + end do + end do + if (nr /= nlr) then + write(psb_err_unit,*) iam,iamx,iamy, 'Initialization error: NR vs NLR ',& + & nr,nlr,mynx,myny + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + end if - nt = nr - call psb_sum(ictxt,nt) - if (nt /= m) then - write(psb_err_unit,*) iam, 'Initialization error ',nr,nt,m + ! + ! Third example of use of CDALL: specify for each process + ! the set of global indices it owns. + ! + call psb_cdall(ictxt,desc_a,info,vl=myidx) + + case default + write(psb_err_unit,*) iam, 'Initialization error: should not get here' info = -1 call psb_barrier(ictxt) call psb_abort(ictxt) - return - end if - call psb_barrier(ictxt) - t0 = psb_wtime() - call psb_cdall(ictxt,desc_a,info,nl=nr) + return + end select + + if (info == psb_success_) call psb_spall(a,desc_a,info,nnz=nnz) ! define rhs from boundary conditions; also build initial guess if (info == psb_success_) call psb_geall(xv,desc_a,info) if (info == psb_success_) call psb_geall(bv,desc_a,info) + call psb_barrier(ictxt) talc = psb_wtime()-t0 @@ -221,9 +328,6 @@ contains endif - myidx = desc_a%get_global_indices() - nlr = size(myidx) - ! loop over rows belonging to current process in a block ! distribution. @@ -237,13 +341,8 @@ contains ! local matrix pointer glob_row=myidx(i) ! compute gridpoint coordinates - if (mod(glob_row,(idim)) == 0) then - ix = glob_row/(idim) - else - ix = glob_row/(idim)+1 - endif - iy = (glob_row-(ix-1)*idim) - ! x, y + call idx2ijk(ix,iy,glob_row,idim,idim) + ! x, y coordinates x = (ix-1)*deltah y = (iy-1)*deltah diff --git a/tests/pdegen/mld_d_pde3d.f90 b/tests/pdegen/mld_d_pde3d.f90 index 63cb0ac3..7f89d06c 100644 --- a/tests/pdegen/mld_d_pde3d.f90 +++ b/tests/pdegen/mld_d_pde3d.f90 @@ -57,10 +57,12 @@ ! ! Note that if b1=b2=b3=c=0., the PDE is the Laplace equation. ! -! In this sample program the index space of the discretized -! computational domain is first numbered sequentially in a standard way, -! then the corresponding vector is distributed according to a BLOCK -! data distribution. +! There are three choices available for data distribution: +! 1. A simple BLOCK distribution +! 2. A ditribution based on arbitrary assignment of indices to processes, +! typically from a graph partitioner +! 3. A 3D distribution in which the unit cube is partitioned +! into subcubes, each one assigned to a process. ! module mld_d_pde3d_mod use psb_base_mod, only : psb_dpk_, psb_ipk_, psb_desc_type,& @@ -96,8 +98,9 @@ contains ! the rhs. ! subroutine mld_d_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt,& - & a1,a2,a3,b1,b2,b3,c,g,info,f,amold,vmold,imold,nrl,iv) + & a1,a2,a3,b1,b2,b3,c,g,info,f,amold,vmold,imold,partition,nrl,iv) use psb_base_mod + use psb_util_mod ! ! Discretizes the partial differential equation ! @@ -125,7 +128,7 @@ contains class(psb_d_base_sparse_mat), optional :: amold class(psb_d_base_vect_type), optional :: vmold class(psb_i_base_vect_type), optional :: imold - integer(psb_ipk_), optional :: nrl,iv(:) + integer(psb_ipk_), optional :: partition, nrl,iv(:) ! Local variables. @@ -134,9 +137,13 @@ contains type(psb_d_coo_sparse_mat) :: acoo type(psb_d_csr_sparse_mat) :: acsr real(psb_dpk_) :: zt(nb),x,y,z - integer(psb_ipk_) :: m,n,nnz,glob_row,nlr,i,ii,ib,k + integer(psb_ipk_) :: m,n,nnz,nr,nt,glob_row,nlr,i,j,ii,ib,k, partition_ integer(psb_ipk_) :: ix,iy,iz,ia,indx_owner - integer(psb_ipk_) :: np, iam, nr, nt + ! For 3D partition + integer(psb_ipk_) :: npx,npy,npz, npdims(3),iamx,iamy,iamz,mynx,myny,mynz + integer(psb_ipk_), allocatable :: bndx(:),bndy(:),bndz(:) + ! Process grid + integer(psb_ipk_) :: np, iam integer(psb_ipk_) :: icoeff integer(psb_ipk_), allocatable :: irow(:),icol(:),myidx(:) real(psb_dpk_), allocatable :: val(:) @@ -166,15 +173,28 @@ contains sqdeltah = deltah*deltah deltah2 = 2.d0* deltah + if (present(partition)) then + if ((1<= partition).and.(partition <= 3)) then + partition_ = partition + else + write(*,*) 'Invalid partition choice ',partition,' defaulting to 3' + partition_ = 3 + end if + else + partition_ = 3 + end if + ! initialize array descriptor and sparse matrix storage. provide an ! estimate of the number of non zeroes - + m = idim*idim*idim n = m nnz = ((n*9)/(np)) if(iam == psb_root_) write(psb_out_unit,'("Generating Matrix (size=",i0,")...")')n - if (.not.present(iv)) then + select case(partition_) + case(1) + ! A BLOCK partition if (present(nrl)) then nr = nrl else @@ -194,24 +214,99 @@ contains call psb_abort(ictxt) return end if - else - if (size(iv) /= m) then - write(psb_err_unit,*) iam, 'Initialization error IV',size(iv),m + + ! + ! First example of use of CDALL: specify for each process a number of + ! contiguous rows + ! + call psb_cdall(ictxt,desc_a,info,nl=nr) + myidx = desc_a%get_global_indices() + nlr = size(myidx) + + case(2) + ! A partition defined by the user through IV + + if (present(iv)) then + if (size(iv) /= m) then + write(psb_err_unit,*) iam, 'Initialization error: wrong IV size',size(iv),m + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + return + end if + else + write(psb_err_unit,*) iam, 'Initialization error: IV not present' info = -1 call psb_barrier(ictxt) call psb_abort(ictxt) return end if - end if - call psb_barrier(ictxt) - t0 = psb_wtime() - if (present(iv)) then + ! + ! Second example of use of CDALL: specify for each row the + ! process that owns it + ! call psb_cdall(ictxt,desc_a,info,vg=iv) - else - call psb_cdall(ictxt,desc_a,info,nl=nr) - end if + myidx = desc_a%get_global_indices() + nlr = size(myidx) + + case(3) + ! A 3-dimensional partition + + ! A nifty MPI function will split the process list + npdims = 0 + call mpi_dims_create(np,3,npdims,info) + npx = npdims(1) + npy = npdims(2) + npz = npdims(3) + + allocate(bndx(0:npx),bndy(0:npy),bndz(0:npz)) + ! We can reuse idx2ijk for process indices as well. + call idx2ijk(iamx,iamy,iamz,iam,npx,npy,npz,base=0) + ! Now let's split the 3D cube in hexahedra + call dist1Didx(bndx,idim,npx) + mynx = bndx(iamx+1)-bndx(iamx) + call dist1Didx(bndy,idim,npy) + myny = bndy(iamy+1)-bndy(iamy) + call dist1Didx(bndz,idim,npz) + mynz = bndz(iamz+1)-bndz(iamz) + + ! How many indices do I own? + nlr = mynx*myny*mynz + allocate(myidx(nlr)) + ! Now, let's generate the list of indices I own + nr = 0 + do i=bndx(iamx),bndx(iamx+1)-1 + do j=bndy(iamy),bndx(iamy+1)-1 + do k=bndz(iamz),bndz(iamz+1)-1 + nr = nr + 1 + call ijk2idx(myidx(nr),i,j,k,idim,idim,idim) + end do + end do + end do + if (nr /= nlr) then + write(psb_err_unit,*) iam,iamx,iamy,iamz, 'Initialization error: NR vs NLR ',& + & nr,nlr,mynx,myny,mynz + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + end if + + ! + ! Third example of use of CDALL: specify for each process + ! the set of global indices it owns. + ! + call psb_cdall(ictxt,desc_a,info,vl=myidx) + + case default + write(psb_err_unit,*) iam, 'Initialization error: should not get here' + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + return + end select + if (info == psb_success_) call psb_spall(a,desc_a,info,nnz=nnz) ! define rhs from boundary conditions; also build initial guess if (info == psb_success_) call psb_geall(xv,desc_a,info) @@ -239,8 +334,6 @@ contains goto 9999 endif - myidx = desc_a%get_global_indices() - nlr = size(myidx) ! loop over rows belonging to current process in a block ! distribution. @@ -255,18 +348,8 @@ contains ! local matrix pointer glob_row=myidx(i) ! compute gridpoint coordinates - if (mod(glob_row,(idim*idim)) == 0) then - ix = glob_row/(idim*idim) - else - ix = glob_row/(idim*idim)+1 - endif - if (mod((glob_row-(ix-1)*idim*idim),idim) == 0) then - iy = (glob_row-(ix-1)*idim*idim)/idim - else - iy = (glob_row-(ix-1)*idim*idim)/idim+1 - endif - iz = glob_row-(ix-1)*idim*idim-(iy-1)*idim - ! x, y, x coordinates + call idx2ijk(ix,iy,iz,glob_row,idim,idim,idim) + ! x, y, z coordinates x = (ix-1)*deltah y = (iy-1)*deltah z = (iz-1)*deltah diff --git a/tests/pdegen/mld_s_pde2d.f90 b/tests/pdegen/mld_s_pde2d.f90 index 01bd11d7..63d82cd3 100644 --- a/tests/pdegen/mld_s_pde2d.f90 +++ b/tests/pdegen/mld_s_pde2d.f90 @@ -56,10 +56,12 @@ ! ! Note that if b1=b2=c=0., the PDE is the Laplace equation. ! -! In this sample program the index space of the discretized -! computational domain is first numbered sequentially in a standard way, -! then the corresponding vector is distributed according to a BLOCK -! data distribution. +! There are three choices available for data distribution: +! 1. A simple BLOCK distribution +! 2. A ditribution based on arbitrary assignment of indices to processes, +! typically from a graph partitioner +! 3. A 2D distribution in which the unit square is partitioned +! into rectangles, each one assigned to a process. ! module mld_s_pde2d_mod use psb_base_mod, only : psb_spk_, psb_ipk_, psb_desc_type,& @@ -94,8 +96,9 @@ contains ! the rhs. ! subroutine mld_s_gen_pde2d(ictxt,idim,a,bv,xv,desc_a,afmt,& - & a1,a2,b1,b2,c,g,info,f,amold,vmold,imold,nrl) + & a1,a2,b1,b2,c,g,info,f,amold,vmold,imold,partition,nrl,iv) use psb_base_mod + use psb_util_mod ! ! Discretizes the partial differential equation ! @@ -123,7 +126,7 @@ contains class(psb_s_base_sparse_mat), optional :: amold class(psb_s_base_vect_type), optional :: vmold class(psb_i_base_vect_type), optional :: imold - integer(psb_ipk_), optional :: nrl + integer(psb_ipk_), optional :: partition, nrl,iv(:) ! Local variables. @@ -132,9 +135,13 @@ contains type(psb_s_coo_sparse_mat) :: acoo type(psb_s_csr_sparse_mat) :: acsr real(psb_spk_) :: zt(nb),x,y,z - integer(psb_ipk_) :: m,n,nnz,glob_row,nlr,i,ii,ib,k + integer(psb_ipk_) :: m,n,nnz,nr,nt,glob_row,nlr,i,j,ii,ib,k, partition_ integer(psb_ipk_) :: ix,iy,iz,ia,indx_owner - integer(psb_ipk_) :: np, iam, nr, nt + ! For 2D partition + integer(psb_ipk_) :: npx,npy,npdims(2),iamx,iamy,mynx,myny + integer(psb_ipk_), allocatable :: bndx(:),bndy(:) + ! Process grid + integer(psb_ipk_) :: np, iam integer(psb_ipk_) :: icoeff integer(psb_ipk_), allocatable :: irow(:),icol(:),myidx(:) real(psb_spk_), allocatable :: val(:) @@ -164,6 +171,17 @@ contains sqdeltah = deltah*deltah deltah2 = 2.e0* deltah + if (present(partition)) then + if ((1<= partition).and.(partition <= 3)) then + partition_ = partition + else + write(*,*) 'Invalid partition choice ',partition,' defaulting to 3' + partition_ = 3 + end if + else + partition_ = 3 + end if + ! initialize array descriptor and sparse matrix storage. provide an ! estimate of the number of non zeroes @@ -172,32 +190,121 @@ contains nnz = ((n*7)/(np)) if(iam == psb_root_) write(psb_out_unit,'("Generating Matrix (size=",i0,")...")')n - if (present(nrl)) then - nr = nrl - else + select case(partition_) + case(1) + ! A BLOCK partition + if (present(nrl)) then + nr = nrl + else + ! + ! Using a simple BLOCK distribution. + ! + nt = (m+np-1)/np + nr = max(0,min(nt,m-(iam*nt))) + end if + + nt = nr + call psb_sum(ictxt,nt) + if (nt /= m) then + write(psb_err_unit,*) iam, 'Initialization error ',nr,nt,m + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + return + end if + ! - ! Using a simple BLOCK distribution. + ! First example of use of CDALL: specify for each process a number of + ! contiguous rows + ! + call psb_cdall(ictxt,desc_a,info,nl=nr) + myidx = desc_a%get_global_indices() + nlr = size(myidx) + + case(2) + ! A partition defined by the user through IV + + if (present(iv)) then + if (size(iv) /= m) then + write(psb_err_unit,*) iam, 'Initialization error: wrong IV size',size(iv),m + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + return + end if + else + write(psb_err_unit,*) iam, 'Initialization error: IV not present' + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + return + end if + ! - nt = (m+np-1)/np - nr = max(0,min(nt,m-(iam*nt))) - end if + ! Second example of use of CDALL: specify for each row the + ! process that owns it + ! + call psb_cdall(ictxt,desc_a,info,vg=iv) + myidx = desc_a%get_global_indices() + nlr = size(myidx) + + case(3) + ! A 2-dimensional partition + + ! A nifty MPI function will split the process list + npdims = 0 + call mpi_dims_create(np,2,npdims,info) + npx = npdims(1) + npy = npdims(2) + + allocate(bndx(0:npx),bndy(0:npy)) + ! We can reuse idx2ijk for process indices as well. + call idx2ijk(iamx,iamy,iam,npx,npy,base=0) + ! Now let's split the 2D square in rectangles + call dist1Didx(bndx,idim,npx) + mynx = bndx(iamx+1)-bndx(iamx) + call dist1Didx(bndy,idim,npy) + myny = bndy(iamy+1)-bndy(iamy) + + ! How many indices do I own? + nlr = mynx*myny + allocate(myidx(nlr)) + ! Now, let's generate the list of indices I own + nr = 0 + do i=bndx(iamx),bndx(iamx+1)-1 + do j=bndy(iamy),bndx(iamy+1)-1 + nr = nr + 1 + call ijk2idx(myidx(nr),i,j,idim,idim) + end do + end do + if (nr /= nlr) then + write(psb_err_unit,*) iam,iamx,iamy, 'Initialization error: NR vs NLR ',& + & nr,nlr,mynx,myny + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + end if - nt = nr - call psb_sum(ictxt,nt) - if (nt /= m) then - write(psb_err_unit,*) iam, 'Initialization error ',nr,nt,m + ! + ! Third example of use of CDALL: specify for each process + ! the set of global indices it owns. + ! + call psb_cdall(ictxt,desc_a,info,vl=myidx) + + case default + write(psb_err_unit,*) iam, 'Initialization error: should not get here' info = -1 call psb_barrier(ictxt) call psb_abort(ictxt) - return - end if - call psb_barrier(ictxt) - t0 = psb_wtime() - call psb_cdall(ictxt,desc_a,info,nl=nr) + return + end select + + if (info == psb_success_) call psb_spall(a,desc_a,info,nnz=nnz) ! define rhs from boundary conditions; also build initial guess if (info == psb_success_) call psb_geall(xv,desc_a,info) if (info == psb_success_) call psb_geall(bv,desc_a,info) + call psb_barrier(ictxt) talc = psb_wtime()-t0 @@ -221,9 +328,6 @@ contains endif - myidx = desc_a%get_global_indices() - nlr = size(myidx) - ! loop over rows belonging to current process in a block ! distribution. @@ -237,13 +341,8 @@ contains ! local matrix pointer glob_row=myidx(i) ! compute gridpoint coordinates - if (mod(glob_row,(idim)) == 0) then - ix = glob_row/(idim) - else - ix = glob_row/(idim)+1 - endif - iy = (glob_row-(ix-1)*idim) - ! x, y + call idx2ijk(ix,iy,glob_row,idim,idim) + ! x, y coordinates x = (ix-1)*deltah y = (iy-1)*deltah diff --git a/tests/pdegen/mld_s_pde3d.f90 b/tests/pdegen/mld_s_pde3d.f90 index 6c7384d9..21d9d1d0 100644 --- a/tests/pdegen/mld_s_pde3d.f90 +++ b/tests/pdegen/mld_s_pde3d.f90 @@ -57,10 +57,12 @@ ! ! Note that if b1=b2=b3=c=0., the PDE is the Laplace equation. ! -! In this sample program the index space of the discretized -! computational domain is first numbered sequentially in a standard way, -! then the corresponding vector is distributed according to a BLOCK -! data distribution. +! There are three choices available for data distribution: +! 1. A simple BLOCK distribution +! 2. A ditribution based on arbitrary assignment of indices to processes, +! typically from a graph partitioner +! 3. A 3D distribution in which the unit cube is partitioned +! into subcubes, each one assigned to a process. ! module mld_s_pde3d_mod use psb_base_mod, only : psb_spk_, psb_ipk_, psb_desc_type,& @@ -96,8 +98,9 @@ contains ! the rhs. ! subroutine mld_s_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt,& - & a1,a2,a3,b1,b2,b3,c,g,info,f,amold,vmold,imold,nrl,iv) + & a1,a2,a3,b1,b2,b3,c,g,info,f,amold,vmold,imold,partition,nrl,iv) use psb_base_mod + use psb_util_mod ! ! Discretizes the partial differential equation ! @@ -125,7 +128,7 @@ contains class(psb_s_base_sparse_mat), optional :: amold class(psb_s_base_vect_type), optional :: vmold class(psb_i_base_vect_type), optional :: imold - integer(psb_ipk_), optional :: nrl,iv(:) + integer(psb_ipk_), optional :: partition, nrl,iv(:) ! Local variables. @@ -134,9 +137,13 @@ contains type(psb_s_coo_sparse_mat) :: acoo type(psb_s_csr_sparse_mat) :: acsr real(psb_spk_) :: zt(nb),x,y,z - integer(psb_ipk_) :: m,n,nnz,glob_row,nlr,i,ii,ib,k + integer(psb_ipk_) :: m,n,nnz,nr,nt,glob_row,nlr,i,j,ii,ib,k, partition_ integer(psb_ipk_) :: ix,iy,iz,ia,indx_owner - integer(psb_ipk_) :: np, iam, nr, nt + ! For 3D partition + integer(psb_ipk_) :: npx,npy,npz, npdims(3),iamx,iamy,iamz,mynx,myny,mynz + integer(psb_ipk_), allocatable :: bndx(:),bndy(:),bndz(:) + ! Process grid + integer(psb_ipk_) :: np, iam integer(psb_ipk_) :: icoeff integer(psb_ipk_), allocatable :: irow(:),icol(:),myidx(:) real(psb_spk_), allocatable :: val(:) @@ -166,15 +173,28 @@ contains sqdeltah = deltah*deltah deltah2 = 2.d0* deltah + if (present(partition)) then + if ((1<= partition).and.(partition <= 3)) then + partition_ = partition + else + write(*,*) 'Invalid partition choice ',partition,' defaulting to 3' + partition_ = 3 + end if + else + partition_ = 3 + end if + ! initialize array descriptor and sparse matrix storage. provide an ! estimate of the number of non zeroes - + m = idim*idim*idim n = m nnz = ((n*9)/(np)) if(iam == psb_root_) write(psb_out_unit,'("Generating Matrix (size=",i0,")...")')n - if (.not.present(iv)) then + select case(partition_) + case(1) + ! A BLOCK partition if (present(nrl)) then nr = nrl else @@ -194,24 +214,99 @@ contains call psb_abort(ictxt) return end if - else - if (size(iv) /= m) then - write(psb_err_unit,*) iam, 'Initialization error IV',size(iv),m + + ! + ! First example of use of CDALL: specify for each process a number of + ! contiguous rows + ! + call psb_cdall(ictxt,desc_a,info,nl=nr) + myidx = desc_a%get_global_indices() + nlr = size(myidx) + + case(2) + ! A partition defined by the user through IV + + if (present(iv)) then + if (size(iv) /= m) then + write(psb_err_unit,*) iam, 'Initialization error: wrong IV size',size(iv),m + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + return + end if + else + write(psb_err_unit,*) iam, 'Initialization error: IV not present' info = -1 call psb_barrier(ictxt) call psb_abort(ictxt) return end if - end if - call psb_barrier(ictxt) - t0 = psb_wtime() - if (present(iv)) then + ! + ! Second example of use of CDALL: specify for each row the + ! process that owns it + ! call psb_cdall(ictxt,desc_a,info,vg=iv) - else - call psb_cdall(ictxt,desc_a,info,nl=nr) - end if + myidx = desc_a%get_global_indices() + nlr = size(myidx) + + case(3) + ! A 3-dimensional partition + + ! A nifty MPI function will split the process list + npdims = 0 + call mpi_dims_create(np,3,npdims,info) + npx = npdims(1) + npy = npdims(2) + npz = npdims(3) + + allocate(bndx(0:npx),bndy(0:npy),bndz(0:npz)) + ! We can reuse idx2ijk for process indices as well. + call idx2ijk(iamx,iamy,iamz,iam,npx,npy,npz,base=0) + ! Now let's split the 3D cube in hexahedra + call dist1Didx(bndx,idim,npx) + mynx = bndx(iamx+1)-bndx(iamx) + call dist1Didx(bndy,idim,npy) + myny = bndy(iamy+1)-bndy(iamy) + call dist1Didx(bndz,idim,npz) + mynz = bndz(iamz+1)-bndz(iamz) + + ! How many indices do I own? + nlr = mynx*myny*mynz + allocate(myidx(nlr)) + ! Now, let's generate the list of indices I own + nr = 0 + do i=bndx(iamx),bndx(iamx+1)-1 + do j=bndy(iamy),bndx(iamy+1)-1 + do k=bndz(iamz),bndz(iamz+1)-1 + nr = nr + 1 + call ijk2idx(myidx(nr),i,j,k,idim,idim,idim) + end do + end do + end do + if (nr /= nlr) then + write(psb_err_unit,*) iam,iamx,iamy,iamz, 'Initialization error: NR vs NLR ',& + & nr,nlr,mynx,myny,mynz + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + end if + + ! + ! Third example of use of CDALL: specify for each process + ! the set of global indices it owns. + ! + call psb_cdall(ictxt,desc_a,info,vl=myidx) + + case default + write(psb_err_unit,*) iam, 'Initialization error: should not get here' + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + return + end select + if (info == psb_success_) call psb_spall(a,desc_a,info,nnz=nnz) ! define rhs from boundary conditions; also build initial guess if (info == psb_success_) call psb_geall(xv,desc_a,info) @@ -239,8 +334,6 @@ contains goto 9999 endif - myidx = desc_a%get_global_indices() - nlr = size(myidx) ! loop over rows belonging to current process in a block ! distribution. @@ -255,18 +348,8 @@ contains ! local matrix pointer glob_row=myidx(i) ! compute gridpoint coordinates - if (mod(glob_row,(idim*idim)) == 0) then - ix = glob_row/(idim*idim) - else - ix = glob_row/(idim*idim)+1 - endif - if (mod((glob_row-(ix-1)*idim*idim),idim) == 0) then - iy = (glob_row-(ix-1)*idim*idim)/idim - else - iy = (glob_row-(ix-1)*idim*idim)/idim+1 - endif - iz = glob_row-(ix-1)*idim*idim-(iy-1)*idim - ! x, y, x coordinates + call idx2ijk(ix,iy,iz,glob_row,idim,idim,idim) + ! x, y, z coordinates x = (ix-1)*deltah y = (iy-1)*deltah z = (iz-1)*deltah From c47913ed3cc7254dfb9bd2eb27722409f3fedd06 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Sun, 18 Feb 2018 15:06:49 +0000 Subject: [PATCH 03/33] Put in new cartesian data partition from PSBLAS. --- examples/pdegen/mld_dpde_mod.f90 | 142 ++++++++++++++++++++++++------- examples/pdegen/mld_spde_mod.f90 | 142 ++++++++++++++++++++++++------- 2 files changed, 222 insertions(+), 62 deletions(-) diff --git a/examples/pdegen/mld_dpde_mod.f90 b/examples/pdegen/mld_dpde_mod.f90 index 461334b6..44f65ff2 100644 --- a/examples/pdegen/mld_dpde_mod.f90 +++ b/examples/pdegen/mld_dpde_mod.f90 @@ -68,8 +68,9 @@ contains ! the rhs. ! subroutine mld_d_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt,& - & a1,a2,a3,b1,b2,b3,c,g,info,f,amold,vmold,imold,nrl,iv) + & a1,a2,a3,b1,b2,b3,c,g,info,f,amold,vmold,imold,partition,nrl,iv) use psb_base_mod + use psb_util_mod ! ! Discretizes the partial differential equation ! @@ -97,7 +98,7 @@ contains class(psb_d_base_sparse_mat), optional :: amold class(psb_d_base_vect_type), optional :: vmold class(psb_i_base_vect_type), optional :: imold - integer(psb_ipk_), optional :: nrl,iv(:) + integer(psb_ipk_), optional :: partition, nrl,iv(:) ! Local variables. @@ -106,9 +107,13 @@ contains type(psb_d_coo_sparse_mat) :: acoo type(psb_d_csr_sparse_mat) :: acsr real(psb_dpk_) :: zt(nb),x,y,z - integer(psb_ipk_) :: m,n,nnz,glob_row,nlr,i,ii,ib,k + integer(psb_ipk_) :: m,n,nnz,nr,nt,glob_row,nlr,i,j,ii,ib,k, partition_ integer(psb_ipk_) :: ix,iy,iz,ia,indx_owner - integer(psb_ipk_) :: np, iam, nr, nt + ! For 3D partition + integer(psb_ipk_) :: npx,npy,npz, npdims(3),iamx,iamy,iamz,mynx,myny,mynz + integer(psb_ipk_), allocatable :: bndx(:),bndy(:),bndz(:) + ! Process grid + integer(psb_ipk_) :: np, iam integer(psb_ipk_) :: icoeff integer(psb_ipk_), allocatable :: irow(:),icol(:),myidx(:) real(psb_dpk_), allocatable :: val(:) @@ -138,15 +143,28 @@ contains sqdeltah = deltah*deltah deltah2 = 2.d0* deltah + if (present(partition)) then + if ((1<= partition).and.(partition <= 3)) then + partition_ = partition + else + write(*,*) 'Invalid partition choice ',partition,' defaulting to 3' + partition_ = 3 + end if + else + partition_ = 3 + end if + ! initialize array descriptor and sparse matrix storage. provide an ! estimate of the number of non zeroes - + m = idim*idim*idim n = m nnz = ((n*9)/(np)) if(iam == psb_root_) write(psb_out_unit,'("Generating Matrix (size=",i0,")...")')n - if (.not.present(iv)) then + select case(partition_) + case(1) + ! A BLOCK partition if (present(nrl)) then nr = nrl else @@ -166,24 +184,99 @@ contains call psb_abort(ictxt) return end if - else - if (size(iv) /= m) then - write(psb_err_unit,*) iam, 'Initialization error IV',size(iv),m + + ! + ! First example of use of CDALL: specify for each process a number of + ! contiguous rows + ! + call psb_cdall(ictxt,desc_a,info,nl=nr) + myidx = desc_a%get_global_indices() + nlr = size(myidx) + + case(2) + ! A partition defined by the user through IV + + if (present(iv)) then + if (size(iv) /= m) then + write(psb_err_unit,*) iam, 'Initialization error: wrong IV size',size(iv),m + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + return + end if + else + write(psb_err_unit,*) iam, 'Initialization error: IV not present' info = -1 call psb_barrier(ictxt) call psb_abort(ictxt) return end if - end if - call psb_barrier(ictxt) - t0 = psb_wtime() - if (present(iv)) then + ! + ! Second example of use of CDALL: specify for each row the + ! process that owns it + ! call psb_cdall(ictxt,desc_a,info,vg=iv) - else - call psb_cdall(ictxt,desc_a,info,nl=nr) - end if + myidx = desc_a%get_global_indices() + nlr = size(myidx) + + case(3) + ! A 3-dimensional partition + + ! A nifty MPI function will split the process list + npdims = 0 + call mpi_dims_create(np,3,npdims,info) + npx = npdims(1) + npy = npdims(2) + npz = npdims(3) + + allocate(bndx(0:npx),bndy(0:npy),bndz(0:npz)) + ! We can reuse idx2ijk for process indices as well. + call idx2ijk(iamx,iamy,iamz,iam,npx,npy,npz,base=0) + ! Now let's split the 3D cube in hexahedra + call dist1Didx(bndx,idim,npx) + mynx = bndx(iamx+1)-bndx(iamx) + call dist1Didx(bndy,idim,npy) + myny = bndy(iamy+1)-bndy(iamy) + call dist1Didx(bndz,idim,npz) + mynz = bndz(iamz+1)-bndz(iamz) + + ! How many indices do I own? + nlr = mynx*myny*mynz + allocate(myidx(nlr)) + ! Now, let's generate the list of indices I own + nr = 0 + do i=bndx(iamx),bndx(iamx+1)-1 + do j=bndy(iamy),bndx(iamy+1)-1 + do k=bndz(iamz),bndz(iamz+1)-1 + nr = nr + 1 + call ijk2idx(myidx(nr),i,j,k,idim,idim,idim) + end do + end do + end do + if (nr /= nlr) then + write(psb_err_unit,*) iam,iamx,iamy,iamz, 'Initialization error: NR vs NLR ',& + & nr,nlr,mynx,myny,mynz + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + end if + ! + ! Third example of use of CDALL: specify for each process + ! the set of global indices it owns. + ! + call psb_cdall(ictxt,desc_a,info,vl=myidx) + + case default + write(psb_err_unit,*) iam, 'Initialization error: should not get here' + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + return + end select + + if (info == psb_success_) call psb_spall(a,desc_a,info,nnz=nnz) ! define rhs from boundary conditions; also build initial guess if (info == psb_success_) call psb_geall(xv,desc_a,info) @@ -211,8 +304,6 @@ contains goto 9999 endif - myidx = desc_a%get_global_indices() - nlr = size(myidx) ! loop over rows belonging to current process in a block ! distribution. @@ -227,18 +318,8 @@ contains ! local matrix pointer glob_row=myidx(i) ! compute gridpoint coordinates - if (mod(glob_row,(idim*idim)) == 0) then - ix = glob_row/(idim*idim) - else - ix = glob_row/(idim*idim)+1 - endif - if (mod((glob_row-(ix-1)*idim*idim),idim) == 0) then - iy = (glob_row-(ix-1)*idim*idim)/idim - else - iy = (glob_row-(ix-1)*idim*idim)/idim+1 - endif - iz = glob_row-(ix-1)*idim*idim-(iy-1)*idim - ! x, y, x coordinates + call idx2ijk(ix,iy,iz,glob_row,idim,idim,idim) + ! x, y, z coordinates x = (ix-1)*deltah y = (iy-1)*deltah z = (iz-1)*deltah @@ -383,7 +464,6 @@ contains return end subroutine mld_d_gen_pde3d - ! ! functions parametrizing the differential equation ! diff --git a/examples/pdegen/mld_spde_mod.f90 b/examples/pdegen/mld_spde_mod.f90 index e14153a3..6548fe00 100644 --- a/examples/pdegen/mld_spde_mod.f90 +++ b/examples/pdegen/mld_spde_mod.f90 @@ -68,8 +68,9 @@ contains ! the rhs. ! subroutine mld_s_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt,& - & a1,a2,a3,b1,b2,b3,c,g,info,f,amold,vmold,imold,nrl,iv) + & a1,a2,a3,b1,b2,b3,c,g,info,f,amold,vmold,imold,partition,nrl,iv) use psb_base_mod + use psb_util_mod ! ! Discretizes the partial differential equation ! @@ -97,7 +98,7 @@ contains class(psb_s_base_sparse_mat), optional :: amold class(psb_s_base_vect_type), optional :: vmold class(psb_i_base_vect_type), optional :: imold - integer(psb_ipk_), optional :: nrl,iv(:) + integer(psb_ipk_), optional :: partition, nrl,iv(:) ! Local variables. @@ -106,9 +107,13 @@ contains type(psb_s_coo_sparse_mat) :: acoo type(psb_s_csr_sparse_mat) :: acsr real(psb_spk_) :: zt(nb),x,y,z - integer(psb_ipk_) :: m,n,nnz,glob_row,nlr,i,ii,ib,k + integer(psb_ipk_) :: m,n,nnz,nr,nt,glob_row,nlr,i,j,ii,ib,k, partition_ integer(psb_ipk_) :: ix,iy,iz,ia,indx_owner - integer(psb_ipk_) :: np, iam, nr, nt + ! For 3D partition + integer(psb_ipk_) :: npx,npy,npz, npdims(3),iamx,iamy,iamz,mynx,myny,mynz + integer(psb_ipk_), allocatable :: bndx(:),bndy(:),bndz(:) + ! Process grid + integer(psb_ipk_) :: np, iam integer(psb_ipk_) :: icoeff integer(psb_ipk_), allocatable :: irow(:),icol(:),myidx(:) real(psb_spk_), allocatable :: val(:) @@ -138,15 +143,28 @@ contains sqdeltah = deltah*deltah deltah2 = 2.d0* deltah + if (present(partition)) then + if ((1<= partition).and.(partition <= 3)) then + partition_ = partition + else + write(*,*) 'Invalid partition choice ',partition,' defaulting to 3' + partition_ = 3 + end if + else + partition_ = 3 + end if + ! initialize array descriptor and sparse matrix storage. provide an ! estimate of the number of non zeroes - + m = idim*idim*idim n = m nnz = ((n*9)/(np)) if(iam == psb_root_) write(psb_out_unit,'("Generating Matrix (size=",i0,")...")')n - if (.not.present(iv)) then + select case(partition_) + case(1) + ! A BLOCK partition if (present(nrl)) then nr = nrl else @@ -166,24 +184,99 @@ contains call psb_abort(ictxt) return end if - else - if (size(iv) /= m) then - write(psb_err_unit,*) iam, 'Initialization error IV',size(iv),m + + ! + ! First example of use of CDALL: specify for each process a number of + ! contiguous rows + ! + call psb_cdall(ictxt,desc_a,info,nl=nr) + myidx = desc_a%get_global_indices() + nlr = size(myidx) + + case(2) + ! A partition defined by the user through IV + + if (present(iv)) then + if (size(iv) /= m) then + write(psb_err_unit,*) iam, 'Initialization error: wrong IV size',size(iv),m + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + return + end if + else + write(psb_err_unit,*) iam, 'Initialization error: IV not present' info = -1 call psb_barrier(ictxt) call psb_abort(ictxt) return end if - end if - call psb_barrier(ictxt) - t0 = psb_wtime() - if (present(iv)) then + ! + ! Second example of use of CDALL: specify for each row the + ! process that owns it + ! call psb_cdall(ictxt,desc_a,info,vg=iv) - else - call psb_cdall(ictxt,desc_a,info,nl=nr) - end if + myidx = desc_a%get_global_indices() + nlr = size(myidx) + + case(3) + ! A 3-dimensional partition + + ! A nifty MPI function will split the process list + npdims = 0 + call mpi_dims_create(np,3,npdims,info) + npx = npdims(1) + npy = npdims(2) + npz = npdims(3) + + allocate(bndx(0:npx),bndy(0:npy),bndz(0:npz)) + ! We can reuse idx2ijk for process indices as well. + call idx2ijk(iamx,iamy,iamz,iam,npx,npy,npz,base=0) + ! Now let's split the 3D cube in hexahedra + call dist1Didx(bndx,idim,npx) + mynx = bndx(iamx+1)-bndx(iamx) + call dist1Didx(bndy,idim,npy) + myny = bndy(iamy+1)-bndy(iamy) + call dist1Didx(bndz,idim,npz) + mynz = bndz(iamz+1)-bndz(iamz) + + ! How many indices do I own? + nlr = mynx*myny*mynz + allocate(myidx(nlr)) + ! Now, let's generate the list of indices I own + nr = 0 + do i=bndx(iamx),bndx(iamx+1)-1 + do j=bndy(iamy),bndx(iamy+1)-1 + do k=bndz(iamz),bndz(iamz+1)-1 + nr = nr + 1 + call ijk2idx(myidx(nr),i,j,k,idim,idim,idim) + end do + end do + end do + if (nr /= nlr) then + write(psb_err_unit,*) iam,iamx,iamy,iamz, 'Initialization error: NR vs NLR ',& + & nr,nlr,mynx,myny,mynz + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + end if + ! + ! Third example of use of CDALL: specify for each process + ! the set of global indices it owns. + ! + call psb_cdall(ictxt,desc_a,info,vl=myidx) + + case default + write(psb_err_unit,*) iam, 'Initialization error: should not get here' + info = -1 + call psb_barrier(ictxt) + call psb_abort(ictxt) + return + end select + + if (info == psb_success_) call psb_spall(a,desc_a,info,nnz=nnz) ! define rhs from boundary conditions; also build initial guess if (info == psb_success_) call psb_geall(xv,desc_a,info) @@ -211,8 +304,6 @@ contains goto 9999 endif - myidx = desc_a%get_global_indices() - nlr = size(myidx) ! loop over rows belonging to current process in a block ! distribution. @@ -227,18 +318,8 @@ contains ! local matrix pointer glob_row=myidx(i) ! compute gridpoint coordinates - if (mod(glob_row,(idim*idim)) == 0) then - ix = glob_row/(idim*idim) - else - ix = glob_row/(idim*idim)+1 - endif - if (mod((glob_row-(ix-1)*idim*idim),idim) == 0) then - iy = (glob_row-(ix-1)*idim*idim)/idim - else - iy = (glob_row-(ix-1)*idim*idim)/idim+1 - endif - iz = glob_row-(ix-1)*idim*idim-(iy-1)*idim - ! x, y, x coordinates + call idx2ijk(ix,iy,iz,glob_row,idim,idim,idim) + ! x, y, z coordinates x = (ix-1)*deltah y = (iy-1)*deltah z = (iz-1)*deltah @@ -383,7 +464,6 @@ contains return end subroutine mld_s_gen_pde3d - ! ! functions parametrizing the differential equation ! From 5b0bd2694b1c96d26c3ab1b18c8b102ddf326282 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Mon, 26 Feb 2018 12:40:11 +0000 Subject: [PATCH 04/33] Fixed bnoundaries in generation loop. --- tests/pdegen/mld_d_pde2d.f90 | 2 +- tests/pdegen/mld_d_pde3d.f90 | 2 +- tests/pdegen/mld_s_pde2d.f90 | 2 +- tests/pdegen/mld_s_pde3d.f90 | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/tests/pdegen/mld_d_pde2d.f90 b/tests/pdegen/mld_d_pde2d.f90 index 15ccd34a..571f6e84 100644 --- a/tests/pdegen/mld_d_pde2d.f90 +++ b/tests/pdegen/mld_d_pde2d.f90 @@ -272,7 +272,7 @@ contains ! Now, let's generate the list of indices I own nr = 0 do i=bndx(iamx),bndx(iamx+1)-1 - do j=bndy(iamy),bndx(iamy+1)-1 + do j=bndy(iamy),bndy(iamy+1)-1 nr = nr + 1 call ijk2idx(myidx(nr),i,j,idim,idim) end do diff --git a/tests/pdegen/mld_d_pde3d.f90 b/tests/pdegen/mld_d_pde3d.f90 index 7f89d06c..3ea85e6a 100644 --- a/tests/pdegen/mld_d_pde3d.f90 +++ b/tests/pdegen/mld_d_pde3d.f90 @@ -277,7 +277,7 @@ contains ! Now, let's generate the list of indices I own nr = 0 do i=bndx(iamx),bndx(iamx+1)-1 - do j=bndy(iamy),bndx(iamy+1)-1 + do j=bndy(iamy),bndy(iamy+1)-1 do k=bndz(iamz),bndz(iamz+1)-1 nr = nr + 1 call ijk2idx(myidx(nr),i,j,k,idim,idim,idim) diff --git a/tests/pdegen/mld_s_pde2d.f90 b/tests/pdegen/mld_s_pde2d.f90 index 63d82cd3..7b730136 100644 --- a/tests/pdegen/mld_s_pde2d.f90 +++ b/tests/pdegen/mld_s_pde2d.f90 @@ -272,7 +272,7 @@ contains ! Now, let's generate the list of indices I own nr = 0 do i=bndx(iamx),bndx(iamx+1)-1 - do j=bndy(iamy),bndx(iamy+1)-1 + do j=bndy(iamy),bndy(iamy+1)-1 nr = nr + 1 call ijk2idx(myidx(nr),i,j,idim,idim) end do diff --git a/tests/pdegen/mld_s_pde3d.f90 b/tests/pdegen/mld_s_pde3d.f90 index 21d9d1d0..257f9521 100644 --- a/tests/pdegen/mld_s_pde3d.f90 +++ b/tests/pdegen/mld_s_pde3d.f90 @@ -277,7 +277,7 @@ contains ! Now, let's generate the list of indices I own nr = 0 do i=bndx(iamx),bndx(iamx+1)-1 - do j=bndy(iamy),bndx(iamy+1)-1 + do j=bndy(iamy),bndy(iamy+1)-1 do k=bndz(iamz),bndz(iamz+1)-1 nr = nr + 1 call ijk2idx(myidx(nr),i,j,k,idim,idim,idim) From 11f25be21828134fb6f4e7bb45e48c11d3da6ecc Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Wed, 14 Mar 2018 20:35:10 +0000 Subject: [PATCH 05/33] Fix time measurements. --- tests/pdegen/mld_d_pde2d.f90 | 2 +- tests/pdegen/mld_d_pde3d.f90 | 2 +- tests/pdegen/mld_s_pde2d.f90 | 2 +- tests/pdegen/mld_s_pde3d.f90 | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/tests/pdegen/mld_d_pde2d.f90 b/tests/pdegen/mld_d_pde2d.f90 index 571f6e84..97c0edc9 100644 --- a/tests/pdegen/mld_d_pde2d.f90 +++ b/tests/pdegen/mld_d_pde2d.f90 @@ -189,7 +189,7 @@ contains n = m nnz = ((n*7)/(np)) if(iam == psb_root_) write(psb_out_unit,'("Generating Matrix (size=",i0,")...")')n - + t0 = psb_wtime() select case(partition_) case(1) ! A BLOCK partition diff --git a/tests/pdegen/mld_d_pde3d.f90 b/tests/pdegen/mld_d_pde3d.f90 index 3ea85e6a..29637311 100644 --- a/tests/pdegen/mld_d_pde3d.f90 +++ b/tests/pdegen/mld_d_pde3d.f90 @@ -191,7 +191,7 @@ contains n = m nnz = ((n*9)/(np)) if(iam == psb_root_) write(psb_out_unit,'("Generating Matrix (size=",i0,")...")')n - + t0 = psb_wtime() select case(partition_) case(1) ! A BLOCK partition diff --git a/tests/pdegen/mld_s_pde2d.f90 b/tests/pdegen/mld_s_pde2d.f90 index 7b730136..58712234 100644 --- a/tests/pdegen/mld_s_pde2d.f90 +++ b/tests/pdegen/mld_s_pde2d.f90 @@ -189,7 +189,7 @@ contains n = m nnz = ((n*7)/(np)) if(iam == psb_root_) write(psb_out_unit,'("Generating Matrix (size=",i0,")...")')n - + t0 = psb_wtime() select case(partition_) case(1) ! A BLOCK partition diff --git a/tests/pdegen/mld_s_pde3d.f90 b/tests/pdegen/mld_s_pde3d.f90 index 257f9521..fca609ce 100644 --- a/tests/pdegen/mld_s_pde3d.f90 +++ b/tests/pdegen/mld_s_pde3d.f90 @@ -191,7 +191,7 @@ contains n = m nnz = ((n*9)/(np)) if(iam == psb_root_) write(psb_out_unit,'("Generating Matrix (size=",i0,")...")')n - + t0 = psb_wtime() select case(partition_) case(1) ! A BLOCK partition From 77624b2518b883066c408270b100afa7b3a513a6 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Mon, 23 Apr 2018 15:03:14 +0100 Subject: [PATCH 06/33] Aligned matrix generation with that from base PSBLAS library. --- tests/pdegen/mld_d_pde2d.f90 | 125 ++++++++++++++-------------- tests/pdegen/mld_d_pde3d.f90 | 153 ++++++++++++++++++----------------- tests/pdegen/mld_s_pde2d.f90 | 125 ++++++++++++++-------------- tests/pdegen/mld_s_pde3d.f90 | 153 ++++++++++++++++++----------------- 4 files changed, 290 insertions(+), 266 deletions(-) diff --git a/tests/pdegen/mld_d_pde2d.f90 b/tests/pdegen/mld_d_pde2d.f90 index 97c0edc9..b8fe23cb 100644 --- a/tests/pdegen/mld_d_pde2d.f90 +++ b/tests/pdegen/mld_d_pde2d.f90 @@ -90,15 +90,66 @@ contains end function d_null_func_2d + ! + ! functions parametrizing the differential equation + ! + function b1(x,y) + use psb_base_mod, only : psb_dpk_, done, dzero + implicit none + real(psb_dpk_) :: b1 + real(psb_dpk_), intent(in) :: x,y + b1=done/sqrt((2*done)) + end function b1 + function b2(x,y) + use psb_base_mod, only : psb_dpk_, done, dzero + implicit none + real(psb_dpk_) :: b2 + real(psb_dpk_), intent(in) :: x,y + b2=done/sqrt((2*done)) + end function b2 + function c(x,y) + use psb_base_mod, only : psb_dpk_, done, dzero + implicit none + real(psb_dpk_) :: c + real(psb_dpk_), intent(in) :: x,y + c=0.d0 + end function c + function a1(x,y) + use psb_base_mod, only : psb_dpk_, done, dzero + implicit none + real(psb_dpk_) :: a1 + real(psb_dpk_), intent(in) :: x,y + a1=done/80 + end function a1 + function a2(x,y) + use psb_base_mod, only : psb_dpk_, done, dzero + implicit none + real(psb_dpk_) :: a2 + real(psb_dpk_), intent(in) :: x,y + a2=done/80 + end function a2 + function g(x,y) + use psb_base_mod, only : psb_dpk_, done, dzero + implicit none + real(psb_dpk_) :: g + real(psb_dpk_), intent(in) :: x,y + g = dzero + if (x == done) then + g = done + else if (x == dzero) then + g = exp(-y**2) + end if + end function g + ! ! subroutine to allocate and fill in the coefficient matrix and ! the rhs. ! - subroutine mld_d_gen_pde2d(ictxt,idim,a,bv,xv,desc_a,afmt,& - & a1,a2,b1,b2,c,g,info,f,amold,vmold,imold,partition,nrl,iv) + subroutine mld_d_gen_pde2d(ictxt,idim,a,bv,xv,desc_a,afmt,info,& + & f,amold,vmold,imold,partition,nrl,iv) use psb_base_mod - use psb_util_mod + use psb_util_mod ! ! Discretizes the partial differential equation ! @@ -115,7 +166,6 @@ contains ! Note that if b1=b2=c=0., the PDE is the Laplace equation. ! implicit none - procedure(d_func_2d) :: b1,b2,c,a1,a2,g integer(psb_ipk_) :: idim type(psb_dspmat_type) :: a type(psb_d_vect_type) :: xv,bv @@ -148,7 +198,7 @@ contains ! deltah dimension of each grid cell ! deltat discretization time real(psb_dpk_) :: deltah, sqdeltah, deltah2 - real(psb_dpk_), parameter :: rhs=0.e0,one=1.e0,zero=0.e0 + real(psb_dpk_), parameter :: rhs=dzero,one=done,zero=dzero real(psb_dpk_) :: t0, t1, t2, t3, tasb, talc, ttot, tgen, tcdasb integer(psb_ipk_) :: err_act procedure(d_func_2d), pointer :: f_ @@ -167,9 +217,9 @@ contains f_ => d_null_func_2d end if - deltah = 1.e0/(idim+2) + deltah = done/(idim+2) sqdeltah = deltah*deltah - deltah2 = 2.e0* deltah + deltah2 = (2*done)* deltah if (present(partition)) then if ((1<= partition).and.(partition <= 3)) then @@ -355,7 +405,7 @@ contains if (ix == 1) then zt(k) = g(dzero,y)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix-2)*idim+iy + call ijk2idx(icol(icoeff),ix-1,iy,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif @@ -364,14 +414,14 @@ contains if (iy == 1) then zt(k) = g(x,dzero)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix-1)*idim+(iy-1) + call ijk2idx(icol(icoeff),ix,iy-1,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif ! term depending on (x,y) - val(icoeff)=2.e0*(a1(x,y) + a2(x,y))/sqdeltah + c(x,y) - icol(icoeff) = (ix-1)*idim+iy + val(icoeff)=(2*done)*(a1(x,y) + a2(x,y))/sqdeltah + c(x,y) + call ijk2idx(icol(icoeff),ix,iy,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 ! term depending on (x,y+1) @@ -379,7 +429,7 @@ contains if (iy == idim) then zt(k) = g(x,done)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix-1)*idim+(iy+1) + call ijk2idx(icol(icoeff),ix,iy+1,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif @@ -388,7 +438,7 @@ contains if (ix==idim) then zt(k) = g(done,y)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix)*idim+(iy) + call ijk2idx(icol(icoeff),ix+1,iy,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif @@ -398,7 +448,7 @@ contains if(info /= psb_success_) exit call psb_geins(ib,myidx(ii:ii+ib-1),zt(1:ib),bv,desc_a,info) if(info /= psb_success_) exit - zt(:)=0.e0 + zt(:)=dzero call psb_geins(ib,myidx(ii:ii+ib-1),zt(1:ib),xv,desc_a,info) if(info /= psb_success_) exit end do @@ -469,50 +519,6 @@ contains end subroutine mld_d_gen_pde2d - ! - ! functions parametrizing the differential equation - ! - function b1(x,y) - use psb_base_mod, only : psb_dpk_,done,dzero - real(psb_dpk_) :: b1 - real(psb_dpk_), intent(in) :: x,y - b1=dzero - end function b1 - function b2(x,y) - use psb_base_mod, only : psb_dpk_,done,dzero - real(psb_dpk_) :: b2 - real(psb_dpk_), intent(in) :: x,y - b2=dzero - end function b2 - function c(x,y) - use psb_base_mod, only : psb_dpk_,done,dzero - real(psb_dpk_) :: c - real(psb_dpk_), intent(in) :: x,y - c=dzero - end function c - function a1(x,y) - use psb_base_mod, only : psb_dpk_,done,dzero - real(psb_dpk_) :: a1 - real(psb_dpk_), intent(in) :: x,y - a1=done - end function a1 - function a2(x,y) - use psb_base_mod, only : psb_dpk_,done,dzero - real(psb_dpk_) :: a2 - real(psb_dpk_), intent(in) :: x,y - a2=done - end function a2 - function g(x,y) - use psb_base_mod, only : psb_dpk_, done, dzero - real(psb_dpk_) :: g - real(psb_dpk_), intent(in) :: x,y - g = dzero - if (x == done) then - g = done - else if (x == dzero) then - g = exp(-y**2) - end if - end function g end module mld_d_pde2d_mod program mld_d_pde2d @@ -654,8 +660,7 @@ program mld_d_pde2d ! call psb_barrier(ictxt) t1 = psb_wtime() - call mld_gen_pde2d(ictxt,idim,a,b,x,desc_a,afmt,& - & a1,a2,b1,b2,c,g,info) + call mld_gen_pde2d(ictxt,idim,a,b,x,desc_a,afmt,info) call psb_barrier(ictxt) t2 = psb_wtime() - t1 if(info /= psb_success_) then diff --git a/tests/pdegen/mld_d_pde3d.f90 b/tests/pdegen/mld_d_pde3d.f90 index 29637311..a0976844 100644 --- a/tests/pdegen/mld_d_pde3d.f90 +++ b/tests/pdegen/mld_d_pde3d.f90 @@ -92,13 +92,78 @@ contains val = dzero end function d_null_func_3d + ! + ! functions parametrizing the differential equation + ! + function b1(x,y,z) + use psb_base_mod, only : psb_dpk_, done, dzero + implicit none + real(psb_dpk_) :: b1 + real(psb_dpk_), intent(in) :: x,y,z + b1=done/sqrt((3*done)) + end function b1 + function b2(x,y,z) + use psb_base_mod, only : psb_dpk_, done, dzero + implicit none + real(psb_dpk_) :: b2 + real(psb_dpk_), intent(in) :: x,y,z + b2=done/sqrt((3*done)) + end function b2 + function b3(x,y,z) + use psb_base_mod, only : psb_dpk_, done, dzero + implicit none + real(psb_dpk_) :: b3 + real(psb_dpk_), intent(in) :: x,y,z + b3=done/sqrt((3*done)) + end function b3 + function c(x,y,z) + use psb_base_mod, only : psb_dpk_, done, dzero + implicit none + real(psb_dpk_) :: c + real(psb_dpk_), intent(in) :: x,y,z + c=dzero + end function c + function a1(x,y,z) + use psb_base_mod, only : psb_dpk_, done, dzero + implicit none + real(psb_dpk_) :: a1 + real(psb_dpk_), intent(in) :: x,y,z + a1=done/80 + end function a1 + function a2(x,y,z) + use psb_base_mod, only : psb_dpk_, done, dzero + implicit none + real(psb_dpk_) :: a2 + real(psb_dpk_), intent(in) :: x,y,z + a2=done/80 + end function a2 + function a3(x,y,z) + use psb_base_mod, only : psb_dpk_, done, dzero + implicit none + real(psb_dpk_) :: a3 + real(psb_dpk_), intent(in) :: x,y,z + a3=done/80 + end function a3 + function g(x,y,z) + use psb_base_mod, only : psb_dpk_, done, dzero + implicit none + real(psb_dpk_) :: g + real(psb_dpk_), intent(in) :: x,y,z + g = dzero + if (x == done) then + g = done + else if (x == dzero) then + g = exp(y**2-z**2) + end if + end function g + ! ! subroutine to allocate and fill in the coefficient matrix and ! the rhs. ! - subroutine mld_d_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt,& - & a1,a2,a3,b1,b2,b3,c,g,info,f,amold,vmold,imold,partition,nrl,iv) + subroutine mld_d_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt,info,& + & f,amold,vmold,imold,partition,nrl,iv) use psb_base_mod use psb_util_mod ! @@ -117,7 +182,6 @@ contains ! Note that if b1=b2=b3=c=0., the PDE is the Laplace equation. ! implicit none - procedure(d_func_3d) :: b1,b2,b3,c,a1,a2,a3,g integer(psb_ipk_) :: idim type(psb_dspmat_type) :: a type(psb_d_vect_type) :: xv,bv @@ -169,9 +233,9 @@ contains f_ => d_null_func_3d end if - deltah = 1.d0/(idim+2) + deltah = done/(idim+2) sqdeltah = deltah*deltah - deltah2 = 2.d0* deltah + deltah2 = (2*done)* deltah if (present(partition)) then if ((1<= partition).and.(partition <= 3)) then @@ -189,7 +253,7 @@ contains m = idim*idim*idim n = m - nnz = ((n*9)/(np)) + nnz = ((n*7)/(np)) if(iam == psb_root_) write(psb_out_unit,'("Generating Matrix (size=",i0,")...")')n t0 = psb_wtime() select case(partition_) @@ -362,7 +426,7 @@ contains if (ix == 1) then zt(k) = g(dzero,y,z)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix-2)*idim*idim+(iy-1)*idim+(iz) + call ijk2idx(icol(icoeff),ix-1,iy,iz,idim,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif @@ -371,7 +435,7 @@ contains if (iy == 1) then zt(k) = g(x,dzero,z)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix-1)*idim*idim+(iy-2)*idim+(iz) + call ijk2idx(icol(icoeff),ix,iy-1,iz,idim,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif @@ -380,15 +444,15 @@ contains if (iz == 1) then zt(k) = g(x,y,dzero)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix-1)*idim*idim+(iy-1)*idim+(iz-1) + call ijk2idx(icol(icoeff),ix,iy,iz-1,idim,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif ! term depending on (x,y,z) - val(icoeff)=2.d0*(a1(x,y,z)+a2(x,y,z)+a3(x,y,z))/sqdeltah & + val(icoeff)=(2*done)*(a1(x,y,z)+a2(x,y,z)+a3(x,y,z))/sqdeltah & & + c(x,y,z) - icol(icoeff) = (ix-1)*idim*idim+(iy-1)*idim+(iz) + call ijk2idx(icol(icoeff),ix,iy,iz,idim,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 ! term depending on (x,y,z+1) @@ -396,7 +460,7 @@ contains if (iz == idim) then zt(k) = g(x,y,done)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix-1)*idim*idim+(iy-1)*idim+(iz+1) + call ijk2idx(icol(icoeff),ix,iy,iz+1,idim,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif @@ -405,7 +469,7 @@ contains if (iy == idim) then zt(k) = g(x,done,z)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix-1)*idim*idim+(iy)*idim+(iz) + call ijk2idx(icol(icoeff),ix,iy+1,iz,idim,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif @@ -414,7 +478,7 @@ contains if (ix==idim) then zt(k) = g(done,y,z)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix)*idim*idim+(iy-1)*idim+(iz) + call ijk2idx(icol(icoeff),ix+1,iy,iz,idim,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif @@ -424,7 +488,7 @@ contains if(info /= psb_success_) exit call psb_geins(ib,myidx(ii:ii+ib-1),zt(1:ib),bv,desc_a,info) if(info /= psb_success_) exit - zt(:)=0.d0 + zt(:)=dzero call psb_geins(ib,myidx(ii:ii+ib-1),zt(1:ib),xv,desc_a,info) if(info /= psb_success_) exit end do @@ -494,62 +558,6 @@ contains return end subroutine mld_d_gen_pde3d - ! - ! functions parametrizing the differential equation - ! - function b1(x,y,z) - use psb_base_mod, only : psb_dpk_,done,dzero - real(psb_dpk_) :: b1 - real(psb_dpk_), intent(in) :: x,y,z - b1=dzero - end function b1 - function b2(x,y,z) - use psb_base_mod, only : psb_dpk_,done,dzero - real(psb_dpk_) :: b2 - real(psb_dpk_), intent(in) :: x,y,z - b2=dzero - end function b2 - function b3(x,y,z) - use psb_base_mod, only : psb_dpk_,done,dzero - real(psb_dpk_) :: b3 - real(psb_dpk_), intent(in) :: x,y,z - b3=dzero - end function b3 - function c(x,y,z) - use psb_base_mod, only : psb_dpk_,done,dzero - real(psb_dpk_) :: c - real(psb_dpk_), intent(in) :: x,y,z - c=dzero - end function c - function a1(x,y,z) - use psb_base_mod, only : psb_dpk_,done,dzero - real(psb_dpk_) :: a1 - real(psb_dpk_), intent(in) :: x,y,z - a1=done - end function a1 - function a2(x,y,z) - use psb_base_mod, only : psb_dpk_,done,dzero - real(psb_dpk_) :: a2 - real(psb_dpk_), intent(in) :: x,y,z - a2=done - end function a2 - function a3(x,y,z) - use psb_base_mod, only : psb_dpk_,done,dzero - real(psb_dpk_) :: a3 - real(psb_dpk_), intent(in) :: x,y,z - a3=done - end function a3 - function g(x,y,z) - use psb_base_mod, only : psb_dpk_,done,dzero - real(psb_dpk_) :: g - real(psb_dpk_), intent(in) :: x,y,z - g = dzero - if (x == done) then - g = done - else if (x == dzero) then - g = exp(y**2-z**2) - end if - end function g end module mld_d_pde3d_mod program mld_d_pde3d @@ -692,8 +700,7 @@ program mld_d_pde3d call psb_barrier(ictxt) t1 = psb_wtime() - call mld_gen_pde3d(ictxt,idim,a,b,x,desc_a,afmt,& - & a1,a2,a3,b1,b2,b3,c,g,info) + call mld_gen_pde3d(ictxt,idim,a,b,x,desc_a,afmt,info) call psb_barrier(ictxt) t2 = psb_wtime() - t1 if(info /= psb_success_) then diff --git a/tests/pdegen/mld_s_pde2d.f90 b/tests/pdegen/mld_s_pde2d.f90 index 58712234..bd5670e7 100644 --- a/tests/pdegen/mld_s_pde2d.f90 +++ b/tests/pdegen/mld_s_pde2d.f90 @@ -90,15 +90,66 @@ contains end function s_null_func_2d + ! + ! functions parametrizing the differential equation + ! + function b1(x,y) + use psb_base_mod, only : psb_spk_, sone, szero + implicit none + real(psb_spk_) :: b1 + real(psb_spk_), intent(in) :: x,y + b1=sone/sqrt((2*sone)) + end function b1 + function b2(x,y) + use psb_base_mod, only : psb_spk_, sone, szero + implicit none + real(psb_spk_) :: b2 + real(psb_spk_), intent(in) :: x,y + b2=sone/sqrt((2*sone)) + end function b2 + function c(x,y) + use psb_base_mod, only : psb_spk_, sone, szero + implicit none + real(psb_spk_) :: c + real(psb_spk_), intent(in) :: x,y + c=0.d0 + end function c + function a1(x,y) + use psb_base_mod, only : psb_spk_, sone, szero + implicit none + real(psb_spk_) :: a1 + real(psb_spk_), intent(in) :: x,y + a1=sone/80 + end function a1 + function a2(x,y) + use psb_base_mod, only : psb_spk_, sone, szero + implicit none + real(psb_spk_) :: a2 + real(psb_spk_), intent(in) :: x,y + a2=sone/80 + end function a2 + function g(x,y) + use psb_base_mod, only : psb_spk_, sone, szero + implicit none + real(psb_spk_) :: g + real(psb_spk_), intent(in) :: x,y + g = szero + if (x == sone) then + g = sone + else if (x == szero) then + g = exp(-y**2) + end if + end function g + ! ! subroutine to allocate and fill in the coefficient matrix and ! the rhs. ! - subroutine mld_s_gen_pde2d(ictxt,idim,a,bv,xv,desc_a,afmt,& - & a1,a2,b1,b2,c,g,info,f,amold,vmold,imold,partition,nrl,iv) + subroutine mld_s_gen_pde2d(ictxt,idim,a,bv,xv,desc_a,afmt,info,& + & f,amold,vmold,imold,partition,nrl,iv) use psb_base_mod - use psb_util_mod + use psb_util_mod ! ! Discretizes the partial differential equation ! @@ -115,7 +166,6 @@ contains ! Note that if b1=b2=c=0., the PDE is the Laplace equation. ! implicit none - procedure(s_func_2d) :: b1,b2,c,a1,a2,g integer(psb_ipk_) :: idim type(psb_sspmat_type) :: a type(psb_s_vect_type) :: xv,bv @@ -148,7 +198,7 @@ contains ! deltah dimension of each grid cell ! deltat discretization time real(psb_spk_) :: deltah, sqdeltah, deltah2 - real(psb_spk_), parameter :: rhs=0.e0,one=1.e0,zero=0.e0 + real(psb_spk_), parameter :: rhs=szero,one=sone,zero=szero real(psb_dpk_) :: t0, t1, t2, t3, tasb, talc, ttot, tgen, tcdasb integer(psb_ipk_) :: err_act procedure(s_func_2d), pointer :: f_ @@ -167,9 +217,9 @@ contains f_ => s_null_func_2d end if - deltah = 1.e0/(idim+2) + deltah = sone/(idim+2) sqdeltah = deltah*deltah - deltah2 = 2.e0* deltah + deltah2 = (2*sone)* deltah if (present(partition)) then if ((1<= partition).and.(partition <= 3)) then @@ -355,7 +405,7 @@ contains if (ix == 1) then zt(k) = g(szero,y)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix-2)*idim+iy + call ijk2idx(icol(icoeff),ix-1,iy,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif @@ -364,14 +414,14 @@ contains if (iy == 1) then zt(k) = g(x,szero)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix-1)*idim+(iy-1) + call ijk2idx(icol(icoeff),ix,iy-1,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif ! term depending on (x,y) - val(icoeff)=2.e0*(a1(x,y) + a2(x,y))/sqdeltah + c(x,y) - icol(icoeff) = (ix-1)*idim+iy + val(icoeff)=(2*sone)*(a1(x,y) + a2(x,y))/sqdeltah + c(x,y) + call ijk2idx(icol(icoeff),ix,iy,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 ! term depending on (x,y+1) @@ -379,7 +429,7 @@ contains if (iy == idim) then zt(k) = g(x,sone)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix-1)*idim+(iy+1) + call ijk2idx(icol(icoeff),ix,iy+1,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif @@ -388,7 +438,7 @@ contains if (ix==idim) then zt(k) = g(sone,y)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix)*idim+(iy) + call ijk2idx(icol(icoeff),ix+1,iy,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif @@ -398,7 +448,7 @@ contains if(info /= psb_success_) exit call psb_geins(ib,myidx(ii:ii+ib-1),zt(1:ib),bv,desc_a,info) if(info /= psb_success_) exit - zt(:)=0.e0 + zt(:)=szero call psb_geins(ib,myidx(ii:ii+ib-1),zt(1:ib),xv,desc_a,info) if(info /= psb_success_) exit end do @@ -469,50 +519,6 @@ contains end subroutine mld_s_gen_pde2d - ! - ! functions parametrizing the differential equation - ! - function b1(x,y) - use psb_base_mod, only : psb_spk_,sone,szero - real(psb_spk_) :: b1 - real(psb_spk_), intent(in) :: x,y - b1=szero - end function b1 - function b2(x,y) - use psb_base_mod, only : psb_spk_,sone,szero - real(psb_spk_) :: b2 - real(psb_spk_), intent(in) :: x,y - b2=szero - end function b2 - function c(x,y) - use psb_base_mod, only : psb_spk_,sone,szero - real(psb_spk_) :: c - real(psb_spk_), intent(in) :: x,y - c=szero - end function c - function a1(x,y) - use psb_base_mod, only : psb_spk_,sone,szero - real(psb_spk_) :: a1 - real(psb_spk_), intent(in) :: x,y - a1=sone - end function a1 - function a2(x,y) - use psb_base_mod, only : psb_spk_,sone,szero - real(psb_spk_) :: a2 - real(psb_spk_), intent(in) :: x,y - a2=sone - end function a2 - function g(x,y) - use psb_base_mod, only : psb_spk_, sone, szero - real(psb_spk_) :: g - real(psb_spk_), intent(in) :: x,y - g = szero - if (x == sone) then - g = sone - else if (x == szero) then - g = exp(-y**2) - end if - end function g end module mld_s_pde2d_mod program mld_s_pde2d @@ -654,8 +660,7 @@ program mld_s_pde2d ! call psb_barrier(ictxt) t1 = psb_wtime() - call mld_gen_pde2d(ictxt,idim,a,b,x,desc_a,afmt,& - & a1,a2,b1,b2,c,g,info) + call mld_gen_pde2d(ictxt,idim,a,b,x,desc_a,afmt,info) call psb_barrier(ictxt) t2 = psb_wtime() - t1 if(info /= psb_success_) then diff --git a/tests/pdegen/mld_s_pde3d.f90 b/tests/pdegen/mld_s_pde3d.f90 index fca609ce..3e2f8c32 100644 --- a/tests/pdegen/mld_s_pde3d.f90 +++ b/tests/pdegen/mld_s_pde3d.f90 @@ -92,13 +92,78 @@ contains val = szero end function s_null_func_3d + ! + ! functions parametrizing the differential equation + ! + function b1(x,y,z) + use psb_base_mod, only : psb_spk_, sone, szero + implicit none + real(psb_spk_) :: b1 + real(psb_spk_), intent(in) :: x,y,z + b1=sone/sqrt((3*sone)) + end function b1 + function b2(x,y,z) + use psb_base_mod, only : psb_spk_, sone, szero + implicit none + real(psb_spk_) :: b2 + real(psb_spk_), intent(in) :: x,y,z + b2=sone/sqrt((3*sone)) + end function b2 + function b3(x,y,z) + use psb_base_mod, only : psb_spk_, sone, szero + implicit none + real(psb_spk_) :: b3 + real(psb_spk_), intent(in) :: x,y,z + b3=sone/sqrt((3*sone)) + end function b3 + function c(x,y,z) + use psb_base_mod, only : psb_spk_, sone, szero + implicit none + real(psb_spk_) :: c + real(psb_spk_), intent(in) :: x,y,z + c=szero + end function c + function a1(x,y,z) + use psb_base_mod, only : psb_spk_, sone, szero + implicit none + real(psb_spk_) :: a1 + real(psb_spk_), intent(in) :: x,y,z + a1=sone/80 + end function a1 + function a2(x,y,z) + use psb_base_mod, only : psb_spk_, sone, szero + implicit none + real(psb_spk_) :: a2 + real(psb_spk_), intent(in) :: x,y,z + a2=sone/80 + end function a2 + function a3(x,y,z) + use psb_base_mod, only : psb_spk_, sone, szero + implicit none + real(psb_spk_) :: a3 + real(psb_spk_), intent(in) :: x,y,z + a3=sone/80 + end function a3 + function g(x,y,z) + use psb_base_mod, only : psb_spk_, sone, szero + implicit none + real(psb_spk_) :: g + real(psb_spk_), intent(in) :: x,y,z + g = szero + if (x == sone) then + g = sone + else if (x == szero) then + g = exp(y**2-z**2) + end if + end function g + ! ! subroutine to allocate and fill in the coefficient matrix and ! the rhs. ! - subroutine mld_s_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt,& - & a1,a2,a3,b1,b2,b3,c,g,info,f,amold,vmold,imold,partition,nrl,iv) + subroutine mld_s_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt,info,& + & f,amold,vmold,imold,partition,nrl,iv) use psb_base_mod use psb_util_mod ! @@ -117,7 +182,6 @@ contains ! Note that if b1=b2=b3=c=0., the PDE is the Laplace equation. ! implicit none - procedure(s_func_3d) :: b1,b2,b3,c,a1,a2,a3,g integer(psb_ipk_) :: idim type(psb_sspmat_type) :: a type(psb_s_vect_type) :: xv,bv @@ -169,9 +233,9 @@ contains f_ => s_null_func_3d end if - deltah = 1.d0/(idim+2) + deltah = sone/(idim+2) sqdeltah = deltah*deltah - deltah2 = 2.d0* deltah + deltah2 = (2*sone)* deltah if (present(partition)) then if ((1<= partition).and.(partition <= 3)) then @@ -189,7 +253,7 @@ contains m = idim*idim*idim n = m - nnz = ((n*9)/(np)) + nnz = ((n*7)/(np)) if(iam == psb_root_) write(psb_out_unit,'("Generating Matrix (size=",i0,")...")')n t0 = psb_wtime() select case(partition_) @@ -362,7 +426,7 @@ contains if (ix == 1) then zt(k) = g(szero,y,z)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix-2)*idim*idim+(iy-1)*idim+(iz) + call ijk2idx(icol(icoeff),ix-1,iy,iz,idim,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif @@ -371,7 +435,7 @@ contains if (iy == 1) then zt(k) = g(x,szero,z)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix-1)*idim*idim+(iy-2)*idim+(iz) + call ijk2idx(icol(icoeff),ix,iy-1,iz,idim,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif @@ -380,15 +444,15 @@ contains if (iz == 1) then zt(k) = g(x,y,szero)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix-1)*idim*idim+(iy-1)*idim+(iz-1) + call ijk2idx(icol(icoeff),ix,iy,iz-1,idim,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif ! term depending on (x,y,z) - val(icoeff)=2.d0*(a1(x,y,z)+a2(x,y,z)+a3(x,y,z))/sqdeltah & + val(icoeff)=(2*sone)*(a1(x,y,z)+a2(x,y,z)+a3(x,y,z))/sqdeltah & & + c(x,y,z) - icol(icoeff) = (ix-1)*idim*idim+(iy-1)*idim+(iz) + call ijk2idx(icol(icoeff),ix,iy,iz,idim,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 ! term depending on (x,y,z+1) @@ -396,7 +460,7 @@ contains if (iz == idim) then zt(k) = g(x,y,sone)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix-1)*idim*idim+(iy-1)*idim+(iz+1) + call ijk2idx(icol(icoeff),ix,iy,iz+1,idim,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif @@ -405,7 +469,7 @@ contains if (iy == idim) then zt(k) = g(x,sone,z)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix-1)*idim*idim+(iy)*idim+(iz) + call ijk2idx(icol(icoeff),ix,iy+1,iz,idim,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif @@ -414,7 +478,7 @@ contains if (ix==idim) then zt(k) = g(sone,y,z)*(-val(icoeff)) + zt(k) else - icol(icoeff) = (ix)*idim*idim+(iy-1)*idim+(iz) + call ijk2idx(icol(icoeff),ix+1,iy,iz,idim,idim,idim) irow(icoeff) = glob_row icoeff = icoeff+1 endif @@ -424,7 +488,7 @@ contains if(info /= psb_success_) exit call psb_geins(ib,myidx(ii:ii+ib-1),zt(1:ib),bv,desc_a,info) if(info /= psb_success_) exit - zt(:)=0.d0 + zt(:)=szero call psb_geins(ib,myidx(ii:ii+ib-1),zt(1:ib),xv,desc_a,info) if(info /= psb_success_) exit end do @@ -494,62 +558,6 @@ contains return end subroutine mld_s_gen_pde3d - ! - ! functions parametrizing the differential equation - ! - function b1(x,y,z) - use psb_base_mod, only : psb_spk_,sone,szero - real(psb_spk_) :: b1 - real(psb_spk_), intent(in) :: x,y,z - b1=szero - end function b1 - function b2(x,y,z) - use psb_base_mod, only : psb_spk_,sone,szero - real(psb_spk_) :: b2 - real(psb_spk_), intent(in) :: x,y,z - b2=szero - end function b2 - function b3(x,y,z) - use psb_base_mod, only : psb_spk_,sone,szero - real(psb_spk_) :: b3 - real(psb_spk_), intent(in) :: x,y,z - b3=szero - end function b3 - function c(x,y,z) - use psb_base_mod, only : psb_spk_,sone,szero - real(psb_spk_) :: c - real(psb_spk_), intent(in) :: x,y,z - c=szero - end function c - function a1(x,y,z) - use psb_base_mod, only : psb_spk_,sone,szero - real(psb_spk_) :: a1 - real(psb_spk_), intent(in) :: x,y,z - a1=sone - end function a1 - function a2(x,y,z) - use psb_base_mod, only : psb_spk_,sone,szero - real(psb_spk_) :: a2 - real(psb_spk_), intent(in) :: x,y,z - a2=sone - end function a2 - function a3(x,y,z) - use psb_base_mod, only : psb_spk_,sone,szero - real(psb_spk_) :: a3 - real(psb_spk_), intent(in) :: x,y,z - a3=sone - end function a3 - function g(x,y,z) - use psb_base_mod, only : psb_spk_,sone,szero - real(psb_spk_) :: g - real(psb_spk_), intent(in) :: x,y,z - g = szero - if (x == sone) then - g = sone - else if (x == szero) then - g = exp(y**2-z**2) - end if - end function g end module mld_s_pde3d_mod program mld_s_pde3d @@ -692,8 +700,7 @@ program mld_s_pde3d call psb_barrier(ictxt) t1 = psb_wtime() - call mld_gen_pde3d(ictxt,idim,a,b,x,desc_a,afmt,& - & a1,a2,a3,b1,b2,b3,c,g,info) + call mld_gen_pde3d(ictxt,idim,a,b,x,desc_a,afmt,info) call psb_barrier(ictxt) t2 = psb_wtime() - t1 if(info /= psb_success_) then From 29232bf0d2b12ef7bb191ed08171de7b61780788 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Thu, 3 May 2018 15:20:31 +0100 Subject: [PATCH 07/33] Moved mld_?ilu?_fact to solver subdir. --- mlprec/impl/Makefile | 8 ++++---- mlprec/impl/solver/Makefile | 12 ++++++++++++ mlprec/impl/{ => solver}/mld_cilu0_fact.f90 | 0 mlprec/impl/{ => solver}/mld_ciluk_fact.f90 | 0 mlprec/impl/{ => solver}/mld_cilut_fact.f90 | 0 mlprec/impl/{ => solver}/mld_dilu0_fact.f90 | 0 mlprec/impl/{ => solver}/mld_diluk_fact.f90 | 0 mlprec/impl/{ => solver}/mld_dilut_fact.f90 | 0 mlprec/impl/{ => solver}/mld_silu0_fact.f90 | 0 mlprec/impl/{ => solver}/mld_siluk_fact.f90 | 0 mlprec/impl/{ => solver}/mld_silut_fact.f90 | 0 mlprec/impl/{ => solver}/mld_zilu0_fact.f90 | 0 mlprec/impl/{ => solver}/mld_ziluk_fact.f90 | 0 mlprec/impl/{ => solver}/mld_zilut_fact.f90 | 0 14 files changed, 16 insertions(+), 4 deletions(-) rename mlprec/impl/{ => solver}/mld_cilu0_fact.f90 (100%) rename mlprec/impl/{ => solver}/mld_ciluk_fact.f90 (100%) rename mlprec/impl/{ => solver}/mld_cilut_fact.f90 (100%) rename mlprec/impl/{ => solver}/mld_dilu0_fact.f90 (100%) rename mlprec/impl/{ => solver}/mld_diluk_fact.f90 (100%) rename mlprec/impl/{ => solver}/mld_dilut_fact.f90 (100%) rename mlprec/impl/{ => solver}/mld_silu0_fact.f90 (100%) rename mlprec/impl/{ => solver}/mld_siluk_fact.f90 (100%) rename mlprec/impl/{ => solver}/mld_silut_fact.f90 (100%) rename mlprec/impl/{ => solver}/mld_zilu0_fact.f90 (100%) rename mlprec/impl/{ => solver}/mld_ziluk_fact.f90 (100%) rename mlprec/impl/{ => solver}/mld_zilut_fact.f90 (100%) diff --git a/mlprec/impl/Makefile b/mlprec/impl/Makefile index 57c1c8eb..a2c35c31 100644 --- a/mlprec/impl/Makefile +++ b/mlprec/impl/Makefile @@ -24,25 +24,25 @@ MPCOBJS=mld_dslud_interface.o mld_zslud_interface.o DINNEROBJS= mld_dmlprec_bld.o mld_dfile_prec_descr.o \ mld_d_smoothers_bld.o mld_d_hierarchy_bld.o \ - mld_dilu0_fact.o mld_diluk_fact.o mld_dilut_fact.o mld_daggrmap_bld.o \ + mld_daggrmap_bld.o \ mld_d_dec_map_bld.o mld_dmlprec_aply.o mld_daggrmat_asb.o \ $(DMPFOBJS) mld_d_extprol_bld.o mld_d_lev_aggrmap_bld.o mld_d_lev_aggrmat_asb.o SINNEROBJS= mld_smlprec_bld.o mld_sfile_prec_descr.o \ mld_s_smoothers_bld.o mld_s_hierarchy_bld.o \ - mld_silu0_fact.o mld_siluk_fact.o mld_silut_fact.o mld_saggrmap_bld.o \ + mld_saggrmap_bld.o \ mld_s_dec_map_bld.o mld_smlprec_aply.o mld_saggrmat_asb.o \ $(SMPFOBJS) mld_s_extprol_bld.o mld_s_lev_aggrmap_bld.o mld_s_lev_aggrmat_asb.o ZINNEROBJS= mld_zmlprec_bld.o mld_zfile_prec_descr.o \ mld_z_smoothers_bld.o mld_z_hierarchy_bld.o \ - mld_zilu0_fact.o mld_ziluk_fact.o mld_zilut_fact.o mld_zaggrmap_bld.o \ + mld_zaggrmap_bld.o \ mld_z_dec_map_bld.o mld_zmlprec_aply.o mld_zaggrmat_asb.o \ $(ZMPFOBJS) mld_z_extprol_bld.o mld_z_lev_aggrmap_bld.o mld_z_lev_aggrmat_asb.o CINNEROBJS= mld_cmlprec_bld.o mld_cfile_prec_descr.o \ mld_c_smoothers_bld.o mld_c_hierarchy_bld.o \ - mld_cilu0_fact.o mld_ciluk_fact.o mld_cilut_fact.o mld_caggrmap_bld.o \ + mld_caggrmap_bld.o \ mld_c_dec_map_bld.o mld_cmlprec_aply.o mld_caggrmat_asb.o \ $(CMPFOBJS) mld_c_extprol_bld.o mld_c_lev_aggrmap_bld.o mld_c_lev_aggrmat_asb.o diff --git a/mlprec/impl/solver/Makefile b/mlprec/impl/solver/Makefile index 90e47229..71dba236 100644 --- a/mlprec/impl/solver/Makefile +++ b/mlprec/impl/solver/Makefile @@ -46,6 +46,9 @@ mld_c_ilu_solver_bld.o \ mld_c_ilu_solver_clone.o \ mld_c_ilu_solver_cnv.o \ mld_c_ilu_solver_dmp.o \ +mld_cilu0_fact.o \ +mld_ciluk_fact.o \ +mld_cilut_fact.o \ mld_c_mumps_solver_apply.o \ mld_c_mumps_solver_apply_vect.o \ mld_c_mumps_solver_bld.o \ @@ -88,6 +91,9 @@ mld_d_ilu_solver_bld.o \ mld_d_ilu_solver_clone.o \ mld_d_ilu_solver_cnv.o \ mld_d_ilu_solver_dmp.o \ +mld_dilu0_fact.o \ +mld_diluk_fact.o \ +mld_dilut_fact.o \ mld_d_mumps_solver_apply.o \ mld_d_mumps_solver_apply_vect.o \ mld_d_mumps_solver_bld.o \ @@ -130,6 +136,9 @@ mld_s_ilu_solver_bld.o \ mld_s_ilu_solver_clone.o \ mld_s_ilu_solver_cnv.o \ mld_s_ilu_solver_dmp.o \ +mld_silu0_fact.o \ +mld_siluk_fact.o \ +mld_silut_fact.o \ mld_s_mumps_solver_apply.o \ mld_s_mumps_solver_apply_vect.o \ mld_s_mumps_solver_bld.o \ @@ -172,6 +181,9 @@ mld_z_ilu_solver_bld.o \ mld_z_ilu_solver_clone.o \ mld_z_ilu_solver_cnv.o \ mld_z_ilu_solver_dmp.o \ +mld_zilu0_fact.o \ +mld_ziluk_fact.o \ +mld_zilut_fact.o \ mld_z_mumps_solver_apply.o \ mld_z_mumps_solver_apply_vect.o \ mld_z_mumps_solver_bld.o \ diff --git a/mlprec/impl/mld_cilu0_fact.f90 b/mlprec/impl/solver/mld_cilu0_fact.f90 similarity index 100% rename from mlprec/impl/mld_cilu0_fact.f90 rename to mlprec/impl/solver/mld_cilu0_fact.f90 diff --git a/mlprec/impl/mld_ciluk_fact.f90 b/mlprec/impl/solver/mld_ciluk_fact.f90 similarity index 100% rename from mlprec/impl/mld_ciluk_fact.f90 rename to mlprec/impl/solver/mld_ciluk_fact.f90 diff --git a/mlprec/impl/mld_cilut_fact.f90 b/mlprec/impl/solver/mld_cilut_fact.f90 similarity index 100% rename from mlprec/impl/mld_cilut_fact.f90 rename to mlprec/impl/solver/mld_cilut_fact.f90 diff --git a/mlprec/impl/mld_dilu0_fact.f90 b/mlprec/impl/solver/mld_dilu0_fact.f90 similarity index 100% rename from mlprec/impl/mld_dilu0_fact.f90 rename to mlprec/impl/solver/mld_dilu0_fact.f90 diff --git a/mlprec/impl/mld_diluk_fact.f90 b/mlprec/impl/solver/mld_diluk_fact.f90 similarity index 100% rename from mlprec/impl/mld_diluk_fact.f90 rename to mlprec/impl/solver/mld_diluk_fact.f90 diff --git a/mlprec/impl/mld_dilut_fact.f90 b/mlprec/impl/solver/mld_dilut_fact.f90 similarity index 100% rename from mlprec/impl/mld_dilut_fact.f90 rename to mlprec/impl/solver/mld_dilut_fact.f90 diff --git a/mlprec/impl/mld_silu0_fact.f90 b/mlprec/impl/solver/mld_silu0_fact.f90 similarity index 100% rename from mlprec/impl/mld_silu0_fact.f90 rename to mlprec/impl/solver/mld_silu0_fact.f90 diff --git a/mlprec/impl/mld_siluk_fact.f90 b/mlprec/impl/solver/mld_siluk_fact.f90 similarity index 100% rename from mlprec/impl/mld_siluk_fact.f90 rename to mlprec/impl/solver/mld_siluk_fact.f90 diff --git a/mlprec/impl/mld_silut_fact.f90 b/mlprec/impl/solver/mld_silut_fact.f90 similarity index 100% rename from mlprec/impl/mld_silut_fact.f90 rename to mlprec/impl/solver/mld_silut_fact.f90 diff --git a/mlprec/impl/mld_zilu0_fact.f90 b/mlprec/impl/solver/mld_zilu0_fact.f90 similarity index 100% rename from mlprec/impl/mld_zilu0_fact.f90 rename to mlprec/impl/solver/mld_zilu0_fact.f90 diff --git a/mlprec/impl/mld_ziluk_fact.f90 b/mlprec/impl/solver/mld_ziluk_fact.f90 similarity index 100% rename from mlprec/impl/mld_ziluk_fact.f90 rename to mlprec/impl/solver/mld_ziluk_fact.f90 diff --git a/mlprec/impl/mld_zilut_fact.f90 b/mlprec/impl/solver/mld_zilut_fact.f90 similarity index 100% rename from mlprec/impl/mld_zilut_fact.f90 rename to mlprec/impl/solver/mld_zilut_fact.f90 From 939ba5f6aadda4c19a459b4af53cbf3837ccd44f Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 4 May 2018 14:21:31 +0100 Subject: [PATCH 08/33] Started merging extaggr branch. --- mlprec/mld_base_prec_type.F90 | 17 ++++++++++------- 1 file changed, 10 insertions(+), 7 deletions(-) diff --git a/mlprec/mld_base_prec_type.F90 b/mlprec/mld_base_prec_type.F90 index 5eb45ab3..5de5c78c 100644 --- a/mlprec/mld_base_prec_type.F90 +++ b/mlprec/mld_base_prec_type.F90 @@ -81,10 +81,10 @@ module mld_base_prec_type ! ! Version numbers ! - character(len=*), parameter :: mld_version_string_ = "2.1.1" + character(len=*), parameter :: mld_version_string_ = "2.2.0" integer(psb_ipk_), parameter :: mld_version_major_ = 2 - integer(psb_ipk_), parameter :: mld_version_minor_ = 1 - integer(psb_ipk_), parameter :: mld_patchlevel_ = 1 + integer(psb_ipk_), parameter :: mld_version_minor_ = 2 + integer(psb_ipk_), parameter :: mld_patchlevel_ = 0 type mld_ml_parms integer(psb_ipk_) :: sweeps_pre, sweeps_post @@ -227,6 +227,7 @@ module mld_base_prec_type ! integer(psb_ipk_), parameter :: mld_noalg_ = 0 integer(psb_ipk_), parameter :: mld_vmb_ = 1 + integer(psb_ipk_), parameter :: mld_hyb_ = 2 ! ! Legal values for entry: mld_aggr_prol_ ! @@ -321,8 +322,8 @@ module mld_base_prec_type character(len=15), parameter, private :: & & matrix_names(0:1)=(/'distributed ','replicated '/) character(len=18), parameter, private :: & - & aggr_type_names(0:1)=(/'No aggregation ',& - & 'VMB aggregation '/) + & aggr_type_names(0:2)=(/'No aggregation ',& + & 'VMB aggregation ', 'Hybrid aggregation'/) character(len=18), parameter, private :: & & par_aggr_alg_names(0:3)=(/'decoupled aggr. ',& & 'sym. dec. aggr. ',& @@ -437,6 +438,8 @@ contains val = mld_kcycle_ml_ case('KCYCLESYM') val = mld_kcyclesym_ml_ + case('HYB') + val = mld_hyb_ case('VMB') val = mld_vmb_ case('DEC') @@ -475,7 +478,7 @@ contains val = mld_eig_est_ case('FILTER') val = mld_filter_mat_ - case('NOFILTER') + case('NOFILTER','NO_FILTER') val = mld_no_filter_mat_ case('OUTER_SWEEPS') val = mld_outer_sweeps_ @@ -759,7 +762,7 @@ contains integer(psb_ipk_), intent(in) :: ip logical :: is_legal_ml_aggr_type - is_legal_ml_aggr_type = (ip == mld_vmb_) + is_legal_ml_aggr_type = (ip >= mld_vmb_) .and. (ip <= mld_hyb_) return end function is_legal_ml_aggr_type function is_legal_ml_aggr_ord(ip) From b331b1b9280ae8f6379c0553caf61b743423191c Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 4 May 2018 14:36:23 +0100 Subject: [PATCH 09/33] Merge aggregator: module interfaces now compile. --- mlprec/Makefile | 36 +++- mlprec/mld_base_prec_type.F90 | 13 +- mlprec/mld_c_base_aggregator_mod.f90 | 209 +++++++++++++++++++ mlprec/mld_c_hybrid_aggregator_mod.F90 | 131 ++++++++++++ mlprec/mld_c_inner_mod.f90 | 25 +++ mlprec/mld_c_onelev_mod.f90 | 49 ++++- mlprec/mld_c_prec_mod.f90 | 11 +- mlprec/mld_c_prec_type.f90 | 17 +- mlprec/mld_c_symdec_aggregator_mod.f90 | 128 ++++++++++++ mlprec/mld_d_base_aggregator_mod.f90 | 209 +++++++++++++++++++ mlprec/mld_d_bcmatch_aggregator_mod.F90 | 262 ++++++++++++++++++++++++ mlprec/mld_d_hybrid_aggregator_mod.F90 | 131 ++++++++++++ mlprec/mld_d_inner_mod.f90 | 25 +++ mlprec/mld_d_onelev_mod.f90 | 49 ++++- mlprec/mld_d_prec_mod.f90 | 11 +- mlprec/mld_d_prec_type.f90 | 17 +- mlprec/mld_d_symdec_aggregator_mod.f90 | 128 ++++++++++++ mlprec/mld_s_base_aggregator_mod.f90 | 209 +++++++++++++++++++ mlprec/mld_s_hybrid_aggregator_mod.F90 | 131 ++++++++++++ mlprec/mld_s_inner_mod.f90 | 25 +++ mlprec/mld_s_onelev_mod.f90 | 49 ++++- mlprec/mld_s_prec_mod.f90 | 11 +- mlprec/mld_s_prec_type.f90 | 17 +- mlprec/mld_s_symdec_aggregator_mod.f90 | 128 ++++++++++++ mlprec/mld_z_base_aggregator_mod.f90 | 209 +++++++++++++++++++ mlprec/mld_z_hybrid_aggregator_mod.F90 | 131 ++++++++++++ mlprec/mld_z_inner_mod.f90 | 25 +++ mlprec/mld_z_onelev_mod.f90 | 49 ++++- mlprec/mld_z_prec_mod.f90 | 11 +- mlprec/mld_z_prec_type.f90 | 17 +- mlprec/mld_z_symdec_aggregator_mod.f90 | 128 ++++++++++++ 31 files changed, 2523 insertions(+), 68 deletions(-) create mode 100644 mlprec/mld_c_base_aggregator_mod.f90 create mode 100644 mlprec/mld_c_hybrid_aggregator_mod.F90 create mode 100644 mlprec/mld_c_symdec_aggregator_mod.f90 create mode 100644 mlprec/mld_d_base_aggregator_mod.f90 create mode 100644 mlprec/mld_d_bcmatch_aggregator_mod.F90 create mode 100644 mlprec/mld_d_hybrid_aggregator_mod.F90 create mode 100644 mlprec/mld_d_symdec_aggregator_mod.f90 create mode 100644 mlprec/mld_s_base_aggregator_mod.f90 create mode 100644 mlprec/mld_s_hybrid_aggregator_mod.F90 create mode 100644 mlprec/mld_s_symdec_aggregator_mod.f90 create mode 100644 mlprec/mld_z_base_aggregator_mod.f90 create mode 100644 mlprec/mld_z_hybrid_aggregator_mod.F90 create mode 100644 mlprec/mld_z_symdec_aggregator_mod.f90 diff --git a/mlprec/Makefile b/mlprec/Makefile index e853352a..d89347b7 100644 --- a/mlprec/Makefile +++ b/mlprec/Makefile @@ -11,25 +11,33 @@ DMODOBJS=mld_d_prec_type.o mld_d_ilu_fact_mod.o \ mld_d_inner_mod.o mld_d_ilu_solver.o mld_d_diag_solver.o mld_d_jac_smoother.o mld_d_as_smoother.o \ mld_d_umf_solver.o mld_d_slu_solver.o mld_d_sludist_solver.o mld_d_id_solver.o\ mld_d_base_solver_mod.o mld_d_base_smoother_mod.o mld_d_onelev_mod.o \ - mld_d_gs_solver.o mld_d_mumps_solver.o + mld_d_gs_solver.o mld_d_mumps_solver.o \ + mld_d_base_aggregator_mod.o mld_d_hybrid_aggregator_mod.o \ + mld_d_symdec_aggregator_mod.o mld_d_bcmatch_aggregator_mod.o SMODOBJS=mld_s_prec_type.o mld_s_ilu_fact_mod.o \ mld_s_inner_mod.o mld_s_ilu_solver.o mld_s_diag_solver.o mld_s_jac_smoother.o mld_s_as_smoother.o \ mld_s_slu_solver.o mld_s_id_solver.o\ mld_s_base_solver_mod.o mld_s_base_smoother_mod.o mld_s_onelev_mod.o \ - mld_s_gs_solver.o mld_s_mumps_solver.o + mld_s_gs_solver.o mld_s_mumps_solver.o \ + mld_s_base_aggregator_mod.o mld_s_hybrid_aggregator_mod.o \ + mld_s_symdec_aggregator_mod.o ZMODOBJS=mld_z_prec_type.o mld_z_ilu_fact_mod.o \ mld_z_inner_mod.o mld_z_ilu_solver.o mld_z_diag_solver.o mld_z_jac_smoother.o mld_z_as_smoother.o \ mld_z_umf_solver.o mld_z_slu_solver.o mld_z_sludist_solver.o mld_z_id_solver.o\ mld_z_base_solver_mod.o mld_z_base_smoother_mod.o mld_z_onelev_mod.o \ - mld_z_gs_solver.o mld_z_mumps_solver.o + mld_z_gs_solver.o mld_z_mumps_solver.o \ + mld_z_base_aggregator_mod.o mld_z_hybrid_aggregator_mod.o \ + mld_z_symdec_aggregator_mod.o CMODOBJS=mld_c_prec_type.o mld_c_ilu_fact_mod.o \ mld_c_inner_mod.o mld_c_ilu_solver.o mld_c_diag_solver.o mld_c_jac_smoother.o mld_c_as_smoother.o \ mld_c_slu_solver.o mld_c_id_solver.o\ mld_c_base_solver_mod.o mld_c_base_smoother_mod.o mld_c_onelev_mod.o \ - mld_c_gs_solver.o mld_c_mumps_solver.o + mld_c_gs_solver.o mld_c_mumps_solver.o \ + mld_c_base_aggregator_mod.o mld_c_hybrid_aggregator_mod.o \ + mld_c_symdec_aggregator_mod.o @@ -84,10 +92,22 @@ mld_d_prec_type.o: mld_d_onelev_mod.o mld_c_prec_type.o: mld_c_onelev_mod.o mld_z_prec_type.o: mld_z_onelev_mod.o -mld_s_onelev_mod.o: mld_s_base_smoother_mod.o -mld_d_onelev_mod.o: mld_d_base_smoother_mod.o -mld_c_onelev_mod.o: mld_c_base_smoother_mod.o -mld_z_onelev_mod.o: mld_z_base_smoother_mod.o +mld_s_onelev_mod.o: mld_s_base_smoother_mod.o mld_s_base_aggregator_mod.o +mld_d_onelev_mod.o: mld_d_base_smoother_mod.o mld_d_base_aggregator_mod.o +mld_c_onelev_mod.o: mld_c_base_smoother_mod.o mld_c_base_aggregator_mod.o +mld_z_onelev_mod.o: mld_z_base_smoother_mod.o mld_z_base_aggregator_mod.o + +mld_s_base_aggregator_mod.o: mld_base_prec_type.o +mld_s_hybrid_aggregator_mod.o mld_s_symdec_aggregator_mod.o: mld_s_base_aggregator_mod.o + +mld_d_base_aggregator_mod.o: mld_base_prec_type.o +mld_d_bcmatch_aggregator_mod.o mld_d_hybrid_aggregator_mod.o mld_d_symdec_aggregator_mod.o: mld_d_base_aggregator_mod.o + +mld_c_base_aggregator_mod.o: mld_base_prec_type.o +mld_c_hybrid_aggregator_mod.o mld_c_symdec_aggregator_mod.o: mld_c_base_aggregator_mod.o + +mld_z_base_aggregator_mod.o: mld_base_prec_type.o +mld_z_hybrid_aggregator_mod.o mld_z_symdec_aggregator_mod.o: mld_z_base_aggregator_mod.o mld_s_base_smoother_mod.o: mld_s_base_solver_mod.o mld_d_base_smoother_mod.o: mld_d_base_solver_mod.o diff --git a/mlprec/mld_base_prec_type.F90 b/mlprec/mld_base_prec_type.F90 index 5de5c78c..d473cb2d 100644 --- a/mlprec/mld_base_prec_type.F90 +++ b/mlprec/mld_base_prec_type.F90 @@ -534,7 +534,7 @@ contains ! Routines printing out a description of the preconditioner ! - subroutine ml_parms_mldescr(pm,iout,info) + subroutine ml_parms_mldescr(pm,iout,info,aggr_name) Implicit None @@ -542,7 +542,7 @@ contains class(mld_ml_parms), intent(in) :: pm integer(psb_ipk_), intent(in) :: iout integer(psb_ipk_), intent(out) :: info - + character(len=*), intent(in), optional :: aggr_name info = psb_success_ if ((pm%ml_cycle>=mld_no_ml_).and.(pm%ml_cycle<=mld_max_ml_cycle_)) then @@ -558,8 +558,13 @@ contains & pm%sweeps_pre ,' post: ', pm%sweeps_post end select - write(iout,*) ' Aggregation type: ',& - & aggr_type_names(pm%aggr_type) + if (present(aggr_name)) then + write(iout,*) ' Aggregation type: ', & + & aggr_name + else + write(iout,*) ' Aggregation type: ',& + & aggr_type_names(pm%aggr_type) + end if write(iout,*) ' parallel algorithm: ',& & par_aggr_alg_names(pm%par_aggr_alg) if (pm%par_aggr_alg /= mld_ext_aggr_) then diff --git a/mlprec/mld_c_base_aggregator_mod.f90 b/mlprec/mld_c_base_aggregator_mod.f90 new file mode 100644 index 00000000..6fd291cc --- /dev/null +++ b/mlprec/mld_c_base_aggregator_mod.f90 @@ -0,0 +1,209 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. The basic version is the +! decoupled aggregation algorithm presented in +! +! M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +module mld_c_base_aggregator_mod + + use mld_base_prec_type, only : mld_sml_parms + use psb_base_mod, only : psb_cspmat_type, psb_c_vect_type, & + & psb_c_base_vect_type, psb_clinmap_type, psb_spk_, & + & psb_ipk_, psb_long_int_k_, psb_desc_type, psb_i_base_vect_type, & + & psb_erractionsave, psb_error_handler, psb_success_ + ! + ! sm - class(mld_T_base_smoother_type), allocatable + ! The current level preconditioner (aka smoother). + ! parms - type(mld_RTml_parms) + ! The parameters defining the multilevel strategy. + ! ac - The local part of the current-level matrix, built by + ! coarsening the previous-level matrix. + ! desc_ac - type(psb_desc_type). + ! The communication descriptor associated to the matrix + ! stored in ac. + ! base_a - type(psb_Tspmat_type), pointer. + ! Pointer (really a pointer!) to the local part of the current + ! matrix (so we have a unified treatment of residuals). + ! We need this to avoid passing explicitly the current matrix + ! to the routine which applies the preconditioner. + ! base_desc - type(psb_desc_type), pointer. + ! Pointer to the communication descriptor associated to the + ! matrix pointed by base_a. + ! map - Stores the maps (restriction and prolongation) between the + ! vector spaces associated to the index spaces of the previous + ! and current levels. + ! + ! Methods: + ! Most methods follow the encapsulation hierarchy: they take whatever action + ! is appropriate for the current object, then call the corresponding method for + ! the contained object. + ! As an example: the descr() method prints out a description of the + ! level. It starts by invoking the descr() method of the parms object, + ! then calls the descr() method of the smoother object. + ! + ! descr - Prints a description of the object. + ! default - Set default values + ! dump - Dump to file object contents + ! set - Sets various parameters; when a request is unknown + ! it is passed to the smoother object for further processing. + ! check - Sanity checks. + ! sizeof - Total memory occupation in bytes + ! get_nzeros - Number of nonzeros + ! + ! + type mld_c_base_aggregator_type + + contains + procedure, pass(ag) :: bld_tprol => mld_c_base_aggregator_build_tprol + procedure, pass(ag) :: mat_asb => mld_c_base_aggregator_mat_asb + procedure, pass(ag) :: update_level => mld_c_base_aggregator_update_level + procedure, pass(ag) :: clone => mld_c_base_aggregator_clone + procedure, pass(ag) :: free => mld_c_base_aggregator_free + procedure, pass(ag) :: default => mld_c_base_aggregator_default + procedure, pass(ag) :: descr => mld_c_base_aggregator_descr + procedure, nopass :: fmt => mld_c_base_aggregator_fmt + end type mld_c_base_aggregator_type + + + interface + subroutine mld_c_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: mld_c_base_aggregator_type, psb_desc_type, psb_cspmat_type, psb_spk_, & + & psb_ipk_, psb_long_int_k_, mld_sml_parms + implicit none + class(mld_c_base_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_cspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_cspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_c_base_aggregator_build_tprol + end interface + + interface + subroutine mld_c_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,& + & op_prol,op_restr,info) + import :: mld_c_base_aggregator_type, psb_desc_type, psb_cspmat_type, psb_spk_, & + & psb_ipk_, psb_long_int_k_, mld_sml_parms + implicit none + class(mld_c_base_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_cspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) + type(psb_cspmat_type), intent(inout) :: op_prol + type(psb_cspmat_type), intent(out) :: ac,op_restr + integer(psb_ipk_), intent(out) :: info + end subroutine mld_c_base_aggregator_mat_asb + end interface + +contains + + subroutine mld_c_base_aggregator_update_level(ag,agnext,info) + implicit none + class(mld_c_base_aggregator_type), target, intent(inout) :: ag, agnext + integer(psb_ipk_), intent(out) :: info + + ! + ! Base version does nothing. + ! + info = 0 + end subroutine mld_c_base_aggregator_update_level + + subroutine mld_c_base_aggregator_clone(ag,agnext,info) + implicit none + class(mld_c_base_aggregator_type), intent(inout) :: ag + class(mld_c_base_aggregator_type), allocatable, intent(inout) :: agnext + integer(psb_ipk_), intent(out) :: info + + info = 0 + if (allocated(agnext)) then + call agnext%free(info) + if (info == 0) deallocate(agnext,stat=info) + end if + if (info /= 0) return + allocate(agnext,source=ag,stat=info) + + end subroutine mld_c_base_aggregator_clone + + subroutine mld_c_base_aggregator_free(ag,info) + implicit none + class(mld_c_base_aggregator_type), intent(inout) :: ag + integer(psb_ipk_), intent(out) :: info + + info = psb_success_ + return + end subroutine mld_c_base_aggregator_free + + subroutine mld_c_base_aggregator_default(ag) + implicit none + class(mld_c_base_aggregator_type), intent(inout) :: ag + + ! Here we need do nothing + + return + end subroutine mld_c_base_aggregator_default + + function mld_c_base_aggregator_fmt() result(val) + implicit none + character(len=32) :: val + + val = "Decoupled aggregation" + end function mld_c_base_aggregator_fmt + + subroutine mld_c_base_aggregator_descr(ag,parms,iout,info) + implicit none + class(mld_c_base_aggregator_type), intent(in) :: ag + type(mld_sml_parms), intent(in) :: parms + integer(psb_ipk_), intent(in) :: iout + integer(psb_ipk_), intent(out) :: info + + call parms%mldescr(iout,info,aggr_name=ag%fmt()) + + return + end subroutine mld_c_base_aggregator_descr + +end module mld_c_base_aggregator_mod diff --git a/mlprec/mld_c_hybrid_aggregator_mod.F90 b/mlprec/mld_c_hybrid_aggregator_mod.F90 new file mode 100644 index 00000000..bbc62953 --- /dev/null +++ b/mlprec/mld_c_hybrid_aggregator_mod.F90 @@ -0,0 +1,131 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. This variant is based on the hybrid method +! presented in +! +! S. Gratton, P. Henon, P. Jiranek and X. Vasseur: +! Reducing complexity of algebraic multigrid by aggregation +! Numerical Lin. Algebra with Applications, 2016, 23:501-518 +! +module mld_c_hybrid_aggregator_mod + + use mld_c_base_aggregator_mod + ! + ! sm - class(mld_T_base_smoother_type), allocatable + ! The current level preconditioner (aka smoother). + ! parms - type(mld_RTml_parms) + ! The parameters defining the multilevel strategy. + ! ac - The local part of the current-level matrix, built by + ! coarsening the previous-level matrix. + ! desc_ac - type(psb_desc_type). + ! The communication descriptor associated to the matrix + ! stored in ac. + ! base_a - type(psb_Tspmat_type), pointer. + ! Pointer (really a pointer!) to the local part of the current + ! matrix (so we have a unified treatment of residuals). + ! We need this to avoid passing explicitly the current matrix + ! to the routine which applies the preconditioner. + ! base_desc - type(psb_desc_type), pointer. + ! Pointer to the communication descriptor associated to the + ! matrix pointed by base_a. + ! map - Stores the maps (restriction and prolongation) between the + ! vector spaces associated to the index spaces of the previous + ! and current levels. + ! + ! Methods: + ! Most methods follow the encapsulation hierarchy: they take whatever action + ! is appropriate for the current object, then call the corresponding method for + ! the contained object. + ! As an example: the descr() method prints out a description of the + ! level. It starts by invoking the descr() method of the parms object, + ! then calls the descr() method of the smoother object. + ! + ! descr - Prints a description of the object. + ! default - Set default values + ! dump - Dump to file object contents + ! set - Sets various parameters; when a request is unknown + ! it is passed to the smoother object for further processing. + ! check - Sanity checks. + ! sizeof - Total memory occupation in bytes + ! get_nzeros - Number of nonzeros + ! + ! + type, extends(mld_c_base_aggregator_type) :: mld_c_hybrid_aggregator_type + + contains + procedure, pass(ag) :: bld_tprol => mld_c_hybrid_aggregator_build_tprol +!!$ procedure, pass(ag) :: mat_asb => mld_c_base_aggregator_mat_asb +!!$ procedure, pass(ag) :: update_level => mld_c_base_aggregator_update_level +!!$ procedure, pass(ag) :: clone => mld_c_base_aggregator_clone +!!$ procedure, pass(ag) :: free => mld_c_base_aggregator_free +!!$ procedure, pass(ag) :: default => mld_c_base_aggregator_default + procedure, nopass :: fmt => mld_c_hybrid_aggregator_fmt + end type mld_c_hybrid_aggregator_type + + + interface + subroutine mld_c_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: mld_c_hybrid_aggregator_type, psb_desc_type, psb_cspmat_type, psb_spk_, & + & psb_ipk_, psb_long_int_k_, mld_sml_parms + implicit none + class(mld_c_hybrid_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_cspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_cspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_c_hybrid_aggregator_build_tprol + end interface + +contains + + + function mld_c_hybrid_aggregator_fmt() result(val) + implicit none + character(len=32) :: val + + val = "Hybrid Decoupled aggregation" + end function mld_c_hybrid_aggregator_fmt + + +end module mld_c_hybrid_aggregator_mod diff --git a/mlprec/mld_c_inner_mod.f90 b/mlprec/mld_c_inner_mod.f90 index e5394d4b..0de61dca 100644 --- a/mlprec/mld_c_inner_mod.f90 +++ b/mlprec/mld_c_inner_mod.f90 @@ -137,6 +137,31 @@ module mld_c_inner_mod end subroutine mld_c_dec_map_bld end interface mld_dec_map_bld + interface mld_hyb_map_bld + subroutine mld_c_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + use psb_base_mod, only : psb_cspmat_type, psb_desc_type, psb_spk_, psb_ipk_ + implicit none + integer(psb_ipk_), intent(in) :: iorder + type(psb_cspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + real(psb_spk_), intent(in) :: theta + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + integer(psb_ipk_), intent(out) :: info + end subroutine mld_c_hyb_map_bld + end interface mld_hyb_map_bld + + interface mld_map_to_tprol + subroutine mld_c_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod, only : psb_cspmat_type, psb_desc_type, psb_spk_, psb_ipk_ + use mld_c_prec_type, only : mld_c_onelev_type + implicit none + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:) + type(psb_cspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_c_map_to_tprol + end interface mld_map_to_tprol + interface mld_lev_mat_asb subroutine mld_c_lev_aggrmat_asb(p,a,desc_a,ilaggr,nlaggr,op_prol,info) diff --git a/mlprec/mld_c_onelev_mod.f90 b/mlprec/mld_c_onelev_mod.f90 index f337d4a9..fe5a84a3 100644 --- a/mlprec/mld_c_onelev_mod.f90 +++ b/mlprec/mld_c_onelev_mod.f90 @@ -55,6 +55,7 @@ module mld_c_onelev_mod use mld_base_prec_type use mld_c_base_smoother_mod + use mld_c_base_aggregator_mod use psb_base_mod, only : psb_cspmat_type, psb_c_vect_type, & & psb_c_base_vect_type, psb_clinmap_type, psb_spk_, & & psb_ipk_, psb_long_int_k_, psb_desc_type, psb_i_base_vect_type, & @@ -136,9 +137,10 @@ module mld_c_onelev_mod & c_wrk_clone, c_wrk_move_alloc, c_wrk_cnv type mld_c_onelev_type - class(mld_c_base_smoother_type), allocatable :: sm, sm2a - class(mld_c_base_smoother_type), pointer :: sm2 => null() - class(mld_cmlprec_wrk_type), allocatable :: wrk + class(mld_c_base_smoother_type), allocatable :: sm, sm2a + class(mld_c_base_smoother_type), pointer :: sm2 => null() + class(mld_cmlprec_wrk_type), allocatable :: wrk + class(mld_c_base_aggregator_type), allocatable :: aggr type(mld_sml_parms) :: parms type(psb_cspmat_type) :: ac integer(psb_ipk_) :: ac_nz_loc, ac_nz_tot @@ -166,8 +168,9 @@ module mld_c_onelev_mod procedure, pass(lv) :: csetc => mld_c_base_onelev_csetc procedure, pass(lv) :: setsm => mld_c_base_onelev_setsm procedure, pass(lv) :: setsv => mld_c_base_onelev_setsv + procedure, pass(lv) :: setag => mld_c_base_onelev_setag generic, public :: set => seti, setr, setc, & - & cseti, csetr, csetc, setsm, setsv + & cseti, csetr, csetc, setsm, setsv, setag procedure, pass(lv) :: sizeof => c_base_onelev_sizeof procedure, pass(lv) :: get_nzeros => c_base_onelev_get_nzeros procedure, pass(lv) :: get_wrksz => c_base_onelev_get_wrksize @@ -299,6 +302,20 @@ module mld_c_onelev_mod end subroutine mld_c_base_onelev_setsv end interface + interface + subroutine mld_c_base_onelev_setag(lv,val,info,pos) + import :: psb_spk_, mld_c_onelev_type, mld_c_base_aggregator_type, & + & psb_ipk_, psb_long_int_k_, psb_desc_type + Implicit None + + ! Arguments + class(mld_c_onelev_type), target, intent(inout) :: lv + class(mld_c_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + character(len=*), optional, intent(in) :: pos + end subroutine mld_c_base_onelev_setag + end interface + interface subroutine mld_c_base_onelev_setc(lv,what,val,info,pos) import :: psb_cspmat_type, psb_c_vect_type, psb_c_base_vect_type, & @@ -323,9 +340,9 @@ module mld_c_onelev_mod class(mld_c_onelev_type), intent(inout) :: lv integer(psb_ipk_), intent(in) :: what - real(psb_spk_), intent(in) :: val + real(psb_spk_), intent(in) :: val integer(psb_ipk_), intent(out) :: info - character(len=*), optional, intent(in) :: pos + character(len=*), optional, intent(in) :: pos end subroutine mld_c_base_onelev_setr end interface @@ -450,7 +467,8 @@ contains Implicit None ! Arguments - class(mld_c_onelev_type), target, intent(inout) :: lv + class(mld_c_onelev_type), target, intent(inout) :: lv + integer(psb_ipk_) :: info lv%parms%sweeps_pre = 1 lv%parms%sweeps_post = 1 @@ -473,7 +491,9 @@ contains else lv%sm2 => lv%sm end if - + if (.not.allocated(lv%aggr)) allocate(mld_c_base_aggregator_type :: lv%aggr,stat=info) + if (allocated(lv%aggr)) call lv%aggr%default() + return end subroutine c_base_onelev_default @@ -508,6 +528,14 @@ contains end if lvout%sm2 => lvout%sm end if + if (allocated(lv%aggr)) then + call lv%aggr%clone(lvout%aggr,info) + else + if (allocated(lvout%aggr)) then + call lvout%aggr%free(info) + if (info==psb_success_) deallocate(lvout%aggr,stat=info) + end if + end if if (info == psb_success_) call lv%parms%clone(lvout%parms,info) if (info == psb_success_) call lv%ac%clone(lvout%ac,info) if (info == psb_success_) call lv%tprol%clone(lvout%tprol,info) @@ -538,8 +566,9 @@ contains call move_alloc(lv%sm2a,b%sm2a) b%sm2 =>b%sm end if - - if (info == psb_success_) call psb_move_alloc(lv%ac,b%ac,info) + + call move_alloc(lv%aggr,b%aggr) + if (info == psb_success_) call psb_move_alloc(lv%ac,b%ac,info) if (info == psb_success_) call psb_move_alloc(lv%tprol,b%tprol,info) if (info == psb_success_) call psb_move_alloc(lv%desc_ac,b%desc_ac,info) if (info == psb_success_) call psb_move_alloc(lv%map,b%map,info) diff --git a/mlprec/mld_c_prec_mod.f90 b/mlprec/mld_c_prec_mod.f90 index 4ec6e9d2..a06680b8 100644 --- a/mlprec/mld_c_prec_mod.f90 +++ b/mlprec/mld_c_prec_mod.f90 @@ -55,7 +55,8 @@ module mld_c_prec_mod interface mld_precset module procedure mld_c_iprecsetsm, mld_c_iprecsetsv, & & mld_c_iprecseti, mld_c_iprecsetc, mld_c_iprecsetr, & - & mld_c_cprecseti, mld_c_cprecsetc, mld_c_cprecsetr + & mld_c_cprecseti, mld_c_cprecsetc, mld_c_cprecsetr, & + & mld_c_iprecsetag end interface mld_precset interface mld_extprol_bld @@ -97,6 +98,14 @@ contains call p%set(val,info, pos=pos) end subroutine mld_c_iprecsetsv + subroutine mld_c_iprecsetag(p,val,info,pos) + type(mld_cprec_type), intent(inout) :: p + class(mld_c_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + character(len=*), optional, intent(in) :: pos + call p%set(val,info, pos=pos) + end subroutine mld_c_iprecsetag + subroutine mld_c_iprecseti(p,what,val,info,pos) type(mld_cprec_type), intent(inout) :: p integer(psb_ipk_), intent(in) :: what diff --git a/mlprec/mld_c_prec_type.f90 b/mlprec/mld_c_prec_type.f90 index 7b0160d7..073f303c 100644 --- a/mlprec/mld_c_prec_type.f90 +++ b/mlprec/mld_c_prec_type.f90 @@ -55,6 +55,7 @@ module mld_c_prec_type use mld_base_prec_type use mld_c_base_solver_mod use mld_c_base_smoother_mod + use mld_c_base_aggregator_mod use mld_c_onelev_mod use psb_prec_mod, only : psb_cprec_type @@ -92,8 +93,8 @@ module mld_c_prec_type ! 2. maximum number of levels. Defaults to 20 integer(psb_ipk_) :: max_levs = 20_psb_ipk_ ! 3. min_cr_ratio = 1.5 - real(psb_spk_) :: min_cr_ratio = 1.5_psb_spk_ - real(psb_spk_) :: op_complexity=szero + real(psb_spk_) :: min_cr_ratio = 1.5_psb_spk_ + real(psb_spk_) :: op_complexity = szero ! ! Number of outer sweeps. Sometimes 2 V-cycles may be better than 1 W-cycle. ! @@ -126,6 +127,7 @@ module mld_c_prec_type procedure, pass(prec) :: sizeof => mld_cprec_sizeof procedure, pass(prec) :: setsm => mld_cprecsetsm procedure, pass(prec) :: setsv => mld_cprecsetsv + procedure, pass(prec) :: setag => mld_cprecsetag procedure, pass(prec) :: seti => mld_cprecseti procedure, pass(prec) :: setc => mld_cprecsetc procedure, pass(prec) :: setr => mld_cprecsetr @@ -133,7 +135,7 @@ module mld_c_prec_type procedure, pass(prec) :: csetc => mld_ccprecsetc procedure, pass(prec) :: csetr => mld_ccprecsetr generic, public :: set => seti, setc, setr, & - & cseti, csetc, csetr, setsm, setsv + & cseti, csetc, csetr, setsm, setsv, setag procedure, pass(prec) :: get_smoother => mld_c_get_smootherp procedure, pass(prec) :: get_solver => mld_c_get_solverp procedure, pass(prec) :: move_alloc => c_prec_move_alloc @@ -234,6 +236,15 @@ module mld_c_prec_type integer(psb_ipk_), optional, intent(in) :: ilev,ilmax character(len=*), optional, intent(in) :: pos end subroutine mld_cprecsetsv + subroutine mld_cprecsetag(prec,val,info,ilev,pos) + import :: psb_cspmat_type, psb_desc_type, psb_spk_, & + & mld_cprec_type, mld_c_base_aggregator_type, psb_ipk_ + class(mld_cprec_type), intent(inout) :: prec + class(mld_c_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), optional, intent(in) :: ilev + character(len=*), optional, intent(in) :: pos + end subroutine mld_cprecsetag subroutine mld_cprecseti(prec,what,val,info,ilev,ilmax,pos) import :: psb_cspmat_type, psb_desc_type, psb_spk_, & & mld_cprec_type, psb_ipk_ diff --git a/mlprec/mld_c_symdec_aggregator_mod.f90 b/mlprec/mld_c_symdec_aggregator_mod.f90 new file mode 100644 index 00000000..4738c595 --- /dev/null +++ b/mlprec/mld_c_symdec_aggregator_mod.f90 @@ -0,0 +1,128 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. This version only differs from the +! basic decoupled aggregation algorithm because it works on (the +! pattern of) A+A^T instead of A. +! +! M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +module mld_c_symdec_aggregator_mod + + use mld_c_base_aggregator_mod + ! + ! sm - class(mld_T_base_smoother_type), allocatable + ! The current level preconditioner (aka smoother). + ! parms - type(mld_RTml_parms) + ! The parameters defining the multilevel strategy. + ! ac - The local part of the current-level matrix, built by + ! coarsening the previous-level matrix. + ! desc_ac - type(psb_desc_type). + ! The communication descriptor associated to the matrix + ! stored in ac. + ! base_a - type(psb_Tspmat_type), pointer. + ! Pointer (really a pointer!) to the local part of the current + ! matrix (so we have a unified treatment of residuals). + ! We need this to avoid passing explicitly the current matrix + ! to the routine which applies the preconditioner. + ! base_desc - type(psb_desc_type), pointer. + ! Pointer to the communication descriptor associated to the + ! matrix pointed by base_a. + ! map - Stores the maps (restriction and prolongation) between the + ! vector spaces associated to the index spaces of the previous + ! and current levels. + ! + ! Methods: + ! Most methods follow the encapsulation hierarchy: they take whatever action + ! is appropriate for the current object, then call the corresponding method for + ! the contained object. + ! As an example: the descr() method prints out a description of the + ! level. It starts by invoking the descr() method of the parms object, + ! then calls the descr() method of the smoother object. + ! + ! descr - Prints a description of the object. + ! default - Set default values + ! dump - Dump to file object contents + ! set - Sets various parameters; when a request is unknown + ! it is passed to the smoother object for further processing. + ! check - Sanity checks. + ! sizeof - Total memory occupation in bytes + ! get_nzeros - Number of nonzeros + ! + ! + type, extends(mld_c_base_aggregator_type) :: mld_c_symdec_aggregator_type + + contains + procedure, pass(ag) :: tprol => mld_c_symdec_aggregator_build_tprol + procedure, nopass :: fmt => mld_c_symdec_aggregator_fmt + end type mld_c_symdec_aggregator_type + + + interface + subroutine mld_c_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: mld_c_symdec_aggregator_type, psb_desc_type, psb_cspmat_type, psb_spk_, & + & psb_ipk_, psb_long_int_k_, mld_sml_parms + implicit none + class(mld_c_symdec_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_cspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_cspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_c_symdec_aggregator_build_tprol + end interface + + +contains + + function mld_c_symdec_aggregator_fmt() result(val) + implicit none + character(len=32) :: val + + val = "Symmetric Decoupled aggregation" + end function mld_c_symdec_aggregator_fmt + +end module mld_c_symdec_aggregator_mod diff --git a/mlprec/mld_d_base_aggregator_mod.f90 b/mlprec/mld_d_base_aggregator_mod.f90 new file mode 100644 index 00000000..fd231c39 --- /dev/null +++ b/mlprec/mld_d_base_aggregator_mod.f90 @@ -0,0 +1,209 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. The basic version is the +! decoupled aggregation algorithm presented in +! +! M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +module mld_d_base_aggregator_mod + + use mld_base_prec_type, only : mld_dml_parms + use psb_base_mod, only : psb_dspmat_type, psb_d_vect_type, & + & psb_d_base_vect_type, psb_dlinmap_type, psb_dpk_, & + & psb_ipk_, psb_long_int_k_, psb_desc_type, psb_i_base_vect_type, & + & psb_erractionsave, psb_error_handler, psb_success_ + ! + ! sm - class(mld_T_base_smoother_type), allocatable + ! The current level preconditioner (aka smoother). + ! parms - type(mld_RTml_parms) + ! The parameters defining the multilevel strategy. + ! ac - The local part of the current-level matrix, built by + ! coarsening the previous-level matrix. + ! desc_ac - type(psb_desc_type). + ! The communication descriptor associated to the matrix + ! stored in ac. + ! base_a - type(psb_Tspmat_type), pointer. + ! Pointer (really a pointer!) to the local part of the current + ! matrix (so we have a unified treatment of residuals). + ! We need this to avoid passing explicitly the current matrix + ! to the routine which applies the preconditioner. + ! base_desc - type(psb_desc_type), pointer. + ! Pointer to the communication descriptor associated to the + ! matrix pointed by base_a. + ! map - Stores the maps (restriction and prolongation) between the + ! vector spaces associated to the index spaces of the previous + ! and current levels. + ! + ! Methods: + ! Most methods follow the encapsulation hierarchy: they take whatever action + ! is appropriate for the current object, then call the corresponding method for + ! the contained object. + ! As an example: the descr() method prints out a description of the + ! level. It starts by invoking the descr() method of the parms object, + ! then calls the descr() method of the smoother object. + ! + ! descr - Prints a description of the object. + ! default - Set default values + ! dump - Dump to file object contents + ! set - Sets various parameters; when a request is unknown + ! it is passed to the smoother object for further processing. + ! check - Sanity checks. + ! sizeof - Total memory occupation in bytes + ! get_nzeros - Number of nonzeros + ! + ! + type mld_d_base_aggregator_type + + contains + procedure, pass(ag) :: bld_tprol => mld_d_base_aggregator_build_tprol + procedure, pass(ag) :: mat_asb => mld_d_base_aggregator_mat_asb + procedure, pass(ag) :: update_level => mld_d_base_aggregator_update_level + procedure, pass(ag) :: clone => mld_d_base_aggregator_clone + procedure, pass(ag) :: free => mld_d_base_aggregator_free + procedure, pass(ag) :: default => mld_d_base_aggregator_default + procedure, pass(ag) :: descr => mld_d_base_aggregator_descr + procedure, nopass :: fmt => mld_d_base_aggregator_fmt + end type mld_d_base_aggregator_type + + + interface + subroutine mld_d_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: mld_d_base_aggregator_type, psb_desc_type, psb_dspmat_type, psb_dpk_, & + & psb_ipk_, psb_long_int_k_, mld_dml_parms + implicit none + class(mld_d_base_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_dspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_d_base_aggregator_build_tprol + end interface + + interface + subroutine mld_d_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,& + & op_prol,op_restr,info) + import :: mld_d_base_aggregator_type, psb_desc_type, psb_dspmat_type, psb_dpk_, & + & psb_ipk_, psb_long_int_k_, mld_dml_parms + implicit none + class(mld_d_base_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) + type(psb_dspmat_type), intent(inout) :: op_prol + type(psb_dspmat_type), intent(out) :: ac,op_restr + integer(psb_ipk_), intent(out) :: info + end subroutine mld_d_base_aggregator_mat_asb + end interface + +contains + + subroutine mld_d_base_aggregator_update_level(ag,agnext,info) + implicit none + class(mld_d_base_aggregator_type), target, intent(inout) :: ag, agnext + integer(psb_ipk_), intent(out) :: info + + ! + ! Base version does nothing. + ! + info = 0 + end subroutine mld_d_base_aggregator_update_level + + subroutine mld_d_base_aggregator_clone(ag,agnext,info) + implicit none + class(mld_d_base_aggregator_type), intent(inout) :: ag + class(mld_d_base_aggregator_type), allocatable, intent(inout) :: agnext + integer(psb_ipk_), intent(out) :: info + + info = 0 + if (allocated(agnext)) then + call agnext%free(info) + if (info == 0) deallocate(agnext,stat=info) + end if + if (info /= 0) return + allocate(agnext,source=ag,stat=info) + + end subroutine mld_d_base_aggregator_clone + + subroutine mld_d_base_aggregator_free(ag,info) + implicit none + class(mld_d_base_aggregator_type), intent(inout) :: ag + integer(psb_ipk_), intent(out) :: info + + info = psb_success_ + return + end subroutine mld_d_base_aggregator_free + + subroutine mld_d_base_aggregator_default(ag) + implicit none + class(mld_d_base_aggregator_type), intent(inout) :: ag + + ! Here we need do nothing + + return + end subroutine mld_d_base_aggregator_default + + function mld_d_base_aggregator_fmt() result(val) + implicit none + character(len=32) :: val + + val = "Decoupled aggregation" + end function mld_d_base_aggregator_fmt + + subroutine mld_d_base_aggregator_descr(ag,parms,iout,info) + implicit none + class(mld_d_base_aggregator_type), intent(in) :: ag + type(mld_dml_parms), intent(in) :: parms + integer(psb_ipk_), intent(in) :: iout + integer(psb_ipk_), intent(out) :: info + + call parms%mldescr(iout,info,aggr_name=ag%fmt()) + + return + end subroutine mld_d_base_aggregator_descr + +end module mld_d_base_aggregator_mod diff --git a/mlprec/mld_d_bcmatch_aggregator_mod.F90 b/mlprec/mld_d_bcmatch_aggregator_mod.F90 new file mode 100644 index 00000000..5f43ac91 --- /dev/null +++ b/mlprec/mld_d_bcmatch_aggregator_mod.F90 @@ -0,0 +1,262 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. This variant is based on the hybrid method +! presented in +! +! S. Gratton, P. Henon, P. Jiranek and X. Vasseur: +! Reducing complexity of algebraic multigrid by aggregation +! Numerical Lin. Algebra with Applications, 2016, 23:501-518 +! + ! + ! sm - class(mld_T_base_smoother_type), allocatable + ! The current level preconditioner (aka smoother). + ! parms - type(mld_RTml_parms) + ! The parameters defining the multilevel strategy. + ! ac - The local part of the current-level matrix, built by + ! coarsening the previous-level matrix. + ! desc_ac - type(psb_desc_type). + ! The communication descriptor associated to the matrix + ! stored in ac. + ! base_a - type(psb_Tspmat_type), pointer. + ! Pointer (really a pointer!) to the local part of the current + ! matrix (so we have a unified treatment of residuals). + ! We need this to avoid passing explicitly the current matrix + ! to the routine which applies the preconditioner. + ! base_desc - type(psb_desc_type), pointer. + ! Pointer to the communication descriptor associated to the + ! matrix pointed by base_a. + ! map - Stores the maps (restriction and prolongation) between the + ! vector spaces associated to the index spaces of the previous + ! and current levels. + ! + ! Methods: + ! Most methods follow the encapsulation hierarchy: they take whatever action + ! is appropriate for the current object, then call the corresponding method for + ! the contained object. + ! As an example: the descr() method prints out a description of the + ! level. It starts by invoking the descr() method of the parms object, + ! then calls the descr() method of the smoother object. + ! + ! descr - Prints a description of the object. + ! default - Set default values + ! dump - Dump to file object contents + ! set - Sets various parameters; when a request is unknown + ! it is passed to the smoother object for further processing. + ! check - Sanity checks. + ! sizeof - Total memory occupation in bytes + ! get_nzeros - Number of nonzeros + ! + ! + +module bcm_csr_type_mod + use iso_c_binding + type, bind(c):: bcm_Vector + type(c_ptr) :: data + integer(c_int) :: size + integer(c_int) :: owns_data + end type + + type, bind(c):: bcm_CSRMatrix + type(c_ptr) :: i + type(c_ptr) :: j + integer(c_int) :: num_rows + integer(c_int) :: num_cols + integer(c_int) :: num_nonzeros + integer(c_int) :: owns_data + type(c_ptr) :: data + end type +end module bcm_csr_type_mod + +module mld_d_bcmatch_aggregator_mod + use mld_d_base_aggregator_mod + use bcm_csr_type_mod + + type, extends(mld_d_base_aggregator_type) :: mld_d_bcmatch_aggregator_type + integer(psb_ipk_) :: matching_alg + integer(psb_ipk_) :: n_sweeps + real(psb_dpk_), allocatable :: w_tmp(:) + type(bcm_Vector) :: w_par + integer(psb_ipk_) :: max_csize + integer(psb_ipk_) :: max_nlevels + !type(psb_d_vect_type) :: w + contains + procedure, pass(ag) :: bld_tprol => mld_d_bcmatch_aggregator_build_tprol + procedure, pass(ag) :: set => d_bcmatch_aggr_cseti + procedure, pass(ag) :: default =>d_bcmatch_aggr_set_default + procedure, pass(ag) :: mat_asb => mld_d_bcmatch_aggregator_mat_asb + procedure, pass(ag) :: update_level => d_bcmatch_aggregator_update_level +!!$ procedure, pass(ag) :: clone => mld_d_base_aggregator_clone +!!$ procedure, pass(ag) :: free => mld_d_bcmatch_aggregator_free +!!$ procedure, pass(ag) :: default => mld_d_base_aggregator_default + procedure, nopass :: fmt => mld_d_bcmatch_aggregator_fmt + end type mld_d_bcmatch_aggregator_type + + + interface + subroutine mld_d_bcmatch_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: mld_d_bcmatch_aggregator_type, psb_desc_type, psb_dspmat_type, psb_dpk_, & + & psb_ipk_, psb_long_int_k_, mld_dml_parms + implicit none + class(mld_d_bcmatch_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_dspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_d_bcmatch_aggregator_build_tprol + end interface + + interface + subroutine mld_d_bcmatch_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,& + & op_prol,op_restr,info) + import :: mld_d_bcmatch_aggregator_type, psb_desc_type, psb_dspmat_type, psb_dpk_, & + & psb_ipk_, psb_long_int_k_, mld_dml_parms + implicit none + class(mld_d_bcmatch_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) + type(psb_dspmat_type), intent(inout) :: op_prol + type(psb_dspmat_type), intent(out) :: ac,op_restr + integer(psb_ipk_), intent(out) :: info + end subroutine mld_d_bcmatch_aggregator_mat_asb + end interface + + +contains + + + function mld_d_bcmatch_aggregator_fmt() result(val) + implicit none + character(len=32) :: val + + val = "BootCMatch aggregation" + end function mld_d_bcmatch_aggregator_fmt + + subroutine d_bcmatch_aggregator_update_level(ag,agnext,info) + implicit none + class(mld_d_bcmatch_aggregator_type), target, intent(inout) :: ag + class(mld_d_base_aggregator_type), target, intent(inout) :: agnext + integer(psb_ipk_), intent(out) :: info + + ! + ! + select type(agnext) + type is (mld_d_bcmatch_aggregator_type) + agnext%matching_alg=ag%matching_alg + agnext%n_sweeps=ag%n_sweeps + agnext%max_csize=ag%max_csize + agnext%max_nlevels=ag%max_nlevels + agnext%w_par=ag%w_par + end select + info = 0 + end subroutine d_bcmatch_aggregator_update_level + + subroutine d_bcmatch_aggr_cseti(ag,what,val,info) + + Implicit None + + ! Arguments + class(mld_d_bcmatch_aggregator_type), intent(inout) :: ag + character(len=*), intent(in) :: what + integer(psb_ipk_), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_) :: err_act, iwhat + character(len=20) :: name='d_bcmatch_aggr_cseti' + info = psb_success_ + + select case(what) + case('BCM_MATCH_ALG') + ag%matching_alg=val + case('BCM_SWEEPS') + ag%n_sweeps=val + case('BCM_MAX_CSIZE') + ag%max_csize=val + case('BCM_MAX_NLEVELS') + ag%max_nlevels=val + case('BCM_W_SIZE') + ag%w_par%size=val + ag%w_par%owns_data=0 + allocate(ag%w_tmp(val)) + ag%w_tmp = 1.0_psb_dpk_ + call set_cloc(ag%w_tmp, ag%w_par) + case default + end select + return + contains + subroutine set_cloc(vect,w_par) + real(psb_dpk_), target :: vect(:) + type(bcm_Vector) :: w_par + + w_par%data = c_loc(vect) + end subroutine set_cloc + + end subroutine d_bcmatch_aggr_cseti + + subroutine d_bcmatch_aggr_set_default(ag) + + Implicit None + + ! Arguments + class(mld_d_bcmatch_aggregator_type), intent(inout) :: ag + character(len=20) :: name='d_bcmatch_aggr_set_default' + ag%matching_alg=0 + ag%n_sweeps=1 + ag%max_nlevels=36 + ag%max_csize=10 + + return + + end subroutine d_bcmatch_aggr_set_default + +!!$ subroutine d_bcmatch_aggregator_free(ag,info) +!!$ implicit none +!!$ class(mld_d_bcmatch_aggregator_type), target, intent(inout) :: ag +!!$ integer(psb_ipk_), intent(out) :: info +!!$ +!!$ info = 0 +!!$ end subroutine d_bcmatch_aggregator_free + + +end module mld_d_bcmatch_aggregator_mod diff --git a/mlprec/mld_d_hybrid_aggregator_mod.F90 b/mlprec/mld_d_hybrid_aggregator_mod.F90 new file mode 100644 index 00000000..50e3215c --- /dev/null +++ b/mlprec/mld_d_hybrid_aggregator_mod.F90 @@ -0,0 +1,131 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. This variant is based on the hybrid method +! presented in +! +! S. Gratton, P. Henon, P. Jiranek and X. Vasseur: +! Reducing complexity of algebraic multigrid by aggregation +! Numerical Lin. Algebra with Applications, 2016, 23:501-518 +! +module mld_d_hybrid_aggregator_mod + + use mld_d_base_aggregator_mod + ! + ! sm - class(mld_T_base_smoother_type), allocatable + ! The current level preconditioner (aka smoother). + ! parms - type(mld_RTml_parms) + ! The parameters defining the multilevel strategy. + ! ac - The local part of the current-level matrix, built by + ! coarsening the previous-level matrix. + ! desc_ac - type(psb_desc_type). + ! The communication descriptor associated to the matrix + ! stored in ac. + ! base_a - type(psb_Tspmat_type), pointer. + ! Pointer (really a pointer!) to the local part of the current + ! matrix (so we have a unified treatment of residuals). + ! We need this to avoid passing explicitly the current matrix + ! to the routine which applies the preconditioner. + ! base_desc - type(psb_desc_type), pointer. + ! Pointer to the communication descriptor associated to the + ! matrix pointed by base_a. + ! map - Stores the maps (restriction and prolongation) between the + ! vector spaces associated to the index spaces of the previous + ! and current levels. + ! + ! Methods: + ! Most methods follow the encapsulation hierarchy: they take whatever action + ! is appropriate for the current object, then call the corresponding method for + ! the contained object. + ! As an example: the descr() method prints out a description of the + ! level. It starts by invoking the descr() method of the parms object, + ! then calls the descr() method of the smoother object. + ! + ! descr - Prints a description of the object. + ! default - Set default values + ! dump - Dump to file object contents + ! set - Sets various parameters; when a request is unknown + ! it is passed to the smoother object for further processing. + ! check - Sanity checks. + ! sizeof - Total memory occupation in bytes + ! get_nzeros - Number of nonzeros + ! + ! + type, extends(mld_d_base_aggregator_type) :: mld_d_hybrid_aggregator_type + + contains + procedure, pass(ag) :: bld_tprol => mld_d_hybrid_aggregator_build_tprol +!!$ procedure, pass(ag) :: mat_asb => mld_d_base_aggregator_mat_asb +!!$ procedure, pass(ag) :: update_level => mld_d_base_aggregator_update_level +!!$ procedure, pass(ag) :: clone => mld_d_base_aggregator_clone +!!$ procedure, pass(ag) :: free => mld_d_base_aggregator_free +!!$ procedure, pass(ag) :: default => mld_d_base_aggregator_default + procedure, nopass :: fmt => mld_d_hybrid_aggregator_fmt + end type mld_d_hybrid_aggregator_type + + + interface + subroutine mld_d_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: mld_d_hybrid_aggregator_type, psb_desc_type, psb_dspmat_type, psb_dpk_, & + & psb_ipk_, psb_long_int_k_, mld_dml_parms + implicit none + class(mld_d_hybrid_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_dspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_d_hybrid_aggregator_build_tprol + end interface + +contains + + + function mld_d_hybrid_aggregator_fmt() result(val) + implicit none + character(len=32) :: val + + val = "Hybrid Decoupled aggregation" + end function mld_d_hybrid_aggregator_fmt + + +end module mld_d_hybrid_aggregator_mod diff --git a/mlprec/mld_d_inner_mod.f90 b/mlprec/mld_d_inner_mod.f90 index e73856a0..810d5831 100644 --- a/mlprec/mld_d_inner_mod.f90 +++ b/mlprec/mld_d_inner_mod.f90 @@ -137,6 +137,31 @@ module mld_d_inner_mod end subroutine mld_d_dec_map_bld end interface mld_dec_map_bld + interface mld_hyb_map_bld + subroutine mld_d_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + use psb_base_mod, only : psb_dspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ + implicit none + integer(psb_ipk_), intent(in) :: iorder + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + real(psb_dpk_), intent(in) :: theta + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + integer(psb_ipk_), intent(out) :: info + end subroutine mld_d_hyb_map_bld + end interface mld_hyb_map_bld + + interface mld_map_to_tprol + subroutine mld_d_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod, only : psb_dspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ + use mld_d_prec_type, only : mld_d_onelev_type + implicit none + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:) + type(psb_dspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_d_map_to_tprol + end interface mld_map_to_tprol + interface mld_lev_mat_asb subroutine mld_d_lev_aggrmat_asb(p,a,desc_a,ilaggr,nlaggr,op_prol,info) diff --git a/mlprec/mld_d_onelev_mod.f90 b/mlprec/mld_d_onelev_mod.f90 index 4420f870..30c7376c 100644 --- a/mlprec/mld_d_onelev_mod.f90 +++ b/mlprec/mld_d_onelev_mod.f90 @@ -55,6 +55,7 @@ module mld_d_onelev_mod use mld_base_prec_type use mld_d_base_smoother_mod + use mld_d_base_aggregator_mod use psb_base_mod, only : psb_dspmat_type, psb_d_vect_type, & & psb_d_base_vect_type, psb_dlinmap_type, psb_dpk_, & & psb_ipk_, psb_long_int_k_, psb_desc_type, psb_i_base_vect_type, & @@ -136,9 +137,10 @@ module mld_d_onelev_mod & d_wrk_clone, d_wrk_move_alloc, d_wrk_cnv type mld_d_onelev_type - class(mld_d_base_smoother_type), allocatable :: sm, sm2a - class(mld_d_base_smoother_type), pointer :: sm2 => null() - class(mld_dmlprec_wrk_type), allocatable :: wrk + class(mld_d_base_smoother_type), allocatable :: sm, sm2a + class(mld_d_base_smoother_type), pointer :: sm2 => null() + class(mld_dmlprec_wrk_type), allocatable :: wrk + class(mld_d_base_aggregator_type), allocatable :: aggr type(mld_dml_parms) :: parms type(psb_dspmat_type) :: ac integer(psb_ipk_) :: ac_nz_loc, ac_nz_tot @@ -166,8 +168,9 @@ module mld_d_onelev_mod procedure, pass(lv) :: csetc => mld_d_base_onelev_csetc procedure, pass(lv) :: setsm => mld_d_base_onelev_setsm procedure, pass(lv) :: setsv => mld_d_base_onelev_setsv + procedure, pass(lv) :: setag => mld_d_base_onelev_setag generic, public :: set => seti, setr, setc, & - & cseti, csetr, csetc, setsm, setsv + & cseti, csetr, csetc, setsm, setsv, setag procedure, pass(lv) :: sizeof => d_base_onelev_sizeof procedure, pass(lv) :: get_nzeros => d_base_onelev_get_nzeros procedure, pass(lv) :: get_wrksz => d_base_onelev_get_wrksize @@ -299,6 +302,20 @@ module mld_d_onelev_mod end subroutine mld_d_base_onelev_setsv end interface + interface + subroutine mld_d_base_onelev_setag(lv,val,info,pos) + import :: psb_dpk_, mld_d_onelev_type, mld_d_base_aggregator_type, & + & psb_ipk_, psb_long_int_k_, psb_desc_type + Implicit None + + ! Arguments + class(mld_d_onelev_type), target, intent(inout) :: lv + class(mld_d_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + character(len=*), optional, intent(in) :: pos + end subroutine mld_d_base_onelev_setag + end interface + interface subroutine mld_d_base_onelev_setc(lv,what,val,info,pos) import :: psb_dspmat_type, psb_d_vect_type, psb_d_base_vect_type, & @@ -323,9 +340,9 @@ module mld_d_onelev_mod class(mld_d_onelev_type), intent(inout) :: lv integer(psb_ipk_), intent(in) :: what - real(psb_dpk_), intent(in) :: val + real(psb_dpk_), intent(in) :: val integer(psb_ipk_), intent(out) :: info - character(len=*), optional, intent(in) :: pos + character(len=*), optional, intent(in) :: pos end subroutine mld_d_base_onelev_setr end interface @@ -450,7 +467,8 @@ contains Implicit None ! Arguments - class(mld_d_onelev_type), target, intent(inout) :: lv + class(mld_d_onelev_type), target, intent(inout) :: lv + integer(psb_ipk_) :: info lv%parms%sweeps_pre = 1 lv%parms%sweeps_post = 1 @@ -473,7 +491,9 @@ contains else lv%sm2 => lv%sm end if - + if (.not.allocated(lv%aggr)) allocate(mld_d_base_aggregator_type :: lv%aggr,stat=info) + if (allocated(lv%aggr)) call lv%aggr%default() + return end subroutine d_base_onelev_default @@ -508,6 +528,14 @@ contains end if lvout%sm2 => lvout%sm end if + if (allocated(lv%aggr)) then + call lv%aggr%clone(lvout%aggr,info) + else + if (allocated(lvout%aggr)) then + call lvout%aggr%free(info) + if (info==psb_success_) deallocate(lvout%aggr,stat=info) + end if + end if if (info == psb_success_) call lv%parms%clone(lvout%parms,info) if (info == psb_success_) call lv%ac%clone(lvout%ac,info) if (info == psb_success_) call lv%tprol%clone(lvout%tprol,info) @@ -538,8 +566,9 @@ contains call move_alloc(lv%sm2a,b%sm2a) b%sm2 =>b%sm end if - - if (info == psb_success_) call psb_move_alloc(lv%ac,b%ac,info) + + call move_alloc(lv%aggr,b%aggr) + if (info == psb_success_) call psb_move_alloc(lv%ac,b%ac,info) if (info == psb_success_) call psb_move_alloc(lv%tprol,b%tprol,info) if (info == psb_success_) call psb_move_alloc(lv%desc_ac,b%desc_ac,info) if (info == psb_success_) call psb_move_alloc(lv%map,b%map,info) diff --git a/mlprec/mld_d_prec_mod.f90 b/mlprec/mld_d_prec_mod.f90 index 152c860f..7e695111 100644 --- a/mlprec/mld_d_prec_mod.f90 +++ b/mlprec/mld_d_prec_mod.f90 @@ -55,7 +55,8 @@ module mld_d_prec_mod interface mld_precset module procedure mld_d_iprecsetsm, mld_d_iprecsetsv, & & mld_d_iprecseti, mld_d_iprecsetc, mld_d_iprecsetr, & - & mld_d_cprecseti, mld_d_cprecsetc, mld_d_cprecsetr + & mld_d_cprecseti, mld_d_cprecsetc, mld_d_cprecsetr, & + & mld_d_iprecsetag end interface mld_precset interface mld_extprol_bld @@ -97,6 +98,14 @@ contains call p%set(val,info, pos=pos) end subroutine mld_d_iprecsetsv + subroutine mld_d_iprecsetag(p,val,info,pos) + type(mld_dprec_type), intent(inout) :: p + class(mld_d_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + character(len=*), optional, intent(in) :: pos + call p%set(val,info, pos=pos) + end subroutine mld_d_iprecsetag + subroutine mld_d_iprecseti(p,what,val,info,pos) type(mld_dprec_type), intent(inout) :: p integer(psb_ipk_), intent(in) :: what diff --git a/mlprec/mld_d_prec_type.f90 b/mlprec/mld_d_prec_type.f90 index 1aa9409c..f62f4760 100644 --- a/mlprec/mld_d_prec_type.f90 +++ b/mlprec/mld_d_prec_type.f90 @@ -55,6 +55,7 @@ module mld_d_prec_type use mld_base_prec_type use mld_d_base_solver_mod use mld_d_base_smoother_mod + use mld_d_base_aggregator_mod use mld_d_onelev_mod use psb_prec_mod, only : psb_dprec_type @@ -92,8 +93,8 @@ module mld_d_prec_type ! 2. maximum number of levels. Defaults to 20 integer(psb_ipk_) :: max_levs = 20_psb_ipk_ ! 3. min_cr_ratio = 1.5 - real(psb_dpk_) :: min_cr_ratio = 1.5_psb_dpk_ - real(psb_dpk_) :: op_complexity=dzero + real(psb_dpk_) :: min_cr_ratio = 1.5_psb_dpk_ + real(psb_dpk_) :: op_complexity = dzero ! ! Number of outer sweeps. Sometimes 2 V-cycles may be better than 1 W-cycle. ! @@ -126,6 +127,7 @@ module mld_d_prec_type procedure, pass(prec) :: sizeof => mld_dprec_sizeof procedure, pass(prec) :: setsm => mld_dprecsetsm procedure, pass(prec) :: setsv => mld_dprecsetsv + procedure, pass(prec) :: setag => mld_dprecsetag procedure, pass(prec) :: seti => mld_dprecseti procedure, pass(prec) :: setc => mld_dprecsetc procedure, pass(prec) :: setr => mld_dprecsetr @@ -133,7 +135,7 @@ module mld_d_prec_type procedure, pass(prec) :: csetc => mld_dcprecsetc procedure, pass(prec) :: csetr => mld_dcprecsetr generic, public :: set => seti, setc, setr, & - & cseti, csetc, csetr, setsm, setsv + & cseti, csetc, csetr, setsm, setsv, setag procedure, pass(prec) :: get_smoother => mld_d_get_smootherp procedure, pass(prec) :: get_solver => mld_d_get_solverp procedure, pass(prec) :: move_alloc => d_prec_move_alloc @@ -234,6 +236,15 @@ module mld_d_prec_type integer(psb_ipk_), optional, intent(in) :: ilev,ilmax character(len=*), optional, intent(in) :: pos end subroutine mld_dprecsetsv + subroutine mld_dprecsetag(prec,val,info,ilev,pos) + import :: psb_dspmat_type, psb_desc_type, psb_dpk_, & + & mld_dprec_type, mld_d_base_aggregator_type, psb_ipk_ + class(mld_dprec_type), intent(inout) :: prec + class(mld_d_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), optional, intent(in) :: ilev + character(len=*), optional, intent(in) :: pos + end subroutine mld_dprecsetag subroutine mld_dprecseti(prec,what,val,info,ilev,ilmax,pos) import :: psb_dspmat_type, psb_desc_type, psb_dpk_, & & mld_dprec_type, psb_ipk_ diff --git a/mlprec/mld_d_symdec_aggregator_mod.f90 b/mlprec/mld_d_symdec_aggregator_mod.f90 new file mode 100644 index 00000000..2532fac9 --- /dev/null +++ b/mlprec/mld_d_symdec_aggregator_mod.f90 @@ -0,0 +1,128 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. This version only differs from the +! basic decoupled aggregation algorithm because it works on (the +! pattern of) A+A^T instead of A. +! +! M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +module mld_d_symdec_aggregator_mod + + use mld_d_base_aggregator_mod + ! + ! sm - class(mld_T_base_smoother_type), allocatable + ! The current level preconditioner (aka smoother). + ! parms - type(mld_RTml_parms) + ! The parameters defining the multilevel strategy. + ! ac - The local part of the current-level matrix, built by + ! coarsening the previous-level matrix. + ! desc_ac - type(psb_desc_type). + ! The communication descriptor associated to the matrix + ! stored in ac. + ! base_a - type(psb_Tspmat_type), pointer. + ! Pointer (really a pointer!) to the local part of the current + ! matrix (so we have a unified treatment of residuals). + ! We need this to avoid passing explicitly the current matrix + ! to the routine which applies the preconditioner. + ! base_desc - type(psb_desc_type), pointer. + ! Pointer to the communication descriptor associated to the + ! matrix pointed by base_a. + ! map - Stores the maps (restriction and prolongation) between the + ! vector spaces associated to the index spaces of the previous + ! and current levels. + ! + ! Methods: + ! Most methods follow the encapsulation hierarchy: they take whatever action + ! is appropriate for the current object, then call the corresponding method for + ! the contained object. + ! As an example: the descr() method prints out a description of the + ! level. It starts by invoking the descr() method of the parms object, + ! then calls the descr() method of the smoother object. + ! + ! descr - Prints a description of the object. + ! default - Set default values + ! dump - Dump to file object contents + ! set - Sets various parameters; when a request is unknown + ! it is passed to the smoother object for further processing. + ! check - Sanity checks. + ! sizeof - Total memory occupation in bytes + ! get_nzeros - Number of nonzeros + ! + ! + type, extends(mld_d_base_aggregator_type) :: mld_d_symdec_aggregator_type + + contains + procedure, pass(ag) :: tprol => mld_d_symdec_aggregator_build_tprol + procedure, nopass :: fmt => mld_d_symdec_aggregator_fmt + end type mld_d_symdec_aggregator_type + + + interface + subroutine mld_d_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: mld_d_symdec_aggregator_type, psb_desc_type, psb_dspmat_type, psb_dpk_, & + & psb_ipk_, psb_long_int_k_, mld_dml_parms + implicit none + class(mld_d_symdec_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_dspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_d_symdec_aggregator_build_tprol + end interface + + +contains + + function mld_d_symdec_aggregator_fmt() result(val) + implicit none + character(len=32) :: val + + val = "Symmetric Decoupled aggregation" + end function mld_d_symdec_aggregator_fmt + +end module mld_d_symdec_aggregator_mod diff --git a/mlprec/mld_s_base_aggregator_mod.f90 b/mlprec/mld_s_base_aggregator_mod.f90 new file mode 100644 index 00000000..3021e19c --- /dev/null +++ b/mlprec/mld_s_base_aggregator_mod.f90 @@ -0,0 +1,209 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. The basic version is the +! decoupled aggregation algorithm presented in +! +! M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +module mld_s_base_aggregator_mod + + use mld_base_prec_type, only : mld_sml_parms + use psb_base_mod, only : psb_sspmat_type, psb_s_vect_type, & + & psb_s_base_vect_type, psb_slinmap_type, psb_spk_, & + & psb_ipk_, psb_long_int_k_, psb_desc_type, psb_i_base_vect_type, & + & psb_erractionsave, psb_error_handler, psb_success_ + ! + ! sm - class(mld_T_base_smoother_type), allocatable + ! The current level preconditioner (aka smoother). + ! parms - type(mld_RTml_parms) + ! The parameters defining the multilevel strategy. + ! ac - The local part of the current-level matrix, built by + ! coarsening the previous-level matrix. + ! desc_ac - type(psb_desc_type). + ! The communication descriptor associated to the matrix + ! stored in ac. + ! base_a - type(psb_Tspmat_type), pointer. + ! Pointer (really a pointer!) to the local part of the current + ! matrix (so we have a unified treatment of residuals). + ! We need this to avoid passing explicitly the current matrix + ! to the routine which applies the preconditioner. + ! base_desc - type(psb_desc_type), pointer. + ! Pointer to the communication descriptor associated to the + ! matrix pointed by base_a. + ! map - Stores the maps (restriction and prolongation) between the + ! vector spaces associated to the index spaces of the previous + ! and current levels. + ! + ! Methods: + ! Most methods follow the encapsulation hierarchy: they take whatever action + ! is appropriate for the current object, then call the corresponding method for + ! the contained object. + ! As an example: the descr() method prints out a description of the + ! level. It starts by invoking the descr() method of the parms object, + ! then calls the descr() method of the smoother object. + ! + ! descr - Prints a description of the object. + ! default - Set default values + ! dump - Dump to file object contents + ! set - Sets various parameters; when a request is unknown + ! it is passed to the smoother object for further processing. + ! check - Sanity checks. + ! sizeof - Total memory occupation in bytes + ! get_nzeros - Number of nonzeros + ! + ! + type mld_s_base_aggregator_type + + contains + procedure, pass(ag) :: bld_tprol => mld_s_base_aggregator_build_tprol + procedure, pass(ag) :: mat_asb => mld_s_base_aggregator_mat_asb + procedure, pass(ag) :: update_level => mld_s_base_aggregator_update_level + procedure, pass(ag) :: clone => mld_s_base_aggregator_clone + procedure, pass(ag) :: free => mld_s_base_aggregator_free + procedure, pass(ag) :: default => mld_s_base_aggregator_default + procedure, pass(ag) :: descr => mld_s_base_aggregator_descr + procedure, nopass :: fmt => mld_s_base_aggregator_fmt + end type mld_s_base_aggregator_type + + + interface + subroutine mld_s_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: mld_s_base_aggregator_type, psb_desc_type, psb_sspmat_type, psb_spk_, & + & psb_ipk_, psb_long_int_k_, mld_sml_parms + implicit none + class(mld_s_base_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_sspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_sspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_s_base_aggregator_build_tprol + end interface + + interface + subroutine mld_s_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,& + & op_prol,op_restr,info) + import :: mld_s_base_aggregator_type, psb_desc_type, psb_sspmat_type, psb_spk_, & + & psb_ipk_, psb_long_int_k_, mld_sml_parms + implicit none + class(mld_s_base_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_sspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) + type(psb_sspmat_type), intent(inout) :: op_prol + type(psb_sspmat_type), intent(out) :: ac,op_restr + integer(psb_ipk_), intent(out) :: info + end subroutine mld_s_base_aggregator_mat_asb + end interface + +contains + + subroutine mld_s_base_aggregator_update_level(ag,agnext,info) + implicit none + class(mld_s_base_aggregator_type), target, intent(inout) :: ag, agnext + integer(psb_ipk_), intent(out) :: info + + ! + ! Base version does nothing. + ! + info = 0 + end subroutine mld_s_base_aggregator_update_level + + subroutine mld_s_base_aggregator_clone(ag,agnext,info) + implicit none + class(mld_s_base_aggregator_type), intent(inout) :: ag + class(mld_s_base_aggregator_type), allocatable, intent(inout) :: agnext + integer(psb_ipk_), intent(out) :: info + + info = 0 + if (allocated(agnext)) then + call agnext%free(info) + if (info == 0) deallocate(agnext,stat=info) + end if + if (info /= 0) return + allocate(agnext,source=ag,stat=info) + + end subroutine mld_s_base_aggregator_clone + + subroutine mld_s_base_aggregator_free(ag,info) + implicit none + class(mld_s_base_aggregator_type), intent(inout) :: ag + integer(psb_ipk_), intent(out) :: info + + info = psb_success_ + return + end subroutine mld_s_base_aggregator_free + + subroutine mld_s_base_aggregator_default(ag) + implicit none + class(mld_s_base_aggregator_type), intent(inout) :: ag + + ! Here we need do nothing + + return + end subroutine mld_s_base_aggregator_default + + function mld_s_base_aggregator_fmt() result(val) + implicit none + character(len=32) :: val + + val = "Decoupled aggregation" + end function mld_s_base_aggregator_fmt + + subroutine mld_s_base_aggregator_descr(ag,parms,iout,info) + implicit none + class(mld_s_base_aggregator_type), intent(in) :: ag + type(mld_sml_parms), intent(in) :: parms + integer(psb_ipk_), intent(in) :: iout + integer(psb_ipk_), intent(out) :: info + + call parms%mldescr(iout,info,aggr_name=ag%fmt()) + + return + end subroutine mld_s_base_aggregator_descr + +end module mld_s_base_aggregator_mod diff --git a/mlprec/mld_s_hybrid_aggregator_mod.F90 b/mlprec/mld_s_hybrid_aggregator_mod.F90 new file mode 100644 index 00000000..5db38098 --- /dev/null +++ b/mlprec/mld_s_hybrid_aggregator_mod.F90 @@ -0,0 +1,131 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. This variant is based on the hybrid method +! presented in +! +! S. Gratton, P. Henon, P. Jiranek and X. Vasseur: +! Reducing complexity of algebraic multigrid by aggregation +! Numerical Lin. Algebra with Applications, 2016, 23:501-518 +! +module mld_s_hybrid_aggregator_mod + + use mld_s_base_aggregator_mod + ! + ! sm - class(mld_T_base_smoother_type), allocatable + ! The current level preconditioner (aka smoother). + ! parms - type(mld_RTml_parms) + ! The parameters defining the multilevel strategy. + ! ac - The local part of the current-level matrix, built by + ! coarsening the previous-level matrix. + ! desc_ac - type(psb_desc_type). + ! The communication descriptor associated to the matrix + ! stored in ac. + ! base_a - type(psb_Tspmat_type), pointer. + ! Pointer (really a pointer!) to the local part of the current + ! matrix (so we have a unified treatment of residuals). + ! We need this to avoid passing explicitly the current matrix + ! to the routine which applies the preconditioner. + ! base_desc - type(psb_desc_type), pointer. + ! Pointer to the communication descriptor associated to the + ! matrix pointed by base_a. + ! map - Stores the maps (restriction and prolongation) between the + ! vector spaces associated to the index spaces of the previous + ! and current levels. + ! + ! Methods: + ! Most methods follow the encapsulation hierarchy: they take whatever action + ! is appropriate for the current object, then call the corresponding method for + ! the contained object. + ! As an example: the descr() method prints out a description of the + ! level. It starts by invoking the descr() method of the parms object, + ! then calls the descr() method of the smoother object. + ! + ! descr - Prints a description of the object. + ! default - Set default values + ! dump - Dump to file object contents + ! set - Sets various parameters; when a request is unknown + ! it is passed to the smoother object for further processing. + ! check - Sanity checks. + ! sizeof - Total memory occupation in bytes + ! get_nzeros - Number of nonzeros + ! + ! + type, extends(mld_s_base_aggregator_type) :: mld_s_hybrid_aggregator_type + + contains + procedure, pass(ag) :: bld_tprol => mld_s_hybrid_aggregator_build_tprol +!!$ procedure, pass(ag) :: mat_asb => mld_s_base_aggregator_mat_asb +!!$ procedure, pass(ag) :: update_level => mld_s_base_aggregator_update_level +!!$ procedure, pass(ag) :: clone => mld_s_base_aggregator_clone +!!$ procedure, pass(ag) :: free => mld_s_base_aggregator_free +!!$ procedure, pass(ag) :: default => mld_s_base_aggregator_default + procedure, nopass :: fmt => mld_s_hybrid_aggregator_fmt + end type mld_s_hybrid_aggregator_type + + + interface + subroutine mld_s_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: mld_s_hybrid_aggregator_type, psb_desc_type, psb_sspmat_type, psb_spk_, & + & psb_ipk_, psb_long_int_k_, mld_sml_parms + implicit none + class(mld_s_hybrid_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_sspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_sspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_s_hybrid_aggregator_build_tprol + end interface + +contains + + + function mld_s_hybrid_aggregator_fmt() result(val) + implicit none + character(len=32) :: val + + val = "Hybrid Decoupled aggregation" + end function mld_s_hybrid_aggregator_fmt + + +end module mld_s_hybrid_aggregator_mod diff --git a/mlprec/mld_s_inner_mod.f90 b/mlprec/mld_s_inner_mod.f90 index 581b943e..73baa6a8 100644 --- a/mlprec/mld_s_inner_mod.f90 +++ b/mlprec/mld_s_inner_mod.f90 @@ -137,6 +137,31 @@ module mld_s_inner_mod end subroutine mld_s_dec_map_bld end interface mld_dec_map_bld + interface mld_hyb_map_bld + subroutine mld_s_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + use psb_base_mod, only : psb_sspmat_type, psb_desc_type, psb_spk_, psb_ipk_ + implicit none + integer(psb_ipk_), intent(in) :: iorder + type(psb_sspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + real(psb_spk_), intent(in) :: theta + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + integer(psb_ipk_), intent(out) :: info + end subroutine mld_s_hyb_map_bld + end interface mld_hyb_map_bld + + interface mld_map_to_tprol + subroutine mld_s_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod, only : psb_sspmat_type, psb_desc_type, psb_spk_, psb_ipk_ + use mld_s_prec_type, only : mld_s_onelev_type + implicit none + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:) + type(psb_sspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_s_map_to_tprol + end interface mld_map_to_tprol + interface mld_lev_mat_asb subroutine mld_s_lev_aggrmat_asb(p,a,desc_a,ilaggr,nlaggr,op_prol,info) diff --git a/mlprec/mld_s_onelev_mod.f90 b/mlprec/mld_s_onelev_mod.f90 index e135b0f4..baba63cc 100644 --- a/mlprec/mld_s_onelev_mod.f90 +++ b/mlprec/mld_s_onelev_mod.f90 @@ -55,6 +55,7 @@ module mld_s_onelev_mod use mld_base_prec_type use mld_s_base_smoother_mod + use mld_s_base_aggregator_mod use psb_base_mod, only : psb_sspmat_type, psb_s_vect_type, & & psb_s_base_vect_type, psb_slinmap_type, psb_spk_, & & psb_ipk_, psb_long_int_k_, psb_desc_type, psb_i_base_vect_type, & @@ -136,9 +137,10 @@ module mld_s_onelev_mod & s_wrk_clone, s_wrk_move_alloc, s_wrk_cnv type mld_s_onelev_type - class(mld_s_base_smoother_type), allocatable :: sm, sm2a - class(mld_s_base_smoother_type), pointer :: sm2 => null() - class(mld_smlprec_wrk_type), allocatable :: wrk + class(mld_s_base_smoother_type), allocatable :: sm, sm2a + class(mld_s_base_smoother_type), pointer :: sm2 => null() + class(mld_smlprec_wrk_type), allocatable :: wrk + class(mld_s_base_aggregator_type), allocatable :: aggr type(mld_sml_parms) :: parms type(psb_sspmat_type) :: ac integer(psb_ipk_) :: ac_nz_loc, ac_nz_tot @@ -166,8 +168,9 @@ module mld_s_onelev_mod procedure, pass(lv) :: csetc => mld_s_base_onelev_csetc procedure, pass(lv) :: setsm => mld_s_base_onelev_setsm procedure, pass(lv) :: setsv => mld_s_base_onelev_setsv + procedure, pass(lv) :: setag => mld_s_base_onelev_setag generic, public :: set => seti, setr, setc, & - & cseti, csetr, csetc, setsm, setsv + & cseti, csetr, csetc, setsm, setsv, setag procedure, pass(lv) :: sizeof => s_base_onelev_sizeof procedure, pass(lv) :: get_nzeros => s_base_onelev_get_nzeros procedure, pass(lv) :: get_wrksz => s_base_onelev_get_wrksize @@ -299,6 +302,20 @@ module mld_s_onelev_mod end subroutine mld_s_base_onelev_setsv end interface + interface + subroutine mld_s_base_onelev_setag(lv,val,info,pos) + import :: psb_spk_, mld_s_onelev_type, mld_s_base_aggregator_type, & + & psb_ipk_, psb_long_int_k_, psb_desc_type + Implicit None + + ! Arguments + class(mld_s_onelev_type), target, intent(inout) :: lv + class(mld_s_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + character(len=*), optional, intent(in) :: pos + end subroutine mld_s_base_onelev_setag + end interface + interface subroutine mld_s_base_onelev_setc(lv,what,val,info,pos) import :: psb_sspmat_type, psb_s_vect_type, psb_s_base_vect_type, & @@ -323,9 +340,9 @@ module mld_s_onelev_mod class(mld_s_onelev_type), intent(inout) :: lv integer(psb_ipk_), intent(in) :: what - real(psb_spk_), intent(in) :: val + real(psb_spk_), intent(in) :: val integer(psb_ipk_), intent(out) :: info - character(len=*), optional, intent(in) :: pos + character(len=*), optional, intent(in) :: pos end subroutine mld_s_base_onelev_setr end interface @@ -450,7 +467,8 @@ contains Implicit None ! Arguments - class(mld_s_onelev_type), target, intent(inout) :: lv + class(mld_s_onelev_type), target, intent(inout) :: lv + integer(psb_ipk_) :: info lv%parms%sweeps_pre = 1 lv%parms%sweeps_post = 1 @@ -473,7 +491,9 @@ contains else lv%sm2 => lv%sm end if - + if (.not.allocated(lv%aggr)) allocate(mld_s_base_aggregator_type :: lv%aggr,stat=info) + if (allocated(lv%aggr)) call lv%aggr%default() + return end subroutine s_base_onelev_default @@ -508,6 +528,14 @@ contains end if lvout%sm2 => lvout%sm end if + if (allocated(lv%aggr)) then + call lv%aggr%clone(lvout%aggr,info) + else + if (allocated(lvout%aggr)) then + call lvout%aggr%free(info) + if (info==psb_success_) deallocate(lvout%aggr,stat=info) + end if + end if if (info == psb_success_) call lv%parms%clone(lvout%parms,info) if (info == psb_success_) call lv%ac%clone(lvout%ac,info) if (info == psb_success_) call lv%tprol%clone(lvout%tprol,info) @@ -538,8 +566,9 @@ contains call move_alloc(lv%sm2a,b%sm2a) b%sm2 =>b%sm end if - - if (info == psb_success_) call psb_move_alloc(lv%ac,b%ac,info) + + call move_alloc(lv%aggr,b%aggr) + if (info == psb_success_) call psb_move_alloc(lv%ac,b%ac,info) if (info == psb_success_) call psb_move_alloc(lv%tprol,b%tprol,info) if (info == psb_success_) call psb_move_alloc(lv%desc_ac,b%desc_ac,info) if (info == psb_success_) call psb_move_alloc(lv%map,b%map,info) diff --git a/mlprec/mld_s_prec_mod.f90 b/mlprec/mld_s_prec_mod.f90 index b7e35d27..27e9c75a 100644 --- a/mlprec/mld_s_prec_mod.f90 +++ b/mlprec/mld_s_prec_mod.f90 @@ -55,7 +55,8 @@ module mld_s_prec_mod interface mld_precset module procedure mld_s_iprecsetsm, mld_s_iprecsetsv, & & mld_s_iprecseti, mld_s_iprecsetc, mld_s_iprecsetr, & - & mld_s_cprecseti, mld_s_cprecsetc, mld_s_cprecsetr + & mld_s_cprecseti, mld_s_cprecsetc, mld_s_cprecsetr, & + & mld_s_iprecsetag end interface mld_precset interface mld_extprol_bld @@ -97,6 +98,14 @@ contains call p%set(val,info, pos=pos) end subroutine mld_s_iprecsetsv + subroutine mld_s_iprecsetag(p,val,info,pos) + type(mld_sprec_type), intent(inout) :: p + class(mld_s_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + character(len=*), optional, intent(in) :: pos + call p%set(val,info, pos=pos) + end subroutine mld_s_iprecsetag + subroutine mld_s_iprecseti(p,what,val,info,pos) type(mld_sprec_type), intent(inout) :: p integer(psb_ipk_), intent(in) :: what diff --git a/mlprec/mld_s_prec_type.f90 b/mlprec/mld_s_prec_type.f90 index 7b67ad66..a53c65e8 100644 --- a/mlprec/mld_s_prec_type.f90 +++ b/mlprec/mld_s_prec_type.f90 @@ -55,6 +55,7 @@ module mld_s_prec_type use mld_base_prec_type use mld_s_base_solver_mod use mld_s_base_smoother_mod + use mld_s_base_aggregator_mod use mld_s_onelev_mod use psb_prec_mod, only : psb_sprec_type @@ -92,8 +93,8 @@ module mld_s_prec_type ! 2. maximum number of levels. Defaults to 20 integer(psb_ipk_) :: max_levs = 20_psb_ipk_ ! 3. min_cr_ratio = 1.5 - real(psb_spk_) :: min_cr_ratio = 1.5_psb_spk_ - real(psb_spk_) :: op_complexity=szero + real(psb_spk_) :: min_cr_ratio = 1.5_psb_spk_ + real(psb_spk_) :: op_complexity = szero ! ! Number of outer sweeps. Sometimes 2 V-cycles may be better than 1 W-cycle. ! @@ -126,6 +127,7 @@ module mld_s_prec_type procedure, pass(prec) :: sizeof => mld_sprec_sizeof procedure, pass(prec) :: setsm => mld_sprecsetsm procedure, pass(prec) :: setsv => mld_sprecsetsv + procedure, pass(prec) :: setag => mld_sprecsetag procedure, pass(prec) :: seti => mld_sprecseti procedure, pass(prec) :: setc => mld_sprecsetc procedure, pass(prec) :: setr => mld_sprecsetr @@ -133,7 +135,7 @@ module mld_s_prec_type procedure, pass(prec) :: csetc => mld_scprecsetc procedure, pass(prec) :: csetr => mld_scprecsetr generic, public :: set => seti, setc, setr, & - & cseti, csetc, csetr, setsm, setsv + & cseti, csetc, csetr, setsm, setsv, setag procedure, pass(prec) :: get_smoother => mld_s_get_smootherp procedure, pass(prec) :: get_solver => mld_s_get_solverp procedure, pass(prec) :: move_alloc => s_prec_move_alloc @@ -234,6 +236,15 @@ module mld_s_prec_type integer(psb_ipk_), optional, intent(in) :: ilev,ilmax character(len=*), optional, intent(in) :: pos end subroutine mld_sprecsetsv + subroutine mld_sprecsetag(prec,val,info,ilev,pos) + import :: psb_sspmat_type, psb_desc_type, psb_spk_, & + & mld_sprec_type, mld_s_base_aggregator_type, psb_ipk_ + class(mld_sprec_type), intent(inout) :: prec + class(mld_s_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), optional, intent(in) :: ilev + character(len=*), optional, intent(in) :: pos + end subroutine mld_sprecsetag subroutine mld_sprecseti(prec,what,val,info,ilev,ilmax,pos) import :: psb_sspmat_type, psb_desc_type, psb_spk_, & & mld_sprec_type, psb_ipk_ diff --git a/mlprec/mld_s_symdec_aggregator_mod.f90 b/mlprec/mld_s_symdec_aggregator_mod.f90 new file mode 100644 index 00000000..fbc89303 --- /dev/null +++ b/mlprec/mld_s_symdec_aggregator_mod.f90 @@ -0,0 +1,128 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. This version only differs from the +! basic decoupled aggregation algorithm because it works on (the +! pattern of) A+A^T instead of A. +! +! M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +module mld_s_symdec_aggregator_mod + + use mld_s_base_aggregator_mod + ! + ! sm - class(mld_T_base_smoother_type), allocatable + ! The current level preconditioner (aka smoother). + ! parms - type(mld_RTml_parms) + ! The parameters defining the multilevel strategy. + ! ac - The local part of the current-level matrix, built by + ! coarsening the previous-level matrix. + ! desc_ac - type(psb_desc_type). + ! The communication descriptor associated to the matrix + ! stored in ac. + ! base_a - type(psb_Tspmat_type), pointer. + ! Pointer (really a pointer!) to the local part of the current + ! matrix (so we have a unified treatment of residuals). + ! We need this to avoid passing explicitly the current matrix + ! to the routine which applies the preconditioner. + ! base_desc - type(psb_desc_type), pointer. + ! Pointer to the communication descriptor associated to the + ! matrix pointed by base_a. + ! map - Stores the maps (restriction and prolongation) between the + ! vector spaces associated to the index spaces of the previous + ! and current levels. + ! + ! Methods: + ! Most methods follow the encapsulation hierarchy: they take whatever action + ! is appropriate for the current object, then call the corresponding method for + ! the contained object. + ! As an example: the descr() method prints out a description of the + ! level. It starts by invoking the descr() method of the parms object, + ! then calls the descr() method of the smoother object. + ! + ! descr - Prints a description of the object. + ! default - Set default values + ! dump - Dump to file object contents + ! set - Sets various parameters; when a request is unknown + ! it is passed to the smoother object for further processing. + ! check - Sanity checks. + ! sizeof - Total memory occupation in bytes + ! get_nzeros - Number of nonzeros + ! + ! + type, extends(mld_s_base_aggregator_type) :: mld_s_symdec_aggregator_type + + contains + procedure, pass(ag) :: tprol => mld_s_symdec_aggregator_build_tprol + procedure, nopass :: fmt => mld_s_symdec_aggregator_fmt + end type mld_s_symdec_aggregator_type + + + interface + subroutine mld_s_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: mld_s_symdec_aggregator_type, psb_desc_type, psb_sspmat_type, psb_spk_, & + & psb_ipk_, psb_long_int_k_, mld_sml_parms + implicit none + class(mld_s_symdec_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_sspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_sspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_s_symdec_aggregator_build_tprol + end interface + + +contains + + function mld_s_symdec_aggregator_fmt() result(val) + implicit none + character(len=32) :: val + + val = "Symmetric Decoupled aggregation" + end function mld_s_symdec_aggregator_fmt + +end module mld_s_symdec_aggregator_mod diff --git a/mlprec/mld_z_base_aggregator_mod.f90 b/mlprec/mld_z_base_aggregator_mod.f90 new file mode 100644 index 00000000..6f3a8096 --- /dev/null +++ b/mlprec/mld_z_base_aggregator_mod.f90 @@ -0,0 +1,209 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. The basic version is the +! decoupled aggregation algorithm presented in +! +! M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +module mld_z_base_aggregator_mod + + use mld_base_prec_type, only : mld_dml_parms + use psb_base_mod, only : psb_zspmat_type, psb_z_vect_type, & + & psb_z_base_vect_type, psb_zlinmap_type, psb_dpk_, & + & psb_ipk_, psb_long_int_k_, psb_desc_type, psb_i_base_vect_type, & + & psb_erractionsave, psb_error_handler, psb_success_ + ! + ! sm - class(mld_T_base_smoother_type), allocatable + ! The current level preconditioner (aka smoother). + ! parms - type(mld_RTml_parms) + ! The parameters defining the multilevel strategy. + ! ac - The local part of the current-level matrix, built by + ! coarsening the previous-level matrix. + ! desc_ac - type(psb_desc_type). + ! The communication descriptor associated to the matrix + ! stored in ac. + ! base_a - type(psb_Tspmat_type), pointer. + ! Pointer (really a pointer!) to the local part of the current + ! matrix (so we have a unified treatment of residuals). + ! We need this to avoid passing explicitly the current matrix + ! to the routine which applies the preconditioner. + ! base_desc - type(psb_desc_type), pointer. + ! Pointer to the communication descriptor associated to the + ! matrix pointed by base_a. + ! map - Stores the maps (restriction and prolongation) between the + ! vector spaces associated to the index spaces of the previous + ! and current levels. + ! + ! Methods: + ! Most methods follow the encapsulation hierarchy: they take whatever action + ! is appropriate for the current object, then call the corresponding method for + ! the contained object. + ! As an example: the descr() method prints out a description of the + ! level. It starts by invoking the descr() method of the parms object, + ! then calls the descr() method of the smoother object. + ! + ! descr - Prints a description of the object. + ! default - Set default values + ! dump - Dump to file object contents + ! set - Sets various parameters; when a request is unknown + ! it is passed to the smoother object for further processing. + ! check - Sanity checks. + ! sizeof - Total memory occupation in bytes + ! get_nzeros - Number of nonzeros + ! + ! + type mld_z_base_aggregator_type + + contains + procedure, pass(ag) :: bld_tprol => mld_z_base_aggregator_build_tprol + procedure, pass(ag) :: mat_asb => mld_z_base_aggregator_mat_asb + procedure, pass(ag) :: update_level => mld_z_base_aggregator_update_level + procedure, pass(ag) :: clone => mld_z_base_aggregator_clone + procedure, pass(ag) :: free => mld_z_base_aggregator_free + procedure, pass(ag) :: default => mld_z_base_aggregator_default + procedure, pass(ag) :: descr => mld_z_base_aggregator_descr + procedure, nopass :: fmt => mld_z_base_aggregator_fmt + end type mld_z_base_aggregator_type + + + interface + subroutine mld_z_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: mld_z_base_aggregator_type, psb_desc_type, psb_zspmat_type, psb_dpk_, & + & psb_ipk_, psb_long_int_k_, mld_dml_parms + implicit none + class(mld_z_base_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_zspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_zspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_z_base_aggregator_build_tprol + end interface + + interface + subroutine mld_z_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,& + & op_prol,op_restr,info) + import :: mld_z_base_aggregator_type, psb_desc_type, psb_zspmat_type, psb_dpk_, & + & psb_ipk_, psb_long_int_k_, mld_dml_parms + implicit none + class(mld_z_base_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_zspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) + type(psb_zspmat_type), intent(inout) :: op_prol + type(psb_zspmat_type), intent(out) :: ac,op_restr + integer(psb_ipk_), intent(out) :: info + end subroutine mld_z_base_aggregator_mat_asb + end interface + +contains + + subroutine mld_z_base_aggregator_update_level(ag,agnext,info) + implicit none + class(mld_z_base_aggregator_type), target, intent(inout) :: ag, agnext + integer(psb_ipk_), intent(out) :: info + + ! + ! Base version does nothing. + ! + info = 0 + end subroutine mld_z_base_aggregator_update_level + + subroutine mld_z_base_aggregator_clone(ag,agnext,info) + implicit none + class(mld_z_base_aggregator_type), intent(inout) :: ag + class(mld_z_base_aggregator_type), allocatable, intent(inout) :: agnext + integer(psb_ipk_), intent(out) :: info + + info = 0 + if (allocated(agnext)) then + call agnext%free(info) + if (info == 0) deallocate(agnext,stat=info) + end if + if (info /= 0) return + allocate(agnext,source=ag,stat=info) + + end subroutine mld_z_base_aggregator_clone + + subroutine mld_z_base_aggregator_free(ag,info) + implicit none + class(mld_z_base_aggregator_type), intent(inout) :: ag + integer(psb_ipk_), intent(out) :: info + + info = psb_success_ + return + end subroutine mld_z_base_aggregator_free + + subroutine mld_z_base_aggregator_default(ag) + implicit none + class(mld_z_base_aggregator_type), intent(inout) :: ag + + ! Here we need do nothing + + return + end subroutine mld_z_base_aggregator_default + + function mld_z_base_aggregator_fmt() result(val) + implicit none + character(len=32) :: val + + val = "Decoupled aggregation" + end function mld_z_base_aggregator_fmt + + subroutine mld_z_base_aggregator_descr(ag,parms,iout,info) + implicit none + class(mld_z_base_aggregator_type), intent(in) :: ag + type(mld_dml_parms), intent(in) :: parms + integer(psb_ipk_), intent(in) :: iout + integer(psb_ipk_), intent(out) :: info + + call parms%mldescr(iout,info,aggr_name=ag%fmt()) + + return + end subroutine mld_z_base_aggregator_descr + +end module mld_z_base_aggregator_mod diff --git a/mlprec/mld_z_hybrid_aggregator_mod.F90 b/mlprec/mld_z_hybrid_aggregator_mod.F90 new file mode 100644 index 00000000..be353fc4 --- /dev/null +++ b/mlprec/mld_z_hybrid_aggregator_mod.F90 @@ -0,0 +1,131 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. This variant is based on the hybrid method +! presented in +! +! S. Gratton, P. Henon, P. Jiranek and X. Vasseur: +! Reducing complexity of algebraic multigrid by aggregation +! Numerical Lin. Algebra with Applications, 2016, 23:501-518 +! +module mld_z_hybrid_aggregator_mod + + use mld_z_base_aggregator_mod + ! + ! sm - class(mld_T_base_smoother_type), allocatable + ! The current level preconditioner (aka smoother). + ! parms - type(mld_RTml_parms) + ! The parameters defining the multilevel strategy. + ! ac - The local part of the current-level matrix, built by + ! coarsening the previous-level matrix. + ! desc_ac - type(psb_desc_type). + ! The communication descriptor associated to the matrix + ! stored in ac. + ! base_a - type(psb_Tspmat_type), pointer. + ! Pointer (really a pointer!) to the local part of the current + ! matrix (so we have a unified treatment of residuals). + ! We need this to avoid passing explicitly the current matrix + ! to the routine which applies the preconditioner. + ! base_desc - type(psb_desc_type), pointer. + ! Pointer to the communication descriptor associated to the + ! matrix pointed by base_a. + ! map - Stores the maps (restriction and prolongation) between the + ! vector spaces associated to the index spaces of the previous + ! and current levels. + ! + ! Methods: + ! Most methods follow the encapsulation hierarchy: they take whatever action + ! is appropriate for the current object, then call the corresponding method for + ! the contained object. + ! As an example: the descr() method prints out a description of the + ! level. It starts by invoking the descr() method of the parms object, + ! then calls the descr() method of the smoother object. + ! + ! descr - Prints a description of the object. + ! default - Set default values + ! dump - Dump to file object contents + ! set - Sets various parameters; when a request is unknown + ! it is passed to the smoother object for further processing. + ! check - Sanity checks. + ! sizeof - Total memory occupation in bytes + ! get_nzeros - Number of nonzeros + ! + ! + type, extends(mld_z_base_aggregator_type) :: mld_z_hybrid_aggregator_type + + contains + procedure, pass(ag) :: bld_tprol => mld_z_hybrid_aggregator_build_tprol +!!$ procedure, pass(ag) :: mat_asb => mld_z_base_aggregator_mat_asb +!!$ procedure, pass(ag) :: update_level => mld_z_base_aggregator_update_level +!!$ procedure, pass(ag) :: clone => mld_z_base_aggregator_clone +!!$ procedure, pass(ag) :: free => mld_z_base_aggregator_free +!!$ procedure, pass(ag) :: default => mld_z_base_aggregator_default + procedure, nopass :: fmt => mld_z_hybrid_aggregator_fmt + end type mld_z_hybrid_aggregator_type + + + interface + subroutine mld_z_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: mld_z_hybrid_aggregator_type, psb_desc_type, psb_zspmat_type, psb_dpk_, & + & psb_ipk_, psb_long_int_k_, mld_dml_parms + implicit none + class(mld_z_hybrid_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_zspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_zspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_z_hybrid_aggregator_build_tprol + end interface + +contains + + + function mld_z_hybrid_aggregator_fmt() result(val) + implicit none + character(len=32) :: val + + val = "Hybrid Decoupled aggregation" + end function mld_z_hybrid_aggregator_fmt + + +end module mld_z_hybrid_aggregator_mod diff --git a/mlprec/mld_z_inner_mod.f90 b/mlprec/mld_z_inner_mod.f90 index 12860b7b..e6dcf6ee 100644 --- a/mlprec/mld_z_inner_mod.f90 +++ b/mlprec/mld_z_inner_mod.f90 @@ -137,6 +137,31 @@ module mld_z_inner_mod end subroutine mld_z_dec_map_bld end interface mld_dec_map_bld + interface mld_hyb_map_bld + subroutine mld_z_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + use psb_base_mod, only : psb_zspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ + implicit none + integer(psb_ipk_), intent(in) :: iorder + type(psb_zspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + real(psb_dpk_), intent(in) :: theta + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + integer(psb_ipk_), intent(out) :: info + end subroutine mld_z_hyb_map_bld + end interface mld_hyb_map_bld + + interface mld_map_to_tprol + subroutine mld_z_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod, only : psb_zspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ + use mld_z_prec_type, only : mld_z_onelev_type + implicit none + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:) + type(psb_zspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_z_map_to_tprol + end interface mld_map_to_tprol + interface mld_lev_mat_asb subroutine mld_z_lev_aggrmat_asb(p,a,desc_a,ilaggr,nlaggr,op_prol,info) diff --git a/mlprec/mld_z_onelev_mod.f90 b/mlprec/mld_z_onelev_mod.f90 index 986ea076..be8eaaf3 100644 --- a/mlprec/mld_z_onelev_mod.f90 +++ b/mlprec/mld_z_onelev_mod.f90 @@ -55,6 +55,7 @@ module mld_z_onelev_mod use mld_base_prec_type use mld_z_base_smoother_mod + use mld_z_base_aggregator_mod use psb_base_mod, only : psb_zspmat_type, psb_z_vect_type, & & psb_z_base_vect_type, psb_zlinmap_type, psb_dpk_, & & psb_ipk_, psb_long_int_k_, psb_desc_type, psb_i_base_vect_type, & @@ -136,9 +137,10 @@ module mld_z_onelev_mod & z_wrk_clone, z_wrk_move_alloc, z_wrk_cnv type mld_z_onelev_type - class(mld_z_base_smoother_type), allocatable :: sm, sm2a - class(mld_z_base_smoother_type), pointer :: sm2 => null() - class(mld_zmlprec_wrk_type), allocatable :: wrk + class(mld_z_base_smoother_type), allocatable :: sm, sm2a + class(mld_z_base_smoother_type), pointer :: sm2 => null() + class(mld_zmlprec_wrk_type), allocatable :: wrk + class(mld_z_base_aggregator_type), allocatable :: aggr type(mld_dml_parms) :: parms type(psb_zspmat_type) :: ac integer(psb_ipk_) :: ac_nz_loc, ac_nz_tot @@ -166,8 +168,9 @@ module mld_z_onelev_mod procedure, pass(lv) :: csetc => mld_z_base_onelev_csetc procedure, pass(lv) :: setsm => mld_z_base_onelev_setsm procedure, pass(lv) :: setsv => mld_z_base_onelev_setsv + procedure, pass(lv) :: setag => mld_z_base_onelev_setag generic, public :: set => seti, setr, setc, & - & cseti, csetr, csetc, setsm, setsv + & cseti, csetr, csetc, setsm, setsv, setag procedure, pass(lv) :: sizeof => z_base_onelev_sizeof procedure, pass(lv) :: get_nzeros => z_base_onelev_get_nzeros procedure, pass(lv) :: get_wrksz => z_base_onelev_get_wrksize @@ -299,6 +302,20 @@ module mld_z_onelev_mod end subroutine mld_z_base_onelev_setsv end interface + interface + subroutine mld_z_base_onelev_setag(lv,val,info,pos) + import :: psb_dpk_, mld_z_onelev_type, mld_z_base_aggregator_type, & + & psb_ipk_, psb_long_int_k_, psb_desc_type + Implicit None + + ! Arguments + class(mld_z_onelev_type), target, intent(inout) :: lv + class(mld_z_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + character(len=*), optional, intent(in) :: pos + end subroutine mld_z_base_onelev_setag + end interface + interface subroutine mld_z_base_onelev_setc(lv,what,val,info,pos) import :: psb_zspmat_type, psb_z_vect_type, psb_z_base_vect_type, & @@ -323,9 +340,9 @@ module mld_z_onelev_mod class(mld_z_onelev_type), intent(inout) :: lv integer(psb_ipk_), intent(in) :: what - real(psb_dpk_), intent(in) :: val + real(psb_dpk_), intent(in) :: val integer(psb_ipk_), intent(out) :: info - character(len=*), optional, intent(in) :: pos + character(len=*), optional, intent(in) :: pos end subroutine mld_z_base_onelev_setr end interface @@ -450,7 +467,8 @@ contains Implicit None ! Arguments - class(mld_z_onelev_type), target, intent(inout) :: lv + class(mld_z_onelev_type), target, intent(inout) :: lv + integer(psb_ipk_) :: info lv%parms%sweeps_pre = 1 lv%parms%sweeps_post = 1 @@ -473,7 +491,9 @@ contains else lv%sm2 => lv%sm end if - + if (.not.allocated(lv%aggr)) allocate(mld_z_base_aggregator_type :: lv%aggr,stat=info) + if (allocated(lv%aggr)) call lv%aggr%default() + return end subroutine z_base_onelev_default @@ -508,6 +528,14 @@ contains end if lvout%sm2 => lvout%sm end if + if (allocated(lv%aggr)) then + call lv%aggr%clone(lvout%aggr,info) + else + if (allocated(lvout%aggr)) then + call lvout%aggr%free(info) + if (info==psb_success_) deallocate(lvout%aggr,stat=info) + end if + end if if (info == psb_success_) call lv%parms%clone(lvout%parms,info) if (info == psb_success_) call lv%ac%clone(lvout%ac,info) if (info == psb_success_) call lv%tprol%clone(lvout%tprol,info) @@ -538,8 +566,9 @@ contains call move_alloc(lv%sm2a,b%sm2a) b%sm2 =>b%sm end if - - if (info == psb_success_) call psb_move_alloc(lv%ac,b%ac,info) + + call move_alloc(lv%aggr,b%aggr) + if (info == psb_success_) call psb_move_alloc(lv%ac,b%ac,info) if (info == psb_success_) call psb_move_alloc(lv%tprol,b%tprol,info) if (info == psb_success_) call psb_move_alloc(lv%desc_ac,b%desc_ac,info) if (info == psb_success_) call psb_move_alloc(lv%map,b%map,info) diff --git a/mlprec/mld_z_prec_mod.f90 b/mlprec/mld_z_prec_mod.f90 index 1c094a84..374a41b2 100644 --- a/mlprec/mld_z_prec_mod.f90 +++ b/mlprec/mld_z_prec_mod.f90 @@ -55,7 +55,8 @@ module mld_z_prec_mod interface mld_precset module procedure mld_z_iprecsetsm, mld_z_iprecsetsv, & & mld_z_iprecseti, mld_z_iprecsetc, mld_z_iprecsetr, & - & mld_z_cprecseti, mld_z_cprecsetc, mld_z_cprecsetr + & mld_z_cprecseti, mld_z_cprecsetc, mld_z_cprecsetr, & + & mld_z_iprecsetag end interface mld_precset interface mld_extprol_bld @@ -97,6 +98,14 @@ contains call p%set(val,info, pos=pos) end subroutine mld_z_iprecsetsv + subroutine mld_z_iprecsetag(p,val,info,pos) + type(mld_zprec_type), intent(inout) :: p + class(mld_z_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + character(len=*), optional, intent(in) :: pos + call p%set(val,info, pos=pos) + end subroutine mld_z_iprecsetag + subroutine mld_z_iprecseti(p,what,val,info,pos) type(mld_zprec_type), intent(inout) :: p integer(psb_ipk_), intent(in) :: what diff --git a/mlprec/mld_z_prec_type.f90 b/mlprec/mld_z_prec_type.f90 index 39b11f96..3def4f30 100644 --- a/mlprec/mld_z_prec_type.f90 +++ b/mlprec/mld_z_prec_type.f90 @@ -55,6 +55,7 @@ module mld_z_prec_type use mld_base_prec_type use mld_z_base_solver_mod use mld_z_base_smoother_mod + use mld_z_base_aggregator_mod use mld_z_onelev_mod use psb_prec_mod, only : psb_zprec_type @@ -92,8 +93,8 @@ module mld_z_prec_type ! 2. maximum number of levels. Defaults to 20 integer(psb_ipk_) :: max_levs = 20_psb_ipk_ ! 3. min_cr_ratio = 1.5 - real(psb_dpk_) :: min_cr_ratio = 1.5_psb_dpk_ - real(psb_dpk_) :: op_complexity=dzero + real(psb_dpk_) :: min_cr_ratio = 1.5_psb_dpk_ + real(psb_dpk_) :: op_complexity = dzero ! ! Number of outer sweeps. Sometimes 2 V-cycles may be better than 1 W-cycle. ! @@ -126,6 +127,7 @@ module mld_z_prec_type procedure, pass(prec) :: sizeof => mld_zprec_sizeof procedure, pass(prec) :: setsm => mld_zprecsetsm procedure, pass(prec) :: setsv => mld_zprecsetsv + procedure, pass(prec) :: setag => mld_zprecsetag procedure, pass(prec) :: seti => mld_zprecseti procedure, pass(prec) :: setc => mld_zprecsetc procedure, pass(prec) :: setr => mld_zprecsetr @@ -133,7 +135,7 @@ module mld_z_prec_type procedure, pass(prec) :: csetc => mld_zcprecsetc procedure, pass(prec) :: csetr => mld_zcprecsetr generic, public :: set => seti, setc, setr, & - & cseti, csetc, csetr, setsm, setsv + & cseti, csetc, csetr, setsm, setsv, setag procedure, pass(prec) :: get_smoother => mld_z_get_smootherp procedure, pass(prec) :: get_solver => mld_z_get_solverp procedure, pass(prec) :: move_alloc => z_prec_move_alloc @@ -234,6 +236,15 @@ module mld_z_prec_type integer(psb_ipk_), optional, intent(in) :: ilev,ilmax character(len=*), optional, intent(in) :: pos end subroutine mld_zprecsetsv + subroutine mld_zprecsetag(prec,val,info,ilev,pos) + import :: psb_zspmat_type, psb_desc_type, psb_dpk_, & + & mld_zprec_type, mld_z_base_aggregator_type, psb_ipk_ + class(mld_zprec_type), intent(inout) :: prec + class(mld_z_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), optional, intent(in) :: ilev + character(len=*), optional, intent(in) :: pos + end subroutine mld_zprecsetag subroutine mld_zprecseti(prec,what,val,info,ilev,ilmax,pos) import :: psb_zspmat_type, psb_desc_type, psb_dpk_, & & mld_zprec_type, psb_ipk_ diff --git a/mlprec/mld_z_symdec_aggregator_mod.f90 b/mlprec/mld_z_symdec_aggregator_mod.f90 new file mode 100644 index 00000000..f1f08e7d --- /dev/null +++ b/mlprec/mld_z_symdec_aggregator_mod.f90 @@ -0,0 +1,128 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. This version only differs from the +! basic decoupled aggregation algorithm because it works on (the +! pattern of) A+A^T instead of A. +! +! M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +module mld_z_symdec_aggregator_mod + + use mld_z_base_aggregator_mod + ! + ! sm - class(mld_T_base_smoother_type), allocatable + ! The current level preconditioner (aka smoother). + ! parms - type(mld_RTml_parms) + ! The parameters defining the multilevel strategy. + ! ac - The local part of the current-level matrix, built by + ! coarsening the previous-level matrix. + ! desc_ac - type(psb_desc_type). + ! The communication descriptor associated to the matrix + ! stored in ac. + ! base_a - type(psb_Tspmat_type), pointer. + ! Pointer (really a pointer!) to the local part of the current + ! matrix (so we have a unified treatment of residuals). + ! We need this to avoid passing explicitly the current matrix + ! to the routine which applies the preconditioner. + ! base_desc - type(psb_desc_type), pointer. + ! Pointer to the communication descriptor associated to the + ! matrix pointed by base_a. + ! map - Stores the maps (restriction and prolongation) between the + ! vector spaces associated to the index spaces of the previous + ! and current levels. + ! + ! Methods: + ! Most methods follow the encapsulation hierarchy: they take whatever action + ! is appropriate for the current object, then call the corresponding method for + ! the contained object. + ! As an example: the descr() method prints out a description of the + ! level. It starts by invoking the descr() method of the parms object, + ! then calls the descr() method of the smoother object. + ! + ! descr - Prints a description of the object. + ! default - Set default values + ! dump - Dump to file object contents + ! set - Sets various parameters; when a request is unknown + ! it is passed to the smoother object for further processing. + ! check - Sanity checks. + ! sizeof - Total memory occupation in bytes + ! get_nzeros - Number of nonzeros + ! + ! + type, extends(mld_z_base_aggregator_type) :: mld_z_symdec_aggregator_type + + contains + procedure, pass(ag) :: tprol => mld_z_symdec_aggregator_build_tprol + procedure, nopass :: fmt => mld_z_symdec_aggregator_fmt + end type mld_z_symdec_aggregator_type + + + interface + subroutine mld_z_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: mld_z_symdec_aggregator_type, psb_desc_type, psb_zspmat_type, psb_dpk_, & + & psb_ipk_, psb_long_int_k_, mld_dml_parms + implicit none + class(mld_z_symdec_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_zspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_zspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_z_symdec_aggregator_build_tprol + end interface + + +contains + + function mld_z_symdec_aggregator_fmt() result(val) + implicit none + character(len=32) :: val + + val = "Symmetric Decoupled aggregation" + end function mld_z_symdec_aggregator_fmt + +end module mld_z_symdec_aggregator_mod From 6ccb787857530020d314588f14bb4ddd9541352c Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 4 May 2018 16:18:36 +0100 Subject: [PATCH 10/33] Created aggregator subdir. --- mlprec/impl/Makefile | 30 +- mlprec/impl/aggregator/Makefile | 61 ++++ .../mld_c_base_aggregator_mat_asb.f90 | 225 ++++++++++++ .../mld_c_base_aggregator_tprol.f90 | 124 +++++++ .../{ => aggregator}/mld_c_dec_map_bld.f90 | 0 mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 | 328 ++++++++++++++++++ .../mld_c_hybrid_aggregator_tprol.f90 | 122 +++++++ mlprec/impl/aggregator/mld_c_map_to_tprol.f90 | 150 ++++++++ .../mld_c_symdec_aggregator_tprol.f90 | 141 ++++++++ .../{ => aggregator}/mld_caggrmat_biz_asb.f90 | 0 .../mld_caggrmat_minnrg_asb.f90 | 0 .../mld_caggrmat_nosmth_asb.f90 | 0 .../mld_caggrmat_smth_asb.f90 | 0 .../mld_d_base_aggregator_mat_asb.f90 | 225 ++++++++++++ .../mld_d_base_aggregator_tprol.f90 | 124 +++++++ .../{ => aggregator}/mld_d_dec_map_bld.f90 | 0 mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 | 328 ++++++++++++++++++ .../mld_d_hybrid_aggregator_tprol.f90 | 122 +++++++ mlprec/impl/aggregator/mld_d_map_to_tprol.f90 | 150 ++++++++ .../mld_d_symdec_aggregator_tprol.f90 | 141 ++++++++ .../{ => aggregator}/mld_daggrmat_biz_asb.f90 | 0 .../mld_daggrmat_minnrg_asb.f90 | 0 .../mld_daggrmat_nosmth_asb.f90 | 0 .../mld_daggrmat_smth_asb.f90 | 0 .../mld_s_base_aggregator_mat_asb.f90 | 225 ++++++++++++ .../mld_s_base_aggregator_tprol.f90 | 124 +++++++ .../{ => aggregator}/mld_s_dec_map_bld.f90 | 0 mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 | 328 ++++++++++++++++++ .../mld_s_hybrid_aggregator_tprol.f90 | 122 +++++++ mlprec/impl/aggregator/mld_s_map_to_tprol.f90 | 150 ++++++++ .../mld_s_symdec_aggregator_tprol.f90 | 141 ++++++++ .../{ => aggregator}/mld_saggrmat_biz_asb.f90 | 0 .../mld_saggrmat_minnrg_asb.f90 | 0 .../mld_saggrmat_nosmth_asb.f90 | 0 .../mld_saggrmat_smth_asb.f90 | 0 .../mld_z_base_aggregator_mat_asb.f90 | 225 ++++++++++++ .../mld_z_base_aggregator_tprol.f90 | 124 +++++++ .../{ => aggregator}/mld_z_dec_map_bld.f90 | 0 mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 | 328 ++++++++++++++++++ .../mld_z_hybrid_aggregator_tprol.f90 | 122 +++++++ mlprec/impl/aggregator/mld_z_map_to_tprol.f90 | 150 ++++++++ .../mld_z_symdec_aggregator_tprol.f90 | 141 ++++++++ .../{ => aggregator}/mld_zaggrmat_biz_asb.f90 | 0 .../mld_zaggrmat_minnrg_asb.f90 | 0 .../mld_zaggrmat_nosmth_asb.f90 | 0 .../mld_zaggrmat_smth_asb.f90 | 0 46 files changed, 4436 insertions(+), 15 deletions(-) create mode 100644 mlprec/impl/aggregator/Makefile create mode 100644 mlprec/impl/aggregator/mld_c_base_aggregator_mat_asb.f90 create mode 100644 mlprec/impl/aggregator/mld_c_base_aggregator_tprol.f90 rename mlprec/impl/{ => aggregator}/mld_c_dec_map_bld.f90 (100%) create mode 100644 mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 create mode 100644 mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 create mode 100644 mlprec/impl/aggregator/mld_c_map_to_tprol.f90 create mode 100644 mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 rename mlprec/impl/{ => aggregator}/mld_caggrmat_biz_asb.f90 (100%) rename mlprec/impl/{ => aggregator}/mld_caggrmat_minnrg_asb.f90 (100%) rename mlprec/impl/{ => aggregator}/mld_caggrmat_nosmth_asb.f90 (100%) rename mlprec/impl/{ => aggregator}/mld_caggrmat_smth_asb.f90 (100%) create mode 100644 mlprec/impl/aggregator/mld_d_base_aggregator_mat_asb.f90 create mode 100644 mlprec/impl/aggregator/mld_d_base_aggregator_tprol.f90 rename mlprec/impl/{ => aggregator}/mld_d_dec_map_bld.f90 (100%) create mode 100644 mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 create mode 100644 mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 create mode 100644 mlprec/impl/aggregator/mld_d_map_to_tprol.f90 create mode 100644 mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 rename mlprec/impl/{ => aggregator}/mld_daggrmat_biz_asb.f90 (100%) rename mlprec/impl/{ => aggregator}/mld_daggrmat_minnrg_asb.f90 (100%) rename mlprec/impl/{ => aggregator}/mld_daggrmat_nosmth_asb.f90 (100%) rename mlprec/impl/{ => aggregator}/mld_daggrmat_smth_asb.f90 (100%) create mode 100644 mlprec/impl/aggregator/mld_s_base_aggregator_mat_asb.f90 create mode 100644 mlprec/impl/aggregator/mld_s_base_aggregator_tprol.f90 rename mlprec/impl/{ => aggregator}/mld_s_dec_map_bld.f90 (100%) create mode 100644 mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 create mode 100644 mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 create mode 100644 mlprec/impl/aggregator/mld_s_map_to_tprol.f90 create mode 100644 mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 rename mlprec/impl/{ => aggregator}/mld_saggrmat_biz_asb.f90 (100%) rename mlprec/impl/{ => aggregator}/mld_saggrmat_minnrg_asb.f90 (100%) rename mlprec/impl/{ => aggregator}/mld_saggrmat_nosmth_asb.f90 (100%) rename mlprec/impl/{ => aggregator}/mld_saggrmat_smth_asb.f90 (100%) create mode 100644 mlprec/impl/aggregator/mld_z_base_aggregator_mat_asb.f90 create mode 100644 mlprec/impl/aggregator/mld_z_base_aggregator_tprol.f90 rename mlprec/impl/{ => aggregator}/mld_z_dec_map_bld.f90 (100%) create mode 100644 mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 create mode 100644 mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 create mode 100644 mlprec/impl/aggregator/mld_z_map_to_tprol.f90 create mode 100644 mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 rename mlprec/impl/{ => aggregator}/mld_zaggrmat_biz_asb.f90 (100%) rename mlprec/impl/{ => aggregator}/mld_zaggrmat_minnrg_asb.f90 (100%) rename mlprec/impl/{ => aggregator}/mld_zaggrmat_nosmth_asb.f90 (100%) rename mlprec/impl/{ => aggregator}/mld_zaggrmat_smth_asb.f90 (100%) diff --git a/mlprec/impl/Makefile b/mlprec/impl/Makefile index a2c35c31..9a0d92bf 100644 --- a/mlprec/impl/Makefile +++ b/mlprec/impl/Makefile @@ -8,13 +8,13 @@ FINCLUDES=$(FMFLAG)$(HERE) $(FMFLAG)$(MODDIR) $(FMFLAG)$(INCDIR) $(PSBLAS_INCLUD -DMPFOBJS=mld_daggrmat_nosmth_asb.o mld_daggrmat_smth_asb.o mld_daggrmat_minnrg_asb.o mld_daggrmat_biz_asb.o +DMPFOBJS= -SMPFOBJS=mld_saggrmat_nosmth_asb.o mld_saggrmat_smth_asb.o mld_saggrmat_minnrg_asb.o mld_saggrmat_biz_asb.o +SMPFOBJS= -ZMPFOBJS=mld_zaggrmat_nosmth_asb.o mld_zaggrmat_smth_asb.o mld_zaggrmat_minnrg_asb.o mld_zaggrmat_biz_asb.o +ZMPFOBJS= -CMPFOBJS=mld_caggrmat_nosmth_asb.o mld_caggrmat_smth_asb.o mld_caggrmat_minnrg_asb.o mld_caggrmat_biz_asb.o +CMPFOBJS= MPFOBJS=$(SMPFOBJS) $(DMPFOBJS) $(CMPFOBJS) $(ZMPFOBJS) @@ -24,26 +24,22 @@ MPCOBJS=mld_dslud_interface.o mld_zslud_interface.o DINNEROBJS= mld_dmlprec_bld.o mld_dfile_prec_descr.o \ mld_d_smoothers_bld.o mld_d_hierarchy_bld.o \ - mld_daggrmap_bld.o \ - mld_d_dec_map_bld.o mld_dmlprec_aply.o mld_daggrmat_asb.o \ - $(DMPFOBJS) mld_d_extprol_bld.o mld_d_lev_aggrmap_bld.o mld_d_lev_aggrmat_asb.o + mld_dmlprec_aply.o \ + $(DMPFOBJS) mld_d_extprol_bld.o mld_d_lev_aggrmap_bld.o mld_d_lev_aggrmat_asb.o SINNEROBJS= mld_smlprec_bld.o mld_sfile_prec_descr.o \ mld_s_smoothers_bld.o mld_s_hierarchy_bld.o \ - mld_saggrmap_bld.o \ - mld_s_dec_map_bld.o mld_smlprec_aply.o mld_saggrmat_asb.o \ + mld_smlprec_aply.o \ $(SMPFOBJS) mld_s_extprol_bld.o mld_s_lev_aggrmap_bld.o mld_s_lev_aggrmat_asb.o ZINNEROBJS= mld_zmlprec_bld.o mld_zfile_prec_descr.o \ mld_z_smoothers_bld.o mld_z_hierarchy_bld.o \ - mld_zaggrmap_bld.o \ - mld_z_dec_map_bld.o mld_zmlprec_aply.o mld_zaggrmat_asb.o \ + mld_zmlprec_aply.o \ $(ZMPFOBJS) mld_z_extprol_bld.o mld_z_lev_aggrmap_bld.o mld_z_lev_aggrmat_asb.o CINNEROBJS= mld_cmlprec_bld.o mld_cfile_prec_descr.o \ mld_c_smoothers_bld.o mld_c_hierarchy_bld.o \ - mld_caggrmap_bld.o \ - mld_c_dec_map_bld.o mld_cmlprec_aply.o mld_caggrmat_asb.o \ + mld_cmlprec_aply.o \ $(CMPFOBJS) mld_c_extprol_bld.o mld_c_lev_aggrmap_bld.o mld_c_lev_aggrmat_asb.o INNEROBJS= $(SINNEROBJS) $(DINNEROBJS) $(CINNEROBJS) $(ZINNEROBJS) @@ -71,10 +67,12 @@ OBJS=$(F90OBJS) $(COBJS) $(MPCOBJS) LIBNAME=libmld_prec.a -lib: $(OBJS) levd smoothd solvd +lib: $(OBJS) levd smoothd solvd aggrd $(AR) $(HERE)/$(LIBNAME) $(OBJS) $(RANLIB) $(HERE)/$(LIBNAME) +aggrd: + cd aggregator && $(MAKE) levd: cd level && $(MAKE) smoothd: @@ -89,9 +87,11 @@ mpobjs: veryclean: clean /bin/rm -f $(LIBNAME) -clean: solvclean smoothclean levclean +clean: solvclean smoothclean levclean aggrclean /bin/rm -f $(OBJS) $(LOCAL_MODS) +aggrclean: + cd aggregator && $(MAKE) clean levclean: cd level && $(MAKE) clean smoothclean: diff --git a/mlprec/impl/aggregator/Makefile b/mlprec/impl/aggregator/Makefile new file mode 100644 index 00000000..762e09eb --- /dev/null +++ b/mlprec/impl/aggregator/Makefile @@ -0,0 +1,61 @@ +include ../../../Make.inc +LIBDIR=../../../lib +INCDIR=../../../include +MODDIR=../../../modules +HERE=../.. + +FINCLUDES=$(FMFLAG)$(HERE) $(FMFLAG)$(MODDIR) $(FMFLAG)$(INCDIR) $(PSBLAS_INCLUDES) + +#CINCLUDES= -I${SUPERLU_INCDIR} -I${HSL_INCDIR} -I${SPRAL_INCDIR} -I/home/users/pasqua/Ambra/BootCMatch/include -lBCM -L/home/users/pasqua/Ambra/BootCMatch/lib -lm + +OBJS= \ +bootCMatch_interface.o\ +mld_s_base_aggregator_mat_asb.o \ +mld_s_base_aggregator_tprol.o \ +mld_s_hybrid_aggregator_tprol.o \ +mld_s_symdec_aggregator_tprol.o \ +mld_s_map_to_tprol.o mld_s_dec_map_bld.o mld_s_hyb_map_bld.o\ +mld_saggrmat_biz_asb.o mld_saggrmat_minnrg_asb.o\ +mld_saggrmat_nosmth_asb.o mld_saggrmat_smth_asb.o \ +mld_d_base_aggregator_mat_asb.o \ +mld_d_base_aggregator_tprol.o \ +mld_d_bcmatch_aggregator_tprol.o\ +mld_d_hybrid_aggregator_tprol.o \ +mld_d_symdec_aggregator_tprol.o \ +mld_d_map_to_tprol.o mld_d_dec_map_bld.o mld_d_hyb_map_bld.o\ +mld_daggrmat_unsmth_spmm_asb.o\ +mld_daggrmat_biz_asb.o mld_daggrmat_minnrg_asb.o\ +mld_daggrmat_nosmth_asb.o mld_daggrmat_smth_asb.o \ +mld_c_base_aggregator_mat_asb.o \ +mld_c_base_aggregator_tprol.o \ +mld_c_hybrid_aggregator_tprol.o \ +mld_c_symdec_aggregator_tprol.o \ +mld_c_map_to_tprol.o mld_c_dec_map_bld.o mld_c_hyb_map_bld.o\ +mld_caggrmat_biz_asb.o mld_caggrmat_minnrg_asb.o\ +mld_caggrmat_nosmth_asb.o mld_caggrmat_smth_asb.o \ +mld_z_base_aggregator_mat_asb.o \ +mld_z_base_aggregator_tprol.o \ +mld_z_hybrid_aggregator_tprol.o \ +mld_z_symdec_aggregator_tprol.o \ +mld_z_map_to_tprol.o mld_z_dec_map_bld.o mld_z_hyb_map_bld.o\ +mld_zaggrmat_biz_asb.o mld_zaggrmat_minnrg_asb.o\ +mld_zaggrmat_nosmth_asb.o mld_zaggrmat_smth_asb.o + +#mld_d_bcmatch_map_to_tprol.o mld_d_bcmatch_aggregator_mat_asb.o \ + + +LIBNAME=libmld_prec.a + +lib: $(OBJS) + $(AR) $(HERE)/$(LIBNAME) $(OBJS) + $(RANLIB) $(HERE)/$(LIBNAME) + +mpobjs: + (make $(MPFOBJS) F90="$(MPF90)" F90COPT="$(F90COPT)") + (make $(MPCOBJS) CC="$(MPCC)" CCOPT="$(CCOPT)") + +veryclean: clean + /bin/rm -f $(LIBNAME) + +clean: + /bin/rm -f $(OBJS) $(LOCAL_MODS) diff --git a/mlprec/impl/aggregator/mld_c_base_aggregator_mat_asb.f90 b/mlprec/impl/aggregator/mld_c_base_aggregator_mat_asb.f90 new file mode 100644 index 00000000..dc4bb1df --- /dev/null +++ b/mlprec/impl/aggregator/mld_c_base_aggregator_mat_asb.f90 @@ -0,0 +1,225 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_c_base_aggregator_mat_asb.f90 +! +! Subroutine: mld_c_base_aggregator_mat_asb +! Version: complex +! +! This routine builds the matrix associated to the current level of the +! multilevel preconditioner from the matrix associated to the previous level, +! by using the user-specified aggregation technique (therefore, it also builds the +! prolongation and restriction operators mapping the current level to the +! previous one and vice versa). +! The current level is regarded as the coarse one, while the previous as +! the fine one. This is in agreement with the fact that the routine is called, +! by mld_mlprec_bld, only on levels >=2. +! The coarse-level matrix A_C is built from a fine-level matrix A +! by using the Galerkin approach, i.e. +! +! A_C = P_C^T A P_C, +! +! where P_C is a prolongator from the coarse level to the fine one. +! +! A mapping from the nodes of the adjacency graph of A to the nodes of the +! adjacency graph of A_C has been computed by the mld_aggrmap_bld subroutine. +! The prolongator P_C is built here from this mapping, according to the +! value of p%iprcparm(mld_aggr_kind_), specified by the user through +! mld_cprecinit and mld_zprecset. +! On output from this routine the entries of AC, op_prol, op_restr +! are still in "global numbering" mode; this is fixed in the calling routine +! mld_c_lev_aggrmat_asb. +! +! Currently four different prolongators are implemented, corresponding to +! four aggregation algorithms: +! 1. un-smoothed aggregation, +! 2. smoothed aggregation, +! 3. "bizarre" aggregation. +! 4. minimum energy +! 1. The non-smoothed aggregation uses as prolongator the piecewise constant +! interpolation operator corresponding to the fine-to-coarse level mapping built +! by p%aggr%bld_tprol. This is called tentative prolongator. +! 2. The smoothed aggregation uses as prolongator the operator obtained by applying +! a damped Jacobi smoother to the tentative prolongator. +! 3. The "bizarre" aggregation uses a prolongator proposed by the authors of MLD2P4. +! This prolongator still requires a deep analysis and testing and its use is +! not recommended. +! 4. Minimum energy aggregation +! +! For more details see +! M. Brezina and P. Vanek, A black-box iterative solver based on a two-level +! Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of PSBLAS-based +! parallel two-level Schwarz preconditioners, Appl. Num. Math., 57 (2007), +! 1181-1196. +! M. Sala, R. Tuminaro: A new Petrov-Galerkin smoothed aggregation preconditioner +! for nonsymmetric linear systems, SIAM J. Sci. Comput., 31(1):143-166 (2008) +! +! +! The main structure is: +! 1. Perform sanity checks; +! 2. Compute prolongator/restrictor/AC +! +! +! Arguments: +! ag - type(mld_c_base_aggregator_type), input/output. +! The aggregator object +! parms - type(mld_sml_parms), input +! The aggregation parameters +! a - type(psb_cspmat_type), input. +! The sparse matrix structure containing the local part of +! the fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of the fine-level matrix. +! The 'one-level' data structure that will contain the local +! part of the matrix to be built as well as the information +! concerning the prolongator and its transpose. +! ilaggr - integer, dimension(:), input +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that the indices +! are assumed to be shifted so as to make sure the ranges on +! the various processes do not overlap. +! nlaggr - integer, dimension(:) input +! nlaggr(i) contains the aggregates held by process i. +! ac - type(psb_cspmat_type), output +! The coarse matrix on output +! +! op_prol - type(psb_cspmat_type), input/output +! The tentative prolongator on input, the computed prolongator on output +! +! op_restr - type(psb_cspmat_type), output +! The restrictor operator; normally, it is the transpose of the prolongator. +! +! info - integer, output. +! Error code. +! +subroutine mld_c_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) + use psb_base_mod + use mld_c_inner_mod, mld_protect_name => mld_c_base_aggregator_mat_asb + implicit none + + class(mld_c_base_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_cspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) + type(psb_cspmat_type), intent(inout) :: op_prol + type(psb_cspmat_type), intent(out) :: ac,op_restr + integer(psb_ipk_), intent(out) :: info + + ! Local variables + character(len=20) :: name + integer(psb_mpik_) :: ictxt, np, me + type(psb_c_coo_sparse_mat) :: acoo, bcoo + type(psb_c_csr_sparse_mat) :: acsr1 + integer(psb_ipk_) :: nzl,ntaggr + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_c_base_aggregator_mat_asb' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(parms%aggr_kind,'Smoother',& + & mld_smooth_prol_,is_legal_ml_aggr_kind) + call mld_check_def(parms%coarse_mat,'Coarse matrix',& + & mld_distr_mat_,is_legal_ml_coarse_mat) + call mld_check_def(parms%aggr_filter,'Use filtered matrix',& + & mld_no_filter_mat_,is_legal_aggr_filter) + call mld_check_def(parms%smoother_pos,'smooth_pos',& + & mld_pre_smooth_,is_legal_ml_smooth_pos) + call mld_check_def(parms%aggr_omega_alg,'Omega Alg.',& + & mld_eig_est_,is_legal_ml_aggr_omega_alg) + call mld_check_def(parms%aggr_eig,'Eigenvalue estimate',& + & mld_max_norm_,is_legal_ml_aggr_eig) + call mld_check_def(parms%aggr_omega_val,'Omega',szero,is_legal_s_omega) + + ! + ! Build the coarse-level matrix from the fine-level one, starting from + ! the mapping defined by mld_aggrmap_bld and applying the aggregation + ! algorithm specified by p%iprcparm(mld_aggr_kind_) + ! + select case (parms%aggr_kind) + case (mld_no_smooth_) + + call mld_caggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,& + & parms,ac,op_prol,op_restr,info) + + case(mld_smooth_prol_) + + call mld_caggrmat_smth_asb(a,desc_a,ilaggr,nlaggr, & + & parms,ac,op_prol,op_restr,info) + + case(mld_biz_prol_) + + call mld_caggrmat_biz_asb(a,desc_a,ilaggr,nlaggr, & + & parms,ac,op_prol,op_restr,info) + + case(mld_min_energy_) + + call mld_caggrmat_minnrg_asb(a,desc_a,ilaggr,nlaggr, & + & parms,ac,op_prol,op_restr,info) + + case default + info = psb_err_internal_error_ + call psb_errpush(info,name,a_err='Invalid aggr kind') + goto 9999 + + end select + if (info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='Inner aggrmat asb') + goto 9999 + end if + + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + + +end subroutine mld_c_base_aggregator_mat_asb diff --git a/mlprec/impl/aggregator/mld_c_base_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_c_base_aggregator_tprol.f90 new file mode 100644 index 00000000..18c5428d --- /dev/null +++ b/mlprec/impl/aggregator/mld_c_base_aggregator_tprol.f90 @@ -0,0 +1,124 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_c_base_aggregator_tprol.f90 +! +! Subroutine: mld_c_base_aggregator_tprol +! Version: complex +! +! This routine is mainly an interface to dec_map_bld where the real work is performed. +! It takes care of some consistency checking, and calls map_to_tprol, which is +! refactored and shared among all the aggregation methods that produce a simple +! integer mapping. +! +! +! Arguments: +! p - type(mld_c_onelev_type), input/output. +! The 'one-level' data structure containing the control +! parameters and (eventually) coarse matrix and prolongator/restrictors. +! +! a - type(psb_cspmat_type). +! The sparse matrix structure containing the local part of the +! fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of a. +! ilaggr - integer, dimension(:), allocatable, output +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that on exit the indices +! will be shifted so as to make sure the ranges on the various processes do not +! overlap. +! nlaggr - integer, dimension(:), allocatable, output +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_cspmat_type), output +! The tentative prolongator, based on ilaggr. +! +! info - integer, output. +! Error code. +! +subroutine mld_c_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod +! use mld_c_base_aggregator_mod + use mld_c_inner_mod, mld_protect_name => mld_c_base_aggregator_build_tprol + implicit none + class(mld_c_base_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_cspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_cspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + ! Local variables + character(len=20) :: name + integer(psb_mpik_) :: ictxt, np, me + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: ntaggr + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_c_base_aggregator_tprol' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(parms%ml_type,'Multilevel type',& + & mld_mult_ml_,is_legal_ml_type) + call mld_check_def(parms%aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_aggr_alg) + call mld_check_def(parms%aggr_ord,'Ordering',& + & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) + call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) + + + call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + + call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + +end subroutine mld_c_base_aggregator_build_tprol diff --git a/mlprec/impl/mld_c_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_c_dec_map_bld.f90 similarity index 100% rename from mlprec/impl/mld_c_dec_map_bld.f90 rename to mlprec/impl/aggregator/mld_c_dec_map_bld.f90 diff --git a/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 new file mode 100644 index 00000000..22ad0a2c --- /dev/null +++ b/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 @@ -0,0 +1,328 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! File: mld_c_hyb_map__bld.f90 +! +! Subroutine: mld_c_hyb_map_bld +! Version: complex +! +! This routine builds the tentative prolongator based on the +! decoupled aggregation algorithm presented in +! +! M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +! Note: upon exit +! +! Arguments: +! a - type(psb_cspmat_type). +! The sparse matrix structure containing the local part of the +! matrix to be preconditioned. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of a. +! p - type(mld_cprec_type), input/output. +! The preconditioner data structure; upon exit it contains +! the multilevel hierarchy of prolongators, restrictors +! and coarse matrices. +! info - integer, output. +! Error code. +! +! +! +subroutine mld_c_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + + use psb_base_mod + use mld_c_inner_mod, mld_protect_name => mld_c_hyb_map_bld + + implicit none + + ! Arguments + integer(psb_ipk_), intent(in) :: iorder + type(psb_cspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + real(psb_spk_), intent(in) :: theta + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + integer(psb_ipk_), intent(out) :: info + + ! Local variables + integer(psb_ipk_), allocatable :: ils(:), neigh(:), irow(:), icol(:),& + & ideg(:), idxs(:), tmpaggr(:) + complex(psb_spk_), allocatable :: val(:), diag(:) + integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m, nz, ilg, ii, ip, ip1,nzcnt + type(psb_c_csr_sparse_mat) :: acsr, muij, s_neigh + type(psb_c_coo_sparse_mat) :: s_neigh_coo + real(psb_spk_) :: cpling, tcl + logical :: disjoint + integer(psb_ipk_) :: debug_level, debug_unit,err_act + integer(psb_ipk_) :: ictxt,np,me + integer(psb_ipk_) :: nrow, ncol, n_ne + character(len=20) :: name, ch_err + + if (psb_get_errstatus() /= 0) return + info=psb_success_ + name = 'mld_hyb_map_bld' + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + ! + ictxt=desc_a%get_context() + call psb_info(ictxt,me,np) + nrow = desc_a%get_local_rows() + ncol = desc_a%get_local_cols() + + nr = a%get_nrows() + allocate(ilaggr(nr),neigh(nr),ideg(nr),idxs(nr),icol(nr),stat=info) + if(info /= psb_success_) then + info=psb_err_alloc_request_ + call psb_errpush(info,name,i_err=(/2*nr,izero,izero,izero,izero/),& + & a_err='integer') + goto 9999 + end if + + diag = a%get_diag(info) + if(info /= psb_success_) then + info=psb_err_from_subroutine_ + call psb_errpush(info,name,a_err='psb_sp_getdiag') + goto 9999 + end if + + ! + ! Phase zero: compute muij + ! + call a%cp_to(muij) + do i=1, nr + do k=muij%irp(i),muij%irp(i+1)-1 + j = muij%ja(k) + muij%val(k) = abs(muij%val(k))/sqrt(abs(diag(i)*diag(j))) + end do + end do + !write(*,*) 'murows/cols ',maxval(mu_rows),maxval(mu_cols) + ! + ! Compute the 1-neigbour; mark strong links with +1, weak links with -1 + ! + call s_neigh_coo%allocate(nr,nr,muij%get_nzeros()) + ip = 0 + do i=1, nr + do k=muij%irp(i),muij%irp(i+1)-1 + j = muij%ja(k) + ip = ip + 1 + s_neigh_coo%ia(ip) = i + s_neigh_coo%ja(ip) = j + if (real(muij%val(k)) >= theta) then + s_neigh_coo%val(ip) = sone + else + s_neigh_coo%val(ip) = -sone + end if + end do + end do + !write(*,*) 'S_NEIGH: ',nr,ip + call s_neigh_coo%set_nzeros(ip) + call s_neigh%mv_from_coo(s_neigh_coo,info) + + if (iorder == mld_aggr_ord_nat_) then + do i=1, nr + ilaggr(i) = -(nr+1) + idxs(i) = i + end do + else + do i=1, nr + ilaggr(i) = -(nr+1) + ideg(i) = muij%irp(i+1) - muij%irp(i) + end do + call psb_msort(ideg,ix=idxs,dir=psb_sort_down_) + end if + + + ! + ! Phase one: Start with disjoint groups. + ! + naggr = 0 + icnt = 0 + step1: do ii=1, nr + i = idxs(ii) + + if (ilaggr(i) == -(nr+1)) then + ! + ! Get the 1-neighbourhood of I + ! + ip1 = s_neigh%irp(i) + nz = s_neigh%irp(i+1)-ip1 + ! + ! If the neighbourhood only contains I, skip it + ! + if (nz ==0) then + ilaggr(i) = 0 + cycle step1 + end if + if ((nz==1).and.(s_neigh%ja(ip1)==i)) then + ilaggr(i) = 0 + cycle step1 + end if + ! + ! If the whole strongly coupled neighborhood of I is + ! as yet unconnected, turn it into the next aggregate. + ! + nzcnt = count(real(s_neigh%val(ip1:ip1+nz-1)) > 0) + icol(1:nzcnt) = pack(s_neigh%ja(ip1:ip1+nz-1),(real(s_neigh%val(ip1:ip1+nz-1)) > 0)) + disjoint = all(ilaggr(icol(1:nzcnt)) == -(nr+1)) + if (disjoint) then + icnt = icnt + 1 + naggr = naggr + 1 + do k=1, nzcnt + ilaggr(icol(k)) = naggr + end do + ilaggr(i) = naggr + end if + endif + enddo step1 + + if (debug_level >= psb_debug_outer_) then + write(debug_unit,*) me,' ',trim(name),& + & ' Check 1:',count(ilaggr == -(nr+1)) + end if + + ! + ! Phase two: join the neighbours + ! + tmpaggr = ilaggr + step2: do ii=1,nr + i = idxs(ii) + + if (ilaggr(i) == -(nr+1)) then + ! + ! Find the most strongly connected neighbour that is + ! already aggregated, if any, and join its aggregate + ! + cpling = szero + ip = 0 + do k=s_neigh%irp(i), s_neigh%irp(i+1)-1 + j = s_neigh%ja(k) + if ((1<=j).and.(j<=nr)) then + if ( (tmpaggr(j) > 0).and. (real(muij%val(k)) > cpling)& + & .and.(real(s_neigh%val(k))>0)) then + ip = k + cpling = muij%val(k) + end if + end if + enddo + if (ip > 0) then + ilaggr(i) = ilaggr(s_neigh%ja(ip)) + end if + end if + end do step2 + + + ! + ! Phase three: sweep over leftovers, if any + ! + step3: do ii=1,nr + i = idxs(ii) + + if (ilaggr(i) < 0) then + ! + ! Find its strongly connected neighbourhood not + ! already aggregated, and make it into a new aggregate. + ! + ip = 0 + do k=s_neigh%irp(i), s_neigh%irp(i+1)-1 + j = s_neigh%ja(k) + if ((1<=j).and.(j<=nr)) then + if (ilaggr(j) < 0) then + ip = ip + 1 + icol(ip) = j + end if + end if + enddo + if (ip > 0) then + icnt = icnt + 1 + naggr = naggr + 1 + ilaggr(i) = naggr + do k=1, ip + ilaggr(icol(k)) = naggr + end do + end if + end if + end do step3 + + + if (count(ilaggr<0) >0) then + info=psb_err_internal_error_ + call psb_errpush(info,name,a_err='Fatal error: some leftovers') + goto 9999 + endif + + if (naggr > ncol) then + write(0,*) name,'Error : naggr > ncol',naggr,ncol + info=psb_err_internal_error_ + call psb_errpush(info,name,a_err='Fatal error: naggr>ncol') + goto 9999 + end if + + call psb_realloc(ncol,ilaggr,info) + if (info /= psb_success_) then + info=psb_err_from_subroutine_ + ch_err='psb_realloc' + call psb_errpush(info,name,a_err=ch_err) + goto 9999 + end if + + allocate(nlaggr(np),stat=info) + if (info /= psb_success_) then + info=psb_err_alloc_request_ + call psb_errpush(info,name,i_err=(/np,izero,izero,izero,izero/),& + & a_err='integer') + goto 9999 + end if + + nlaggr(:) = 0 + nlaggr(me+1) = naggr + call psb_sum(ictxt,nlaggr(1:np)) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + +end subroutine mld_c_hyb_map_bld + diff --git a/mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 new file mode 100644 index 00000000..675baaa7 --- /dev/null +++ b/mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 @@ -0,0 +1,122 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 +! +! Salvatore Filippone Cranfield University, UK +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_c_hybrid_aggregator_tprol.f90 +! +! Subroutine: mld_c_hybrid_aggregator_tprol +! Version: complex +! +! +! This routine is mainly an interface to hyb_map_bld where the real work is performed. +! It takes care of some consistency checking, and calls map_to_tprol, which is +! refactored and shared among all the aggregation methods that produce a simple +! integer mapping. +! +! +! Arguments: +! p - type(mld_c_onelev_type), input/output. +! The 'one-level' data structure containing the control +! parameters and (eventually) coarse matrix and prolongator/restrictors. +! +! a - type(psb_cspmat_type). +! The sparse matrix structure containing the local part of the +! fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of a. +! ilaggr - integer, dimension(:), allocatable, output +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that on exit the indices +! will be shifted so as to make sure the ranges on the various processes do not +! overlap. +! nlaggr - integer, dimension(:), allocatable, output +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_cspmat_type), output +! The tentative prolongator, based on ilaggr. +! +! info - integer, output. +! Error code. +! +subroutine mld_c_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod + use mld_c_hybrid_aggregator_mod, mld_protect_name => mld_c_hybrid_aggregator_build_tprol + use mld_c_inner_mod + implicit none + class(mld_c_hybrid_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_cspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_cspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + ! Local variables + character(len=20) :: name + integer(psb_mpik_) :: ictxt, np, me + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: ntaggr + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_c_hybrid_aggregator_tprol' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(p%parms%ml_cycle,'Multilevel cycle',& + & mld_mult_ml_,is_legal_ml_cycle) + call mld_check_def(p%parms%par_aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_par_aggr_alg) + call mld_check_def(p%parms%aggr_ord,'Ordering',& + & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) + call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) + call mld_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + + call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + +end subroutine mld_c_hybrid_aggregator_build_tprol diff --git a/mlprec/impl/aggregator/mld_c_map_to_tprol.f90 b/mlprec/impl/aggregator/mld_c_map_to_tprol.f90 new file mode 100644 index 00000000..ae2154c5 --- /dev/null +++ b/mlprec/impl/aggregator/mld_c_map_to_tprol.f90 @@ -0,0 +1,150 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 +! +! Salvatore Filippone Cranfield University, UK +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_c_map_to_tprol.f90 +! +! Subroutine: mld_c_map_to_tprol +! Version: complex +! +! This routine uses a mapping from the row indices of the fine-level matrix +! to the row indices of the coarse-level matrix to build a tentative +! prolongator, i.e. a piecewise constant operator. +! This is later used to build the final operator; the code has been refactored here +! to be shared among all the methods that provide the tentative prolongator +! through a simple integer mapping. +! +! The aggregation algorithm is a parallel version of that described in +! * M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! * P. Vanek, J. Mandel and M. Brezina, Algebraic Multigrid by Smoothed +! Aggregation for Second and Fourth Order Elliptic Problems, Computing, 56 +! (1996), 179-196. +! For more details see +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +! +! Arguments: +! aggr_type - integer, input. +! The scalar used to identify the aggregation algorithm. +! theta - real, input. +! The aggregation threshold used in the aggregation algorithm. +! a - type(psb_cspmat_type), input. +! The sparse matrix structure containing the local part of +! the fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of the fine-level matrix. +! ilaggr - integer, dimension(:), allocatable. +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that on exit the indices +! will be shifted so as to make sure the ranges on the various processes do not +! overlap. +! nlaggr - integer, dimension(:), allocatable. +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_cspmat_type). +! The tentative prolongator, based on ilaggr. +! +! info - integer, output. +! Error code. +! +subroutine mld_c_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + use psb_base_mod + use mld_c_inner_mod, mld_protect_name => mld_c_map_to_tprol + + implicit none + + ! Arguments + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:) + type(psb_cspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + ! Local variables + integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m,naggrm1, naggrp1, ntaggr + type(psb_c_coo_sparse_mat) :: tmpcoo + integer(psb_ipk_) :: debug_level, debug_unit,err_act + integer(psb_ipk_) :: ictxt,np,me + integer(psb_ipk_) :: nrow, ncol, n_ne + character(len=20) :: name, ch_err + + if(psb_get_errstatus() /= 0) return + info=psb_success_ + name = 'mld_map_to_tprol' + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + ! + ictxt=desc_a%get_context() + call psb_info(ictxt,me,np) + nrow = desc_a%get_local_rows() + ncol = desc_a%get_local_cols() + + naggr = nlaggr(me+1) + ntaggr = sum(nlaggr) + naggrm1 = sum(nlaggr(1:me)) + naggrp1 = sum(nlaggr(1:me+1)) + ilaggr(1:nrow) = ilaggr(1:nrow) + naggrm1 + call psb_halo(ilaggr,desc_a,info) + if (info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_halo') + goto 9999 + end if + + call tmpcoo%allocate(ncol,ntaggr,ncol) + do i=1,ncol + tmpcoo%val(i) = cone + tmpcoo%ia(i) = i + tmpcoo%ja(i) = ilaggr(i) + end do + call tmpcoo%set_nzeros(ncol) + call tmpcoo%set_dupl(psb_dupl_add_) + call tmpcoo%set_sorted() ! At this point this is in row-major + call op_prol%mv_from(tmpcoo) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + +end subroutine mld_c_map_to_tprol diff --git a/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 new file mode 100644 index 00000000..8fe0b7a8 --- /dev/null +++ b/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 @@ -0,0 +1,141 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_c_symdec_aggregator_tprol.f90 +! +! Subroutine: mld_c_symdec_aggregator_tprol +! Version: complex +! +! +! This routine is mainly an interface to dec_map_bld where the real work is performed. +! It takes care of some consistency checking, and calls map_to_tprol, which is +! refactored and shared among all the aggregation methods that produce a simple +! integer mapping. +! +! +! +! Arguments: +! p - type(mld_c_onelev_type), input/output. +! The 'one-level' data structure containing the control +! parameters and (eventually) coarse matrix and prolongator/restrictors. +! +! a - type(psb_cspmat_type). +! The sparse matrix structure containing the local part of the +! fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of a. +! ilaggr - integer, dimension(:), allocatable, output +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that on exit the indices +! will be shifted so as to make sure the ranges on the various processes do not +! overlap. +! nlaggr - integer, dimension(:), allocatable, output +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_cspmat_type), output +! The tentative prolongator, based on ilaggr. +! +! info - integer, output. +! Error code. +! +subroutine mld_c_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod + use mld_c_symdec_aggregator_mod, mld_protect_name => mld_c_symdec_aggregator_build_tprol + use mld_c_inner_mod + implicit none + class(mld_c_symdec_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_cspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_cspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + ! Local variables + type(psb_cspmat_type) :: atmp, atrans + character(len=20) :: name + integer(psb_mpik_) :: ictxt, np, me + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: ntaggr, nr + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_c_symdec_aggregator_tprol' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(parms%ml_type,'Multilevel type',& + & mld_mult_ml_,is_legal_ml_type) + call mld_check_def(parms%aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_aggr_alg) + call mld_check_def(parms%aggr_ord,'Ordering',& + & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) + call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) + + nr = a%get_nrows() + call a%csclip(atmp,info,imax=nr,jmax=nr,& + & rscale=.false.,cscale=.false.) + call atmp%set_nrows(nr) + call atmp%set_ncols(nr) + if (info == psb_success_) call atmp%transp(atrans) + if (info == psb_success_) call atrans%cscnv(info,type='COO') + if (info == psb_success_) call psb_rwextd(nr,atmp,info,b=atrans,rowscale=.false.) + call atmp%set_nrows(nr) + call atmp%set_ncols(nr) + if (info == psb_success_) call atrans%free() + if (info == psb_success_) call atmp%cscnv(info,type='CSR') + + if (info == psb_success_) & + & call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) + if (info == psb_success_) call atmp%free() + + if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + +end subroutine mld_c_symdec_aggregator_build_tprol diff --git a/mlprec/impl/mld_caggrmat_biz_asb.f90 b/mlprec/impl/aggregator/mld_caggrmat_biz_asb.f90 similarity index 100% rename from mlprec/impl/mld_caggrmat_biz_asb.f90 rename to mlprec/impl/aggregator/mld_caggrmat_biz_asb.f90 diff --git a/mlprec/impl/mld_caggrmat_minnrg_asb.f90 b/mlprec/impl/aggregator/mld_caggrmat_minnrg_asb.f90 similarity index 100% rename from mlprec/impl/mld_caggrmat_minnrg_asb.f90 rename to mlprec/impl/aggregator/mld_caggrmat_minnrg_asb.f90 diff --git a/mlprec/impl/mld_caggrmat_nosmth_asb.f90 b/mlprec/impl/aggregator/mld_caggrmat_nosmth_asb.f90 similarity index 100% rename from mlprec/impl/mld_caggrmat_nosmth_asb.f90 rename to mlprec/impl/aggregator/mld_caggrmat_nosmth_asb.f90 diff --git a/mlprec/impl/mld_caggrmat_smth_asb.f90 b/mlprec/impl/aggregator/mld_caggrmat_smth_asb.f90 similarity index 100% rename from mlprec/impl/mld_caggrmat_smth_asb.f90 rename to mlprec/impl/aggregator/mld_caggrmat_smth_asb.f90 diff --git a/mlprec/impl/aggregator/mld_d_base_aggregator_mat_asb.f90 b/mlprec/impl/aggregator/mld_d_base_aggregator_mat_asb.f90 new file mode 100644 index 00000000..ba600776 --- /dev/null +++ b/mlprec/impl/aggregator/mld_d_base_aggregator_mat_asb.f90 @@ -0,0 +1,225 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_d_base_aggregator_mat_asb.f90 +! +! Subroutine: mld_d_base_aggregator_mat_asb +! Version: real +! +! This routine builds the matrix associated to the current level of the +! multilevel preconditioner from the matrix associated to the previous level, +! by using the user-specified aggregation technique (therefore, it also builds the +! prolongation and restriction operators mapping the current level to the +! previous one and vice versa). +! The current level is regarded as the coarse one, while the previous as +! the fine one. This is in agreement with the fact that the routine is called, +! by mld_mlprec_bld, only on levels >=2. +! The coarse-level matrix A_C is built from a fine-level matrix A +! by using the Galerkin approach, i.e. +! +! A_C = P_C^T A P_C, +! +! where P_C is a prolongator from the coarse level to the fine one. +! +! A mapping from the nodes of the adjacency graph of A to the nodes of the +! adjacency graph of A_C has been computed by the mld_aggrmap_bld subroutine. +! The prolongator P_C is built here from this mapping, according to the +! value of p%iprcparm(mld_aggr_kind_), specified by the user through +! mld_dprecinit and mld_zprecset. +! On output from this routine the entries of AC, op_prol, op_restr +! are still in "global numbering" mode; this is fixed in the calling routine +! mld_d_lev_aggrmat_asb. +! +! Currently four different prolongators are implemented, corresponding to +! four aggregation algorithms: +! 1. un-smoothed aggregation, +! 2. smoothed aggregation, +! 3. "bizarre" aggregation. +! 4. minimum energy +! 1. The non-smoothed aggregation uses as prolongator the piecewise constant +! interpolation operator corresponding to the fine-to-coarse level mapping built +! by p%aggr%bld_tprol. This is called tentative prolongator. +! 2. The smoothed aggregation uses as prolongator the operator obtained by applying +! a damped Jacobi smoother to the tentative prolongator. +! 3. The "bizarre" aggregation uses a prolongator proposed by the authors of MLD2P4. +! This prolongator still requires a deep analysis and testing and its use is +! not recommended. +! 4. Minimum energy aggregation +! +! For more details see +! M. Brezina and P. Vanek, A black-box iterative solver based on a two-level +! Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of PSBLAS-based +! parallel two-level Schwarz preconditioners, Appl. Num. Math., 57 (2007), +! 1181-1196. +! M. Sala, R. Tuminaro: A new Petrov-Galerkin smoothed aggregation preconditioner +! for nonsymmetric linear systems, SIAM J. Sci. Comput., 31(1):143-166 (2008) +! +! +! The main structure is: +! 1. Perform sanity checks; +! 2. Compute prolongator/restrictor/AC +! +! +! Arguments: +! ag - type(mld_d_base_aggregator_type), input/output. +! The aggregator object +! parms - type(mld_dml_parms), input +! The aggregation parameters +! 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. +! The communication descriptor of the fine-level matrix. +! The 'one-level' data structure that will contain the local +! part of the matrix to be built as well as the information +! concerning the prolongator and its transpose. +! ilaggr - integer, dimension(:), input +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that the indices +! are assumed to be shifted so as to make sure the ranges on +! the various processes do not overlap. +! nlaggr - integer, dimension(:) input +! nlaggr(i) contains the aggregates held by process i. +! ac - type(psb_dspmat_type), output +! The coarse matrix on output +! +! op_prol - type(psb_dspmat_type), input/output +! The tentative prolongator on input, the computed prolongator on output +! +! op_restr - type(psb_dspmat_type), output +! The restrictor operator; normally, it is the transpose of the prolongator. +! +! info - integer, output. +! Error code. +! +subroutine mld_d_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) + use psb_base_mod + use mld_d_inner_mod, mld_protect_name => mld_d_base_aggregator_mat_asb + implicit none + + class(mld_d_base_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) + type(psb_dspmat_type), intent(inout) :: op_prol + type(psb_dspmat_type), intent(out) :: ac,op_restr + integer(psb_ipk_), intent(out) :: info + + ! Local variables + character(len=20) :: name + integer(psb_mpik_) :: ictxt, np, me + type(psb_d_coo_sparse_mat) :: acoo, bcoo + type(psb_d_csr_sparse_mat) :: acsr1 + integer(psb_ipk_) :: nzl,ntaggr + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_d_base_aggregator_mat_asb' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(parms%aggr_kind,'Smoother',& + & mld_smooth_prol_,is_legal_ml_aggr_kind) + call mld_check_def(parms%coarse_mat,'Coarse matrix',& + & mld_distr_mat_,is_legal_ml_coarse_mat) + call mld_check_def(parms%aggr_filter,'Use filtered matrix',& + & mld_no_filter_mat_,is_legal_aggr_filter) + call mld_check_def(parms%smoother_pos,'smooth_pos',& + & mld_pre_smooth_,is_legal_ml_smooth_pos) + call mld_check_def(parms%aggr_omega_alg,'Omega Alg.',& + & mld_eig_est_,is_legal_ml_aggr_omega_alg) + call mld_check_def(parms%aggr_eig,'Eigenvalue estimate',& + & mld_max_norm_,is_legal_ml_aggr_eig) + call mld_check_def(parms%aggr_omega_val,'Omega',dzero,is_legal_d_omega) + + ! + ! Build the coarse-level matrix from the fine-level one, starting from + ! the mapping defined by mld_aggrmap_bld and applying the aggregation + ! algorithm specified by p%iprcparm(mld_aggr_kind_) + ! + select case (parms%aggr_kind) + case (mld_no_smooth_) + + call mld_daggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,& + & parms,ac,op_prol,op_restr,info) + + case(mld_smooth_prol_) + + call mld_daggrmat_smth_asb(a,desc_a,ilaggr,nlaggr, & + & parms,ac,op_prol,op_restr,info) + + case(mld_biz_prol_) + + call mld_daggrmat_biz_asb(a,desc_a,ilaggr,nlaggr, & + & parms,ac,op_prol,op_restr,info) + + case(mld_min_energy_) + + call mld_daggrmat_minnrg_asb(a,desc_a,ilaggr,nlaggr, & + & parms,ac,op_prol,op_restr,info) + + case default + info = psb_err_internal_error_ + call psb_errpush(info,name,a_err='Invalid aggr kind') + goto 9999 + + end select + if (info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='Inner aggrmat asb') + goto 9999 + end if + + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + + +end subroutine mld_d_base_aggregator_mat_asb diff --git a/mlprec/impl/aggregator/mld_d_base_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_d_base_aggregator_tprol.f90 new file mode 100644 index 00000000..02ffb7d7 --- /dev/null +++ b/mlprec/impl/aggregator/mld_d_base_aggregator_tprol.f90 @@ -0,0 +1,124 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_d_base_aggregator_tprol.f90 +! +! Subroutine: mld_d_base_aggregator_tprol +! Version: real +! +! This routine is mainly an interface to dec_map_bld where the real work is performed. +! It takes care of some consistency checking, and calls map_to_tprol, which is +! refactored and shared among all the aggregation methods that produce a simple +! integer mapping. +! +! +! Arguments: +! p - type(mld_d_onelev_type), input/output. +! The 'one-level' data structure containing the control +! parameters and (eventually) coarse matrix and prolongator/restrictors. +! +! a - type(psb_dspmat_type). +! The sparse matrix structure containing the local part of the +! fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of a. +! ilaggr - integer, dimension(:), allocatable, output +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that on exit the indices +! will be shifted so as to make sure the ranges on the various processes do not +! overlap. +! nlaggr - integer, dimension(:), allocatable, output +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_dspmat_type), output +! The tentative prolongator, based on ilaggr. +! +! info - integer, output. +! Error code. +! +subroutine mld_d_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod +! use mld_d_base_aggregator_mod + use mld_d_inner_mod, mld_protect_name => mld_d_base_aggregator_build_tprol + implicit none + class(mld_d_base_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_dspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + ! Local variables + character(len=20) :: name + integer(psb_mpik_) :: ictxt, np, me + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: ntaggr + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_d_base_aggregator_tprol' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(parms%ml_type,'Multilevel type',& + & mld_mult_ml_,is_legal_ml_type) + call mld_check_def(parms%aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_aggr_alg) + call mld_check_def(parms%aggr_ord,'Ordering',& + & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) + call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) + + + call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + + call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + +end subroutine mld_d_base_aggregator_build_tprol diff --git a/mlprec/impl/mld_d_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_d_dec_map_bld.f90 similarity index 100% rename from mlprec/impl/mld_d_dec_map_bld.f90 rename to mlprec/impl/aggregator/mld_d_dec_map_bld.f90 diff --git a/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 new file mode 100644 index 00000000..a0f7f7cb --- /dev/null +++ b/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 @@ -0,0 +1,328 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! File: mld_d_hyb_map__bld.f90 +! +! Subroutine: mld_d_hyb_map_bld +! Version: real +! +! This routine builds the tentative prolongator based on the +! decoupled aggregation algorithm presented in +! +! M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +! Note: upon exit +! +! Arguments: +! 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. +! The communication descriptor of a. +! p - type(mld_dprec_type), input/output. +! The preconditioner data structure; upon exit it contains +! the multilevel hierarchy of prolongators, restrictors +! and coarse matrices. +! info - integer, output. +! Error code. +! +! +! +subroutine mld_d_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + + use psb_base_mod + use mld_d_inner_mod, mld_protect_name => mld_d_hyb_map_bld + + implicit none + + ! Arguments + integer(psb_ipk_), intent(in) :: iorder + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + real(psb_dpk_), intent(in) :: theta + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + integer(psb_ipk_), intent(out) :: info + + ! Local variables + integer(psb_ipk_), allocatable :: ils(:), neigh(:), irow(:), icol(:),& + & ideg(:), idxs(:), tmpaggr(:) + real(psb_dpk_), allocatable :: val(:), diag(:) + integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m, nz, ilg, ii, ip, ip1,nzcnt + type(psb_d_csr_sparse_mat) :: acsr, muij, s_neigh + type(psb_d_coo_sparse_mat) :: s_neigh_coo + real(psb_dpk_) :: cpling, tcl + logical :: disjoint + integer(psb_ipk_) :: debug_level, debug_unit,err_act + integer(psb_ipk_) :: ictxt,np,me + integer(psb_ipk_) :: nrow, ncol, n_ne + character(len=20) :: name, ch_err + + if (psb_get_errstatus() /= 0) return + info=psb_success_ + name = 'mld_hyb_map_bld' + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + ! + ictxt=desc_a%get_context() + call psb_info(ictxt,me,np) + nrow = desc_a%get_local_rows() + ncol = desc_a%get_local_cols() + + nr = a%get_nrows() + allocate(ilaggr(nr),neigh(nr),ideg(nr),idxs(nr),icol(nr),stat=info) + if(info /= psb_success_) then + info=psb_err_alloc_request_ + call psb_errpush(info,name,i_err=(/2*nr,izero,izero,izero,izero/),& + & a_err='integer') + goto 9999 + end if + + diag = a%get_diag(info) + if(info /= psb_success_) then + info=psb_err_from_subroutine_ + call psb_errpush(info,name,a_err='psb_sp_getdiag') + goto 9999 + end if + + ! + ! Phase zero: compute muij + ! + call a%cp_to(muij) + do i=1, nr + do k=muij%irp(i),muij%irp(i+1)-1 + j = muij%ja(k) + muij%val(k) = abs(muij%val(k))/sqrt(abs(diag(i)*diag(j))) + end do + end do + !write(*,*) 'murows/cols ',maxval(mu_rows),maxval(mu_cols) + ! + ! Compute the 1-neigbour; mark strong links with +1, weak links with -1 + ! + call s_neigh_coo%allocate(nr,nr,muij%get_nzeros()) + ip = 0 + do i=1, nr + do k=muij%irp(i),muij%irp(i+1)-1 + j = muij%ja(k) + ip = ip + 1 + s_neigh_coo%ia(ip) = i + s_neigh_coo%ja(ip) = j + if (real(muij%val(k)) >= theta) then + s_neigh_coo%val(ip) = done + else + s_neigh_coo%val(ip) = -done + end if + end do + end do + !write(*,*) 'S_NEIGH: ',nr,ip + call s_neigh_coo%set_nzeros(ip) + call s_neigh%mv_from_coo(s_neigh_coo,info) + + if (iorder == mld_aggr_ord_nat_) then + do i=1, nr + ilaggr(i) = -(nr+1) + idxs(i) = i + end do + else + do i=1, nr + ilaggr(i) = -(nr+1) + ideg(i) = muij%irp(i+1) - muij%irp(i) + end do + call psb_msort(ideg,ix=idxs,dir=psb_sort_down_) + end if + + + ! + ! Phase one: Start with disjoint groups. + ! + naggr = 0 + icnt = 0 + step1: do ii=1, nr + i = idxs(ii) + + if (ilaggr(i) == -(nr+1)) then + ! + ! Get the 1-neighbourhood of I + ! + ip1 = s_neigh%irp(i) + nz = s_neigh%irp(i+1)-ip1 + ! + ! If the neighbourhood only contains I, skip it + ! + if (nz ==0) then + ilaggr(i) = 0 + cycle step1 + end if + if ((nz==1).and.(s_neigh%ja(ip1)==i)) then + ilaggr(i) = 0 + cycle step1 + end if + ! + ! If the whole strongly coupled neighborhood of I is + ! as yet unconnected, turn it into the next aggregate. + ! + nzcnt = count(real(s_neigh%val(ip1:ip1+nz-1)) > 0) + icol(1:nzcnt) = pack(s_neigh%ja(ip1:ip1+nz-1),(real(s_neigh%val(ip1:ip1+nz-1)) > 0)) + disjoint = all(ilaggr(icol(1:nzcnt)) == -(nr+1)) + if (disjoint) then + icnt = icnt + 1 + naggr = naggr + 1 + do k=1, nzcnt + ilaggr(icol(k)) = naggr + end do + ilaggr(i) = naggr + end if + endif + enddo step1 + + if (debug_level >= psb_debug_outer_) then + write(debug_unit,*) me,' ',trim(name),& + & ' Check 1:',count(ilaggr == -(nr+1)) + end if + + ! + ! Phase two: join the neighbours + ! + tmpaggr = ilaggr + step2: do ii=1,nr + i = idxs(ii) + + if (ilaggr(i) == -(nr+1)) then + ! + ! Find the most strongly connected neighbour that is + ! already aggregated, if any, and join its aggregate + ! + cpling = dzero + ip = 0 + do k=s_neigh%irp(i), s_neigh%irp(i+1)-1 + j = s_neigh%ja(k) + if ((1<=j).and.(j<=nr)) then + if ( (tmpaggr(j) > 0).and. (real(muij%val(k)) > cpling)& + & .and.(real(s_neigh%val(k))>0)) then + ip = k + cpling = muij%val(k) + end if + end if + enddo + if (ip > 0) then + ilaggr(i) = ilaggr(s_neigh%ja(ip)) + end if + end if + end do step2 + + + ! + ! Phase three: sweep over leftovers, if any + ! + step3: do ii=1,nr + i = idxs(ii) + + if (ilaggr(i) < 0) then + ! + ! Find its strongly connected neighbourhood not + ! already aggregated, and make it into a new aggregate. + ! + ip = 0 + do k=s_neigh%irp(i), s_neigh%irp(i+1)-1 + j = s_neigh%ja(k) + if ((1<=j).and.(j<=nr)) then + if (ilaggr(j) < 0) then + ip = ip + 1 + icol(ip) = j + end if + end if + enddo + if (ip > 0) then + icnt = icnt + 1 + naggr = naggr + 1 + ilaggr(i) = naggr + do k=1, ip + ilaggr(icol(k)) = naggr + end do + end if + end if + end do step3 + + + if (count(ilaggr<0) >0) then + info=psb_err_internal_error_ + call psb_errpush(info,name,a_err='Fatal error: some leftovers') + goto 9999 + endif + + if (naggr > ncol) then + write(0,*) name,'Error : naggr > ncol',naggr,ncol + info=psb_err_internal_error_ + call psb_errpush(info,name,a_err='Fatal error: naggr>ncol') + goto 9999 + end if + + call psb_realloc(ncol,ilaggr,info) + if (info /= psb_success_) then + info=psb_err_from_subroutine_ + ch_err='psb_realloc' + call psb_errpush(info,name,a_err=ch_err) + goto 9999 + end if + + allocate(nlaggr(np),stat=info) + if (info /= psb_success_) then + info=psb_err_alloc_request_ + call psb_errpush(info,name,i_err=(/np,izero,izero,izero,izero/),& + & a_err='integer') + goto 9999 + end if + + nlaggr(:) = 0 + nlaggr(me+1) = naggr + call psb_sum(ictxt,nlaggr(1:np)) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + +end subroutine mld_d_hyb_map_bld + diff --git a/mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 new file mode 100644 index 00000000..43506b48 --- /dev/null +++ b/mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 @@ -0,0 +1,122 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 +! +! Salvatore Filippone Cranfield University, UK +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_d_hybrid_aggregator_tprol.f90 +! +! Subroutine: mld_d_hybrid_aggregator_tprol +! Version: real +! +! +! This routine is mainly an interface to hyb_map_bld where the real work is performed. +! It takes care of some consistency checking, and calls map_to_tprol, which is +! refactored and shared among all the aggregation methods that produce a simple +! integer mapping. +! +! +! Arguments: +! p - type(mld_d_onelev_type), input/output. +! The 'one-level' data structure containing the control +! parameters and (eventually) coarse matrix and prolongator/restrictors. +! +! a - type(psb_dspmat_type). +! The sparse matrix structure containing the local part of the +! fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of a. +! ilaggr - integer, dimension(:), allocatable, output +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that on exit the indices +! will be shifted so as to make sure the ranges on the various processes do not +! overlap. +! nlaggr - integer, dimension(:), allocatable, output +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_dspmat_type), output +! The tentative prolongator, based on ilaggr. +! +! info - integer, output. +! Error code. +! +subroutine mld_d_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod + use mld_d_hybrid_aggregator_mod, mld_protect_name => mld_d_hybrid_aggregator_build_tprol + use mld_d_inner_mod + implicit none + class(mld_d_hybrid_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_dspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + ! Local variables + character(len=20) :: name + integer(psb_mpik_) :: ictxt, np, me + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: ntaggr + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_d_hybrid_aggregator_tprol' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(p%parms%ml_cycle,'Multilevel cycle',& + & mld_mult_ml_,is_legal_ml_cycle) + call mld_check_def(p%parms%par_aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_par_aggr_alg) + call mld_check_def(p%parms%aggr_ord,'Ordering',& + & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) + call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) + call mld_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + + call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + +end subroutine mld_d_hybrid_aggregator_build_tprol diff --git a/mlprec/impl/aggregator/mld_d_map_to_tprol.f90 b/mlprec/impl/aggregator/mld_d_map_to_tprol.f90 new file mode 100644 index 00000000..1688b979 --- /dev/null +++ b/mlprec/impl/aggregator/mld_d_map_to_tprol.f90 @@ -0,0 +1,150 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 +! +! Salvatore Filippone Cranfield University, UK +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_d_map_to_tprol.f90 +! +! Subroutine: mld_d_map_to_tprol +! Version: real +! +! This routine uses a mapping from the row indices of the fine-level matrix +! to the row indices of the coarse-level matrix to build a tentative +! prolongator, i.e. a piecewise constant operator. +! This is later used to build the final operator; the code has been refactored here +! to be shared among all the methods that provide the tentative prolongator +! through a simple integer mapping. +! +! The aggregation algorithm is a parallel version of that described in +! * M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! * P. Vanek, J. Mandel and M. Brezina, Algebraic Multigrid by Smoothed +! Aggregation for Second and Fourth Order Elliptic Problems, Computing, 56 +! (1996), 179-196. +! For more details see +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +! +! Arguments: +! aggr_type - integer, input. +! The scalar used to identify the aggregation algorithm. +! theta - real, input. +! The aggregation threshold used in the aggregation algorithm. +! 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. +! The communication descriptor of the fine-level matrix. +! ilaggr - integer, dimension(:), allocatable. +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that on exit the indices +! will be shifted so as to make sure the ranges on the various processes do not +! overlap. +! nlaggr - integer, dimension(:), allocatable. +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_dspmat_type). +! The tentative prolongator, based on ilaggr. +! +! info - integer, output. +! Error code. +! +subroutine mld_d_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + use psb_base_mod + use mld_d_inner_mod, mld_protect_name => mld_d_map_to_tprol + + implicit none + + ! Arguments + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:) + type(psb_dspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + ! Local variables + integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m,naggrm1, naggrp1, ntaggr + type(psb_d_coo_sparse_mat) :: tmpcoo + integer(psb_ipk_) :: debug_level, debug_unit,err_act + integer(psb_ipk_) :: ictxt,np,me + integer(psb_ipk_) :: nrow, ncol, n_ne + character(len=20) :: name, ch_err + + if(psb_get_errstatus() /= 0) return + info=psb_success_ + name = 'mld_map_to_tprol' + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + ! + ictxt=desc_a%get_context() + call psb_info(ictxt,me,np) + nrow = desc_a%get_local_rows() + ncol = desc_a%get_local_cols() + + naggr = nlaggr(me+1) + ntaggr = sum(nlaggr) + naggrm1 = sum(nlaggr(1:me)) + naggrp1 = sum(nlaggr(1:me+1)) + ilaggr(1:nrow) = ilaggr(1:nrow) + naggrm1 + call psb_halo(ilaggr,desc_a,info) + if (info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_halo') + goto 9999 + end if + + call tmpcoo%allocate(ncol,ntaggr,ncol) + do i=1,ncol + tmpcoo%val(i) = done + tmpcoo%ia(i) = i + tmpcoo%ja(i) = ilaggr(i) + end do + call tmpcoo%set_nzeros(ncol) + call tmpcoo%set_dupl(psb_dupl_add_) + call tmpcoo%set_sorted() ! At this point this is in row-major + call op_prol%mv_from(tmpcoo) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + +end subroutine mld_d_map_to_tprol diff --git a/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 new file mode 100644 index 00000000..8133b712 --- /dev/null +++ b/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 @@ -0,0 +1,141 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_d_symdec_aggregator_tprol.f90 +! +! Subroutine: mld_d_symdec_aggregator_tprol +! Version: real +! +! +! This routine is mainly an interface to dec_map_bld where the real work is performed. +! It takes care of some consistency checking, and calls map_to_tprol, which is +! refactored and shared among all the aggregation methods that produce a simple +! integer mapping. +! +! +! +! Arguments: +! p - type(mld_d_onelev_type), input/output. +! The 'one-level' data structure containing the control +! parameters and (eventually) coarse matrix and prolongator/restrictors. +! +! a - type(psb_dspmat_type). +! The sparse matrix structure containing the local part of the +! fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of a. +! ilaggr - integer, dimension(:), allocatable, output +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that on exit the indices +! will be shifted so as to make sure the ranges on the various processes do not +! overlap. +! nlaggr - integer, dimension(:), allocatable, output +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_dspmat_type), output +! The tentative prolongator, based on ilaggr. +! +! info - integer, output. +! Error code. +! +subroutine mld_d_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod + use mld_d_symdec_aggregator_mod, mld_protect_name => mld_d_symdec_aggregator_build_tprol + use mld_d_inner_mod + implicit none + class(mld_d_symdec_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_dspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + ! Local variables + type(psb_dspmat_type) :: atmp, atrans + character(len=20) :: name + integer(psb_mpik_) :: ictxt, np, me + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: ntaggr, nr + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_d_symdec_aggregator_tprol' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(parms%ml_type,'Multilevel type',& + & mld_mult_ml_,is_legal_ml_type) + call mld_check_def(parms%aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_aggr_alg) + call mld_check_def(parms%aggr_ord,'Ordering',& + & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) + call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) + + nr = a%get_nrows() + call a%csclip(atmp,info,imax=nr,jmax=nr,& + & rscale=.false.,cscale=.false.) + call atmp%set_nrows(nr) + call atmp%set_ncols(nr) + if (info == psb_success_) call atmp%transp(atrans) + if (info == psb_success_) call atrans%cscnv(info,type='COO') + if (info == psb_success_) call psb_rwextd(nr,atmp,info,b=atrans,rowscale=.false.) + call atmp%set_nrows(nr) + call atmp%set_ncols(nr) + if (info == psb_success_) call atrans%free() + if (info == psb_success_) call atmp%cscnv(info,type='CSR') + + if (info == psb_success_) & + & call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) + if (info == psb_success_) call atmp%free() + + if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + +end subroutine mld_d_symdec_aggregator_build_tprol diff --git a/mlprec/impl/mld_daggrmat_biz_asb.f90 b/mlprec/impl/aggregator/mld_daggrmat_biz_asb.f90 similarity index 100% rename from mlprec/impl/mld_daggrmat_biz_asb.f90 rename to mlprec/impl/aggregator/mld_daggrmat_biz_asb.f90 diff --git a/mlprec/impl/mld_daggrmat_minnrg_asb.f90 b/mlprec/impl/aggregator/mld_daggrmat_minnrg_asb.f90 similarity index 100% rename from mlprec/impl/mld_daggrmat_minnrg_asb.f90 rename to mlprec/impl/aggregator/mld_daggrmat_minnrg_asb.f90 diff --git a/mlprec/impl/mld_daggrmat_nosmth_asb.f90 b/mlprec/impl/aggregator/mld_daggrmat_nosmth_asb.f90 similarity index 100% rename from mlprec/impl/mld_daggrmat_nosmth_asb.f90 rename to mlprec/impl/aggregator/mld_daggrmat_nosmth_asb.f90 diff --git a/mlprec/impl/mld_daggrmat_smth_asb.f90 b/mlprec/impl/aggregator/mld_daggrmat_smth_asb.f90 similarity index 100% rename from mlprec/impl/mld_daggrmat_smth_asb.f90 rename to mlprec/impl/aggregator/mld_daggrmat_smth_asb.f90 diff --git a/mlprec/impl/aggregator/mld_s_base_aggregator_mat_asb.f90 b/mlprec/impl/aggregator/mld_s_base_aggregator_mat_asb.f90 new file mode 100644 index 00000000..4464cc84 --- /dev/null +++ b/mlprec/impl/aggregator/mld_s_base_aggregator_mat_asb.f90 @@ -0,0 +1,225 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_s_base_aggregator_mat_asb.f90 +! +! Subroutine: mld_s_base_aggregator_mat_asb +! Version: real +! +! This routine builds the matrix associated to the current level of the +! multilevel preconditioner from the matrix associated to the previous level, +! by using the user-specified aggregation technique (therefore, it also builds the +! prolongation and restriction operators mapping the current level to the +! previous one and vice versa). +! The current level is regarded as the coarse one, while the previous as +! the fine one. This is in agreement with the fact that the routine is called, +! by mld_mlprec_bld, only on levels >=2. +! The coarse-level matrix A_C is built from a fine-level matrix A +! by using the Galerkin approach, i.e. +! +! A_C = P_C^T A P_C, +! +! where P_C is a prolongator from the coarse level to the fine one. +! +! A mapping from the nodes of the adjacency graph of A to the nodes of the +! adjacency graph of A_C has been computed by the mld_aggrmap_bld subroutine. +! The prolongator P_C is built here from this mapping, according to the +! value of p%iprcparm(mld_aggr_kind_), specified by the user through +! mld_sprecinit and mld_zprecset. +! On output from this routine the entries of AC, op_prol, op_restr +! are still in "global numbering" mode; this is fixed in the calling routine +! mld_s_lev_aggrmat_asb. +! +! Currently four different prolongators are implemented, corresponding to +! four aggregation algorithms: +! 1. un-smoothed aggregation, +! 2. smoothed aggregation, +! 3. "bizarre" aggregation. +! 4. minimum energy +! 1. The non-smoothed aggregation uses as prolongator the piecewise constant +! interpolation operator corresponding to the fine-to-coarse level mapping built +! by p%aggr%bld_tprol. This is called tentative prolongator. +! 2. The smoothed aggregation uses as prolongator the operator obtained by applying +! a damped Jacobi smoother to the tentative prolongator. +! 3. The "bizarre" aggregation uses a prolongator proposed by the authors of MLD2P4. +! This prolongator still requires a deep analysis and testing and its use is +! not recommended. +! 4. Minimum energy aggregation +! +! For more details see +! M. Brezina and P. Vanek, A black-box iterative solver based on a two-level +! Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of PSBLAS-based +! parallel two-level Schwarz preconditioners, Appl. Num. Math., 57 (2007), +! 1181-1196. +! M. Sala, R. Tuminaro: A new Petrov-Galerkin smoothed aggregation preconditioner +! for nonsymmetric linear systems, SIAM J. Sci. Comput., 31(1):143-166 (2008) +! +! +! The main structure is: +! 1. Perform sanity checks; +! 2. Compute prolongator/restrictor/AC +! +! +! Arguments: +! ag - type(mld_s_base_aggregator_type), input/output. +! The aggregator object +! parms - type(mld_sml_parms), input +! The aggregation parameters +! a - type(psb_sspmat_type), input. +! The sparse matrix structure containing the local part of +! the fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of the fine-level matrix. +! The 'one-level' data structure that will contain the local +! part of the matrix to be built as well as the information +! concerning the prolongator and its transpose. +! ilaggr - integer, dimension(:), input +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that the indices +! are assumed to be shifted so as to make sure the ranges on +! the various processes do not overlap. +! nlaggr - integer, dimension(:) input +! nlaggr(i) contains the aggregates held by process i. +! ac - type(psb_sspmat_type), output +! The coarse matrix on output +! +! op_prol - type(psb_sspmat_type), input/output +! The tentative prolongator on input, the computed prolongator on output +! +! op_restr - type(psb_sspmat_type), output +! The restrictor operator; normally, it is the transpose of the prolongator. +! +! info - integer, output. +! Error code. +! +subroutine mld_s_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) + use psb_base_mod + use mld_s_inner_mod, mld_protect_name => mld_s_base_aggregator_mat_asb + implicit none + + class(mld_s_base_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_sspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) + type(psb_sspmat_type), intent(inout) :: op_prol + type(psb_sspmat_type), intent(out) :: ac,op_restr + integer(psb_ipk_), intent(out) :: info + + ! Local variables + character(len=20) :: name + integer(psb_mpik_) :: ictxt, np, me + type(psb_s_coo_sparse_mat) :: acoo, bcoo + type(psb_s_csr_sparse_mat) :: acsr1 + integer(psb_ipk_) :: nzl,ntaggr + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_s_base_aggregator_mat_asb' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(parms%aggr_kind,'Smoother',& + & mld_smooth_prol_,is_legal_ml_aggr_kind) + call mld_check_def(parms%coarse_mat,'Coarse matrix',& + & mld_distr_mat_,is_legal_ml_coarse_mat) + call mld_check_def(parms%aggr_filter,'Use filtered matrix',& + & mld_no_filter_mat_,is_legal_aggr_filter) + call mld_check_def(parms%smoother_pos,'smooth_pos',& + & mld_pre_smooth_,is_legal_ml_smooth_pos) + call mld_check_def(parms%aggr_omega_alg,'Omega Alg.',& + & mld_eig_est_,is_legal_ml_aggr_omega_alg) + call mld_check_def(parms%aggr_eig,'Eigenvalue estimate',& + & mld_max_norm_,is_legal_ml_aggr_eig) + call mld_check_def(parms%aggr_omega_val,'Omega',szero,is_legal_s_omega) + + ! + ! Build the coarse-level matrix from the fine-level one, starting from + ! the mapping defined by mld_aggrmap_bld and applying the aggregation + ! algorithm specified by p%iprcparm(mld_aggr_kind_) + ! + select case (parms%aggr_kind) + case (mld_no_smooth_) + + call mld_saggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,& + & parms,ac,op_prol,op_restr,info) + + case(mld_smooth_prol_) + + call mld_saggrmat_smth_asb(a,desc_a,ilaggr,nlaggr, & + & parms,ac,op_prol,op_restr,info) + + case(mld_biz_prol_) + + call mld_saggrmat_biz_asb(a,desc_a,ilaggr,nlaggr, & + & parms,ac,op_prol,op_restr,info) + + case(mld_min_energy_) + + call mld_saggrmat_minnrg_asb(a,desc_a,ilaggr,nlaggr, & + & parms,ac,op_prol,op_restr,info) + + case default + info = psb_err_internal_error_ + call psb_errpush(info,name,a_err='Invalid aggr kind') + goto 9999 + + end select + if (info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='Inner aggrmat asb') + goto 9999 + end if + + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + + +end subroutine mld_s_base_aggregator_mat_asb diff --git a/mlprec/impl/aggregator/mld_s_base_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_s_base_aggregator_tprol.f90 new file mode 100644 index 00000000..bf83a553 --- /dev/null +++ b/mlprec/impl/aggregator/mld_s_base_aggregator_tprol.f90 @@ -0,0 +1,124 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_s_base_aggregator_tprol.f90 +! +! Subroutine: mld_s_base_aggregator_tprol +! Version: real +! +! This routine is mainly an interface to dec_map_bld where the real work is performed. +! It takes care of some consistency checking, and calls map_to_tprol, which is +! refactored and shared among all the aggregation methods that produce a simple +! integer mapping. +! +! +! Arguments: +! p - type(mld_s_onelev_type), input/output. +! The 'one-level' data structure containing the control +! parameters and (eventually) coarse matrix and prolongator/restrictors. +! +! a - type(psb_sspmat_type). +! The sparse matrix structure containing the local part of the +! fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of a. +! ilaggr - integer, dimension(:), allocatable, output +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that on exit the indices +! will be shifted so as to make sure the ranges on the various processes do not +! overlap. +! nlaggr - integer, dimension(:), allocatable, output +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_sspmat_type), output +! The tentative prolongator, based on ilaggr. +! +! info - integer, output. +! Error code. +! +subroutine mld_s_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod +! use mld_s_base_aggregator_mod + use mld_s_inner_mod, mld_protect_name => mld_s_base_aggregator_build_tprol + implicit none + class(mld_s_base_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_sspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_sspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + ! Local variables + character(len=20) :: name + integer(psb_mpik_) :: ictxt, np, me + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: ntaggr + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_s_base_aggregator_tprol' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(parms%ml_type,'Multilevel type',& + & mld_mult_ml_,is_legal_ml_type) + call mld_check_def(parms%aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_aggr_alg) + call mld_check_def(parms%aggr_ord,'Ordering',& + & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) + call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) + + + call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + + call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + +end subroutine mld_s_base_aggregator_build_tprol diff --git a/mlprec/impl/mld_s_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_s_dec_map_bld.f90 similarity index 100% rename from mlprec/impl/mld_s_dec_map_bld.f90 rename to mlprec/impl/aggregator/mld_s_dec_map_bld.f90 diff --git a/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 new file mode 100644 index 00000000..8331ae05 --- /dev/null +++ b/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 @@ -0,0 +1,328 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! File: mld_s_hyb_map__bld.f90 +! +! Subroutine: mld_s_hyb_map_bld +! Version: real +! +! This routine builds the tentative prolongator based on the +! decoupled aggregation algorithm presented in +! +! M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +! Note: upon exit +! +! Arguments: +! a - type(psb_sspmat_type). +! The sparse matrix structure containing the local part of the +! matrix to be preconditioned. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of a. +! p - type(mld_sprec_type), input/output. +! The preconditioner data structure; upon exit it contains +! the multilevel hierarchy of prolongators, restrictors +! and coarse matrices. +! info - integer, output. +! Error code. +! +! +! +subroutine mld_s_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + + use psb_base_mod + use mld_s_inner_mod, mld_protect_name => mld_s_hyb_map_bld + + implicit none + + ! Arguments + integer(psb_ipk_), intent(in) :: iorder + type(psb_sspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + real(psb_spk_), intent(in) :: theta + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + integer(psb_ipk_), intent(out) :: info + + ! Local variables + integer(psb_ipk_), allocatable :: ils(:), neigh(:), irow(:), icol(:),& + & ideg(:), idxs(:), tmpaggr(:) + real(psb_spk_), allocatable :: val(:), diag(:) + integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m, nz, ilg, ii, ip, ip1,nzcnt + type(psb_s_csr_sparse_mat) :: acsr, muij, s_neigh + type(psb_s_coo_sparse_mat) :: s_neigh_coo + real(psb_spk_) :: cpling, tcl + logical :: disjoint + integer(psb_ipk_) :: debug_level, debug_unit,err_act + integer(psb_ipk_) :: ictxt,np,me + integer(psb_ipk_) :: nrow, ncol, n_ne + character(len=20) :: name, ch_err + + if (psb_get_errstatus() /= 0) return + info=psb_success_ + name = 'mld_hyb_map_bld' + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + ! + ictxt=desc_a%get_context() + call psb_info(ictxt,me,np) + nrow = desc_a%get_local_rows() + ncol = desc_a%get_local_cols() + + nr = a%get_nrows() + allocate(ilaggr(nr),neigh(nr),ideg(nr),idxs(nr),icol(nr),stat=info) + if(info /= psb_success_) then + info=psb_err_alloc_request_ + call psb_errpush(info,name,i_err=(/2*nr,izero,izero,izero,izero/),& + & a_err='integer') + goto 9999 + end if + + diag = a%get_diag(info) + if(info /= psb_success_) then + info=psb_err_from_subroutine_ + call psb_errpush(info,name,a_err='psb_sp_getdiag') + goto 9999 + end if + + ! + ! Phase zero: compute muij + ! + call a%cp_to(muij) + do i=1, nr + do k=muij%irp(i),muij%irp(i+1)-1 + j = muij%ja(k) + muij%val(k) = abs(muij%val(k))/sqrt(abs(diag(i)*diag(j))) + end do + end do + !write(*,*) 'murows/cols ',maxval(mu_rows),maxval(mu_cols) + ! + ! Compute the 1-neigbour; mark strong links with +1, weak links with -1 + ! + call s_neigh_coo%allocate(nr,nr,muij%get_nzeros()) + ip = 0 + do i=1, nr + do k=muij%irp(i),muij%irp(i+1)-1 + j = muij%ja(k) + ip = ip + 1 + s_neigh_coo%ia(ip) = i + s_neigh_coo%ja(ip) = j + if (real(muij%val(k)) >= theta) then + s_neigh_coo%val(ip) = sone + else + s_neigh_coo%val(ip) = -sone + end if + end do + end do + !write(*,*) 'S_NEIGH: ',nr,ip + call s_neigh_coo%set_nzeros(ip) + call s_neigh%mv_from_coo(s_neigh_coo,info) + + if (iorder == mld_aggr_ord_nat_) then + do i=1, nr + ilaggr(i) = -(nr+1) + idxs(i) = i + end do + else + do i=1, nr + ilaggr(i) = -(nr+1) + ideg(i) = muij%irp(i+1) - muij%irp(i) + end do + call psb_msort(ideg,ix=idxs,dir=psb_sort_down_) + end if + + + ! + ! Phase one: Start with disjoint groups. + ! + naggr = 0 + icnt = 0 + step1: do ii=1, nr + i = idxs(ii) + + if (ilaggr(i) == -(nr+1)) then + ! + ! Get the 1-neighbourhood of I + ! + ip1 = s_neigh%irp(i) + nz = s_neigh%irp(i+1)-ip1 + ! + ! If the neighbourhood only contains I, skip it + ! + if (nz ==0) then + ilaggr(i) = 0 + cycle step1 + end if + if ((nz==1).and.(s_neigh%ja(ip1)==i)) then + ilaggr(i) = 0 + cycle step1 + end if + ! + ! If the whole strongly coupled neighborhood of I is + ! as yet unconnected, turn it into the next aggregate. + ! + nzcnt = count(real(s_neigh%val(ip1:ip1+nz-1)) > 0) + icol(1:nzcnt) = pack(s_neigh%ja(ip1:ip1+nz-1),(real(s_neigh%val(ip1:ip1+nz-1)) > 0)) + disjoint = all(ilaggr(icol(1:nzcnt)) == -(nr+1)) + if (disjoint) then + icnt = icnt + 1 + naggr = naggr + 1 + do k=1, nzcnt + ilaggr(icol(k)) = naggr + end do + ilaggr(i) = naggr + end if + endif + enddo step1 + + if (debug_level >= psb_debug_outer_) then + write(debug_unit,*) me,' ',trim(name),& + & ' Check 1:',count(ilaggr == -(nr+1)) + end if + + ! + ! Phase two: join the neighbours + ! + tmpaggr = ilaggr + step2: do ii=1,nr + i = idxs(ii) + + if (ilaggr(i) == -(nr+1)) then + ! + ! Find the most strongly connected neighbour that is + ! already aggregated, if any, and join its aggregate + ! + cpling = szero + ip = 0 + do k=s_neigh%irp(i), s_neigh%irp(i+1)-1 + j = s_neigh%ja(k) + if ((1<=j).and.(j<=nr)) then + if ( (tmpaggr(j) > 0).and. (real(muij%val(k)) > cpling)& + & .and.(real(s_neigh%val(k))>0)) then + ip = k + cpling = muij%val(k) + end if + end if + enddo + if (ip > 0) then + ilaggr(i) = ilaggr(s_neigh%ja(ip)) + end if + end if + end do step2 + + + ! + ! Phase three: sweep over leftovers, if any + ! + step3: do ii=1,nr + i = idxs(ii) + + if (ilaggr(i) < 0) then + ! + ! Find its strongly connected neighbourhood not + ! already aggregated, and make it into a new aggregate. + ! + ip = 0 + do k=s_neigh%irp(i), s_neigh%irp(i+1)-1 + j = s_neigh%ja(k) + if ((1<=j).and.(j<=nr)) then + if (ilaggr(j) < 0) then + ip = ip + 1 + icol(ip) = j + end if + end if + enddo + if (ip > 0) then + icnt = icnt + 1 + naggr = naggr + 1 + ilaggr(i) = naggr + do k=1, ip + ilaggr(icol(k)) = naggr + end do + end if + end if + end do step3 + + + if (count(ilaggr<0) >0) then + info=psb_err_internal_error_ + call psb_errpush(info,name,a_err='Fatal error: some leftovers') + goto 9999 + endif + + if (naggr > ncol) then + write(0,*) name,'Error : naggr > ncol',naggr,ncol + info=psb_err_internal_error_ + call psb_errpush(info,name,a_err='Fatal error: naggr>ncol') + goto 9999 + end if + + call psb_realloc(ncol,ilaggr,info) + if (info /= psb_success_) then + info=psb_err_from_subroutine_ + ch_err='psb_realloc' + call psb_errpush(info,name,a_err=ch_err) + goto 9999 + end if + + allocate(nlaggr(np),stat=info) + if (info /= psb_success_) then + info=psb_err_alloc_request_ + call psb_errpush(info,name,i_err=(/np,izero,izero,izero,izero/),& + & a_err='integer') + goto 9999 + end if + + nlaggr(:) = 0 + nlaggr(me+1) = naggr + call psb_sum(ictxt,nlaggr(1:np)) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + +end subroutine mld_s_hyb_map_bld + diff --git a/mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 new file mode 100644 index 00000000..806f3184 --- /dev/null +++ b/mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 @@ -0,0 +1,122 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 +! +! Salvatore Filippone Cranfield University, UK +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_s_hybrid_aggregator_tprol.f90 +! +! Subroutine: mld_s_hybrid_aggregator_tprol +! Version: real +! +! +! This routine is mainly an interface to hyb_map_bld where the real work is performed. +! It takes care of some consistency checking, and calls map_to_tprol, which is +! refactored and shared among all the aggregation methods that produce a simple +! integer mapping. +! +! +! Arguments: +! p - type(mld_s_onelev_type), input/output. +! The 'one-level' data structure containing the control +! parameters and (eventually) coarse matrix and prolongator/restrictors. +! +! a - type(psb_sspmat_type). +! The sparse matrix structure containing the local part of the +! fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of a. +! ilaggr - integer, dimension(:), allocatable, output +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that on exit the indices +! will be shifted so as to make sure the ranges on the various processes do not +! overlap. +! nlaggr - integer, dimension(:), allocatable, output +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_sspmat_type), output +! The tentative prolongator, based on ilaggr. +! +! info - integer, output. +! Error code. +! +subroutine mld_s_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod + use mld_s_hybrid_aggregator_mod, mld_protect_name => mld_s_hybrid_aggregator_build_tprol + use mld_s_inner_mod + implicit none + class(mld_s_hybrid_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_sspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_sspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + ! Local variables + character(len=20) :: name + integer(psb_mpik_) :: ictxt, np, me + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: ntaggr + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_s_hybrid_aggregator_tprol' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(p%parms%ml_cycle,'Multilevel cycle',& + & mld_mult_ml_,is_legal_ml_cycle) + call mld_check_def(p%parms%par_aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_par_aggr_alg) + call mld_check_def(p%parms%aggr_ord,'Ordering',& + & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) + call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) + call mld_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + + call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + +end subroutine mld_s_hybrid_aggregator_build_tprol diff --git a/mlprec/impl/aggregator/mld_s_map_to_tprol.f90 b/mlprec/impl/aggregator/mld_s_map_to_tprol.f90 new file mode 100644 index 00000000..0b41787c --- /dev/null +++ b/mlprec/impl/aggregator/mld_s_map_to_tprol.f90 @@ -0,0 +1,150 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 +! +! Salvatore Filippone Cranfield University, UK +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_s_map_to_tprol.f90 +! +! Subroutine: mld_s_map_to_tprol +! Version: real +! +! This routine uses a mapping from the row indices of the fine-level matrix +! to the row indices of the coarse-level matrix to build a tentative +! prolongator, i.e. a piecewise constant operator. +! This is later used to build the final operator; the code has been refactored here +! to be shared among all the methods that provide the tentative prolongator +! through a simple integer mapping. +! +! The aggregation algorithm is a parallel version of that described in +! * M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! * P. Vanek, J. Mandel and M. Brezina, Algebraic Multigrid by Smoothed +! Aggregation for Second and Fourth Order Elliptic Problems, Computing, 56 +! (1996), 179-196. +! For more details see +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +! +! Arguments: +! aggr_type - integer, input. +! The scalar used to identify the aggregation algorithm. +! theta - real, input. +! The aggregation threshold used in the aggregation algorithm. +! a - type(psb_sspmat_type), input. +! The sparse matrix structure containing the local part of +! the fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of the fine-level matrix. +! ilaggr - integer, dimension(:), allocatable. +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that on exit the indices +! will be shifted so as to make sure the ranges on the various processes do not +! overlap. +! nlaggr - integer, dimension(:), allocatable. +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_sspmat_type). +! The tentative prolongator, based on ilaggr. +! +! info - integer, output. +! Error code. +! +subroutine mld_s_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + use psb_base_mod + use mld_s_inner_mod, mld_protect_name => mld_s_map_to_tprol + + implicit none + + ! Arguments + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:) + type(psb_sspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + ! Local variables + integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m,naggrm1, naggrp1, ntaggr + type(psb_s_coo_sparse_mat) :: tmpcoo + integer(psb_ipk_) :: debug_level, debug_unit,err_act + integer(psb_ipk_) :: ictxt,np,me + integer(psb_ipk_) :: nrow, ncol, n_ne + character(len=20) :: name, ch_err + + if(psb_get_errstatus() /= 0) return + info=psb_success_ + name = 'mld_map_to_tprol' + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + ! + ictxt=desc_a%get_context() + call psb_info(ictxt,me,np) + nrow = desc_a%get_local_rows() + ncol = desc_a%get_local_cols() + + naggr = nlaggr(me+1) + ntaggr = sum(nlaggr) + naggrm1 = sum(nlaggr(1:me)) + naggrp1 = sum(nlaggr(1:me+1)) + ilaggr(1:nrow) = ilaggr(1:nrow) + naggrm1 + call psb_halo(ilaggr,desc_a,info) + if (info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_halo') + goto 9999 + end if + + call tmpcoo%allocate(ncol,ntaggr,ncol) + do i=1,ncol + tmpcoo%val(i) = sone + tmpcoo%ia(i) = i + tmpcoo%ja(i) = ilaggr(i) + end do + call tmpcoo%set_nzeros(ncol) + call tmpcoo%set_dupl(psb_dupl_add_) + call tmpcoo%set_sorted() ! At this point this is in row-major + call op_prol%mv_from(tmpcoo) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + +end subroutine mld_s_map_to_tprol diff --git a/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 new file mode 100644 index 00000000..b73fe100 --- /dev/null +++ b/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 @@ -0,0 +1,141 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_s_symdec_aggregator_tprol.f90 +! +! Subroutine: mld_s_symdec_aggregator_tprol +! Version: real +! +! +! This routine is mainly an interface to dec_map_bld where the real work is performed. +! It takes care of some consistency checking, and calls map_to_tprol, which is +! refactored and shared among all the aggregation methods that produce a simple +! integer mapping. +! +! +! +! Arguments: +! p - type(mld_s_onelev_type), input/output. +! The 'one-level' data structure containing the control +! parameters and (eventually) coarse matrix and prolongator/restrictors. +! +! a - type(psb_sspmat_type). +! The sparse matrix structure containing the local part of the +! fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of a. +! ilaggr - integer, dimension(:), allocatable, output +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that on exit the indices +! will be shifted so as to make sure the ranges on the various processes do not +! overlap. +! nlaggr - integer, dimension(:), allocatable, output +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_sspmat_type), output +! The tentative prolongator, based on ilaggr. +! +! info - integer, output. +! Error code. +! +subroutine mld_s_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod + use mld_s_symdec_aggregator_mod, mld_protect_name => mld_s_symdec_aggregator_build_tprol + use mld_s_inner_mod + implicit none + class(mld_s_symdec_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_sspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_sspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + ! Local variables + type(psb_sspmat_type) :: atmp, atrans + character(len=20) :: name + integer(psb_mpik_) :: ictxt, np, me + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: ntaggr, nr + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_s_symdec_aggregator_tprol' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(parms%ml_type,'Multilevel type',& + & mld_mult_ml_,is_legal_ml_type) + call mld_check_def(parms%aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_aggr_alg) + call mld_check_def(parms%aggr_ord,'Ordering',& + & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) + call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) + + nr = a%get_nrows() + call a%csclip(atmp,info,imax=nr,jmax=nr,& + & rscale=.false.,cscale=.false.) + call atmp%set_nrows(nr) + call atmp%set_ncols(nr) + if (info == psb_success_) call atmp%transp(atrans) + if (info == psb_success_) call atrans%cscnv(info,type='COO') + if (info == psb_success_) call psb_rwextd(nr,atmp,info,b=atrans,rowscale=.false.) + call atmp%set_nrows(nr) + call atmp%set_ncols(nr) + if (info == psb_success_) call atrans%free() + if (info == psb_success_) call atmp%cscnv(info,type='CSR') + + if (info == psb_success_) & + & call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) + if (info == psb_success_) call atmp%free() + + if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + +end subroutine mld_s_symdec_aggregator_build_tprol diff --git a/mlprec/impl/mld_saggrmat_biz_asb.f90 b/mlprec/impl/aggregator/mld_saggrmat_biz_asb.f90 similarity index 100% rename from mlprec/impl/mld_saggrmat_biz_asb.f90 rename to mlprec/impl/aggregator/mld_saggrmat_biz_asb.f90 diff --git a/mlprec/impl/mld_saggrmat_minnrg_asb.f90 b/mlprec/impl/aggregator/mld_saggrmat_minnrg_asb.f90 similarity index 100% rename from mlprec/impl/mld_saggrmat_minnrg_asb.f90 rename to mlprec/impl/aggregator/mld_saggrmat_minnrg_asb.f90 diff --git a/mlprec/impl/mld_saggrmat_nosmth_asb.f90 b/mlprec/impl/aggregator/mld_saggrmat_nosmth_asb.f90 similarity index 100% rename from mlprec/impl/mld_saggrmat_nosmth_asb.f90 rename to mlprec/impl/aggregator/mld_saggrmat_nosmth_asb.f90 diff --git a/mlprec/impl/mld_saggrmat_smth_asb.f90 b/mlprec/impl/aggregator/mld_saggrmat_smth_asb.f90 similarity index 100% rename from mlprec/impl/mld_saggrmat_smth_asb.f90 rename to mlprec/impl/aggregator/mld_saggrmat_smth_asb.f90 diff --git a/mlprec/impl/aggregator/mld_z_base_aggregator_mat_asb.f90 b/mlprec/impl/aggregator/mld_z_base_aggregator_mat_asb.f90 new file mode 100644 index 00000000..5bda2a48 --- /dev/null +++ b/mlprec/impl/aggregator/mld_z_base_aggregator_mat_asb.f90 @@ -0,0 +1,225 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_z_base_aggregator_mat_asb.f90 +! +! Subroutine: mld_z_base_aggregator_mat_asb +! Version: complex +! +! This routine builds the matrix associated to the current level of the +! multilevel preconditioner from the matrix associated to the previous level, +! by using the user-specified aggregation technique (therefore, it also builds the +! prolongation and restriction operators mapping the current level to the +! previous one and vice versa). +! The current level is regarded as the coarse one, while the previous as +! the fine one. This is in agreement with the fact that the routine is called, +! by mld_mlprec_bld, only on levels >=2. +! The coarse-level matrix A_C is built from a fine-level matrix A +! by using the Galerkin approach, i.e. +! +! A_C = P_C^T A P_C, +! +! where P_C is a prolongator from the coarse level to the fine one. +! +! A mapping from the nodes of the adjacency graph of A to the nodes of the +! adjacency graph of A_C has been computed by the mld_aggrmap_bld subroutine. +! The prolongator P_C is built here from this mapping, according to the +! value of p%iprcparm(mld_aggr_kind_), specified by the user through +! mld_zprecinit and mld_zprecset. +! On output from this routine the entries of AC, op_prol, op_restr +! are still in "global numbering" mode; this is fixed in the calling routine +! mld_z_lev_aggrmat_asb. +! +! Currently four different prolongators are implemented, corresponding to +! four aggregation algorithms: +! 1. un-smoothed aggregation, +! 2. smoothed aggregation, +! 3. "bizarre" aggregation. +! 4. minimum energy +! 1. The non-smoothed aggregation uses as prolongator the piecewise constant +! interpolation operator corresponding to the fine-to-coarse level mapping built +! by p%aggr%bld_tprol. This is called tentative prolongator. +! 2. The smoothed aggregation uses as prolongator the operator obtained by applying +! a damped Jacobi smoother to the tentative prolongator. +! 3. The "bizarre" aggregation uses a prolongator proposed by the authors of MLD2P4. +! This prolongator still requires a deep analysis and testing and its use is +! not recommended. +! 4. Minimum energy aggregation +! +! For more details see +! M. Brezina and P. Vanek, A black-box iterative solver based on a two-level +! Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of PSBLAS-based +! parallel two-level Schwarz preconditioners, Appl. Num. Math., 57 (2007), +! 1181-1196. +! M. Sala, R. Tuminaro: A new Petrov-Galerkin smoothed aggregation preconditioner +! for nonsymmetric linear systems, SIAM J. Sci. Comput., 31(1):143-166 (2008) +! +! +! The main structure is: +! 1. Perform sanity checks; +! 2. Compute prolongator/restrictor/AC +! +! +! Arguments: +! ag - type(mld_z_base_aggregator_type), input/output. +! The aggregator object +! parms - type(mld_dml_parms), input +! The aggregation parameters +! 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. +! The communication descriptor of the fine-level matrix. +! The 'one-level' data structure that will contain the local +! part of the matrix to be built as well as the information +! concerning the prolongator and its transpose. +! ilaggr - integer, dimension(:), input +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that the indices +! are assumed to be shifted so as to make sure the ranges on +! the various processes do not overlap. +! nlaggr - integer, dimension(:) input +! nlaggr(i) contains the aggregates held by process i. +! ac - type(psb_zspmat_type), output +! The coarse matrix on output +! +! op_prol - type(psb_zspmat_type), input/output +! The tentative prolongator on input, the computed prolongator on output +! +! op_restr - type(psb_zspmat_type), output +! The restrictor operator; normally, it is the transpose of the prolongator. +! +! info - integer, output. +! Error code. +! +subroutine mld_z_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) + use psb_base_mod + use mld_z_inner_mod, mld_protect_name => mld_z_base_aggregator_mat_asb + implicit none + + class(mld_z_base_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_zspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) + type(psb_zspmat_type), intent(inout) :: op_prol + type(psb_zspmat_type), intent(out) :: ac,op_restr + integer(psb_ipk_), intent(out) :: info + + ! Local variables + character(len=20) :: name + integer(psb_mpik_) :: ictxt, np, me + type(psb_z_coo_sparse_mat) :: acoo, bcoo + type(psb_z_csr_sparse_mat) :: acsr1 + integer(psb_ipk_) :: nzl,ntaggr + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_z_base_aggregator_mat_asb' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(parms%aggr_kind,'Smoother',& + & mld_smooth_prol_,is_legal_ml_aggr_kind) + call mld_check_def(parms%coarse_mat,'Coarse matrix',& + & mld_distr_mat_,is_legal_ml_coarse_mat) + call mld_check_def(parms%aggr_filter,'Use filtered matrix',& + & mld_no_filter_mat_,is_legal_aggr_filter) + call mld_check_def(parms%smoother_pos,'smooth_pos',& + & mld_pre_smooth_,is_legal_ml_smooth_pos) + call mld_check_def(parms%aggr_omega_alg,'Omega Alg.',& + & mld_eig_est_,is_legal_ml_aggr_omega_alg) + call mld_check_def(parms%aggr_eig,'Eigenvalue estimate',& + & mld_max_norm_,is_legal_ml_aggr_eig) + call mld_check_def(parms%aggr_omega_val,'Omega',dzero,is_legal_d_omega) + + ! + ! Build the coarse-level matrix from the fine-level one, starting from + ! the mapping defined by mld_aggrmap_bld and applying the aggregation + ! algorithm specified by p%iprcparm(mld_aggr_kind_) + ! + select case (parms%aggr_kind) + case (mld_no_smooth_) + + call mld_zaggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,& + & parms,ac,op_prol,op_restr,info) + + case(mld_smooth_prol_) + + call mld_zaggrmat_smth_asb(a,desc_a,ilaggr,nlaggr, & + & parms,ac,op_prol,op_restr,info) + + case(mld_biz_prol_) + + call mld_zaggrmat_biz_asb(a,desc_a,ilaggr,nlaggr, & + & parms,ac,op_prol,op_restr,info) + + case(mld_min_energy_) + + call mld_zaggrmat_minnrg_asb(a,desc_a,ilaggr,nlaggr, & + & parms,ac,op_prol,op_restr,info) + + case default + info = psb_err_internal_error_ + call psb_errpush(info,name,a_err='Invalid aggr kind') + goto 9999 + + end select + if (info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='Inner aggrmat asb') + goto 9999 + end if + + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + + +end subroutine mld_z_base_aggregator_mat_asb diff --git a/mlprec/impl/aggregator/mld_z_base_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_z_base_aggregator_tprol.f90 new file mode 100644 index 00000000..81d8910f --- /dev/null +++ b/mlprec/impl/aggregator/mld_z_base_aggregator_tprol.f90 @@ -0,0 +1,124 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_z_base_aggregator_tprol.f90 +! +! Subroutine: mld_z_base_aggregator_tprol +! Version: complex +! +! This routine is mainly an interface to dec_map_bld where the real work is performed. +! It takes care of some consistency checking, and calls map_to_tprol, which is +! refactored and shared among all the aggregation methods that produce a simple +! integer mapping. +! +! +! Arguments: +! p - type(mld_z_onelev_type), input/output. +! The 'one-level' data structure containing the control +! parameters and (eventually) coarse matrix and prolongator/restrictors. +! +! a - type(psb_zspmat_type). +! The sparse matrix structure containing the local part of the +! fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of a. +! ilaggr - integer, dimension(:), allocatable, output +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that on exit the indices +! will be shifted so as to make sure the ranges on the various processes do not +! overlap. +! nlaggr - integer, dimension(:), allocatable, output +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_zspmat_type), output +! The tentative prolongator, based on ilaggr. +! +! info - integer, output. +! Error code. +! +subroutine mld_z_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod +! use mld_z_base_aggregator_mod + use mld_z_inner_mod, mld_protect_name => mld_z_base_aggregator_build_tprol + implicit none + class(mld_z_base_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_zspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_zspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + ! Local variables + character(len=20) :: name + integer(psb_mpik_) :: ictxt, np, me + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: ntaggr + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_z_base_aggregator_tprol' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(parms%ml_type,'Multilevel type',& + & mld_mult_ml_,is_legal_ml_type) + call mld_check_def(parms%aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_aggr_alg) + call mld_check_def(parms%aggr_ord,'Ordering',& + & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) + call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) + + + call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + + call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + +end subroutine mld_z_base_aggregator_build_tprol diff --git a/mlprec/impl/mld_z_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_z_dec_map_bld.f90 similarity index 100% rename from mlprec/impl/mld_z_dec_map_bld.f90 rename to mlprec/impl/aggregator/mld_z_dec_map_bld.f90 diff --git a/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 new file mode 100644 index 00000000..cc795465 --- /dev/null +++ b/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 @@ -0,0 +1,328 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! File: mld_z_hyb_map__bld.f90 +! +! Subroutine: mld_z_hyb_map_bld +! Version: complex +! +! This routine builds the tentative prolongator based on the +! decoupled aggregation algorithm presented in +! +! M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +! Note: upon exit +! +! Arguments: +! 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. +! The communication descriptor of a. +! p - type(mld_zprec_type), input/output. +! The preconditioner data structure; upon exit it contains +! the multilevel hierarchy of prolongators, restrictors +! and coarse matrices. +! info - integer, output. +! Error code. +! +! +! +subroutine mld_z_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + + use psb_base_mod + use mld_z_inner_mod, mld_protect_name => mld_z_hyb_map_bld + + implicit none + + ! Arguments + integer(psb_ipk_), intent(in) :: iorder + type(psb_zspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + real(psb_dpk_), intent(in) :: theta + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + integer(psb_ipk_), intent(out) :: info + + ! Local variables + integer(psb_ipk_), allocatable :: ils(:), neigh(:), irow(:), icol(:),& + & ideg(:), idxs(:), tmpaggr(:) + complex(psb_dpk_), allocatable :: val(:), diag(:) + integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m, nz, ilg, ii, ip, ip1,nzcnt + type(psb_z_csr_sparse_mat) :: acsr, muij, s_neigh + type(psb_z_coo_sparse_mat) :: s_neigh_coo + real(psb_dpk_) :: cpling, tcl + logical :: disjoint + integer(psb_ipk_) :: debug_level, debug_unit,err_act + integer(psb_ipk_) :: ictxt,np,me + integer(psb_ipk_) :: nrow, ncol, n_ne + character(len=20) :: name, ch_err + + if (psb_get_errstatus() /= 0) return + info=psb_success_ + name = 'mld_hyb_map_bld' + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + ! + ictxt=desc_a%get_context() + call psb_info(ictxt,me,np) + nrow = desc_a%get_local_rows() + ncol = desc_a%get_local_cols() + + nr = a%get_nrows() + allocate(ilaggr(nr),neigh(nr),ideg(nr),idxs(nr),icol(nr),stat=info) + if(info /= psb_success_) then + info=psb_err_alloc_request_ + call psb_errpush(info,name,i_err=(/2*nr,izero,izero,izero,izero/),& + & a_err='integer') + goto 9999 + end if + + diag = a%get_diag(info) + if(info /= psb_success_) then + info=psb_err_from_subroutine_ + call psb_errpush(info,name,a_err='psb_sp_getdiag') + goto 9999 + end if + + ! + ! Phase zero: compute muij + ! + call a%cp_to(muij) + do i=1, nr + do k=muij%irp(i),muij%irp(i+1)-1 + j = muij%ja(k) + muij%val(k) = abs(muij%val(k))/sqrt(abs(diag(i)*diag(j))) + end do + end do + !write(*,*) 'murows/cols ',maxval(mu_rows),maxval(mu_cols) + ! + ! Compute the 1-neigbour; mark strong links with +1, weak links with -1 + ! + call s_neigh_coo%allocate(nr,nr,muij%get_nzeros()) + ip = 0 + do i=1, nr + do k=muij%irp(i),muij%irp(i+1)-1 + j = muij%ja(k) + ip = ip + 1 + s_neigh_coo%ia(ip) = i + s_neigh_coo%ja(ip) = j + if (real(muij%val(k)) >= theta) then + s_neigh_coo%val(ip) = done + else + s_neigh_coo%val(ip) = -done + end if + end do + end do + !write(*,*) 'S_NEIGH: ',nr,ip + call s_neigh_coo%set_nzeros(ip) + call s_neigh%mv_from_coo(s_neigh_coo,info) + + if (iorder == mld_aggr_ord_nat_) then + do i=1, nr + ilaggr(i) = -(nr+1) + idxs(i) = i + end do + else + do i=1, nr + ilaggr(i) = -(nr+1) + ideg(i) = muij%irp(i+1) - muij%irp(i) + end do + call psb_msort(ideg,ix=idxs,dir=psb_sort_down_) + end if + + + ! + ! Phase one: Start with disjoint groups. + ! + naggr = 0 + icnt = 0 + step1: do ii=1, nr + i = idxs(ii) + + if (ilaggr(i) == -(nr+1)) then + ! + ! Get the 1-neighbourhood of I + ! + ip1 = s_neigh%irp(i) + nz = s_neigh%irp(i+1)-ip1 + ! + ! If the neighbourhood only contains I, skip it + ! + if (nz ==0) then + ilaggr(i) = 0 + cycle step1 + end if + if ((nz==1).and.(s_neigh%ja(ip1)==i)) then + ilaggr(i) = 0 + cycle step1 + end if + ! + ! If the whole strongly coupled neighborhood of I is + ! as yet unconnected, turn it into the next aggregate. + ! + nzcnt = count(real(s_neigh%val(ip1:ip1+nz-1)) > 0) + icol(1:nzcnt) = pack(s_neigh%ja(ip1:ip1+nz-1),(real(s_neigh%val(ip1:ip1+nz-1)) > 0)) + disjoint = all(ilaggr(icol(1:nzcnt)) == -(nr+1)) + if (disjoint) then + icnt = icnt + 1 + naggr = naggr + 1 + do k=1, nzcnt + ilaggr(icol(k)) = naggr + end do + ilaggr(i) = naggr + end if + endif + enddo step1 + + if (debug_level >= psb_debug_outer_) then + write(debug_unit,*) me,' ',trim(name),& + & ' Check 1:',count(ilaggr == -(nr+1)) + end if + + ! + ! Phase two: join the neighbours + ! + tmpaggr = ilaggr + step2: do ii=1,nr + i = idxs(ii) + + if (ilaggr(i) == -(nr+1)) then + ! + ! Find the most strongly connected neighbour that is + ! already aggregated, if any, and join its aggregate + ! + cpling = dzero + ip = 0 + do k=s_neigh%irp(i), s_neigh%irp(i+1)-1 + j = s_neigh%ja(k) + if ((1<=j).and.(j<=nr)) then + if ( (tmpaggr(j) > 0).and. (real(muij%val(k)) > cpling)& + & .and.(real(s_neigh%val(k))>0)) then + ip = k + cpling = muij%val(k) + end if + end if + enddo + if (ip > 0) then + ilaggr(i) = ilaggr(s_neigh%ja(ip)) + end if + end if + end do step2 + + + ! + ! Phase three: sweep over leftovers, if any + ! + step3: do ii=1,nr + i = idxs(ii) + + if (ilaggr(i) < 0) then + ! + ! Find its strongly connected neighbourhood not + ! already aggregated, and make it into a new aggregate. + ! + ip = 0 + do k=s_neigh%irp(i), s_neigh%irp(i+1)-1 + j = s_neigh%ja(k) + if ((1<=j).and.(j<=nr)) then + if (ilaggr(j) < 0) then + ip = ip + 1 + icol(ip) = j + end if + end if + enddo + if (ip > 0) then + icnt = icnt + 1 + naggr = naggr + 1 + ilaggr(i) = naggr + do k=1, ip + ilaggr(icol(k)) = naggr + end do + end if + end if + end do step3 + + + if (count(ilaggr<0) >0) then + info=psb_err_internal_error_ + call psb_errpush(info,name,a_err='Fatal error: some leftovers') + goto 9999 + endif + + if (naggr > ncol) then + write(0,*) name,'Error : naggr > ncol',naggr,ncol + info=psb_err_internal_error_ + call psb_errpush(info,name,a_err='Fatal error: naggr>ncol') + goto 9999 + end if + + call psb_realloc(ncol,ilaggr,info) + if (info /= psb_success_) then + info=psb_err_from_subroutine_ + ch_err='psb_realloc' + call psb_errpush(info,name,a_err=ch_err) + goto 9999 + end if + + allocate(nlaggr(np),stat=info) + if (info /= psb_success_) then + info=psb_err_alloc_request_ + call psb_errpush(info,name,i_err=(/np,izero,izero,izero,izero/),& + & a_err='integer') + goto 9999 + end if + + nlaggr(:) = 0 + nlaggr(me+1) = naggr + call psb_sum(ictxt,nlaggr(1:np)) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + +end subroutine mld_z_hyb_map_bld + diff --git a/mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 new file mode 100644 index 00000000..d0a83ea4 --- /dev/null +++ b/mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 @@ -0,0 +1,122 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 +! +! Salvatore Filippone Cranfield University, UK +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_z_hybrid_aggregator_tprol.f90 +! +! Subroutine: mld_z_hybrid_aggregator_tprol +! Version: complex +! +! +! This routine is mainly an interface to hyb_map_bld where the real work is performed. +! It takes care of some consistency checking, and calls map_to_tprol, which is +! refactored and shared among all the aggregation methods that produce a simple +! integer mapping. +! +! +! Arguments: +! p - type(mld_z_onelev_type), input/output. +! The 'one-level' data structure containing the control +! parameters and (eventually) coarse matrix and prolongator/restrictors. +! +! a - type(psb_zspmat_type). +! The sparse matrix structure containing the local part of the +! fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of a. +! ilaggr - integer, dimension(:), allocatable, output +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that on exit the indices +! will be shifted so as to make sure the ranges on the various processes do not +! overlap. +! nlaggr - integer, dimension(:), allocatable, output +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_zspmat_type), output +! The tentative prolongator, based on ilaggr. +! +! info - integer, output. +! Error code. +! +subroutine mld_z_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod + use mld_z_hybrid_aggregator_mod, mld_protect_name => mld_z_hybrid_aggregator_build_tprol + use mld_z_inner_mod + implicit none + class(mld_z_hybrid_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_zspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_zspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + ! Local variables + character(len=20) :: name + integer(psb_mpik_) :: ictxt, np, me + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: ntaggr + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_z_hybrid_aggregator_tprol' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(p%parms%ml_cycle,'Multilevel cycle',& + & mld_mult_ml_,is_legal_ml_cycle) + call mld_check_def(p%parms%par_aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_par_aggr_alg) + call mld_check_def(p%parms%aggr_ord,'Ordering',& + & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) + call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) + call mld_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + + call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + +end subroutine mld_z_hybrid_aggregator_build_tprol diff --git a/mlprec/impl/aggregator/mld_z_map_to_tprol.f90 b/mlprec/impl/aggregator/mld_z_map_to_tprol.f90 new file mode 100644 index 00000000..5a9491e9 --- /dev/null +++ b/mlprec/impl/aggregator/mld_z_map_to_tprol.f90 @@ -0,0 +1,150 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 +! +! Salvatore Filippone Cranfield University, UK +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_z_map_to_tprol.f90 +! +! Subroutine: mld_z_map_to_tprol +! Version: complex +! +! This routine uses a mapping from the row indices of the fine-level matrix +! to the row indices of the coarse-level matrix to build a tentative +! prolongator, i.e. a piecewise constant operator. +! This is later used to build the final operator; the code has been refactored here +! to be shared among all the methods that provide the tentative prolongator +! through a simple integer mapping. +! +! The aggregation algorithm is a parallel version of that described in +! * M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! * P. Vanek, J. Mandel and M. Brezina, Algebraic Multigrid by Smoothed +! Aggregation for Second and Fourth Order Elliptic Problems, Computing, 56 +! (1996), 179-196. +! For more details see +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +! +! Arguments: +! aggr_type - integer, input. +! The scalar used to identify the aggregation algorithm. +! theta - real, input. +! The aggregation threshold used in the aggregation algorithm. +! 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. +! The communication descriptor of the fine-level matrix. +! ilaggr - integer, dimension(:), allocatable. +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that on exit the indices +! will be shifted so as to make sure the ranges on the various processes do not +! overlap. +! nlaggr - integer, dimension(:), allocatable. +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_zspmat_type). +! The tentative prolongator, based on ilaggr. +! +! info - integer, output. +! Error code. +! +subroutine mld_z_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + use psb_base_mod + use mld_z_inner_mod, mld_protect_name => mld_z_map_to_tprol + + implicit none + + ! Arguments + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:) + type(psb_zspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + ! Local variables + integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m,naggrm1, naggrp1, ntaggr + type(psb_z_coo_sparse_mat) :: tmpcoo + integer(psb_ipk_) :: debug_level, debug_unit,err_act + integer(psb_ipk_) :: ictxt,np,me + integer(psb_ipk_) :: nrow, ncol, n_ne + character(len=20) :: name, ch_err + + if(psb_get_errstatus() /= 0) return + info=psb_success_ + name = 'mld_map_to_tprol' + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + ! + ictxt=desc_a%get_context() + call psb_info(ictxt,me,np) + nrow = desc_a%get_local_rows() + ncol = desc_a%get_local_cols() + + naggr = nlaggr(me+1) + ntaggr = sum(nlaggr) + naggrm1 = sum(nlaggr(1:me)) + naggrp1 = sum(nlaggr(1:me+1)) + ilaggr(1:nrow) = ilaggr(1:nrow) + naggrm1 + call psb_halo(ilaggr,desc_a,info) + if (info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_halo') + goto 9999 + end if + + call tmpcoo%allocate(ncol,ntaggr,ncol) + do i=1,ncol + tmpcoo%val(i) = zone + tmpcoo%ia(i) = i + tmpcoo%ja(i) = ilaggr(i) + end do + call tmpcoo%set_nzeros(ncol) + call tmpcoo%set_dupl(psb_dupl_add_) + call tmpcoo%set_sorted() ! At this point this is in row-major + call op_prol%mv_from(tmpcoo) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + +end subroutine mld_z_map_to_tprol diff --git a/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 new file mode 100644 index 00000000..7a8d5967 --- /dev/null +++ b/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 @@ -0,0 +1,141 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_z_symdec_aggregator_tprol.f90 +! +! Subroutine: mld_z_symdec_aggregator_tprol +! Version: complex +! +! +! This routine is mainly an interface to dec_map_bld where the real work is performed. +! It takes care of some consistency checking, and calls map_to_tprol, which is +! refactored and shared among all the aggregation methods that produce a simple +! integer mapping. +! +! +! +! Arguments: +! p - type(mld_z_onelev_type), input/output. +! The 'one-level' data structure containing the control +! parameters and (eventually) coarse matrix and prolongator/restrictors. +! +! a - type(psb_zspmat_type). +! The sparse matrix structure containing the local part of the +! fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of a. +! ilaggr - integer, dimension(:), allocatable, output +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that on exit the indices +! will be shifted so as to make sure the ranges on the various processes do not +! overlap. +! nlaggr - integer, dimension(:), allocatable, output +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_zspmat_type), output +! The tentative prolongator, based on ilaggr. +! +! info - integer, output. +! Error code. +! +subroutine mld_z_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod + use mld_z_symdec_aggregator_mod, mld_protect_name => mld_z_symdec_aggregator_build_tprol + use mld_z_inner_mod + implicit none + class(mld_z_symdec_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_zspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_zspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + ! Local variables + type(psb_zspmat_type) :: atmp, atrans + character(len=20) :: name + integer(psb_mpik_) :: ictxt, np, me + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: ntaggr, nr + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_z_symdec_aggregator_tprol' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(parms%ml_type,'Multilevel type',& + & mld_mult_ml_,is_legal_ml_type) + call mld_check_def(parms%aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_aggr_alg) + call mld_check_def(parms%aggr_ord,'Ordering',& + & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) + call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) + + nr = a%get_nrows() + call a%csclip(atmp,info,imax=nr,jmax=nr,& + & rscale=.false.,cscale=.false.) + call atmp%set_nrows(nr) + call atmp%set_ncols(nr) + if (info == psb_success_) call atmp%transp(atrans) + if (info == psb_success_) call atrans%cscnv(info,type='COO') + if (info == psb_success_) call psb_rwextd(nr,atmp,info,b=atrans,rowscale=.false.) + call atmp%set_nrows(nr) + call atmp%set_ncols(nr) + if (info == psb_success_) call atrans%free() + if (info == psb_success_) call atmp%cscnv(info,type='CSR') + + if (info == psb_success_) & + & call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) + if (info == psb_success_) call atmp%free() + + if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + +end subroutine mld_z_symdec_aggregator_build_tprol diff --git a/mlprec/impl/mld_zaggrmat_biz_asb.f90 b/mlprec/impl/aggregator/mld_zaggrmat_biz_asb.f90 similarity index 100% rename from mlprec/impl/mld_zaggrmat_biz_asb.f90 rename to mlprec/impl/aggregator/mld_zaggrmat_biz_asb.f90 diff --git a/mlprec/impl/mld_zaggrmat_minnrg_asb.f90 b/mlprec/impl/aggregator/mld_zaggrmat_minnrg_asb.f90 similarity index 100% rename from mlprec/impl/mld_zaggrmat_minnrg_asb.f90 rename to mlprec/impl/aggregator/mld_zaggrmat_minnrg_asb.f90 diff --git a/mlprec/impl/mld_zaggrmat_nosmth_asb.f90 b/mlprec/impl/aggregator/mld_zaggrmat_nosmth_asb.f90 similarity index 100% rename from mlprec/impl/mld_zaggrmat_nosmth_asb.f90 rename to mlprec/impl/aggregator/mld_zaggrmat_nosmth_asb.f90 diff --git a/mlprec/impl/mld_zaggrmat_smth_asb.f90 b/mlprec/impl/aggregator/mld_zaggrmat_smth_asb.f90 similarity index 100% rename from mlprec/impl/mld_zaggrmat_smth_asb.f90 rename to mlprec/impl/aggregator/mld_zaggrmat_smth_asb.f90 From 535d3aa05967c5039d3a8f07ee5ebfbb73cfe97f Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 4 May 2018 16:23:25 +0100 Subject: [PATCH 11/33] Fixed Makefile. --- mlprec/impl/aggregator/Makefile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/mlprec/impl/aggregator/Makefile b/mlprec/impl/aggregator/Makefile index 762e09eb..1015a765 100644 --- a/mlprec/impl/aggregator/Makefile +++ b/mlprec/impl/aggregator/Makefile @@ -9,7 +9,6 @@ FINCLUDES=$(FMFLAG)$(HERE) $(FMFLAG)$(MODDIR) $(FMFLAG)$(INCDIR) $(PSBLAS_INCLUD #CINCLUDES= -I${SUPERLU_INCDIR} -I${HSL_INCDIR} -I${SPRAL_INCDIR} -I/home/users/pasqua/Ambra/BootCMatch/include -lBCM -L/home/users/pasqua/Ambra/BootCMatch/lib -lm OBJS= \ -bootCMatch_interface.o\ mld_s_base_aggregator_mat_asb.o \ mld_s_base_aggregator_tprol.o \ mld_s_hybrid_aggregator_tprol.o \ @@ -41,6 +40,7 @@ mld_z_map_to_tprol.o mld_z_dec_map_bld.o mld_z_hyb_map_bld.o\ mld_zaggrmat_biz_asb.o mld_zaggrmat_minnrg_asb.o\ mld_zaggrmat_nosmth_asb.o mld_zaggrmat_smth_asb.o +#bootCMatch_interface.o\ #mld_d_bcmatch_map_to_tprol.o mld_d_bcmatch_aggregator_mat_asb.o \ From d707a6c9ba88f25849c140db19b6f279023f8d46 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 4 May 2018 21:05:10 +0100 Subject: [PATCH 12/33] Progress with compilation in aggregator subdir. --- mlprec/impl/Makefile | 10 +- mlprec/impl/aggregator/Makefile | 1 - .../mld_c_base_aggregator_mat_asb.f90 | 21 +- .../mld_c_base_aggregator_tprol.f90 | 20 +- mlprec/impl/aggregator/mld_c_dec_map_bld.f90 | 12 +- .../mld_c_hybrid_aggregator_tprol.f90 | 18 +- .../mld_c_symdec_aggregator_tprol.f90 | 14 +- .../mld_d_base_aggregator_mat_asb.f90 | 21 +- .../mld_d_base_aggregator_tprol.f90 | 20 +- mlprec/impl/aggregator/mld_d_dec_map_bld.f90 | 10 +- .../mld_d_hybrid_aggregator_tprol.f90 | 18 +- .../mld_d_symdec_aggregator_tprol.f90 | 14 +- .../mld_s_base_aggregator_mat_asb.f90 | 21 +- .../mld_s_base_aggregator_tprol.f90 | 20 +- mlprec/impl/aggregator/mld_s_dec_map_bld.f90 | 12 +- .../mld_s_hybrid_aggregator_tprol.f90 | 18 +- .../mld_s_symdec_aggregator_tprol.f90 | 14 +- .../mld_z_base_aggregator_mat_asb.f90 | 21 +- .../mld_z_base_aggregator_tprol.f90 | 20 +- mlprec/impl/aggregator/mld_z_dec_map_bld.f90 | 10 +- .../mld_z_hybrid_aggregator_tprol.f90 | 18 +- .../mld_z_symdec_aggregator_tprol.f90 | 14 +- mlprec/impl/mld_c_hierarchy_bld.f90 | 27 +- mlprec/impl/mld_c_lev_aggrmat_asb.f90 | 267 ------------------ mlprec/impl/mld_caggrmap_bld.f90 | 189 ------------- mlprec/impl/mld_caggrmat_asb.f90 | 193 ------------- mlprec/impl/mld_d_hierarchy_bld.f90 | 27 +- mlprec/impl/mld_d_lev_aggrmat_asb.f90 | 267 ------------------ mlprec/impl/mld_daggrmap_bld.f90 | 189 ------------- mlprec/impl/mld_daggrmat_asb.f90 | 193 ------------- mlprec/impl/mld_s_hierarchy_bld.f90 | 27 +- mlprec/impl/mld_s_lev_aggrmat_asb.f90 | 267 ------------------ mlprec/impl/mld_saggrmap_bld.f90 | 189 ------------- mlprec/impl/mld_saggrmat_asb.f90 | 193 ------------- mlprec/impl/mld_z_hierarchy_bld.f90 | 27 +- mlprec/impl/mld_z_lev_aggrmat_asb.f90 | 267 ------------------ mlprec/impl/mld_zaggrmap_bld.f90 | 189 ------------- mlprec/impl/mld_zaggrmat_asb.f90 | 193 ------------- mlprec/mld_c_base_aggregator_mod.f90 | 20 +- mlprec/mld_c_inner_mod.f90 | 2 +- mlprec/mld_c_onelev_mod.f90 | 41 ++- mlprec/mld_d_base_aggregator_mod.f90 | 20 +- mlprec/mld_d_inner_mod.f90 | 2 +- mlprec/mld_d_onelev_mod.f90 | 41 ++- mlprec/mld_s_base_aggregator_mod.f90 | 20 +- mlprec/mld_s_inner_mod.f90 | 2 +- mlprec/mld_s_onelev_mod.f90 | 41 ++- mlprec/mld_z_base_aggregator_mod.f90 | 20 +- mlprec/mld_z_inner_mod.f90 | 2 +- mlprec/mld_z_onelev_mod.f90 | 41 ++- 50 files changed, 467 insertions(+), 2836 deletions(-) delete mode 100644 mlprec/impl/mld_c_lev_aggrmat_asb.f90 delete mode 100644 mlprec/impl/mld_caggrmap_bld.f90 delete mode 100644 mlprec/impl/mld_caggrmat_asb.f90 delete mode 100644 mlprec/impl/mld_d_lev_aggrmat_asb.f90 delete mode 100644 mlprec/impl/mld_daggrmap_bld.f90 delete mode 100644 mlprec/impl/mld_daggrmat_asb.f90 delete mode 100644 mlprec/impl/mld_s_lev_aggrmat_asb.f90 delete mode 100644 mlprec/impl/mld_saggrmap_bld.f90 delete mode 100644 mlprec/impl/mld_saggrmat_asb.f90 delete mode 100644 mlprec/impl/mld_z_lev_aggrmat_asb.f90 delete mode 100644 mlprec/impl/mld_zaggrmap_bld.f90 delete mode 100644 mlprec/impl/mld_zaggrmat_asb.f90 diff --git a/mlprec/impl/Makefile b/mlprec/impl/Makefile index 9a0d92bf..27842294 100644 --- a/mlprec/impl/Makefile +++ b/mlprec/impl/Makefile @@ -25,22 +25,22 @@ MPCOBJS=mld_dslud_interface.o mld_zslud_interface.o DINNEROBJS= mld_dmlprec_bld.o mld_dfile_prec_descr.o \ mld_d_smoothers_bld.o mld_d_hierarchy_bld.o \ mld_dmlprec_aply.o \ - $(DMPFOBJS) mld_d_extprol_bld.o mld_d_lev_aggrmap_bld.o mld_d_lev_aggrmat_asb.o + $(DMPFOBJS) mld_d_extprol_bld.o SINNEROBJS= mld_smlprec_bld.o mld_sfile_prec_descr.o \ mld_s_smoothers_bld.o mld_s_hierarchy_bld.o \ mld_smlprec_aply.o \ - $(SMPFOBJS) mld_s_extprol_bld.o mld_s_lev_aggrmap_bld.o mld_s_lev_aggrmat_asb.o + $(SMPFOBJS) mld_s_extprol_bld.o ZINNEROBJS= mld_zmlprec_bld.o mld_zfile_prec_descr.o \ mld_z_smoothers_bld.o mld_z_hierarchy_bld.o \ mld_zmlprec_aply.o \ - $(ZMPFOBJS) mld_z_extprol_bld.o mld_z_lev_aggrmap_bld.o mld_z_lev_aggrmat_asb.o + $(ZMPFOBJS) mld_z_extprol_bld.o CINNEROBJS= mld_cmlprec_bld.o mld_cfile_prec_descr.o \ mld_c_smoothers_bld.o mld_c_hierarchy_bld.o \ mld_cmlprec_aply.o \ - $(CMPFOBJS) mld_c_extprol_bld.o mld_c_lev_aggrmap_bld.o mld_c_lev_aggrmat_asb.o + $(CMPFOBJS) mld_c_extprol_bld.o INNEROBJS= $(SINNEROBJS) $(DINNEROBJS) $(CINNEROBJS) $(ZINNEROBJS) @@ -67,7 +67,7 @@ OBJS=$(F90OBJS) $(COBJS) $(MPCOBJS) LIBNAME=libmld_prec.a -lib: $(OBJS) levd smoothd solvd aggrd +lib: $(OBJS) aggrd levd smoothd solvd $(AR) $(HERE)/$(LIBNAME) $(OBJS) $(RANLIB) $(HERE)/$(LIBNAME) diff --git a/mlprec/impl/aggregator/Makefile b/mlprec/impl/aggregator/Makefile index 1015a765..d96b835b 100644 --- a/mlprec/impl/aggregator/Makefile +++ b/mlprec/impl/aggregator/Makefile @@ -22,7 +22,6 @@ mld_d_bcmatch_aggregator_tprol.o\ mld_d_hybrid_aggregator_tprol.o \ mld_d_symdec_aggregator_tprol.o \ mld_d_map_to_tprol.o mld_d_dec_map_bld.o mld_d_hyb_map_bld.o\ -mld_daggrmat_unsmth_spmm_asb.o\ mld_daggrmat_biz_asb.o mld_daggrmat_minnrg_asb.o\ mld_daggrmat_nosmth_asb.o mld_daggrmat_smth_asb.o \ mld_c_base_aggregator_mat_asb.o \ diff --git a/mlprec/impl/aggregator/mld_c_base_aggregator_mat_asb.f90 b/mlprec/impl/aggregator/mld_c_base_aggregator_mat_asb.f90 index dc4bb1df..d67f2e3e 100644 --- a/mlprec/impl/aggregator/mld_c_base_aggregator_mat_asb.f90 +++ b/mlprec/impl/aggregator/mld_c_base_aggregator_mat_asb.f90 @@ -133,7 +133,8 @@ ! subroutine mld_c_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) use psb_base_mod - use mld_c_inner_mod, mld_protect_name => mld_c_base_aggregator_mat_asb + use mld_c_prec_type, mld_protect_name => mld_c_base_aggregator_mat_asb + use mld_c_inner_mod implicit none class(mld_c_base_aggregator_type), target, intent(inout) :: ag @@ -163,26 +164,12 @@ subroutine mld_c_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_ ictxt = desc_a%get_context() call psb_info(ictxt,me,np) - call mld_check_def(parms%aggr_kind,'Smoother',& - & mld_smooth_prol_,is_legal_ml_aggr_kind) - call mld_check_def(parms%coarse_mat,'Coarse matrix',& - & mld_distr_mat_,is_legal_ml_coarse_mat) - call mld_check_def(parms%aggr_filter,'Use filtered matrix',& - & mld_no_filter_mat_,is_legal_aggr_filter) - call mld_check_def(parms%smoother_pos,'smooth_pos',& - & mld_pre_smooth_,is_legal_ml_smooth_pos) - call mld_check_def(parms%aggr_omega_alg,'Omega Alg.',& - & mld_eig_est_,is_legal_ml_aggr_omega_alg) - call mld_check_def(parms%aggr_eig,'Eigenvalue estimate',& - & mld_max_norm_,is_legal_ml_aggr_eig) - call mld_check_def(parms%aggr_omega_val,'Omega',szero,is_legal_s_omega) - ! ! Build the coarse-level matrix from the fine-level one, starting from ! the mapping defined by mld_aggrmap_bld and applying the aggregation - ! algorithm specified by p%iprcparm(mld_aggr_kind_) + ! algorithm specified by ! - select case (parms%aggr_kind) + select case (parms%aggr_prol) case (mld_no_smooth_) call mld_caggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,& diff --git a/mlprec/impl/aggregator/mld_c_base_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_c_base_aggregator_tprol.f90 index 18c5428d..92a685a9 100644 --- a/mlprec/impl/aggregator/mld_c_base_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_c_base_aggregator_tprol.f90 @@ -1,3 +1,4 @@ + ! ! ! MLD2P4 version 2.1 @@ -75,8 +76,8 @@ ! subroutine mld_c_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod -! use mld_c_base_aggregator_mod - use mld_c_inner_mod, mld_protect_name => mld_c_base_aggregator_build_tprol + use mld_c_prec_type, mld_protect_name => mld_c_base_aggregator_build_tprol + use mld_c_inner_mod implicit none class(mld_c_base_aggregator_type), target, intent(inout) :: ag type(mld_sml_parms), intent(inout) :: parms @@ -102,10 +103,10 @@ subroutine mld_c_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op ictxt = desc_a%get_context() call psb_info(ictxt,me,np) - call mld_check_def(parms%ml_type,'Multilevel type',& - & mld_mult_ml_,is_legal_ml_type) - call mld_check_def(parms%aggr_alg,'Aggregation',& - & mld_dec_aggr_,is_legal_ml_aggr_alg) + call mld_check_def(parms%ml_cycle,'Multilevel cycle',& + & mld_mult_ml_,is_legal_ml_cycle) + call mld_check_def(parms%par_aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_par_aggr_alg) call mld_check_def(parms%aggr_ord,'Ordering',& & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) @@ -113,7 +114,12 @@ subroutine mld_c_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) - call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + if (info /= psb_success_) then + info=psb_err_from_subroutine_ + call psb_errpush(info,name,a_err='dec_map_bld/map_to_tprol') + goto 9999 + endif call psb_erractionrestore(err_act) return diff --git a/mlprec/impl/aggregator/mld_c_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_c_dec_map_bld.f90 index 4c480c94..4f98159a 100644 --- a/mlprec/impl/aggregator/mld_c_dec_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_c_dec_map_bld.f90 @@ -4,11 +4,12 @@ ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008-2018 +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 ! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions @@ -70,7 +71,6 @@ subroutine mld_c_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod - use mld_base_prec_type use mld_c_inner_mod, mld_protect_name => mld_c_dec_map_bld implicit none @@ -247,7 +247,7 @@ subroutine mld_c_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) ! Find its strongly connected neighbourhood not ! already aggregated, and make it into a new aggregate. ! - cpling = dzero + cpling = szero ip = 0 do k=1, nz j = icol(k) diff --git a/mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 index 675baaa7..291e17fc 100644 --- a/mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 @@ -75,6 +75,7 @@ ! subroutine mld_c_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod + use mld_c_prec_type use mld_c_hybrid_aggregator_mod, mld_protect_name => mld_c_hybrid_aggregator_build_tprol use mld_c_inner_mod implicit none @@ -102,16 +103,23 @@ subroutine mld_c_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, ictxt = desc_a%get_context() call psb_info(ictxt,me,np) - call mld_check_def(p%parms%ml_cycle,'Multilevel cycle',& + call mld_check_def(parms%ml_cycle,'Multilevel cycle',& & mld_mult_ml_,is_legal_ml_cycle) - call mld_check_def(p%parms%par_aggr_alg,'Aggregation',& + call mld_check_def(parms%par_aggr_alg,'Aggregation',& & mld_dec_aggr_,is_legal_ml_par_aggr_alg) - call mld_check_def(p%parms%aggr_ord,'Ordering',& + call mld_check_def(parms%aggr_ord,'Ordering',& & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) + + call mld_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) - - call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + if (info /= psb_success_) then + info=psb_err_from_subroutine_ + call psb_errpush(info,name,a_err='hyb_map_bld/map_to_tprol') + goto 9999 + endif call psb_erractionrestore(err_act) return diff --git a/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 index 8fe0b7a8..fc5c3611 100644 --- a/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 @@ -77,6 +77,7 @@ ! subroutine mld_c_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod + use mld_c_prec_type use mld_c_symdec_aggregator_mod, mld_protect_name => mld_c_symdec_aggregator_build_tprol use mld_c_inner_mod implicit none @@ -105,10 +106,10 @@ subroutine mld_c_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, ictxt = desc_a%get_context() call psb_info(ictxt,me,np) - call mld_check_def(parms%ml_type,'Multilevel type',& - & mld_mult_ml_,is_legal_ml_type) - call mld_check_def(parms%aggr_alg,'Aggregation',& - & mld_dec_aggr_,is_legal_ml_aggr_alg) + call mld_check_def(parms%ml_cycle,'Multilevel cycle',& + & mld_mult_ml_,is_legal_ml_cycle) + call mld_check_def(parms%par_aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_par_aggr_alg) call mld_check_def(parms%aggr_ord,'Ordering',& & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) @@ -131,6 +132,11 @@ subroutine mld_c_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, if (info == psb_success_) call atmp%free() if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + if (info /= psb_success_) then + info=psb_err_from_subroutine_ + call psb_errpush(info,name,a_err='dec_map_bld/map_to_tprol') + goto 9999 + endif call psb_erractionrestore(err_act) return diff --git a/mlprec/impl/aggregator/mld_d_base_aggregator_mat_asb.f90 b/mlprec/impl/aggregator/mld_d_base_aggregator_mat_asb.f90 index ba600776..efbee053 100644 --- a/mlprec/impl/aggregator/mld_d_base_aggregator_mat_asb.f90 +++ b/mlprec/impl/aggregator/mld_d_base_aggregator_mat_asb.f90 @@ -133,7 +133,8 @@ ! subroutine mld_d_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) use psb_base_mod - use mld_d_inner_mod, mld_protect_name => mld_d_base_aggregator_mat_asb + use mld_d_prec_type, mld_protect_name => mld_d_base_aggregator_mat_asb + use mld_d_inner_mod implicit none class(mld_d_base_aggregator_type), target, intent(inout) :: ag @@ -163,26 +164,12 @@ subroutine mld_d_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_ ictxt = desc_a%get_context() call psb_info(ictxt,me,np) - call mld_check_def(parms%aggr_kind,'Smoother',& - & mld_smooth_prol_,is_legal_ml_aggr_kind) - call mld_check_def(parms%coarse_mat,'Coarse matrix',& - & mld_distr_mat_,is_legal_ml_coarse_mat) - call mld_check_def(parms%aggr_filter,'Use filtered matrix',& - & mld_no_filter_mat_,is_legal_aggr_filter) - call mld_check_def(parms%smoother_pos,'smooth_pos',& - & mld_pre_smooth_,is_legal_ml_smooth_pos) - call mld_check_def(parms%aggr_omega_alg,'Omega Alg.',& - & mld_eig_est_,is_legal_ml_aggr_omega_alg) - call mld_check_def(parms%aggr_eig,'Eigenvalue estimate',& - & mld_max_norm_,is_legal_ml_aggr_eig) - call mld_check_def(parms%aggr_omega_val,'Omega',dzero,is_legal_d_omega) - ! ! Build the coarse-level matrix from the fine-level one, starting from ! the mapping defined by mld_aggrmap_bld and applying the aggregation - ! algorithm specified by p%iprcparm(mld_aggr_kind_) + ! algorithm specified by ! - select case (parms%aggr_kind) + select case (parms%aggr_prol) case (mld_no_smooth_) call mld_daggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,& diff --git a/mlprec/impl/aggregator/mld_d_base_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_d_base_aggregator_tprol.f90 index 02ffb7d7..61e7ba86 100644 --- a/mlprec/impl/aggregator/mld_d_base_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_d_base_aggregator_tprol.f90 @@ -1,3 +1,4 @@ + ! ! ! MLD2P4 version 2.1 @@ -75,8 +76,8 @@ ! subroutine mld_d_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod -! use mld_d_base_aggregator_mod - use mld_d_inner_mod, mld_protect_name => mld_d_base_aggregator_build_tprol + use mld_d_prec_type, mld_protect_name => mld_d_base_aggregator_build_tprol + use mld_d_inner_mod implicit none class(mld_d_base_aggregator_type), target, intent(inout) :: ag type(mld_dml_parms), intent(inout) :: parms @@ -102,10 +103,10 @@ subroutine mld_d_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op ictxt = desc_a%get_context() call psb_info(ictxt,me,np) - call mld_check_def(parms%ml_type,'Multilevel type',& - & mld_mult_ml_,is_legal_ml_type) - call mld_check_def(parms%aggr_alg,'Aggregation',& - & mld_dec_aggr_,is_legal_ml_aggr_alg) + call mld_check_def(parms%ml_cycle,'Multilevel cycle',& + & mld_mult_ml_,is_legal_ml_cycle) + call mld_check_def(parms%par_aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_par_aggr_alg) call mld_check_def(parms%aggr_ord,'Ordering',& & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) @@ -113,7 +114,12 @@ subroutine mld_d_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) - call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + if (info /= psb_success_) then + info=psb_err_from_subroutine_ + call psb_errpush(info,name,a_err='dec_map_bld/map_to_tprol') + goto 9999 + endif call psb_erractionrestore(err_act) return diff --git a/mlprec/impl/aggregator/mld_d_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_d_dec_map_bld.f90 index 4925233c..d7576861 100644 --- a/mlprec/impl/aggregator/mld_d_dec_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_d_dec_map_bld.f90 @@ -4,11 +4,12 @@ ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008-2018 +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 ! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions @@ -70,7 +71,6 @@ subroutine mld_d_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod - use mld_base_prec_type use mld_d_inner_mod, mld_protect_name => mld_d_dec_map_bld implicit none diff --git a/mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 index 43506b48..98e43275 100644 --- a/mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 @@ -75,6 +75,7 @@ ! subroutine mld_d_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod + use mld_d_prec_type use mld_d_hybrid_aggregator_mod, mld_protect_name => mld_d_hybrid_aggregator_build_tprol use mld_d_inner_mod implicit none @@ -102,16 +103,23 @@ subroutine mld_d_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, ictxt = desc_a%get_context() call psb_info(ictxt,me,np) - call mld_check_def(p%parms%ml_cycle,'Multilevel cycle',& + call mld_check_def(parms%ml_cycle,'Multilevel cycle',& & mld_mult_ml_,is_legal_ml_cycle) - call mld_check_def(p%parms%par_aggr_alg,'Aggregation',& + call mld_check_def(parms%par_aggr_alg,'Aggregation',& & mld_dec_aggr_,is_legal_ml_par_aggr_alg) - call mld_check_def(p%parms%aggr_ord,'Ordering',& + call mld_check_def(parms%aggr_ord,'Ordering',& & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) + + call mld_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) - - call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + if (info /= psb_success_) then + info=psb_err_from_subroutine_ + call psb_errpush(info,name,a_err='hyb_map_bld/map_to_tprol') + goto 9999 + endif call psb_erractionrestore(err_act) return diff --git a/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 index 8133b712..c9c00780 100644 --- a/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 @@ -77,6 +77,7 @@ ! subroutine mld_d_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod + use mld_d_prec_type use mld_d_symdec_aggregator_mod, mld_protect_name => mld_d_symdec_aggregator_build_tprol use mld_d_inner_mod implicit none @@ -105,10 +106,10 @@ subroutine mld_d_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, ictxt = desc_a%get_context() call psb_info(ictxt,me,np) - call mld_check_def(parms%ml_type,'Multilevel type',& - & mld_mult_ml_,is_legal_ml_type) - call mld_check_def(parms%aggr_alg,'Aggregation',& - & mld_dec_aggr_,is_legal_ml_aggr_alg) + call mld_check_def(parms%ml_cycle,'Multilevel cycle',& + & mld_mult_ml_,is_legal_ml_cycle) + call mld_check_def(parms%par_aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_par_aggr_alg) call mld_check_def(parms%aggr_ord,'Ordering',& & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) @@ -131,6 +132,11 @@ subroutine mld_d_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, if (info == psb_success_) call atmp%free() if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + if (info /= psb_success_) then + info=psb_err_from_subroutine_ + call psb_errpush(info,name,a_err='dec_map_bld/map_to_tprol') + goto 9999 + endif call psb_erractionrestore(err_act) return diff --git a/mlprec/impl/aggregator/mld_s_base_aggregator_mat_asb.f90 b/mlprec/impl/aggregator/mld_s_base_aggregator_mat_asb.f90 index 4464cc84..10285bfa 100644 --- a/mlprec/impl/aggregator/mld_s_base_aggregator_mat_asb.f90 +++ b/mlprec/impl/aggregator/mld_s_base_aggregator_mat_asb.f90 @@ -133,7 +133,8 @@ ! subroutine mld_s_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) use psb_base_mod - use mld_s_inner_mod, mld_protect_name => mld_s_base_aggregator_mat_asb + use mld_s_prec_type, mld_protect_name => mld_s_base_aggregator_mat_asb + use mld_s_inner_mod implicit none class(mld_s_base_aggregator_type), target, intent(inout) :: ag @@ -163,26 +164,12 @@ subroutine mld_s_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_ ictxt = desc_a%get_context() call psb_info(ictxt,me,np) - call mld_check_def(parms%aggr_kind,'Smoother',& - & mld_smooth_prol_,is_legal_ml_aggr_kind) - call mld_check_def(parms%coarse_mat,'Coarse matrix',& - & mld_distr_mat_,is_legal_ml_coarse_mat) - call mld_check_def(parms%aggr_filter,'Use filtered matrix',& - & mld_no_filter_mat_,is_legal_aggr_filter) - call mld_check_def(parms%smoother_pos,'smooth_pos',& - & mld_pre_smooth_,is_legal_ml_smooth_pos) - call mld_check_def(parms%aggr_omega_alg,'Omega Alg.',& - & mld_eig_est_,is_legal_ml_aggr_omega_alg) - call mld_check_def(parms%aggr_eig,'Eigenvalue estimate',& - & mld_max_norm_,is_legal_ml_aggr_eig) - call mld_check_def(parms%aggr_omega_val,'Omega',szero,is_legal_s_omega) - ! ! Build the coarse-level matrix from the fine-level one, starting from ! the mapping defined by mld_aggrmap_bld and applying the aggregation - ! algorithm specified by p%iprcparm(mld_aggr_kind_) + ! algorithm specified by ! - select case (parms%aggr_kind) + select case (parms%aggr_prol) case (mld_no_smooth_) call mld_saggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,& diff --git a/mlprec/impl/aggregator/mld_s_base_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_s_base_aggregator_tprol.f90 index bf83a553..786748d1 100644 --- a/mlprec/impl/aggregator/mld_s_base_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_s_base_aggregator_tprol.f90 @@ -1,3 +1,4 @@ + ! ! ! MLD2P4 version 2.1 @@ -75,8 +76,8 @@ ! subroutine mld_s_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod -! use mld_s_base_aggregator_mod - use mld_s_inner_mod, mld_protect_name => mld_s_base_aggregator_build_tprol + use mld_s_prec_type, mld_protect_name => mld_s_base_aggregator_build_tprol + use mld_s_inner_mod implicit none class(mld_s_base_aggregator_type), target, intent(inout) :: ag type(mld_sml_parms), intent(inout) :: parms @@ -102,10 +103,10 @@ subroutine mld_s_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op ictxt = desc_a%get_context() call psb_info(ictxt,me,np) - call mld_check_def(parms%ml_type,'Multilevel type',& - & mld_mult_ml_,is_legal_ml_type) - call mld_check_def(parms%aggr_alg,'Aggregation',& - & mld_dec_aggr_,is_legal_ml_aggr_alg) + call mld_check_def(parms%ml_cycle,'Multilevel cycle',& + & mld_mult_ml_,is_legal_ml_cycle) + call mld_check_def(parms%par_aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_par_aggr_alg) call mld_check_def(parms%aggr_ord,'Ordering',& & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) @@ -113,7 +114,12 @@ subroutine mld_s_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) - call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + if (info /= psb_success_) then + info=psb_err_from_subroutine_ + call psb_errpush(info,name,a_err='dec_map_bld/map_to_tprol') + goto 9999 + endif call psb_erractionrestore(err_act) return diff --git a/mlprec/impl/aggregator/mld_s_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_s_dec_map_bld.f90 index 24f1b408..d9af2f5f 100644 --- a/mlprec/impl/aggregator/mld_s_dec_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_s_dec_map_bld.f90 @@ -4,11 +4,12 @@ ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008-2018 +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 ! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions @@ -70,7 +71,6 @@ subroutine mld_s_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod - use mld_base_prec_type use mld_s_inner_mod, mld_protect_name => mld_s_dec_map_bld implicit none @@ -247,7 +247,7 @@ subroutine mld_s_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) ! Find its strongly connected neighbourhood not ! already aggregated, and make it into a new aggregate. ! - cpling = dzero + cpling = szero ip = 0 do k=1, nz j = icol(k) diff --git a/mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 index 806f3184..659c3f86 100644 --- a/mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 @@ -75,6 +75,7 @@ ! subroutine mld_s_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod + use mld_s_prec_type use mld_s_hybrid_aggregator_mod, mld_protect_name => mld_s_hybrid_aggregator_build_tprol use mld_s_inner_mod implicit none @@ -102,16 +103,23 @@ subroutine mld_s_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, ictxt = desc_a%get_context() call psb_info(ictxt,me,np) - call mld_check_def(p%parms%ml_cycle,'Multilevel cycle',& + call mld_check_def(parms%ml_cycle,'Multilevel cycle',& & mld_mult_ml_,is_legal_ml_cycle) - call mld_check_def(p%parms%par_aggr_alg,'Aggregation',& + call mld_check_def(parms%par_aggr_alg,'Aggregation',& & mld_dec_aggr_,is_legal_ml_par_aggr_alg) - call mld_check_def(p%parms%aggr_ord,'Ordering',& + call mld_check_def(parms%aggr_ord,'Ordering',& & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) + + call mld_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) - - call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + if (info /= psb_success_) then + info=psb_err_from_subroutine_ + call psb_errpush(info,name,a_err='hyb_map_bld/map_to_tprol') + goto 9999 + endif call psb_erractionrestore(err_act) return diff --git a/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 index b73fe100..e308ab5f 100644 --- a/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 @@ -77,6 +77,7 @@ ! subroutine mld_s_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod + use mld_s_prec_type use mld_s_symdec_aggregator_mod, mld_protect_name => mld_s_symdec_aggregator_build_tprol use mld_s_inner_mod implicit none @@ -105,10 +106,10 @@ subroutine mld_s_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, ictxt = desc_a%get_context() call psb_info(ictxt,me,np) - call mld_check_def(parms%ml_type,'Multilevel type',& - & mld_mult_ml_,is_legal_ml_type) - call mld_check_def(parms%aggr_alg,'Aggregation',& - & mld_dec_aggr_,is_legal_ml_aggr_alg) + call mld_check_def(parms%ml_cycle,'Multilevel cycle',& + & mld_mult_ml_,is_legal_ml_cycle) + call mld_check_def(parms%par_aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_par_aggr_alg) call mld_check_def(parms%aggr_ord,'Ordering',& & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) @@ -131,6 +132,11 @@ subroutine mld_s_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, if (info == psb_success_) call atmp%free() if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + if (info /= psb_success_) then + info=psb_err_from_subroutine_ + call psb_errpush(info,name,a_err='dec_map_bld/map_to_tprol') + goto 9999 + endif call psb_erractionrestore(err_act) return diff --git a/mlprec/impl/aggregator/mld_z_base_aggregator_mat_asb.f90 b/mlprec/impl/aggregator/mld_z_base_aggregator_mat_asb.f90 index 5bda2a48..b9eda046 100644 --- a/mlprec/impl/aggregator/mld_z_base_aggregator_mat_asb.f90 +++ b/mlprec/impl/aggregator/mld_z_base_aggregator_mat_asb.f90 @@ -133,7 +133,8 @@ ! subroutine mld_z_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) use psb_base_mod - use mld_z_inner_mod, mld_protect_name => mld_z_base_aggregator_mat_asb + use mld_z_prec_type, mld_protect_name => mld_z_base_aggregator_mat_asb + use mld_z_inner_mod implicit none class(mld_z_base_aggregator_type), target, intent(inout) :: ag @@ -163,26 +164,12 @@ subroutine mld_z_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_ ictxt = desc_a%get_context() call psb_info(ictxt,me,np) - call mld_check_def(parms%aggr_kind,'Smoother',& - & mld_smooth_prol_,is_legal_ml_aggr_kind) - call mld_check_def(parms%coarse_mat,'Coarse matrix',& - & mld_distr_mat_,is_legal_ml_coarse_mat) - call mld_check_def(parms%aggr_filter,'Use filtered matrix',& - & mld_no_filter_mat_,is_legal_aggr_filter) - call mld_check_def(parms%smoother_pos,'smooth_pos',& - & mld_pre_smooth_,is_legal_ml_smooth_pos) - call mld_check_def(parms%aggr_omega_alg,'Omega Alg.',& - & mld_eig_est_,is_legal_ml_aggr_omega_alg) - call mld_check_def(parms%aggr_eig,'Eigenvalue estimate',& - & mld_max_norm_,is_legal_ml_aggr_eig) - call mld_check_def(parms%aggr_omega_val,'Omega',dzero,is_legal_d_omega) - ! ! Build the coarse-level matrix from the fine-level one, starting from ! the mapping defined by mld_aggrmap_bld and applying the aggregation - ! algorithm specified by p%iprcparm(mld_aggr_kind_) + ! algorithm specified by ! - select case (parms%aggr_kind) + select case (parms%aggr_prol) case (mld_no_smooth_) call mld_zaggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,& diff --git a/mlprec/impl/aggregator/mld_z_base_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_z_base_aggregator_tprol.f90 index 81d8910f..894e4e7a 100644 --- a/mlprec/impl/aggregator/mld_z_base_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_z_base_aggregator_tprol.f90 @@ -1,3 +1,4 @@ + ! ! ! MLD2P4 version 2.1 @@ -75,8 +76,8 @@ ! subroutine mld_z_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod -! use mld_z_base_aggregator_mod - use mld_z_inner_mod, mld_protect_name => mld_z_base_aggregator_build_tprol + use mld_z_prec_type, mld_protect_name => mld_z_base_aggregator_build_tprol + use mld_z_inner_mod implicit none class(mld_z_base_aggregator_type), target, intent(inout) :: ag type(mld_dml_parms), intent(inout) :: parms @@ -102,10 +103,10 @@ subroutine mld_z_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op ictxt = desc_a%get_context() call psb_info(ictxt,me,np) - call mld_check_def(parms%ml_type,'Multilevel type',& - & mld_mult_ml_,is_legal_ml_type) - call mld_check_def(parms%aggr_alg,'Aggregation',& - & mld_dec_aggr_,is_legal_ml_aggr_alg) + call mld_check_def(parms%ml_cycle,'Multilevel cycle',& + & mld_mult_ml_,is_legal_ml_cycle) + call mld_check_def(parms%par_aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_par_aggr_alg) call mld_check_def(parms%aggr_ord,'Ordering',& & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) @@ -113,7 +114,12 @@ subroutine mld_z_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) - call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + if (info /= psb_success_) then + info=psb_err_from_subroutine_ + call psb_errpush(info,name,a_err='dec_map_bld/map_to_tprol') + goto 9999 + endif call psb_erractionrestore(err_act) return diff --git a/mlprec/impl/aggregator/mld_z_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_z_dec_map_bld.f90 index 6900b221..7c992167 100644 --- a/mlprec/impl/aggregator/mld_z_dec_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_z_dec_map_bld.f90 @@ -4,11 +4,12 @@ ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008-2018 +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 ! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions @@ -70,7 +71,6 @@ subroutine mld_z_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod - use mld_base_prec_type use mld_z_inner_mod, mld_protect_name => mld_z_dec_map_bld implicit none diff --git a/mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 index d0a83ea4..742dbc80 100644 --- a/mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 @@ -75,6 +75,7 @@ ! subroutine mld_z_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod + use mld_z_prec_type use mld_z_hybrid_aggregator_mod, mld_protect_name => mld_z_hybrid_aggregator_build_tprol use mld_z_inner_mod implicit none @@ -102,16 +103,23 @@ subroutine mld_z_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, ictxt = desc_a%get_context() call psb_info(ictxt,me,np) - call mld_check_def(p%parms%ml_cycle,'Multilevel cycle',& + call mld_check_def(parms%ml_cycle,'Multilevel cycle',& & mld_mult_ml_,is_legal_ml_cycle) - call mld_check_def(p%parms%par_aggr_alg,'Aggregation',& + call mld_check_def(parms%par_aggr_alg,'Aggregation',& & mld_dec_aggr_,is_legal_ml_par_aggr_alg) - call mld_check_def(p%parms%aggr_ord,'Ordering',& + call mld_check_def(parms%aggr_ord,'Ordering',& & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) + + call mld_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) - - call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + + if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + if (info /= psb_success_) then + info=psb_err_from_subroutine_ + call psb_errpush(info,name,a_err='hyb_map_bld/map_to_tprol') + goto 9999 + endif call psb_erractionrestore(err_act) return diff --git a/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 index 7a8d5967..8f1e8ff8 100644 --- a/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 @@ -77,6 +77,7 @@ ! subroutine mld_z_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod + use mld_z_prec_type use mld_z_symdec_aggregator_mod, mld_protect_name => mld_z_symdec_aggregator_build_tprol use mld_z_inner_mod implicit none @@ -105,10 +106,10 @@ subroutine mld_z_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, ictxt = desc_a%get_context() call psb_info(ictxt,me,np) - call mld_check_def(parms%ml_type,'Multilevel type',& - & mld_mult_ml_,is_legal_ml_type) - call mld_check_def(parms%aggr_alg,'Aggregation',& - & mld_dec_aggr_,is_legal_ml_aggr_alg) + call mld_check_def(parms%ml_cycle,'Multilevel cycle',& + & mld_mult_ml_,is_legal_ml_cycle) + call mld_check_def(parms%par_aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_par_aggr_alg) call mld_check_def(parms%aggr_ord,'Ordering',& & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) @@ -131,6 +132,11 @@ subroutine mld_z_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, if (info == psb_success_) call atmp%free() if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) + if (info /= psb_success_) then + info=psb_err_from_subroutine_ + call psb_errpush(info,name,a_err='dec_map_bld/map_to_tprol') + goto 9999 + endif call psb_erractionrestore(err_act) return diff --git a/mlprec/impl/mld_c_hierarchy_bld.f90 b/mlprec/impl/mld_c_hierarchy_bld.f90 index a3bd0b10..38684e6a 100644 --- a/mlprec/impl/mld_c_hierarchy_bld.f90 +++ b/mlprec/impl/mld_c_hierarchy_bld.f90 @@ -84,6 +84,7 @@ subroutine mld_c_hierarchy_bld(a,desc_a,prec,info) real(psb_spk_) :: mnaggratio, sizeratio, athresh, aomega class(mld_c_base_smoother_type), allocatable :: coarse_sm, base_sm, med_sm, & & base_sm2, med_sm2, coarse_sm2 + class(mld_c_base_aggregator_type), allocatable :: tmp_aggr type(mld_sml_parms) :: baseparms, medparms, coarseparms integer(psb_ipk_), allocatable :: ilaggr(:), nlaggr(:) type(psb_cspmat_type) :: op_prol @@ -216,19 +217,26 @@ subroutine mld_c_hierarchy_bld(a,desc_a,prec,info) allocate(tprecv(nplevs),stat=info) ! First all existing levels if (info == 0) tprecv(1)%parms = baseparms - if (info == 0) call restore_smoothers(tprecv(1),prec%precv(1)%sm,prec%precv(1)%sm2a,info) + if (info == 0) call restore_smoothers(tprecv(1),& + & prec%precv(1)%sm,prec%precv(1)%sm2a,info) + if (info == 0) call move_alloc(prec%precv(1)%aggr,tprecv(1)%aggr) do i=2, min(iszv,nplevs) - 1 if (info == 0) tprecv(i)%parms = medparms - if (info == 0) call restore_smoothers(tprecv(i),prec%precv(i)%sm,prec%precv(i)%sm2a,info) + if (info == 0) call restore_smoothers(tprecv(i),& + & prec%precv(i)%sm,prec%precv(i)%sm2a,info) + if (info == 0) call move_alloc(prec%precv(i)%aggr,tprecv(i)%aggr) end do ! Further intermediates, if any do i=iszv-1, nplevs - 1 if (info == 0) tprecv(i)%parms = medparms if (info == 0) call restore_smoothers(tprecv(i),med_sm,med_sm2,info) + if ((info == 0).and..not.allocated(tprecv(i)%aggr))& + & allocate(tprecv(i)%aggr,source=tprecv(1)%aggr,stat=info) end do ! Then coarse if (info == 0) tprecv(nplevs)%parms = coarseparms if (info == 0) call restore_smoothers(tprecv(nplevs),coarse_sm,coarse_sm2,info) + if (info == 0) allocate(tprecv(nplevs)%aggr,source=tprecv(i)%aggr,stat=info) if (info /= psb_success_) then call psb_errpush(psb_err_from_subroutine_,name,& & a_err='prec reallocation') @@ -272,9 +280,10 @@ subroutine mld_c_hierarchy_bld(a,desc_a,prec,info) ! ! Build the mapping between levels i-1 and i and the matrix ! at level i - ! - if (info == psb_success_) call mld_aggrmap_bld(prec%precv(i),& - & prec%precv(i-1)%base_a,prec%precv(i-1)%base_desc,& + ! + if (info == psb_success_)& + & call prec%precv(i)%bld_tprol(prec%precv(i-1)%base_a,& + & prec%precv(i-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then @@ -282,6 +291,7 @@ subroutine mld_c_hierarchy_bld(a,desc_a,prec,info) & a_err='Map build') goto 9999 endif + if (i= psb_debug_outer_) & & write(debug_unit,*) me,' ',trim(name),& @@ -346,7 +356,8 @@ subroutine mld_c_hierarchy_bld(a,desc_a,prec,info) prec%precv(newsz)%parms%aggr_thresh = athresh prec%precv(newsz)%parms%aggr_omega_val = aomega - if (info == 0) call restore_smoothers(prec%precv(newsz),coarse_sm,coarse_sm2,info) + if (info == 0) call restore_smoothers(prec%precv(newsz),& + & coarse_sm,coarse_sm2,info) if (newsz < i) then ! ! We are going back and revisit a previous leve; @@ -357,7 +368,7 @@ subroutine mld_c_hierarchy_bld(a,desc_a,prec,info) call prec%precv(newsz)%tprol%clone(op_prol,info) end if - if (info == psb_success_) call mld_lev_mat_asb(prec%precv(newsz),& + if (info == psb_success_) call prec%precv(newsz)%mat_asb( & & prec%precv(newsz-1)%base_a,prec%precv(newsz-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) if (info /= 0) then @@ -367,7 +378,7 @@ subroutine mld_c_hierarchy_bld(a,desc_a,prec,info) endif exit array_build_loop else - if (info == psb_success_) call mld_lev_mat_asb(prec%precv(i),& + if (info == psb_success_) call prec%precv(i)%mat_asb(& & prec%precv(i-1)%base_a,prec%precv(i-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) end if diff --git a/mlprec/impl/mld_c_lev_aggrmat_asb.f90 b/mlprec/impl/mld_c_lev_aggrmat_asb.f90 deleted file mode 100644 index 5aa1730e..00000000 --- a/mlprec/impl/mld_c_lev_aggrmat_asb.f90 +++ /dev/null @@ -1,267 +0,0 @@ -! -! -! MLD2P4 version 2.1 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_c_lev_aggrmat_asb.f90 -! -! Subroutine: mld_c_lev_aggrmat_asb -! Version: complex -! -! This routine builds the matrix associated to the current level of the -! multilevel preconditioner from the matrix associated to the previous level, -! by using the user-specified aggregation technique (therefore, it also builds the -! prolongation and restriction operators mapping the current level to the -! previous one and vice versa). -! The current level is regarded as the coarse one, while the previous as -! the fine one. This is in agreement with the fact that the routine is called, -! by mld_mlprec_bld, only on levels >=2. -! The main structure is: -! 1. Perform sanity checks; -! 2. Call mld_Xaggrmat_asb to compute prolongator/restrictor/AC -! 3. According to the choice of DIST/REPL for AC, build a descriptor DESC_AC, -! and adjust the column numbering of AC/OP_PROL/OP_RESTR -! 4. Pack restrictor and prolongator into p%map -! 5. Fix base_a and base_desc pointers. -! -! -! Arguments: -! p - type(mld_c_onelev_type), input/output. -! The 'one-level' data structure containing the control -! parameters and (eventually) coarse matrix and prolongator/restrictors. -! -! a - type(psb_cspmat_type). -! The sparse matrix structure containing the local part of the -! fine-level matrix. -! desc_a - type(psb_desc_type), input. -! The communication descriptor of a. -! ilaggr - integer, dimension(:), input -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that the indices -! are assumed to be shifted so as to make sure the ranges on -! the various processes do not overlap. -! nlaggr - integer, dimension(:) input -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_cspmat_type), input/output -! The tentative prolongator on input, released on output. -! -! info - integer, output. -! Error code. -! -subroutine mld_c_lev_aggrmat_asb(p,a,desc_a,ilaggr,nlaggr,op_prol,info) - - use psb_base_mod - use mld_base_prec_type - use mld_c_inner_mod, mld_protect_name => mld_c_lev_aggrmat_asb - - implicit none - - ! Arguments - type(mld_c_onelev_type), intent(inout), target :: p - type(psb_cspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(inout) :: ilaggr(:),nlaggr(:) - type(psb_cspmat_type), intent(inout) :: op_prol - integer(psb_ipk_), intent(out) :: info - - - ! Local variables - character(len=24) :: name - integer(psb_mpik_) :: ictxt, np, me - integer(psb_ipk_) :: err_act - type(psb_cspmat_type) :: ac, op_restr - type(psb_c_coo_sparse_mat) :: acoo, bcoo - type(psb_c_csr_sparse_mat) :: acsr1 - integer(psb_ipk_) :: nzl, ntaggr - integer(psb_ipk_) :: debug_level, debug_unit - - name='mld_c_lev_aggrmat_asb' - if (psb_get_errstatus().ne.0) return - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - info = psb_success_ - ictxt = desc_a%get_context() - call psb_info(ictxt,me,np) - - call mld_check_def(p%parms%aggr_prol,'Smoother',& - & mld_smooth_prol_,is_legal_ml_aggr_prol) - call mld_check_def(p%parms%coarse_mat,'Coarse matrix',& - & mld_distr_mat_,is_legal_ml_coarse_mat) - call mld_check_def(p%parms%aggr_filter,'Use filtered matrix',& - & mld_no_filter_mat_,is_legal_aggr_filter) - call mld_check_def(p%parms%aggr_omega_alg,'Omega Alg.',& - & mld_eig_est_,is_legal_ml_aggr_omega_alg) - call mld_check_def(p%parms%aggr_eig,'Eigenvalue estimate',& - & mld_max_norm_,is_legal_ml_aggr_eig) - call mld_check_def(p%parms%aggr_omega_val,'Omega',szero,is_legal_s_omega) - - - ! - ! Build the coarse-level matrix from the fine-level one, starting from - ! the mapping defined by mld_aggrmap_bld and applying the aggregation - ! algorithm specified by p%iprcparm(mld_aggr_prol_) - ! - call mld_caggrmat_asb(a,desc_a,ilaggr,nlaggr,p%parms,ac,op_prol,op_restr,info) - - if(info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='mld_aggrmat_asb') - goto 9999 - end if - - - ! Common code refactored here. - - ntaggr = sum(nlaggr) - - select case(p%parms%coarse_mat) - - case(mld_distr_mat_) - - call ac%mv_to(bcoo) - nzl = bcoo%get_nzeros() - - if (info == psb_success_) call psb_cdall(ictxt,p%desc_ac,info,nl=nlaggr(me+1)) - if (info == psb_success_) call psb_cdins(nzl,bcoo%ia,bcoo%ja,p%desc_ac,info) - if (info == psb_success_) call psb_cdasb(p%desc_ac,info) - if (info == psb_success_) call psb_glob_to_loc(bcoo%ia(1:nzl),p%desc_ac,info,iact='I') - if (info == psb_success_) call psb_glob_to_loc(bcoo%ja(1:nzl),p%desc_ac,info,iact='I') - if (info /= psb_success_) then - call psb_errpush(psb_err_internal_error_,name,& - & a_err='Creating p%desc_ac and converting ac') - goto 9999 - end if - if (debug_level >= psb_debug_outer_) & - & write(debug_unit,*) me,' ',trim(name),& - & 'Assembld aux descr. distr.' - call p%ac%mv_from(bcoo) - - call p%ac%set_nrows(p%desc_ac%get_local_rows()) - call p%ac%set_ncols(p%desc_ac%get_local_cols()) - call p%ac%set_asb() - - if (info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_sp_free') - goto 9999 - end if - - if (np>1) then - call op_prol%mv_to(acsr1) - nzl = acsr1%get_nzeros() - call psb_glob_to_loc(acsr1%ja(1:nzl),p%desc_ac,info,'I') - if(info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_glob_to_loc') - goto 9999 - end if - call op_prol%mv_from(acsr1) - endif - call op_prol%set_ncols(p%desc_ac%get_local_cols()) - - if (np>1) then - call op_restr%cscnv(info,type='coo',dupl=psb_dupl_add_) - call op_restr%mv_to(acoo) - nzl = acoo%get_nzeros() - if (info == psb_success_) call psb_glob_to_loc(acoo%ia(1:nzl),p%desc_ac,info,'I') - call acoo%set_dupl(psb_dupl_add_) - if (info == psb_success_) call op_restr%mv_from(acoo) - if (info == psb_success_) call op_restr%cscnv(info,type='csr') - if(info /= psb_success_) then - call psb_errpush(psb_err_internal_error_,name,& - & a_err='Converting op_restr to local') - goto 9999 - end if - end if - ! - ! Clip to local rows. - ! - call op_restr%set_nrows(p%desc_ac%get_local_rows()) - - if (debug_level >= psb_debug_outer_) & - & write(debug_unit,*) me,' ',trim(name),& - & 'Done ac ' - - case(mld_repl_mat_) - ! - ! - call psb_cdall(ictxt,p%desc_ac,info,mg=ntaggr,repl=.true.) - if (info == psb_success_) call psb_cdasb(p%desc_ac,info) - if (info == psb_success_) & - & call psb_gather(p%ac,ac,p%desc_ac,info,dupl=psb_dupl_add_,keeploc=.false.) - - if (info /= psb_success_) goto 9999 - - case default - info = psb_err_internal_error_ - call psb_errpush(info,name,a_err='invalid mld_coarse_mat_') - goto 9999 - end select - - call p%ac%cscnv(info,type='csr',dupl=psb_dupl_add_) - if(info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='spcnv') - goto 9999 - end if - - ! - ! Copy the prolongation/restriction matrices into the descriptor map. - ! op_restr => PR^T i.e. restriction operator - ! op_prol => PR i.e. prolongation operator - ! - - p%map = psb_linmap(psb_map_aggr_,desc_a,& - & p%desc_ac,op_restr,op_prol,ilaggr,nlaggr) - if (info == psb_success_) call op_prol%free() - if (info == psb_success_) call op_restr%free() - if(info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='sp_Free') - goto 9999 - end if - ! - ! Fix the base_a and base_desc pointers for handling of residuals. - ! This is correct because this routine is only called at levels >=2. - ! - p%base_a => p%ac - p%base_desc => p%desc_ac - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - return - -end subroutine mld_c_lev_aggrmat_asb diff --git a/mlprec/impl/mld_caggrmap_bld.f90 b/mlprec/impl/mld_caggrmap_bld.f90 deleted file mode 100644 index 0ef77481..00000000 --- a/mlprec/impl/mld_caggrmap_bld.f90 +++ /dev/null @@ -1,189 +0,0 @@ -! -! -! MLD2P4 version 2.1 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_caggrmap_bld.f90 -! -! Subroutine: mld_caggrmap_bld -! Version: complex -! -! This routine builds a mapping from the row indices of the fine-level matrix -! to the row indices of the coarse-level matrix, according to a decoupled -! aggregation algorithm. This mapping will be used by mld_aggrmat_asb to -! build the coarse-level matrix. -! -! The aggregation algorithm is a parallel version of that described in -! * M. Brezina and P. Vanek, A black-box iterative solver based on a -! two-level Schwarz method, Computing, 63 (1999), 233-263. -! * P. Vanek, J. Mandel and M. Brezina, Algebraic Multigrid by Smoothed -! Aggregation for Second and Fourth Order Elliptic Problems, Computing, 56 -! (1996), 179-196. -! For more details see -! P. D'Ambra, D. di Serafino and S. Filippone, On the development of -! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. -! 57 (2007), 1181-1196. -! -! -! Arguments: -! aggr_type - integer, input. -! The scalar used to identify the aggregation algorithm. -! theta - real, input. -! The aggregation threshold used in the aggregation algorithm. -! a - type(psb_cspmat_type), input. -! The sparse matrix structure containing the local part of -! the fine-level matrix. -! desc_a - type(psb_desc_type), input. -! The communication descriptor of the fine-level matrix. -! ilaggr - integer, dimension(:), allocatable. -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that on exit the indices -! will be shifted so as to make sure the ranges on the various processes do not -! overlap. -! nlaggr - integer, dimension(:), allocatable. -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_cspmat_type). -! The tentative prolongator, based on ilaggr. -! -! info - integer, output. -! Error code. -! -subroutine mld_caggrmap_bld(aggr_type,iorder,theta,a,desc_a,ilaggr,nlaggr,op_prol,info) - - use psb_base_mod - use mld_base_prec_type - use mld_c_inner_mod, mld_protect_name => mld_caggrmap_bld - - implicit none - - ! Arguments - integer(psb_ipk_), intent(in) :: iorder - integer(psb_ipk_), intent(in) :: aggr_type - real(psb_spk_), intent(in) :: theta - type(psb_cspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - type(psb_cspmat_type), intent(out) :: op_prol - integer(psb_ipk_), intent(out) :: info - - ! Local variables - integer(psb_ipk_), allocatable :: ils(:), neigh(:) - integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m,naggrm1, naggrp1, ntaggr - type(psb_cspmat_type) :: atmp, atrans - type(psb_c_coo_sparse_mat) :: tmpcoo - integer(psb_ipk_) :: debug_level, debug_unit,err_act - integer(psb_ipk_) :: ictxt,np,me - integer(psb_ipk_) :: nrow, ncol, n_ne - character(len=20) :: name, ch_err - - if(psb_get_errstatus() /= 0) return - info=psb_success_ - name = 'mld_aggrmap_bld' - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - ! - ictxt=desc_a%get_context() - call psb_info(ictxt,me,np) - nrow = desc_a%get_local_rows() - ncol = desc_a%get_local_cols() - - select case (aggr_type) - case (mld_dec_aggr_) - call mld_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) - - case (mld_sym_dec_aggr_) - nr = a%get_nrows() - call a%csclip(atmp,info,imax=nr,jmax=nr,& - & rscale=.false.,cscale=.false.) - call atmp%set_nrows(nr) - call atmp%set_ncols(nr) - if (info == psb_success_) call atmp%transp(atrans) - if (info == psb_success_) call atrans%cscnv(info,type='COO') - if (info == psb_success_) call psb_rwextd(nr,atmp,info,b=atrans,rowscale=.false.) - call atmp%set_nrows(nr) - call atmp%set_ncols(nr) - if (info == psb_success_) call atrans%free() - if (info == psb_success_) call atmp%cscnv(info,type='CSR') - if (info == psb_success_) call mld_dec_map_bld(iorder,theta,atmp,desc_a,nlaggr,ilaggr,info) - if (info == psb_success_) call atmp%free() - - case default - - info = -1 - call psb_errpush(psb_err_input_value_invalid_i_,name,& - & i_err=(/ione,aggr_type,izero,izero,izero/)) - goto 9999 - end select - - if (info /= psb_success_) then - info=psb_err_internal_error_ - call psb_errpush(info,name,a_err='dec_map_bld') - goto 9999 - end if - - naggr = nlaggr(me+1) - ntaggr = sum(nlaggr) - naggrm1 = sum(nlaggr(1:me)) - naggrp1 = sum(nlaggr(1:me+1)) - ilaggr(1:nrow) = ilaggr(1:nrow) + naggrm1 - call psb_halo(ilaggr,desc_a,info) - if (info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_halo') - goto 9999 - end if - - call tmpcoo%allocate(ncol,ntaggr,ncol) - do i=1,ncol - tmpcoo%val(i) = cone - tmpcoo%ia(i) = i - tmpcoo%ja(i) = ilaggr(i) - end do - call tmpcoo%set_nzeros(ncol) - call tmpcoo%set_dupl(psb_dupl_add_) - call tmpcoo%set_sorted() ! At this point this is in row-major - call op_prol%mv_from(tmpcoo) - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - - return - -end subroutine mld_caggrmap_bld diff --git a/mlprec/impl/mld_caggrmat_asb.f90 b/mlprec/impl/mld_caggrmat_asb.f90 deleted file mode 100644 index 4804626b..00000000 --- a/mlprec/impl/mld_caggrmat_asb.f90 +++ /dev/null @@ -1,193 +0,0 @@ -! -! -! MLD2P4 version 2.1 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_caggrmat_asb.f90 -! -! Subroutine: mld_caggrmat_asb -! Version: complex -! -! This routine builds a coarse-level matrix A_C from a fine-level matrix A -! by using the Galerkin approach, i.e. -! -! A_C = P_C^T A P_C, -! -! where P_C is a prolongator from the coarse level to the fine one. -! -! A mapping from the nodes of the adjacency graph of A to the nodes of the -! adjacency graph of A_C has been computed by the mld_aggrmap_bld subroutine. -! The prolongator P_C is built here from this mapping, according to the -! value of p%iprcparm(mld_aggr_prol_), specified by the user through -! mld_cprecinit and mld_zprecset. -! On output from this routine the entries of AC, op_prol, op_restr -! are still in "global numbering" mode; this is fixed in the calling routine -! mld_c_lev_aggrmat_asb. -! -! Currently four different prolongators are implemented, corresponding to -! four aggregation algorithms: -! 1. un-smoothed aggregation, -! 2. smoothed aggregation, -! 3. "bizarre" aggregation. -! 4. minimum energy -! 1. The non-smoothed aggregation uses as prolongator the piecewise constant -! interpolation operator corresponding to the fine-to-coarse level mapping built -! by mld_aggrmap_bld. This is called tentative prolongator. -! 2. The smoothed aggregation uses as prolongator the operator obtained by applying -! a damped Jacobi smoother to the tentative prolongator. -! 3. The "bizarre" aggregation uses a prolongator proposed by the authors of MLD2P4. -! This prolongator still requires a deep analysis and testing and its use is -! not recommended. -! 4. Minimum energy aggregation: ADD REFERENCE. -! -! For more details see -! M. Brezina and P. Vanek, A black-box iterative solver based on a two-level -! Schwarz method, Computing, 63 (1999), 233-263. -! P. D'Ambra, D. di Serafino and S. Filippone, On the development of PSBLAS-based -! parallel two-level Schwarz preconditioners, Appl. Num. Math., 57 (2007), -! 1181-1196. -! -! -! -! Arguments: -! a - type(psb_cspmat_type), input. -! The sparse matrix structure containing the local part of -! the fine-level matrix. -! desc_a - type(psb_desc_type), input. -! The communication descriptor of the fine-level matrix. -! p - type(mld_c_onelev_type), input/output. -! The 'one-level' data structure that will contain the local -! part of the matrix to be built as well as the information -! concerning the prolongator and its transpose. -! parms - type(mld_sml_parms), input -! Parameters controlling the choice of algorithm -! ac - type(psb_cspmat_type), output -! The coarse matrix on output -! -! ilaggr - integer, dimension(:), input -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that the indices -! are assumed to be shifted so as to make sure the ranges on -! the various processes do not overlap. -! nlaggr - integer, dimension(:) input -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_cspmat_type), input/output -! The tentative prolongator on input, the computed prolongator on output -! -! op_restr - type(psb_cspmat_type), output -! The restrictor operator; normally, it is the transpose of the prolongator. -! -! info - integer, output. -! Error code. -! -subroutine mld_caggrmat_asb(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_restr,info) - - use psb_base_mod - use mld_base_prec_type - use mld_c_inner_mod, mld_protect_name => mld_caggrmat_asb - - implicit none - -! Arguments - type(psb_cspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) - type(mld_sml_parms), intent(inout) :: parms - type(psb_cspmat_type), intent(inout) :: ac, op_prol,op_restr - integer(psb_ipk_), intent(out) :: info - -! Local variables - type(psb_c_coo_sparse_mat) :: acoo, bcoo - type(psb_c_csr_sparse_mat) :: acsr1 - integer(psb_ipk_) :: nzl,ntaggr, err_act - integer(psb_ipk_) :: debug_level, debug_unit - integer(psb_ipk_) :: ictxt,np,me - character(len=20) :: name - - name='mld_aggrmat_asb' - if(psb_get_errstatus().ne.0) return - info=psb_success_ - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - - - ictxt = desc_a%get_context() - - call psb_info(ictxt, me, np) - - select case (parms%aggr_prol) - case (mld_no_smooth_) - - call mld_caggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,& - & parms,ac,op_prol,op_restr,info) - - case(mld_smooth_prol_) - - call mld_caggrmat_smth_asb(a,desc_a,ilaggr,nlaggr, & - & parms,ac,op_prol,op_restr,info) - - case(mld_biz_prol_) - - call mld_caggrmat_biz_asb(a,desc_a,ilaggr,nlaggr, & - & parms,ac,op_prol,op_restr,info) - - case(mld_min_energy_) - - call mld_caggrmat_minnrg_asb(a,desc_a,ilaggr,nlaggr, & - & parms,ac,op_prol,op_restr,info) - - case default - info = psb_err_internal_error_ - call psb_errpush(info,name,a_err='Invalid aggr kind') - goto 9999 - - end select - if (info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='Inner aggrmat asb') - goto 9999 - end if - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - - return - -end subroutine mld_caggrmat_asb diff --git a/mlprec/impl/mld_d_hierarchy_bld.f90 b/mlprec/impl/mld_d_hierarchy_bld.f90 index 6b68fa58..c7b882e3 100644 --- a/mlprec/impl/mld_d_hierarchy_bld.f90 +++ b/mlprec/impl/mld_d_hierarchy_bld.f90 @@ -84,6 +84,7 @@ subroutine mld_d_hierarchy_bld(a,desc_a,prec,info) real(psb_dpk_) :: mnaggratio, sizeratio, athresh, aomega class(mld_d_base_smoother_type), allocatable :: coarse_sm, base_sm, med_sm, & & base_sm2, med_sm2, coarse_sm2 + class(mld_d_base_aggregator_type), allocatable :: tmp_aggr type(mld_dml_parms) :: baseparms, medparms, coarseparms integer(psb_ipk_), allocatable :: ilaggr(:), nlaggr(:) type(psb_dspmat_type) :: op_prol @@ -216,19 +217,26 @@ subroutine mld_d_hierarchy_bld(a,desc_a,prec,info) allocate(tprecv(nplevs),stat=info) ! First all existing levels if (info == 0) tprecv(1)%parms = baseparms - if (info == 0) call restore_smoothers(tprecv(1),prec%precv(1)%sm,prec%precv(1)%sm2a,info) + if (info == 0) call restore_smoothers(tprecv(1),& + & prec%precv(1)%sm,prec%precv(1)%sm2a,info) + if (info == 0) call move_alloc(prec%precv(1)%aggr,tprecv(1)%aggr) do i=2, min(iszv,nplevs) - 1 if (info == 0) tprecv(i)%parms = medparms - if (info == 0) call restore_smoothers(tprecv(i),prec%precv(i)%sm,prec%precv(i)%sm2a,info) + if (info == 0) call restore_smoothers(tprecv(i),& + & prec%precv(i)%sm,prec%precv(i)%sm2a,info) + if (info == 0) call move_alloc(prec%precv(i)%aggr,tprecv(i)%aggr) end do ! Further intermediates, if any do i=iszv-1, nplevs - 1 if (info == 0) tprecv(i)%parms = medparms if (info == 0) call restore_smoothers(tprecv(i),med_sm,med_sm2,info) + if ((info == 0).and..not.allocated(tprecv(i)%aggr))& + & allocate(tprecv(i)%aggr,source=tprecv(1)%aggr,stat=info) end do ! Then coarse if (info == 0) tprecv(nplevs)%parms = coarseparms if (info == 0) call restore_smoothers(tprecv(nplevs),coarse_sm,coarse_sm2,info) + if (info == 0) allocate(tprecv(nplevs)%aggr,source=tprecv(i)%aggr,stat=info) if (info /= psb_success_) then call psb_errpush(psb_err_from_subroutine_,name,& & a_err='prec reallocation') @@ -272,9 +280,10 @@ subroutine mld_d_hierarchy_bld(a,desc_a,prec,info) ! ! Build the mapping between levels i-1 and i and the matrix ! at level i - ! - if (info == psb_success_) call mld_aggrmap_bld(prec%precv(i),& - & prec%precv(i-1)%base_a,prec%precv(i-1)%base_desc,& + ! + if (info == psb_success_)& + & call prec%precv(i)%bld_tprol(prec%precv(i-1)%base_a,& + & prec%precv(i-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then @@ -282,6 +291,7 @@ subroutine mld_d_hierarchy_bld(a,desc_a,prec,info) & a_err='Map build') goto 9999 endif + if (i= psb_debug_outer_) & & write(debug_unit,*) me,' ',trim(name),& @@ -346,7 +356,8 @@ subroutine mld_d_hierarchy_bld(a,desc_a,prec,info) prec%precv(newsz)%parms%aggr_thresh = athresh prec%precv(newsz)%parms%aggr_omega_val = aomega - if (info == 0) call restore_smoothers(prec%precv(newsz),coarse_sm,coarse_sm2,info) + if (info == 0) call restore_smoothers(prec%precv(newsz),& + & coarse_sm,coarse_sm2,info) if (newsz < i) then ! ! We are going back and revisit a previous leve; @@ -357,7 +368,7 @@ subroutine mld_d_hierarchy_bld(a,desc_a,prec,info) call prec%precv(newsz)%tprol%clone(op_prol,info) end if - if (info == psb_success_) call mld_lev_mat_asb(prec%precv(newsz),& + if (info == psb_success_) call prec%precv(newsz)%mat_asb( & & prec%precv(newsz-1)%base_a,prec%precv(newsz-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) if (info /= 0) then @@ -367,7 +378,7 @@ subroutine mld_d_hierarchy_bld(a,desc_a,prec,info) endif exit array_build_loop else - if (info == psb_success_) call mld_lev_mat_asb(prec%precv(i),& + if (info == psb_success_) call prec%precv(i)%mat_asb(& & prec%precv(i-1)%base_a,prec%precv(i-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) end if diff --git a/mlprec/impl/mld_d_lev_aggrmat_asb.f90 b/mlprec/impl/mld_d_lev_aggrmat_asb.f90 deleted file mode 100644 index 98c579a6..00000000 --- a/mlprec/impl/mld_d_lev_aggrmat_asb.f90 +++ /dev/null @@ -1,267 +0,0 @@ -! -! -! MLD2P4 version 2.1 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_d_lev_aggrmat_asb.f90 -! -! Subroutine: mld_d_lev_aggrmat_asb -! Version: real -! -! This routine builds the matrix associated to the current level of the -! multilevel preconditioner from the matrix associated to the previous level, -! by using the user-specified aggregation technique (therefore, it also builds the -! prolongation and restriction operators mapping the current level to the -! previous one and vice versa). -! The current level is regarded as the coarse one, while the previous as -! the fine one. This is in agreement with the fact that the routine is called, -! by mld_mlprec_bld, only on levels >=2. -! The main structure is: -! 1. Perform sanity checks; -! 2. Call mld_Xaggrmat_asb to compute prolongator/restrictor/AC -! 3. According to the choice of DIST/REPL for AC, build a descriptor DESC_AC, -! and adjust the column numbering of AC/OP_PROL/OP_RESTR -! 4. Pack restrictor and prolongator into p%map -! 5. Fix base_a and base_desc pointers. -! -! -! Arguments: -! p - type(mld_d_onelev_type), input/output. -! The 'one-level' data structure containing the control -! parameters and (eventually) coarse matrix and prolongator/restrictors. -! -! a - type(psb_dspmat_type). -! The sparse matrix structure containing the local part of the -! fine-level matrix. -! desc_a - type(psb_desc_type), input. -! The communication descriptor of a. -! ilaggr - integer, dimension(:), input -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that the indices -! are assumed to be shifted so as to make sure the ranges on -! the various processes do not overlap. -! nlaggr - integer, dimension(:) input -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_dspmat_type), input/output -! The tentative prolongator on input, released on output. -! -! info - integer, output. -! Error code. -! -subroutine mld_d_lev_aggrmat_asb(p,a,desc_a,ilaggr,nlaggr,op_prol,info) - - use psb_base_mod - use mld_base_prec_type - use mld_d_inner_mod, mld_protect_name => mld_d_lev_aggrmat_asb - - implicit none - - ! Arguments - type(mld_d_onelev_type), intent(inout), target :: p - type(psb_dspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(inout) :: ilaggr(:),nlaggr(:) - type(psb_dspmat_type), intent(inout) :: op_prol - integer(psb_ipk_), intent(out) :: info - - - ! Local variables - character(len=24) :: name - integer(psb_mpik_) :: ictxt, np, me - integer(psb_ipk_) :: err_act - type(psb_dspmat_type) :: ac, op_restr - type(psb_d_coo_sparse_mat) :: acoo, bcoo - type(psb_d_csr_sparse_mat) :: acsr1 - integer(psb_ipk_) :: nzl, ntaggr - integer(psb_ipk_) :: debug_level, debug_unit - - name='mld_d_lev_aggrmat_asb' - if (psb_get_errstatus().ne.0) return - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - info = psb_success_ - ictxt = desc_a%get_context() - call psb_info(ictxt,me,np) - - call mld_check_def(p%parms%aggr_prol,'Smoother',& - & mld_smooth_prol_,is_legal_ml_aggr_prol) - call mld_check_def(p%parms%coarse_mat,'Coarse matrix',& - & mld_distr_mat_,is_legal_ml_coarse_mat) - call mld_check_def(p%parms%aggr_filter,'Use filtered matrix',& - & mld_no_filter_mat_,is_legal_aggr_filter) - call mld_check_def(p%parms%aggr_omega_alg,'Omega Alg.',& - & mld_eig_est_,is_legal_ml_aggr_omega_alg) - call mld_check_def(p%parms%aggr_eig,'Eigenvalue estimate',& - & mld_max_norm_,is_legal_ml_aggr_eig) - call mld_check_def(p%parms%aggr_omega_val,'Omega',dzero,is_legal_d_omega) - - - ! - ! Build the coarse-level matrix from the fine-level one, starting from - ! the mapping defined by mld_aggrmap_bld and applying the aggregation - ! algorithm specified by p%iprcparm(mld_aggr_prol_) - ! - call mld_daggrmat_asb(a,desc_a,ilaggr,nlaggr,p%parms,ac,op_prol,op_restr,info) - - if(info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='mld_aggrmat_asb') - goto 9999 - end if - - - ! Common code refactored here. - - ntaggr = sum(nlaggr) - - select case(p%parms%coarse_mat) - - case(mld_distr_mat_) - - call ac%mv_to(bcoo) - nzl = bcoo%get_nzeros() - - if (info == psb_success_) call psb_cdall(ictxt,p%desc_ac,info,nl=nlaggr(me+1)) - if (info == psb_success_) call psb_cdins(nzl,bcoo%ia,bcoo%ja,p%desc_ac,info) - if (info == psb_success_) call psb_cdasb(p%desc_ac,info) - if (info == psb_success_) call psb_glob_to_loc(bcoo%ia(1:nzl),p%desc_ac,info,iact='I') - if (info == psb_success_) call psb_glob_to_loc(bcoo%ja(1:nzl),p%desc_ac,info,iact='I') - if (info /= psb_success_) then - call psb_errpush(psb_err_internal_error_,name,& - & a_err='Creating p%desc_ac and converting ac') - goto 9999 - end if - if (debug_level >= psb_debug_outer_) & - & write(debug_unit,*) me,' ',trim(name),& - & 'Assembld aux descr. distr.' - call p%ac%mv_from(bcoo) - - call p%ac%set_nrows(p%desc_ac%get_local_rows()) - call p%ac%set_ncols(p%desc_ac%get_local_cols()) - call p%ac%set_asb() - - if (info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_sp_free') - goto 9999 - end if - - if (np>1) then - call op_prol%mv_to(acsr1) - nzl = acsr1%get_nzeros() - call psb_glob_to_loc(acsr1%ja(1:nzl),p%desc_ac,info,'I') - if(info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_glob_to_loc') - goto 9999 - end if - call op_prol%mv_from(acsr1) - endif - call op_prol%set_ncols(p%desc_ac%get_local_cols()) - - if (np>1) then - call op_restr%cscnv(info,type='coo',dupl=psb_dupl_add_) - call op_restr%mv_to(acoo) - nzl = acoo%get_nzeros() - if (info == psb_success_) call psb_glob_to_loc(acoo%ia(1:nzl),p%desc_ac,info,'I') - call acoo%set_dupl(psb_dupl_add_) - if (info == psb_success_) call op_restr%mv_from(acoo) - if (info == psb_success_) call op_restr%cscnv(info,type='csr') - if(info /= psb_success_) then - call psb_errpush(psb_err_internal_error_,name,& - & a_err='Converting op_restr to local') - goto 9999 - end if - end if - ! - ! Clip to local rows. - ! - call op_restr%set_nrows(p%desc_ac%get_local_rows()) - - if (debug_level >= psb_debug_outer_) & - & write(debug_unit,*) me,' ',trim(name),& - & 'Done ac ' - - case(mld_repl_mat_) - ! - ! - call psb_cdall(ictxt,p%desc_ac,info,mg=ntaggr,repl=.true.) - if (info == psb_success_) call psb_cdasb(p%desc_ac,info) - if (info == psb_success_) & - & call psb_gather(p%ac,ac,p%desc_ac,info,dupl=psb_dupl_add_,keeploc=.false.) - - if (info /= psb_success_) goto 9999 - - case default - info = psb_err_internal_error_ - call psb_errpush(info,name,a_err='invalid mld_coarse_mat_') - goto 9999 - end select - - call p%ac%cscnv(info,type='csr',dupl=psb_dupl_add_) - if(info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='spcnv') - goto 9999 - end if - - ! - ! Copy the prolongation/restriction matrices into the descriptor map. - ! op_restr => PR^T i.e. restriction operator - ! op_prol => PR i.e. prolongation operator - ! - - p%map = psb_linmap(psb_map_aggr_,desc_a,& - & p%desc_ac,op_restr,op_prol,ilaggr,nlaggr) - if (info == psb_success_) call op_prol%free() - if (info == psb_success_) call op_restr%free() - if(info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='sp_Free') - goto 9999 - end if - ! - ! Fix the base_a and base_desc pointers for handling of residuals. - ! This is correct because this routine is only called at levels >=2. - ! - p%base_a => p%ac - p%base_desc => p%desc_ac - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - return - -end subroutine mld_d_lev_aggrmat_asb diff --git a/mlprec/impl/mld_daggrmap_bld.f90 b/mlprec/impl/mld_daggrmap_bld.f90 deleted file mode 100644 index e186d719..00000000 --- a/mlprec/impl/mld_daggrmap_bld.f90 +++ /dev/null @@ -1,189 +0,0 @@ -! -! -! MLD2P4 version 2.1 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_daggrmap_bld.f90 -! -! Subroutine: mld_daggrmap_bld -! Version: real -! -! This routine builds a mapping from the row indices of the fine-level matrix -! to the row indices of the coarse-level matrix, according to a decoupled -! aggregation algorithm. This mapping will be used by mld_aggrmat_asb to -! build the coarse-level matrix. -! -! The aggregation algorithm is a parallel version of that described in -! * M. Brezina and P. Vanek, A black-box iterative solver based on a -! two-level Schwarz method, Computing, 63 (1999), 233-263. -! * P. Vanek, J. Mandel and M. Brezina, Algebraic Multigrid by Smoothed -! Aggregation for Second and Fourth Order Elliptic Problems, Computing, 56 -! (1996), 179-196. -! For more details see -! P. D'Ambra, D. di Serafino and S. Filippone, On the development of -! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. -! 57 (2007), 1181-1196. -! -! -! Arguments: -! aggr_type - integer, input. -! The scalar used to identify the aggregation algorithm. -! theta - real, input. -! The aggregation threshold used in the aggregation algorithm. -! 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. -! The communication descriptor of the fine-level matrix. -! ilaggr - integer, dimension(:), allocatable. -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that on exit the indices -! will be shifted so as to make sure the ranges on the various processes do not -! overlap. -! nlaggr - integer, dimension(:), allocatable. -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_dspmat_type). -! The tentative prolongator, based on ilaggr. -! -! info - integer, output. -! Error code. -! -subroutine mld_daggrmap_bld(aggr_type,iorder,theta,a,desc_a,ilaggr,nlaggr,op_prol,info) - - use psb_base_mod - use mld_base_prec_type - use mld_d_inner_mod, mld_protect_name => mld_daggrmap_bld - - implicit none - - ! Arguments - integer(psb_ipk_), intent(in) :: iorder - integer(psb_ipk_), intent(in) :: aggr_type - real(psb_dpk_), intent(in) :: theta - type(psb_dspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - type(psb_dspmat_type), intent(out) :: op_prol - integer(psb_ipk_), intent(out) :: info - - ! Local variables - integer(psb_ipk_), allocatable :: ils(:), neigh(:) - integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m,naggrm1, naggrp1, ntaggr - type(psb_dspmat_type) :: atmp, atrans - type(psb_d_coo_sparse_mat) :: tmpcoo - integer(psb_ipk_) :: debug_level, debug_unit,err_act - integer(psb_ipk_) :: ictxt,np,me - integer(psb_ipk_) :: nrow, ncol, n_ne - character(len=20) :: name, ch_err - - if(psb_get_errstatus() /= 0) return - info=psb_success_ - name = 'mld_aggrmap_bld' - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - ! - ictxt=desc_a%get_context() - call psb_info(ictxt,me,np) - nrow = desc_a%get_local_rows() - ncol = desc_a%get_local_cols() - - select case (aggr_type) - case (mld_dec_aggr_) - call mld_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) - - case (mld_sym_dec_aggr_) - nr = a%get_nrows() - call a%csclip(atmp,info,imax=nr,jmax=nr,& - & rscale=.false.,cscale=.false.) - call atmp%set_nrows(nr) - call atmp%set_ncols(nr) - if (info == psb_success_) call atmp%transp(atrans) - if (info == psb_success_) call atrans%cscnv(info,type='COO') - if (info == psb_success_) call psb_rwextd(nr,atmp,info,b=atrans,rowscale=.false.) - call atmp%set_nrows(nr) - call atmp%set_ncols(nr) - if (info == psb_success_) call atrans%free() - if (info == psb_success_) call atmp%cscnv(info,type='CSR') - if (info == psb_success_) call mld_dec_map_bld(iorder,theta,atmp,desc_a,nlaggr,ilaggr,info) - if (info == psb_success_) call atmp%free() - - case default - - info = -1 - call psb_errpush(psb_err_input_value_invalid_i_,name,& - & i_err=(/ione,aggr_type,izero,izero,izero/)) - goto 9999 - end select - - if (info /= psb_success_) then - info=psb_err_internal_error_ - call psb_errpush(info,name,a_err='dec_map_bld') - goto 9999 - end if - - naggr = nlaggr(me+1) - ntaggr = sum(nlaggr) - naggrm1 = sum(nlaggr(1:me)) - naggrp1 = sum(nlaggr(1:me+1)) - ilaggr(1:nrow) = ilaggr(1:nrow) + naggrm1 - call psb_halo(ilaggr,desc_a,info) - if (info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_halo') - goto 9999 - end if - - call tmpcoo%allocate(ncol,ntaggr,ncol) - do i=1,ncol - tmpcoo%val(i) = done - tmpcoo%ia(i) = i - tmpcoo%ja(i) = ilaggr(i) - end do - call tmpcoo%set_nzeros(ncol) - call tmpcoo%set_dupl(psb_dupl_add_) - call tmpcoo%set_sorted() ! At this point this is in row-major - call op_prol%mv_from(tmpcoo) - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - - return - -end subroutine mld_daggrmap_bld diff --git a/mlprec/impl/mld_daggrmat_asb.f90 b/mlprec/impl/mld_daggrmat_asb.f90 deleted file mode 100644 index 55f8a5b7..00000000 --- a/mlprec/impl/mld_daggrmat_asb.f90 +++ /dev/null @@ -1,193 +0,0 @@ -! -! -! MLD2P4 version 2.1 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_daggrmat_asb.f90 -! -! Subroutine: mld_daggrmat_asb -! Version: real -! -! This routine builds a coarse-level matrix A_C from a fine-level matrix A -! by using the Galerkin approach, i.e. -! -! A_C = P_C^T A P_C, -! -! where P_C is a prolongator from the coarse level to the fine one. -! -! A mapping from the nodes of the adjacency graph of A to the nodes of the -! adjacency graph of A_C has been computed by the mld_aggrmap_bld subroutine. -! The prolongator P_C is built here from this mapping, according to the -! value of p%iprcparm(mld_aggr_prol_), specified by the user through -! mld_dprecinit and mld_zprecset. -! On output from this routine the entries of AC, op_prol, op_restr -! are still in "global numbering" mode; this is fixed in the calling routine -! mld_d_lev_aggrmat_asb. -! -! Currently four different prolongators are implemented, corresponding to -! four aggregation algorithms: -! 1. un-smoothed aggregation, -! 2. smoothed aggregation, -! 3. "bizarre" aggregation. -! 4. minimum energy -! 1. The non-smoothed aggregation uses as prolongator the piecewise constant -! interpolation operator corresponding to the fine-to-coarse level mapping built -! by mld_aggrmap_bld. This is called tentative prolongator. -! 2. The smoothed aggregation uses as prolongator the operator obtained by applying -! a damped Jacobi smoother to the tentative prolongator. -! 3. The "bizarre" aggregation uses a prolongator proposed by the authors of MLD2P4. -! This prolongator still requires a deep analysis and testing and its use is -! not recommended. -! 4. Minimum energy aggregation: ADD REFERENCE. -! -! For more details see -! M. Brezina and P. Vanek, A black-box iterative solver based on a two-level -! Schwarz method, Computing, 63 (1999), 233-263. -! P. D'Ambra, D. di Serafino and S. Filippone, On the development of PSBLAS-based -! parallel two-level Schwarz preconditioners, Appl. Num. Math., 57 (2007), -! 1181-1196. -! -! -! -! Arguments: -! 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. -! The communication descriptor of the fine-level matrix. -! p - type(mld_d_onelev_type), input/output. -! The 'one-level' data structure that will contain the local -! part of the matrix to be built as well as the information -! concerning the prolongator and its transpose. -! parms - type(mld_dml_parms), input -! Parameters controlling the choice of algorithm -! ac - type(psb_dspmat_type), output -! The coarse matrix on output -! -! ilaggr - integer, dimension(:), input -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that the indices -! are assumed to be shifted so as to make sure the ranges on -! the various processes do not overlap. -! nlaggr - integer, dimension(:) input -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_dspmat_type), input/output -! The tentative prolongator on input, the computed prolongator on output -! -! op_restr - type(psb_dspmat_type), output -! The restrictor operator; normally, it is the transpose of the prolongator. -! -! info - integer, output. -! Error code. -! -subroutine mld_daggrmat_asb(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_restr,info) - - use psb_base_mod - use mld_base_prec_type - use mld_d_inner_mod, mld_protect_name => mld_daggrmat_asb - - implicit none - -! Arguments - type(psb_dspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) - type(mld_dml_parms), intent(inout) :: parms - type(psb_dspmat_type), intent(inout) :: ac, op_prol,op_restr - integer(psb_ipk_), intent(out) :: info - -! Local variables - type(psb_d_coo_sparse_mat) :: acoo, bcoo - type(psb_d_csr_sparse_mat) :: acsr1 - integer(psb_ipk_) :: nzl,ntaggr, err_act - integer(psb_ipk_) :: debug_level, debug_unit - integer(psb_ipk_) :: ictxt,np,me - character(len=20) :: name - - name='mld_aggrmat_asb' - if(psb_get_errstatus().ne.0) return - info=psb_success_ - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - - - ictxt = desc_a%get_context() - - call psb_info(ictxt, me, np) - - select case (parms%aggr_prol) - case (mld_no_smooth_) - - call mld_daggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,& - & parms,ac,op_prol,op_restr,info) - - case(mld_smooth_prol_) - - call mld_daggrmat_smth_asb(a,desc_a,ilaggr,nlaggr, & - & parms,ac,op_prol,op_restr,info) - - case(mld_biz_prol_) - - call mld_daggrmat_biz_asb(a,desc_a,ilaggr,nlaggr, & - & parms,ac,op_prol,op_restr,info) - - case(mld_min_energy_) - - call mld_daggrmat_minnrg_asb(a,desc_a,ilaggr,nlaggr, & - & parms,ac,op_prol,op_restr,info) - - case default - info = psb_err_internal_error_ - call psb_errpush(info,name,a_err='Invalid aggr kind') - goto 9999 - - end select - if (info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='Inner aggrmat asb') - goto 9999 - end if - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - - return - -end subroutine mld_daggrmat_asb diff --git a/mlprec/impl/mld_s_hierarchy_bld.f90 b/mlprec/impl/mld_s_hierarchy_bld.f90 index 28fbf51d..a579348b 100644 --- a/mlprec/impl/mld_s_hierarchy_bld.f90 +++ b/mlprec/impl/mld_s_hierarchy_bld.f90 @@ -84,6 +84,7 @@ subroutine mld_s_hierarchy_bld(a,desc_a,prec,info) real(psb_spk_) :: mnaggratio, sizeratio, athresh, aomega class(mld_s_base_smoother_type), allocatable :: coarse_sm, base_sm, med_sm, & & base_sm2, med_sm2, coarse_sm2 + class(mld_s_base_aggregator_type), allocatable :: tmp_aggr type(mld_sml_parms) :: baseparms, medparms, coarseparms integer(psb_ipk_), allocatable :: ilaggr(:), nlaggr(:) type(psb_sspmat_type) :: op_prol @@ -216,19 +217,26 @@ subroutine mld_s_hierarchy_bld(a,desc_a,prec,info) allocate(tprecv(nplevs),stat=info) ! First all existing levels if (info == 0) tprecv(1)%parms = baseparms - if (info == 0) call restore_smoothers(tprecv(1),prec%precv(1)%sm,prec%precv(1)%sm2a,info) + if (info == 0) call restore_smoothers(tprecv(1),& + & prec%precv(1)%sm,prec%precv(1)%sm2a,info) + if (info == 0) call move_alloc(prec%precv(1)%aggr,tprecv(1)%aggr) do i=2, min(iszv,nplevs) - 1 if (info == 0) tprecv(i)%parms = medparms - if (info == 0) call restore_smoothers(tprecv(i),prec%precv(i)%sm,prec%precv(i)%sm2a,info) + if (info == 0) call restore_smoothers(tprecv(i),& + & prec%precv(i)%sm,prec%precv(i)%sm2a,info) + if (info == 0) call move_alloc(prec%precv(i)%aggr,tprecv(i)%aggr) end do ! Further intermediates, if any do i=iszv-1, nplevs - 1 if (info == 0) tprecv(i)%parms = medparms if (info == 0) call restore_smoothers(tprecv(i),med_sm,med_sm2,info) + if ((info == 0).and..not.allocated(tprecv(i)%aggr))& + & allocate(tprecv(i)%aggr,source=tprecv(1)%aggr,stat=info) end do ! Then coarse if (info == 0) tprecv(nplevs)%parms = coarseparms if (info == 0) call restore_smoothers(tprecv(nplevs),coarse_sm,coarse_sm2,info) + if (info == 0) allocate(tprecv(nplevs)%aggr,source=tprecv(i)%aggr,stat=info) if (info /= psb_success_) then call psb_errpush(psb_err_from_subroutine_,name,& & a_err='prec reallocation') @@ -272,9 +280,10 @@ subroutine mld_s_hierarchy_bld(a,desc_a,prec,info) ! ! Build the mapping between levels i-1 and i and the matrix ! at level i - ! - if (info == psb_success_) call mld_aggrmap_bld(prec%precv(i),& - & prec%precv(i-1)%base_a,prec%precv(i-1)%base_desc,& + ! + if (info == psb_success_)& + & call prec%precv(i)%bld_tprol(prec%precv(i-1)%base_a,& + & prec%precv(i-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then @@ -282,6 +291,7 @@ subroutine mld_s_hierarchy_bld(a,desc_a,prec,info) & a_err='Map build') goto 9999 endif + if (i= psb_debug_outer_) & & write(debug_unit,*) me,' ',trim(name),& @@ -346,7 +356,8 @@ subroutine mld_s_hierarchy_bld(a,desc_a,prec,info) prec%precv(newsz)%parms%aggr_thresh = athresh prec%precv(newsz)%parms%aggr_omega_val = aomega - if (info == 0) call restore_smoothers(prec%precv(newsz),coarse_sm,coarse_sm2,info) + if (info == 0) call restore_smoothers(prec%precv(newsz),& + & coarse_sm,coarse_sm2,info) if (newsz < i) then ! ! We are going back and revisit a previous leve; @@ -357,7 +368,7 @@ subroutine mld_s_hierarchy_bld(a,desc_a,prec,info) call prec%precv(newsz)%tprol%clone(op_prol,info) end if - if (info == psb_success_) call mld_lev_mat_asb(prec%precv(newsz),& + if (info == psb_success_) call prec%precv(newsz)%mat_asb( & & prec%precv(newsz-1)%base_a,prec%precv(newsz-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) if (info /= 0) then @@ -367,7 +378,7 @@ subroutine mld_s_hierarchy_bld(a,desc_a,prec,info) endif exit array_build_loop else - if (info == psb_success_) call mld_lev_mat_asb(prec%precv(i),& + if (info == psb_success_) call prec%precv(i)%mat_asb(& & prec%precv(i-1)%base_a,prec%precv(i-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) end if diff --git a/mlprec/impl/mld_s_lev_aggrmat_asb.f90 b/mlprec/impl/mld_s_lev_aggrmat_asb.f90 deleted file mode 100644 index 2433a1a0..00000000 --- a/mlprec/impl/mld_s_lev_aggrmat_asb.f90 +++ /dev/null @@ -1,267 +0,0 @@ -! -! -! MLD2P4 version 2.1 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_s_lev_aggrmat_asb.f90 -! -! Subroutine: mld_s_lev_aggrmat_asb -! Version: real -! -! This routine builds the matrix associated to the current level of the -! multilevel preconditioner from the matrix associated to the previous level, -! by using the user-specified aggregation technique (therefore, it also builds the -! prolongation and restriction operators mapping the current level to the -! previous one and vice versa). -! The current level is regarded as the coarse one, while the previous as -! the fine one. This is in agreement with the fact that the routine is called, -! by mld_mlprec_bld, only on levels >=2. -! The main structure is: -! 1. Perform sanity checks; -! 2. Call mld_Xaggrmat_asb to compute prolongator/restrictor/AC -! 3. According to the choice of DIST/REPL for AC, build a descriptor DESC_AC, -! and adjust the column numbering of AC/OP_PROL/OP_RESTR -! 4. Pack restrictor and prolongator into p%map -! 5. Fix base_a and base_desc pointers. -! -! -! Arguments: -! p - type(mld_s_onelev_type), input/output. -! The 'one-level' data structure containing the control -! parameters and (eventually) coarse matrix and prolongator/restrictors. -! -! a - type(psb_sspmat_type). -! The sparse matrix structure containing the local part of the -! fine-level matrix. -! desc_a - type(psb_desc_type), input. -! The communication descriptor of a. -! ilaggr - integer, dimension(:), input -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that the indices -! are assumed to be shifted so as to make sure the ranges on -! the various processes do not overlap. -! nlaggr - integer, dimension(:) input -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_sspmat_type), input/output -! The tentative prolongator on input, released on output. -! -! info - integer, output. -! Error code. -! -subroutine mld_s_lev_aggrmat_asb(p,a,desc_a,ilaggr,nlaggr,op_prol,info) - - use psb_base_mod - use mld_base_prec_type - use mld_s_inner_mod, mld_protect_name => mld_s_lev_aggrmat_asb - - implicit none - - ! Arguments - type(mld_s_onelev_type), intent(inout), target :: p - type(psb_sspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(inout) :: ilaggr(:),nlaggr(:) - type(psb_sspmat_type), intent(inout) :: op_prol - integer(psb_ipk_), intent(out) :: info - - - ! Local variables - character(len=24) :: name - integer(psb_mpik_) :: ictxt, np, me - integer(psb_ipk_) :: err_act - type(psb_sspmat_type) :: ac, op_restr - type(psb_s_coo_sparse_mat) :: acoo, bcoo - type(psb_s_csr_sparse_mat) :: acsr1 - integer(psb_ipk_) :: nzl, ntaggr - integer(psb_ipk_) :: debug_level, debug_unit - - name='mld_s_lev_aggrmat_asb' - if (psb_get_errstatus().ne.0) return - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - info = psb_success_ - ictxt = desc_a%get_context() - call psb_info(ictxt,me,np) - - call mld_check_def(p%parms%aggr_prol,'Smoother',& - & mld_smooth_prol_,is_legal_ml_aggr_prol) - call mld_check_def(p%parms%coarse_mat,'Coarse matrix',& - & mld_distr_mat_,is_legal_ml_coarse_mat) - call mld_check_def(p%parms%aggr_filter,'Use filtered matrix',& - & mld_no_filter_mat_,is_legal_aggr_filter) - call mld_check_def(p%parms%aggr_omega_alg,'Omega Alg.',& - & mld_eig_est_,is_legal_ml_aggr_omega_alg) - call mld_check_def(p%parms%aggr_eig,'Eigenvalue estimate',& - & mld_max_norm_,is_legal_ml_aggr_eig) - call mld_check_def(p%parms%aggr_omega_val,'Omega',szero,is_legal_s_omega) - - - ! - ! Build the coarse-level matrix from the fine-level one, starting from - ! the mapping defined by mld_aggrmap_bld and applying the aggregation - ! algorithm specified by p%iprcparm(mld_aggr_prol_) - ! - call mld_saggrmat_asb(a,desc_a,ilaggr,nlaggr,p%parms,ac,op_prol,op_restr,info) - - if(info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='mld_aggrmat_asb') - goto 9999 - end if - - - ! Common code refactored here. - - ntaggr = sum(nlaggr) - - select case(p%parms%coarse_mat) - - case(mld_distr_mat_) - - call ac%mv_to(bcoo) - nzl = bcoo%get_nzeros() - - if (info == psb_success_) call psb_cdall(ictxt,p%desc_ac,info,nl=nlaggr(me+1)) - if (info == psb_success_) call psb_cdins(nzl,bcoo%ia,bcoo%ja,p%desc_ac,info) - if (info == psb_success_) call psb_cdasb(p%desc_ac,info) - if (info == psb_success_) call psb_glob_to_loc(bcoo%ia(1:nzl),p%desc_ac,info,iact='I') - if (info == psb_success_) call psb_glob_to_loc(bcoo%ja(1:nzl),p%desc_ac,info,iact='I') - if (info /= psb_success_) then - call psb_errpush(psb_err_internal_error_,name,& - & a_err='Creating p%desc_ac and converting ac') - goto 9999 - end if - if (debug_level >= psb_debug_outer_) & - & write(debug_unit,*) me,' ',trim(name),& - & 'Assembld aux descr. distr.' - call p%ac%mv_from(bcoo) - - call p%ac%set_nrows(p%desc_ac%get_local_rows()) - call p%ac%set_ncols(p%desc_ac%get_local_cols()) - call p%ac%set_asb() - - if (info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_sp_free') - goto 9999 - end if - - if (np>1) then - call op_prol%mv_to(acsr1) - nzl = acsr1%get_nzeros() - call psb_glob_to_loc(acsr1%ja(1:nzl),p%desc_ac,info,'I') - if(info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_glob_to_loc') - goto 9999 - end if - call op_prol%mv_from(acsr1) - endif - call op_prol%set_ncols(p%desc_ac%get_local_cols()) - - if (np>1) then - call op_restr%cscnv(info,type='coo',dupl=psb_dupl_add_) - call op_restr%mv_to(acoo) - nzl = acoo%get_nzeros() - if (info == psb_success_) call psb_glob_to_loc(acoo%ia(1:nzl),p%desc_ac,info,'I') - call acoo%set_dupl(psb_dupl_add_) - if (info == psb_success_) call op_restr%mv_from(acoo) - if (info == psb_success_) call op_restr%cscnv(info,type='csr') - if(info /= psb_success_) then - call psb_errpush(psb_err_internal_error_,name,& - & a_err='Converting op_restr to local') - goto 9999 - end if - end if - ! - ! Clip to local rows. - ! - call op_restr%set_nrows(p%desc_ac%get_local_rows()) - - if (debug_level >= psb_debug_outer_) & - & write(debug_unit,*) me,' ',trim(name),& - & 'Done ac ' - - case(mld_repl_mat_) - ! - ! - call psb_cdall(ictxt,p%desc_ac,info,mg=ntaggr,repl=.true.) - if (info == psb_success_) call psb_cdasb(p%desc_ac,info) - if (info == psb_success_) & - & call psb_gather(p%ac,ac,p%desc_ac,info,dupl=psb_dupl_add_,keeploc=.false.) - - if (info /= psb_success_) goto 9999 - - case default - info = psb_err_internal_error_ - call psb_errpush(info,name,a_err='invalid mld_coarse_mat_') - goto 9999 - end select - - call p%ac%cscnv(info,type='csr',dupl=psb_dupl_add_) - if(info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='spcnv') - goto 9999 - end if - - ! - ! Copy the prolongation/restriction matrices into the descriptor map. - ! op_restr => PR^T i.e. restriction operator - ! op_prol => PR i.e. prolongation operator - ! - - p%map = psb_linmap(psb_map_aggr_,desc_a,& - & p%desc_ac,op_restr,op_prol,ilaggr,nlaggr) - if (info == psb_success_) call op_prol%free() - if (info == psb_success_) call op_restr%free() - if(info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='sp_Free') - goto 9999 - end if - ! - ! Fix the base_a and base_desc pointers for handling of residuals. - ! This is correct because this routine is only called at levels >=2. - ! - p%base_a => p%ac - p%base_desc => p%desc_ac - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - return - -end subroutine mld_s_lev_aggrmat_asb diff --git a/mlprec/impl/mld_saggrmap_bld.f90 b/mlprec/impl/mld_saggrmap_bld.f90 deleted file mode 100644 index 2009bf6e..00000000 --- a/mlprec/impl/mld_saggrmap_bld.f90 +++ /dev/null @@ -1,189 +0,0 @@ -! -! -! MLD2P4 version 2.1 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_saggrmap_bld.f90 -! -! Subroutine: mld_saggrmap_bld -! Version: real -! -! This routine builds a mapping from the row indices of the fine-level matrix -! to the row indices of the coarse-level matrix, according to a decoupled -! aggregation algorithm. This mapping will be used by mld_aggrmat_asb to -! build the coarse-level matrix. -! -! The aggregation algorithm is a parallel version of that described in -! * M. Brezina and P. Vanek, A black-box iterative solver based on a -! two-level Schwarz method, Computing, 63 (1999), 233-263. -! * P. Vanek, J. Mandel and M. Brezina, Algebraic Multigrid by Smoothed -! Aggregation for Second and Fourth Order Elliptic Problems, Computing, 56 -! (1996), 179-196. -! For more details see -! P. D'Ambra, D. di Serafino and S. Filippone, On the development of -! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. -! 57 (2007), 1181-1196. -! -! -! Arguments: -! aggr_type - integer, input. -! The scalar used to identify the aggregation algorithm. -! theta - real, input. -! The aggregation threshold used in the aggregation algorithm. -! a - type(psb_sspmat_type), input. -! The sparse matrix structure containing the local part of -! the fine-level matrix. -! desc_a - type(psb_desc_type), input. -! The communication descriptor of the fine-level matrix. -! ilaggr - integer, dimension(:), allocatable. -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that on exit the indices -! will be shifted so as to make sure the ranges on the various processes do not -! overlap. -! nlaggr - integer, dimension(:), allocatable. -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_sspmat_type). -! The tentative prolongator, based on ilaggr. -! -! info - integer, output. -! Error code. -! -subroutine mld_saggrmap_bld(aggr_type,iorder,theta,a,desc_a,ilaggr,nlaggr,op_prol,info) - - use psb_base_mod - use mld_base_prec_type - use mld_s_inner_mod, mld_protect_name => mld_saggrmap_bld - - implicit none - - ! Arguments - integer(psb_ipk_), intent(in) :: iorder - integer(psb_ipk_), intent(in) :: aggr_type - real(psb_spk_), intent(in) :: theta - type(psb_sspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - type(psb_sspmat_type), intent(out) :: op_prol - integer(psb_ipk_), intent(out) :: info - - ! Local variables - integer(psb_ipk_), allocatable :: ils(:), neigh(:) - integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m,naggrm1, naggrp1, ntaggr - type(psb_sspmat_type) :: atmp, atrans - type(psb_s_coo_sparse_mat) :: tmpcoo - integer(psb_ipk_) :: debug_level, debug_unit,err_act - integer(psb_ipk_) :: ictxt,np,me - integer(psb_ipk_) :: nrow, ncol, n_ne - character(len=20) :: name, ch_err - - if(psb_get_errstatus() /= 0) return - info=psb_success_ - name = 'mld_aggrmap_bld' - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - ! - ictxt=desc_a%get_context() - call psb_info(ictxt,me,np) - nrow = desc_a%get_local_rows() - ncol = desc_a%get_local_cols() - - select case (aggr_type) - case (mld_dec_aggr_) - call mld_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) - - case (mld_sym_dec_aggr_) - nr = a%get_nrows() - call a%csclip(atmp,info,imax=nr,jmax=nr,& - & rscale=.false.,cscale=.false.) - call atmp%set_nrows(nr) - call atmp%set_ncols(nr) - if (info == psb_success_) call atmp%transp(atrans) - if (info == psb_success_) call atrans%cscnv(info,type='COO') - if (info == psb_success_) call psb_rwextd(nr,atmp,info,b=atrans,rowscale=.false.) - call atmp%set_nrows(nr) - call atmp%set_ncols(nr) - if (info == psb_success_) call atrans%free() - if (info == psb_success_) call atmp%cscnv(info,type='CSR') - if (info == psb_success_) call mld_dec_map_bld(iorder,theta,atmp,desc_a,nlaggr,ilaggr,info) - if (info == psb_success_) call atmp%free() - - case default - - info = -1 - call psb_errpush(psb_err_input_value_invalid_i_,name,& - & i_err=(/ione,aggr_type,izero,izero,izero/)) - goto 9999 - end select - - if (info /= psb_success_) then - info=psb_err_internal_error_ - call psb_errpush(info,name,a_err='dec_map_bld') - goto 9999 - end if - - naggr = nlaggr(me+1) - ntaggr = sum(nlaggr) - naggrm1 = sum(nlaggr(1:me)) - naggrp1 = sum(nlaggr(1:me+1)) - ilaggr(1:nrow) = ilaggr(1:nrow) + naggrm1 - call psb_halo(ilaggr,desc_a,info) - if (info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_halo') - goto 9999 - end if - - call tmpcoo%allocate(ncol,ntaggr,ncol) - do i=1,ncol - tmpcoo%val(i) = sone - tmpcoo%ia(i) = i - tmpcoo%ja(i) = ilaggr(i) - end do - call tmpcoo%set_nzeros(ncol) - call tmpcoo%set_dupl(psb_dupl_add_) - call tmpcoo%set_sorted() ! At this point this is in row-major - call op_prol%mv_from(tmpcoo) - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - - return - -end subroutine mld_saggrmap_bld diff --git a/mlprec/impl/mld_saggrmat_asb.f90 b/mlprec/impl/mld_saggrmat_asb.f90 deleted file mode 100644 index 263fa5e6..00000000 --- a/mlprec/impl/mld_saggrmat_asb.f90 +++ /dev/null @@ -1,193 +0,0 @@ -! -! -! MLD2P4 version 2.1 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_saggrmat_asb.f90 -! -! Subroutine: mld_saggrmat_asb -! Version: real -! -! This routine builds a coarse-level matrix A_C from a fine-level matrix A -! by using the Galerkin approach, i.e. -! -! A_C = P_C^T A P_C, -! -! where P_C is a prolongator from the coarse level to the fine one. -! -! A mapping from the nodes of the adjacency graph of A to the nodes of the -! adjacency graph of A_C has been computed by the mld_aggrmap_bld subroutine. -! The prolongator P_C is built here from this mapping, according to the -! value of p%iprcparm(mld_aggr_prol_), specified by the user through -! mld_sprecinit and mld_zprecset. -! On output from this routine the entries of AC, op_prol, op_restr -! are still in "global numbering" mode; this is fixed in the calling routine -! mld_s_lev_aggrmat_asb. -! -! Currently four different prolongators are implemented, corresponding to -! four aggregation algorithms: -! 1. un-smoothed aggregation, -! 2. smoothed aggregation, -! 3. "bizarre" aggregation. -! 4. minimum energy -! 1. The non-smoothed aggregation uses as prolongator the piecewise constant -! interpolation operator corresponding to the fine-to-coarse level mapping built -! by mld_aggrmap_bld. This is called tentative prolongator. -! 2. The smoothed aggregation uses as prolongator the operator obtained by applying -! a damped Jacobi smoother to the tentative prolongator. -! 3. The "bizarre" aggregation uses a prolongator proposed by the authors of MLD2P4. -! This prolongator still requires a deep analysis and testing and its use is -! not recommended. -! 4. Minimum energy aggregation: ADD REFERENCE. -! -! For more details see -! M. Brezina and P. Vanek, A black-box iterative solver based on a two-level -! Schwarz method, Computing, 63 (1999), 233-263. -! P. D'Ambra, D. di Serafino and S. Filippone, On the development of PSBLAS-based -! parallel two-level Schwarz preconditioners, Appl. Num. Math., 57 (2007), -! 1181-1196. -! -! -! -! Arguments: -! a - type(psb_sspmat_type), input. -! The sparse matrix structure containing the local part of -! the fine-level matrix. -! desc_a - type(psb_desc_type), input. -! The communication descriptor of the fine-level matrix. -! p - type(mld_s_onelev_type), input/output. -! The 'one-level' data structure that will contain the local -! part of the matrix to be built as well as the information -! concerning the prolongator and its transpose. -! parms - type(mld_sml_parms), input -! Parameters controlling the choice of algorithm -! ac - type(psb_sspmat_type), output -! The coarse matrix on output -! -! ilaggr - integer, dimension(:), input -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that the indices -! are assumed to be shifted so as to make sure the ranges on -! the various processes do not overlap. -! nlaggr - integer, dimension(:) input -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_sspmat_type), input/output -! The tentative prolongator on input, the computed prolongator on output -! -! op_restr - type(psb_sspmat_type), output -! The restrictor operator; normally, it is the transpose of the prolongator. -! -! info - integer, output. -! Error code. -! -subroutine mld_saggrmat_asb(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_restr,info) - - use psb_base_mod - use mld_base_prec_type - use mld_s_inner_mod, mld_protect_name => mld_saggrmat_asb - - implicit none - -! Arguments - type(psb_sspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) - type(mld_sml_parms), intent(inout) :: parms - type(psb_sspmat_type), intent(inout) :: ac, op_prol,op_restr - integer(psb_ipk_), intent(out) :: info - -! Local variables - type(psb_s_coo_sparse_mat) :: acoo, bcoo - type(psb_s_csr_sparse_mat) :: acsr1 - integer(psb_ipk_) :: nzl,ntaggr, err_act - integer(psb_ipk_) :: debug_level, debug_unit - integer(psb_ipk_) :: ictxt,np,me - character(len=20) :: name - - name='mld_aggrmat_asb' - if(psb_get_errstatus().ne.0) return - info=psb_success_ - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - - - ictxt = desc_a%get_context() - - call psb_info(ictxt, me, np) - - select case (parms%aggr_prol) - case (mld_no_smooth_) - - call mld_saggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,& - & parms,ac,op_prol,op_restr,info) - - case(mld_smooth_prol_) - - call mld_saggrmat_smth_asb(a,desc_a,ilaggr,nlaggr, & - & parms,ac,op_prol,op_restr,info) - - case(mld_biz_prol_) - - call mld_saggrmat_biz_asb(a,desc_a,ilaggr,nlaggr, & - & parms,ac,op_prol,op_restr,info) - - case(mld_min_energy_) - - call mld_saggrmat_minnrg_asb(a,desc_a,ilaggr,nlaggr, & - & parms,ac,op_prol,op_restr,info) - - case default - info = psb_err_internal_error_ - call psb_errpush(info,name,a_err='Invalid aggr kind') - goto 9999 - - end select - if (info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='Inner aggrmat asb') - goto 9999 - end if - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - - return - -end subroutine mld_saggrmat_asb diff --git a/mlprec/impl/mld_z_hierarchy_bld.f90 b/mlprec/impl/mld_z_hierarchy_bld.f90 index 1c68b7c3..eeafc9f7 100644 --- a/mlprec/impl/mld_z_hierarchy_bld.f90 +++ b/mlprec/impl/mld_z_hierarchy_bld.f90 @@ -84,6 +84,7 @@ subroutine mld_z_hierarchy_bld(a,desc_a,prec,info) real(psb_dpk_) :: mnaggratio, sizeratio, athresh, aomega class(mld_z_base_smoother_type), allocatable :: coarse_sm, base_sm, med_sm, & & base_sm2, med_sm2, coarse_sm2 + class(mld_z_base_aggregator_type), allocatable :: tmp_aggr type(mld_dml_parms) :: baseparms, medparms, coarseparms integer(psb_ipk_), allocatable :: ilaggr(:), nlaggr(:) type(psb_zspmat_type) :: op_prol @@ -216,19 +217,26 @@ subroutine mld_z_hierarchy_bld(a,desc_a,prec,info) allocate(tprecv(nplevs),stat=info) ! First all existing levels if (info == 0) tprecv(1)%parms = baseparms - if (info == 0) call restore_smoothers(tprecv(1),prec%precv(1)%sm,prec%precv(1)%sm2a,info) + if (info == 0) call restore_smoothers(tprecv(1),& + & prec%precv(1)%sm,prec%precv(1)%sm2a,info) + if (info == 0) call move_alloc(prec%precv(1)%aggr,tprecv(1)%aggr) do i=2, min(iszv,nplevs) - 1 if (info == 0) tprecv(i)%parms = medparms - if (info == 0) call restore_smoothers(tprecv(i),prec%precv(i)%sm,prec%precv(i)%sm2a,info) + if (info == 0) call restore_smoothers(tprecv(i),& + & prec%precv(i)%sm,prec%precv(i)%sm2a,info) + if (info == 0) call move_alloc(prec%precv(i)%aggr,tprecv(i)%aggr) end do ! Further intermediates, if any do i=iszv-1, nplevs - 1 if (info == 0) tprecv(i)%parms = medparms if (info == 0) call restore_smoothers(tprecv(i),med_sm,med_sm2,info) + if ((info == 0).and..not.allocated(tprecv(i)%aggr))& + & allocate(tprecv(i)%aggr,source=tprecv(1)%aggr,stat=info) end do ! Then coarse if (info == 0) tprecv(nplevs)%parms = coarseparms if (info == 0) call restore_smoothers(tprecv(nplevs),coarse_sm,coarse_sm2,info) + if (info == 0) allocate(tprecv(nplevs)%aggr,source=tprecv(i)%aggr,stat=info) if (info /= psb_success_) then call psb_errpush(psb_err_from_subroutine_,name,& & a_err='prec reallocation') @@ -272,9 +280,10 @@ subroutine mld_z_hierarchy_bld(a,desc_a,prec,info) ! ! Build the mapping between levels i-1 and i and the matrix ! at level i - ! - if (info == psb_success_) call mld_aggrmap_bld(prec%precv(i),& - & prec%precv(i-1)%base_a,prec%precv(i-1)%base_desc,& + ! + if (info == psb_success_)& + & call prec%precv(i)%bld_tprol(prec%precv(i-1)%base_a,& + & prec%precv(i-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then @@ -282,6 +291,7 @@ subroutine mld_z_hierarchy_bld(a,desc_a,prec,info) & a_err='Map build') goto 9999 endif + if (i= psb_debug_outer_) & & write(debug_unit,*) me,' ',trim(name),& @@ -346,7 +356,8 @@ subroutine mld_z_hierarchy_bld(a,desc_a,prec,info) prec%precv(newsz)%parms%aggr_thresh = athresh prec%precv(newsz)%parms%aggr_omega_val = aomega - if (info == 0) call restore_smoothers(prec%precv(newsz),coarse_sm,coarse_sm2,info) + if (info == 0) call restore_smoothers(prec%precv(newsz),& + & coarse_sm,coarse_sm2,info) if (newsz < i) then ! ! We are going back and revisit a previous leve; @@ -357,7 +368,7 @@ subroutine mld_z_hierarchy_bld(a,desc_a,prec,info) call prec%precv(newsz)%tprol%clone(op_prol,info) end if - if (info == psb_success_) call mld_lev_mat_asb(prec%precv(newsz),& + if (info == psb_success_) call prec%precv(newsz)%mat_asb( & & prec%precv(newsz-1)%base_a,prec%precv(newsz-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) if (info /= 0) then @@ -367,7 +378,7 @@ subroutine mld_z_hierarchy_bld(a,desc_a,prec,info) endif exit array_build_loop else - if (info == psb_success_) call mld_lev_mat_asb(prec%precv(i),& + if (info == psb_success_) call prec%precv(i)%mat_asb(& & prec%precv(i-1)%base_a,prec%precv(i-1)%base_desc,& & ilaggr,nlaggr,op_prol,info) end if diff --git a/mlprec/impl/mld_z_lev_aggrmat_asb.f90 b/mlprec/impl/mld_z_lev_aggrmat_asb.f90 deleted file mode 100644 index 07cac52e..00000000 --- a/mlprec/impl/mld_z_lev_aggrmat_asb.f90 +++ /dev/null @@ -1,267 +0,0 @@ -! -! -! MLD2P4 version 2.1 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_z_lev_aggrmat_asb.f90 -! -! Subroutine: mld_z_lev_aggrmat_asb -! Version: complex -! -! This routine builds the matrix associated to the current level of the -! multilevel preconditioner from the matrix associated to the previous level, -! by using the user-specified aggregation technique (therefore, it also builds the -! prolongation and restriction operators mapping the current level to the -! previous one and vice versa). -! The current level is regarded as the coarse one, while the previous as -! the fine one. This is in agreement with the fact that the routine is called, -! by mld_mlprec_bld, only on levels >=2. -! The main structure is: -! 1. Perform sanity checks; -! 2. Call mld_Xaggrmat_asb to compute prolongator/restrictor/AC -! 3. According to the choice of DIST/REPL for AC, build a descriptor DESC_AC, -! and adjust the column numbering of AC/OP_PROL/OP_RESTR -! 4. Pack restrictor and prolongator into p%map -! 5. Fix base_a and base_desc pointers. -! -! -! Arguments: -! p - type(mld_z_onelev_type), input/output. -! The 'one-level' data structure containing the control -! parameters and (eventually) coarse matrix and prolongator/restrictors. -! -! a - type(psb_zspmat_type). -! The sparse matrix structure containing the local part of the -! fine-level matrix. -! desc_a - type(psb_desc_type), input. -! The communication descriptor of a. -! ilaggr - integer, dimension(:), input -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that the indices -! are assumed to be shifted so as to make sure the ranges on -! the various processes do not overlap. -! nlaggr - integer, dimension(:) input -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_zspmat_type), input/output -! The tentative prolongator on input, released on output. -! -! info - integer, output. -! Error code. -! -subroutine mld_z_lev_aggrmat_asb(p,a,desc_a,ilaggr,nlaggr,op_prol,info) - - use psb_base_mod - use mld_base_prec_type - use mld_z_inner_mod, mld_protect_name => mld_z_lev_aggrmat_asb - - implicit none - - ! Arguments - type(mld_z_onelev_type), intent(inout), target :: p - type(psb_zspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(inout) :: ilaggr(:),nlaggr(:) - type(psb_zspmat_type), intent(inout) :: op_prol - integer(psb_ipk_), intent(out) :: info - - - ! Local variables - character(len=24) :: name - integer(psb_mpik_) :: ictxt, np, me - integer(psb_ipk_) :: err_act - type(psb_zspmat_type) :: ac, op_restr - type(psb_z_coo_sparse_mat) :: acoo, bcoo - type(psb_z_csr_sparse_mat) :: acsr1 - integer(psb_ipk_) :: nzl, ntaggr - integer(psb_ipk_) :: debug_level, debug_unit - - name='mld_z_lev_aggrmat_asb' - if (psb_get_errstatus().ne.0) return - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - info = psb_success_ - ictxt = desc_a%get_context() - call psb_info(ictxt,me,np) - - call mld_check_def(p%parms%aggr_prol,'Smoother',& - & mld_smooth_prol_,is_legal_ml_aggr_prol) - call mld_check_def(p%parms%coarse_mat,'Coarse matrix',& - & mld_distr_mat_,is_legal_ml_coarse_mat) - call mld_check_def(p%parms%aggr_filter,'Use filtered matrix',& - & mld_no_filter_mat_,is_legal_aggr_filter) - call mld_check_def(p%parms%aggr_omega_alg,'Omega Alg.',& - & mld_eig_est_,is_legal_ml_aggr_omega_alg) - call mld_check_def(p%parms%aggr_eig,'Eigenvalue estimate',& - & mld_max_norm_,is_legal_ml_aggr_eig) - call mld_check_def(p%parms%aggr_omega_val,'Omega',dzero,is_legal_d_omega) - - - ! - ! Build the coarse-level matrix from the fine-level one, starting from - ! the mapping defined by mld_aggrmap_bld and applying the aggregation - ! algorithm specified by p%iprcparm(mld_aggr_prol_) - ! - call mld_zaggrmat_asb(a,desc_a,ilaggr,nlaggr,p%parms,ac,op_prol,op_restr,info) - - if(info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='mld_aggrmat_asb') - goto 9999 - end if - - - ! Common code refactored here. - - ntaggr = sum(nlaggr) - - select case(p%parms%coarse_mat) - - case(mld_distr_mat_) - - call ac%mv_to(bcoo) - nzl = bcoo%get_nzeros() - - if (info == psb_success_) call psb_cdall(ictxt,p%desc_ac,info,nl=nlaggr(me+1)) - if (info == psb_success_) call psb_cdins(nzl,bcoo%ia,bcoo%ja,p%desc_ac,info) - if (info == psb_success_) call psb_cdasb(p%desc_ac,info) - if (info == psb_success_) call psb_glob_to_loc(bcoo%ia(1:nzl),p%desc_ac,info,iact='I') - if (info == psb_success_) call psb_glob_to_loc(bcoo%ja(1:nzl),p%desc_ac,info,iact='I') - if (info /= psb_success_) then - call psb_errpush(psb_err_internal_error_,name,& - & a_err='Creating p%desc_ac and converting ac') - goto 9999 - end if - if (debug_level >= psb_debug_outer_) & - & write(debug_unit,*) me,' ',trim(name),& - & 'Assembld aux descr. distr.' - call p%ac%mv_from(bcoo) - - call p%ac%set_nrows(p%desc_ac%get_local_rows()) - call p%ac%set_ncols(p%desc_ac%get_local_cols()) - call p%ac%set_asb() - - if (info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_sp_free') - goto 9999 - end if - - if (np>1) then - call op_prol%mv_to(acsr1) - nzl = acsr1%get_nzeros() - call psb_glob_to_loc(acsr1%ja(1:nzl),p%desc_ac,info,'I') - if(info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_glob_to_loc') - goto 9999 - end if - call op_prol%mv_from(acsr1) - endif - call op_prol%set_ncols(p%desc_ac%get_local_cols()) - - if (np>1) then - call op_restr%cscnv(info,type='coo',dupl=psb_dupl_add_) - call op_restr%mv_to(acoo) - nzl = acoo%get_nzeros() - if (info == psb_success_) call psb_glob_to_loc(acoo%ia(1:nzl),p%desc_ac,info,'I') - call acoo%set_dupl(psb_dupl_add_) - if (info == psb_success_) call op_restr%mv_from(acoo) - if (info == psb_success_) call op_restr%cscnv(info,type='csr') - if(info /= psb_success_) then - call psb_errpush(psb_err_internal_error_,name,& - & a_err='Converting op_restr to local') - goto 9999 - end if - end if - ! - ! Clip to local rows. - ! - call op_restr%set_nrows(p%desc_ac%get_local_rows()) - - if (debug_level >= psb_debug_outer_) & - & write(debug_unit,*) me,' ',trim(name),& - & 'Done ac ' - - case(mld_repl_mat_) - ! - ! - call psb_cdall(ictxt,p%desc_ac,info,mg=ntaggr,repl=.true.) - if (info == psb_success_) call psb_cdasb(p%desc_ac,info) - if (info == psb_success_) & - & call psb_gather(p%ac,ac,p%desc_ac,info,dupl=psb_dupl_add_,keeploc=.false.) - - if (info /= psb_success_) goto 9999 - - case default - info = psb_err_internal_error_ - call psb_errpush(info,name,a_err='invalid mld_coarse_mat_') - goto 9999 - end select - - call p%ac%cscnv(info,type='csr',dupl=psb_dupl_add_) - if(info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='spcnv') - goto 9999 - end if - - ! - ! Copy the prolongation/restriction matrices into the descriptor map. - ! op_restr => PR^T i.e. restriction operator - ! op_prol => PR i.e. prolongation operator - ! - - p%map = psb_linmap(psb_map_aggr_,desc_a,& - & p%desc_ac,op_restr,op_prol,ilaggr,nlaggr) - if (info == psb_success_) call op_prol%free() - if (info == psb_success_) call op_restr%free() - if(info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='sp_Free') - goto 9999 - end if - ! - ! Fix the base_a and base_desc pointers for handling of residuals. - ! This is correct because this routine is only called at levels >=2. - ! - p%base_a => p%ac - p%base_desc => p%desc_ac - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - return - -end subroutine mld_z_lev_aggrmat_asb diff --git a/mlprec/impl/mld_zaggrmap_bld.f90 b/mlprec/impl/mld_zaggrmap_bld.f90 deleted file mode 100644 index dc9adbc9..00000000 --- a/mlprec/impl/mld_zaggrmap_bld.f90 +++ /dev/null @@ -1,189 +0,0 @@ -! -! -! MLD2P4 version 2.1 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_zaggrmap_bld.f90 -! -! Subroutine: mld_zaggrmap_bld -! Version: complex -! -! This routine builds a mapping from the row indices of the fine-level matrix -! to the row indices of the coarse-level matrix, according to a decoupled -! aggregation algorithm. This mapping will be used by mld_aggrmat_asb to -! build the coarse-level matrix. -! -! The aggregation algorithm is a parallel version of that described in -! * M. Brezina and P. Vanek, A black-box iterative solver based on a -! two-level Schwarz method, Computing, 63 (1999), 233-263. -! * P. Vanek, J. Mandel and M. Brezina, Algebraic Multigrid by Smoothed -! Aggregation for Second and Fourth Order Elliptic Problems, Computing, 56 -! (1996), 179-196. -! For more details see -! P. D'Ambra, D. di Serafino and S. Filippone, On the development of -! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. -! 57 (2007), 1181-1196. -! -! -! Arguments: -! aggr_type - integer, input. -! The scalar used to identify the aggregation algorithm. -! theta - real, input. -! The aggregation threshold used in the aggregation algorithm. -! 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. -! The communication descriptor of the fine-level matrix. -! ilaggr - integer, dimension(:), allocatable. -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that on exit the indices -! will be shifted so as to make sure the ranges on the various processes do not -! overlap. -! nlaggr - integer, dimension(:), allocatable. -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_zspmat_type). -! The tentative prolongator, based on ilaggr. -! -! info - integer, output. -! Error code. -! -subroutine mld_zaggrmap_bld(aggr_type,iorder,theta,a,desc_a,ilaggr,nlaggr,op_prol,info) - - use psb_base_mod - use mld_base_prec_type - use mld_z_inner_mod, mld_protect_name => mld_zaggrmap_bld - - implicit none - - ! Arguments - integer(psb_ipk_), intent(in) :: iorder - integer(psb_ipk_), intent(in) :: aggr_type - real(psb_dpk_), intent(in) :: theta - type(psb_zspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - type(psb_zspmat_type), intent(out) :: op_prol - integer(psb_ipk_), intent(out) :: info - - ! Local variables - integer(psb_ipk_), allocatable :: ils(:), neigh(:) - integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m,naggrm1, naggrp1, ntaggr - type(psb_zspmat_type) :: atmp, atrans - type(psb_z_coo_sparse_mat) :: tmpcoo - integer(psb_ipk_) :: debug_level, debug_unit,err_act - integer(psb_ipk_) :: ictxt,np,me - integer(psb_ipk_) :: nrow, ncol, n_ne - character(len=20) :: name, ch_err - - if(psb_get_errstatus() /= 0) return - info=psb_success_ - name = 'mld_aggrmap_bld' - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - ! - ictxt=desc_a%get_context() - call psb_info(ictxt,me,np) - nrow = desc_a%get_local_rows() - ncol = desc_a%get_local_cols() - - select case (aggr_type) - case (mld_dec_aggr_) - call mld_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) - - case (mld_sym_dec_aggr_) - nr = a%get_nrows() - call a%csclip(atmp,info,imax=nr,jmax=nr,& - & rscale=.false.,cscale=.false.) - call atmp%set_nrows(nr) - call atmp%set_ncols(nr) - if (info == psb_success_) call atmp%transp(atrans) - if (info == psb_success_) call atrans%cscnv(info,type='COO') - if (info == psb_success_) call psb_rwextd(nr,atmp,info,b=atrans,rowscale=.false.) - call atmp%set_nrows(nr) - call atmp%set_ncols(nr) - if (info == psb_success_) call atrans%free() - if (info == psb_success_) call atmp%cscnv(info,type='CSR') - if (info == psb_success_) call mld_dec_map_bld(iorder,theta,atmp,desc_a,nlaggr,ilaggr,info) - if (info == psb_success_) call atmp%free() - - case default - - info = -1 - call psb_errpush(psb_err_input_value_invalid_i_,name,& - & i_err=(/ione,aggr_type,izero,izero,izero/)) - goto 9999 - end select - - if (info /= psb_success_) then - info=psb_err_internal_error_ - call psb_errpush(info,name,a_err='dec_map_bld') - goto 9999 - end if - - naggr = nlaggr(me+1) - ntaggr = sum(nlaggr) - naggrm1 = sum(nlaggr(1:me)) - naggrp1 = sum(nlaggr(1:me+1)) - ilaggr(1:nrow) = ilaggr(1:nrow) + naggrm1 - call psb_halo(ilaggr,desc_a,info) - if (info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_halo') - goto 9999 - end if - - call tmpcoo%allocate(ncol,ntaggr,ncol) - do i=1,ncol - tmpcoo%val(i) = zone - tmpcoo%ia(i) = i - tmpcoo%ja(i) = ilaggr(i) - end do - call tmpcoo%set_nzeros(ncol) - call tmpcoo%set_dupl(psb_dupl_add_) - call tmpcoo%set_sorted() ! At this point this is in row-major - call op_prol%mv_from(tmpcoo) - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - - return - -end subroutine mld_zaggrmap_bld diff --git a/mlprec/impl/mld_zaggrmat_asb.f90 b/mlprec/impl/mld_zaggrmat_asb.f90 deleted file mode 100644 index afb53865..00000000 --- a/mlprec/impl/mld_zaggrmat_asb.f90 +++ /dev/null @@ -1,193 +0,0 @@ -! -! -! MLD2P4 version 2.1 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_zaggrmat_asb.f90 -! -! Subroutine: mld_zaggrmat_asb -! Version: complex -! -! This routine builds a coarse-level matrix A_C from a fine-level matrix A -! by using the Galerkin approach, i.e. -! -! A_C = P_C^T A P_C, -! -! where P_C is a prolongator from the coarse level to the fine one. -! -! A mapping from the nodes of the adjacency graph of A to the nodes of the -! adjacency graph of A_C has been computed by the mld_aggrmap_bld subroutine. -! The prolongator P_C is built here from this mapping, according to the -! value of p%iprcparm(mld_aggr_prol_), specified by the user through -! mld_zprecinit and mld_zprecset. -! On output from this routine the entries of AC, op_prol, op_restr -! are still in "global numbering" mode; this is fixed in the calling routine -! mld_z_lev_aggrmat_asb. -! -! Currently four different prolongators are implemented, corresponding to -! four aggregation algorithms: -! 1. un-smoothed aggregation, -! 2. smoothed aggregation, -! 3. "bizarre" aggregation. -! 4. minimum energy -! 1. The non-smoothed aggregation uses as prolongator the piecewise constant -! interpolation operator corresponding to the fine-to-coarse level mapping built -! by mld_aggrmap_bld. This is called tentative prolongator. -! 2. The smoothed aggregation uses as prolongator the operator obtained by applying -! a damped Jacobi smoother to the tentative prolongator. -! 3. The "bizarre" aggregation uses a prolongator proposed by the authors of MLD2P4. -! This prolongator still requires a deep analysis and testing and its use is -! not recommended. -! 4. Minimum energy aggregation: ADD REFERENCE. -! -! For more details see -! M. Brezina and P. Vanek, A black-box iterative solver based on a two-level -! Schwarz method, Computing, 63 (1999), 233-263. -! P. D'Ambra, D. di Serafino and S. Filippone, On the development of PSBLAS-based -! parallel two-level Schwarz preconditioners, Appl. Num. Math., 57 (2007), -! 1181-1196. -! -! -! -! Arguments: -! 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. -! The communication descriptor of the fine-level matrix. -! p - type(mld_z_onelev_type), input/output. -! The 'one-level' data structure that will contain the local -! part of the matrix to be built as well as the information -! concerning the prolongator and its transpose. -! parms - type(mld_dml_parms), input -! Parameters controlling the choice of algorithm -! ac - type(psb_zspmat_type), output -! The coarse matrix on output -! -! ilaggr - integer, dimension(:), input -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that the indices -! are assumed to be shifted so as to make sure the ranges on -! the various processes do not overlap. -! nlaggr - integer, dimension(:) input -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_zspmat_type), input/output -! The tentative prolongator on input, the computed prolongator on output -! -! op_restr - type(psb_zspmat_type), output -! The restrictor operator; normally, it is the transpose of the prolongator. -! -! info - integer, output. -! Error code. -! -subroutine mld_zaggrmat_asb(a,desc_a,ilaggr,nlaggr,parms,ac,op_prol,op_restr,info) - - use psb_base_mod - use mld_base_prec_type - use mld_z_inner_mod, mld_protect_name => mld_zaggrmat_asb - - implicit none - -! Arguments - type(psb_zspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) - type(mld_dml_parms), intent(inout) :: parms - type(psb_zspmat_type), intent(inout) :: ac, op_prol,op_restr - integer(psb_ipk_), intent(out) :: info - -! Local variables - type(psb_z_coo_sparse_mat) :: acoo, bcoo - type(psb_z_csr_sparse_mat) :: acsr1 - integer(psb_ipk_) :: nzl,ntaggr, err_act - integer(psb_ipk_) :: debug_level, debug_unit - integer(psb_ipk_) :: ictxt,np,me - character(len=20) :: name - - name='mld_aggrmat_asb' - if(psb_get_errstatus().ne.0) return - info=psb_success_ - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - - - ictxt = desc_a%get_context() - - call psb_info(ictxt, me, np) - - select case (parms%aggr_prol) - case (mld_no_smooth_) - - call mld_zaggrmat_nosmth_asb(a,desc_a,ilaggr,nlaggr,& - & parms,ac,op_prol,op_restr,info) - - case(mld_smooth_prol_) - - call mld_zaggrmat_smth_asb(a,desc_a,ilaggr,nlaggr, & - & parms,ac,op_prol,op_restr,info) - - case(mld_biz_prol_) - - call mld_zaggrmat_biz_asb(a,desc_a,ilaggr,nlaggr, & - & parms,ac,op_prol,op_restr,info) - - case(mld_min_energy_) - - call mld_zaggrmat_minnrg_asb(a,desc_a,ilaggr,nlaggr, & - & parms,ac,op_prol,op_restr,info) - - case default - info = psb_err_internal_error_ - call psb_errpush(info,name,a_err='Invalid aggr kind') - goto 9999 - - end select - if (info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='Inner aggrmat asb') - goto 9999 - end if - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - - return - -end subroutine mld_zaggrmat_asb diff --git a/mlprec/mld_c_base_aggregator_mod.f90 b/mlprec/mld_c_base_aggregator_mod.f90 index 6fd291cc..7bfb4428 100644 --- a/mlprec/mld_c_base_aggregator_mod.f90 +++ b/mlprec/mld_c_base_aggregator_mod.f90 @@ -97,14 +97,14 @@ module mld_c_base_aggregator_mod type mld_c_base_aggregator_type contains - procedure, pass(ag) :: bld_tprol => mld_c_base_aggregator_build_tprol - procedure, pass(ag) :: mat_asb => mld_c_base_aggregator_mat_asb - procedure, pass(ag) :: update_level => mld_c_base_aggregator_update_level - procedure, pass(ag) :: clone => mld_c_base_aggregator_clone - procedure, pass(ag) :: free => mld_c_base_aggregator_free - procedure, pass(ag) :: default => mld_c_base_aggregator_default - procedure, pass(ag) :: descr => mld_c_base_aggregator_descr - procedure, nopass :: fmt => mld_c_base_aggregator_fmt + procedure, pass(ag) :: bld_tprol => mld_c_base_aggregator_build_tprol + procedure, pass(ag) :: mat_asb => mld_c_base_aggregator_mat_asb + procedure, pass(ag) :: update_next => mld_c_base_aggregator_update_next + procedure, pass(ag) :: clone => mld_c_base_aggregator_clone + procedure, pass(ag) :: free => mld_c_base_aggregator_free + procedure, pass(ag) :: default => mld_c_base_aggregator_default + procedure, pass(ag) :: descr => mld_c_base_aggregator_descr + procedure, nopass :: fmt => mld_c_base_aggregator_fmt end type mld_c_base_aggregator_type @@ -142,7 +142,7 @@ module mld_c_base_aggregator_mod contains - subroutine mld_c_base_aggregator_update_level(ag,agnext,info) + subroutine mld_c_base_aggregator_update_next(ag,agnext,info) implicit none class(mld_c_base_aggregator_type), target, intent(inout) :: ag, agnext integer(psb_ipk_), intent(out) :: info @@ -151,7 +151,7 @@ contains ! Base version does nothing. ! info = 0 - end subroutine mld_c_base_aggregator_update_level + end subroutine mld_c_base_aggregator_update_next subroutine mld_c_base_aggregator_clone(ag,agnext,info) implicit none diff --git a/mlprec/mld_c_inner_mod.f90 b/mlprec/mld_c_inner_mod.f90 index 0de61dca..432c73b5 100644 --- a/mlprec/mld_c_inner_mod.f90 +++ b/mlprec/mld_c_inner_mod.f90 @@ -44,7 +44,7 @@ ! The interfaces of the user level routines are defined in mld_prec_mod.f90. ! module mld_c_inner_mod -! use mld_c_prec_type, only : mld_c_prec_type + use psb_base_mod, only : psb_cspmat_type, psb_desc_type, psb_i_base_vect_type, & & psb_spk_, psb_c_base_sparse_mat, psb_c_base_vect_type, psb_ipk_, & & psb_c_vect_type diff --git a/mlprec/mld_c_onelev_mod.f90 b/mlprec/mld_c_onelev_mod.f90 index fe5a84a3..de6ec194 100644 --- a/mlprec/mld_c_onelev_mod.f90 +++ b/mlprec/mld_c_onelev_mod.f90 @@ -151,6 +151,9 @@ module mld_c_onelev_mod type(psb_clinmap_type) :: map real(psb_spk_) :: szratio contains + procedure, pass(lv) :: bld_tprol => c_base_onelev_bld_tprol + procedure, pass(lv) :: mat_asb => mld_c_base_onelev_mat_asb + procedure, pass(lv) :: update_aggr => c_base_onelev_update_aggr procedure, pass(lv) :: bld => mld_c_base_onelev_build procedure, pass(lv) :: clone => c_base_onelev_clone procedure, pass(lv) :: cnv => mld_c_base_onelev_cnv @@ -178,6 +181,7 @@ module mld_c_onelev_mod procedure, pass(lv) :: free_wrk => c_base_onelev_free_wrk procedure, nopass :: stringval => mld_stringval procedure, pass(lv) :: move_alloc => c_base_onelev_move_alloc + end type mld_c_onelev_type type mld_c_onelev_node @@ -191,7 +195,19 @@ module mld_c_onelev_mod & c_base_onelev_get_wrksize, c_base_onelev_allocate_wrk, & & c_base_onelev_free_wrk - + interface + subroutine mld_c_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: psb_cspmat_type, psb_desc_type, psb_spk_, psb_ipk_ + import :: mld_c_onelev_type + implicit none + class(mld_c_onelev_type), intent(inout), target :: lv + type(psb_cspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:),nlaggr(:) + type(psb_cspmat_type), intent(inout) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_c_base_onelev_mat_asb + end interface interface subroutine mld_c_base_onelev_build(lv,info,amold,vmold,imold) @@ -498,6 +514,29 @@ contains end subroutine c_base_onelev_default + subroutine c_base_onelev_bld_tprol(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) + implicit none + class(mld_c_onelev_type), intent(inout), target :: lv + type(psb_cspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_cspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + call lv%aggr%bld_tprol(lv%parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + + end subroutine c_base_onelev_bld_tprol + + + subroutine c_base_onelev_update_aggr(lv,lvnext,info) + implicit none + class(mld_c_onelev_type), intent(inout), target :: lv, lvnext + integer(psb_ipk_), intent(out) :: info + + call lv%aggr%update_next(lvnext%aggr,info) + + end subroutine c_base_onelev_update_aggr + subroutine c_base_onelev_clone(lv,lvout,info) diff --git a/mlprec/mld_d_base_aggregator_mod.f90 b/mlprec/mld_d_base_aggregator_mod.f90 index fd231c39..876e36d4 100644 --- a/mlprec/mld_d_base_aggregator_mod.f90 +++ b/mlprec/mld_d_base_aggregator_mod.f90 @@ -97,14 +97,14 @@ module mld_d_base_aggregator_mod type mld_d_base_aggregator_type contains - procedure, pass(ag) :: bld_tprol => mld_d_base_aggregator_build_tprol - procedure, pass(ag) :: mat_asb => mld_d_base_aggregator_mat_asb - procedure, pass(ag) :: update_level => mld_d_base_aggregator_update_level - procedure, pass(ag) :: clone => mld_d_base_aggregator_clone - procedure, pass(ag) :: free => mld_d_base_aggregator_free - procedure, pass(ag) :: default => mld_d_base_aggregator_default - procedure, pass(ag) :: descr => mld_d_base_aggregator_descr - procedure, nopass :: fmt => mld_d_base_aggregator_fmt + procedure, pass(ag) :: bld_tprol => mld_d_base_aggregator_build_tprol + procedure, pass(ag) :: mat_asb => mld_d_base_aggregator_mat_asb + procedure, pass(ag) :: update_next => mld_d_base_aggregator_update_next + procedure, pass(ag) :: clone => mld_d_base_aggregator_clone + procedure, pass(ag) :: free => mld_d_base_aggregator_free + procedure, pass(ag) :: default => mld_d_base_aggregator_default + procedure, pass(ag) :: descr => mld_d_base_aggregator_descr + procedure, nopass :: fmt => mld_d_base_aggregator_fmt end type mld_d_base_aggregator_type @@ -142,7 +142,7 @@ module mld_d_base_aggregator_mod contains - subroutine mld_d_base_aggregator_update_level(ag,agnext,info) + subroutine mld_d_base_aggregator_update_next(ag,agnext,info) implicit none class(mld_d_base_aggregator_type), target, intent(inout) :: ag, agnext integer(psb_ipk_), intent(out) :: info @@ -151,7 +151,7 @@ contains ! Base version does nothing. ! info = 0 - end subroutine mld_d_base_aggregator_update_level + end subroutine mld_d_base_aggregator_update_next subroutine mld_d_base_aggregator_clone(ag,agnext,info) implicit none diff --git a/mlprec/mld_d_inner_mod.f90 b/mlprec/mld_d_inner_mod.f90 index 810d5831..ed052f69 100644 --- a/mlprec/mld_d_inner_mod.f90 +++ b/mlprec/mld_d_inner_mod.f90 @@ -44,7 +44,7 @@ ! The interfaces of the user level routines are defined in mld_prec_mod.f90. ! module mld_d_inner_mod -! use mld_d_prec_type, only : mld_d_prec_type + use psb_base_mod, only : psb_dspmat_type, psb_desc_type, psb_i_base_vect_type, & & psb_dpk_, psb_d_base_sparse_mat, psb_d_base_vect_type, psb_ipk_, & & psb_d_vect_type diff --git a/mlprec/mld_d_onelev_mod.f90 b/mlprec/mld_d_onelev_mod.f90 index 30c7376c..1c5da02a 100644 --- a/mlprec/mld_d_onelev_mod.f90 +++ b/mlprec/mld_d_onelev_mod.f90 @@ -151,6 +151,9 @@ module mld_d_onelev_mod type(psb_dlinmap_type) :: map real(psb_dpk_) :: szratio contains + procedure, pass(lv) :: bld_tprol => d_base_onelev_bld_tprol + procedure, pass(lv) :: mat_asb => mld_d_base_onelev_mat_asb + procedure, pass(lv) :: update_aggr => d_base_onelev_update_aggr procedure, pass(lv) :: bld => mld_d_base_onelev_build procedure, pass(lv) :: clone => d_base_onelev_clone procedure, pass(lv) :: cnv => mld_d_base_onelev_cnv @@ -178,6 +181,7 @@ module mld_d_onelev_mod procedure, pass(lv) :: free_wrk => d_base_onelev_free_wrk procedure, nopass :: stringval => mld_stringval procedure, pass(lv) :: move_alloc => d_base_onelev_move_alloc + end type mld_d_onelev_type type mld_d_onelev_node @@ -191,7 +195,19 @@ module mld_d_onelev_mod & d_base_onelev_get_wrksize, d_base_onelev_allocate_wrk, & & d_base_onelev_free_wrk - + interface + subroutine mld_d_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: psb_dspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ + import :: mld_d_onelev_type + implicit none + class(mld_d_onelev_type), intent(inout), target :: lv + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:),nlaggr(:) + type(psb_dspmat_type), intent(inout) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_d_base_onelev_mat_asb + end interface interface subroutine mld_d_base_onelev_build(lv,info,amold,vmold,imold) @@ -498,6 +514,29 @@ contains end subroutine d_base_onelev_default + subroutine d_base_onelev_bld_tprol(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) + implicit none + class(mld_d_onelev_type), intent(inout), target :: lv + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_dspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + call lv%aggr%bld_tprol(lv%parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + + end subroutine d_base_onelev_bld_tprol + + + subroutine d_base_onelev_update_aggr(lv,lvnext,info) + implicit none + class(mld_d_onelev_type), intent(inout), target :: lv, lvnext + integer(psb_ipk_), intent(out) :: info + + call lv%aggr%update_next(lvnext%aggr,info) + + end subroutine d_base_onelev_update_aggr + subroutine d_base_onelev_clone(lv,lvout,info) diff --git a/mlprec/mld_s_base_aggregator_mod.f90 b/mlprec/mld_s_base_aggregator_mod.f90 index 3021e19c..79eb9ca7 100644 --- a/mlprec/mld_s_base_aggregator_mod.f90 +++ b/mlprec/mld_s_base_aggregator_mod.f90 @@ -97,14 +97,14 @@ module mld_s_base_aggregator_mod type mld_s_base_aggregator_type contains - procedure, pass(ag) :: bld_tprol => mld_s_base_aggregator_build_tprol - procedure, pass(ag) :: mat_asb => mld_s_base_aggregator_mat_asb - procedure, pass(ag) :: update_level => mld_s_base_aggregator_update_level - procedure, pass(ag) :: clone => mld_s_base_aggregator_clone - procedure, pass(ag) :: free => mld_s_base_aggregator_free - procedure, pass(ag) :: default => mld_s_base_aggregator_default - procedure, pass(ag) :: descr => mld_s_base_aggregator_descr - procedure, nopass :: fmt => mld_s_base_aggregator_fmt + procedure, pass(ag) :: bld_tprol => mld_s_base_aggregator_build_tprol + procedure, pass(ag) :: mat_asb => mld_s_base_aggregator_mat_asb + procedure, pass(ag) :: update_next => mld_s_base_aggregator_update_next + procedure, pass(ag) :: clone => mld_s_base_aggregator_clone + procedure, pass(ag) :: free => mld_s_base_aggregator_free + procedure, pass(ag) :: default => mld_s_base_aggregator_default + procedure, pass(ag) :: descr => mld_s_base_aggregator_descr + procedure, nopass :: fmt => mld_s_base_aggregator_fmt end type mld_s_base_aggregator_type @@ -142,7 +142,7 @@ module mld_s_base_aggregator_mod contains - subroutine mld_s_base_aggregator_update_level(ag,agnext,info) + subroutine mld_s_base_aggregator_update_next(ag,agnext,info) implicit none class(mld_s_base_aggregator_type), target, intent(inout) :: ag, agnext integer(psb_ipk_), intent(out) :: info @@ -151,7 +151,7 @@ contains ! Base version does nothing. ! info = 0 - end subroutine mld_s_base_aggregator_update_level + end subroutine mld_s_base_aggregator_update_next subroutine mld_s_base_aggregator_clone(ag,agnext,info) implicit none diff --git a/mlprec/mld_s_inner_mod.f90 b/mlprec/mld_s_inner_mod.f90 index 73baa6a8..42317490 100644 --- a/mlprec/mld_s_inner_mod.f90 +++ b/mlprec/mld_s_inner_mod.f90 @@ -44,7 +44,7 @@ ! The interfaces of the user level routines are defined in mld_prec_mod.f90. ! module mld_s_inner_mod -! use mld_s_prec_type, only : mld_s_prec_type + use psb_base_mod, only : psb_sspmat_type, psb_desc_type, psb_i_base_vect_type, & & psb_spk_, psb_s_base_sparse_mat, psb_s_base_vect_type, psb_ipk_, & & psb_s_vect_type diff --git a/mlprec/mld_s_onelev_mod.f90 b/mlprec/mld_s_onelev_mod.f90 index baba63cc..0c6b653d 100644 --- a/mlprec/mld_s_onelev_mod.f90 +++ b/mlprec/mld_s_onelev_mod.f90 @@ -151,6 +151,9 @@ module mld_s_onelev_mod type(psb_slinmap_type) :: map real(psb_spk_) :: szratio contains + procedure, pass(lv) :: bld_tprol => s_base_onelev_bld_tprol + procedure, pass(lv) :: mat_asb => mld_s_base_onelev_mat_asb + procedure, pass(lv) :: update_aggr => s_base_onelev_update_aggr procedure, pass(lv) :: bld => mld_s_base_onelev_build procedure, pass(lv) :: clone => s_base_onelev_clone procedure, pass(lv) :: cnv => mld_s_base_onelev_cnv @@ -178,6 +181,7 @@ module mld_s_onelev_mod procedure, pass(lv) :: free_wrk => s_base_onelev_free_wrk procedure, nopass :: stringval => mld_stringval procedure, pass(lv) :: move_alloc => s_base_onelev_move_alloc + end type mld_s_onelev_type type mld_s_onelev_node @@ -191,7 +195,19 @@ module mld_s_onelev_mod & s_base_onelev_get_wrksize, s_base_onelev_allocate_wrk, & & s_base_onelev_free_wrk - + interface + subroutine mld_s_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: psb_sspmat_type, psb_desc_type, psb_spk_, psb_ipk_ + import :: mld_s_onelev_type + implicit none + class(mld_s_onelev_type), intent(inout), target :: lv + type(psb_sspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:),nlaggr(:) + type(psb_sspmat_type), intent(inout) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_s_base_onelev_mat_asb + end interface interface subroutine mld_s_base_onelev_build(lv,info,amold,vmold,imold) @@ -498,6 +514,29 @@ contains end subroutine s_base_onelev_default + subroutine s_base_onelev_bld_tprol(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) + implicit none + class(mld_s_onelev_type), intent(inout), target :: lv + type(psb_sspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_sspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + call lv%aggr%bld_tprol(lv%parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + + end subroutine s_base_onelev_bld_tprol + + + subroutine s_base_onelev_update_aggr(lv,lvnext,info) + implicit none + class(mld_s_onelev_type), intent(inout), target :: lv, lvnext + integer(psb_ipk_), intent(out) :: info + + call lv%aggr%update_next(lvnext%aggr,info) + + end subroutine s_base_onelev_update_aggr + subroutine s_base_onelev_clone(lv,lvout,info) diff --git a/mlprec/mld_z_base_aggregator_mod.f90 b/mlprec/mld_z_base_aggregator_mod.f90 index 6f3a8096..b3bd3cf2 100644 --- a/mlprec/mld_z_base_aggregator_mod.f90 +++ b/mlprec/mld_z_base_aggregator_mod.f90 @@ -97,14 +97,14 @@ module mld_z_base_aggregator_mod type mld_z_base_aggregator_type contains - procedure, pass(ag) :: bld_tprol => mld_z_base_aggregator_build_tprol - procedure, pass(ag) :: mat_asb => mld_z_base_aggregator_mat_asb - procedure, pass(ag) :: update_level => mld_z_base_aggregator_update_level - procedure, pass(ag) :: clone => mld_z_base_aggregator_clone - procedure, pass(ag) :: free => mld_z_base_aggregator_free - procedure, pass(ag) :: default => mld_z_base_aggregator_default - procedure, pass(ag) :: descr => mld_z_base_aggregator_descr - procedure, nopass :: fmt => mld_z_base_aggregator_fmt + procedure, pass(ag) :: bld_tprol => mld_z_base_aggregator_build_tprol + procedure, pass(ag) :: mat_asb => mld_z_base_aggregator_mat_asb + procedure, pass(ag) :: update_next => mld_z_base_aggregator_update_next + procedure, pass(ag) :: clone => mld_z_base_aggregator_clone + procedure, pass(ag) :: free => mld_z_base_aggregator_free + procedure, pass(ag) :: default => mld_z_base_aggregator_default + procedure, pass(ag) :: descr => mld_z_base_aggregator_descr + procedure, nopass :: fmt => mld_z_base_aggregator_fmt end type mld_z_base_aggregator_type @@ -142,7 +142,7 @@ module mld_z_base_aggregator_mod contains - subroutine mld_z_base_aggregator_update_level(ag,agnext,info) + subroutine mld_z_base_aggregator_update_next(ag,agnext,info) implicit none class(mld_z_base_aggregator_type), target, intent(inout) :: ag, agnext integer(psb_ipk_), intent(out) :: info @@ -151,7 +151,7 @@ contains ! Base version does nothing. ! info = 0 - end subroutine mld_z_base_aggregator_update_level + end subroutine mld_z_base_aggregator_update_next subroutine mld_z_base_aggregator_clone(ag,agnext,info) implicit none diff --git a/mlprec/mld_z_inner_mod.f90 b/mlprec/mld_z_inner_mod.f90 index e6dcf6ee..b512d3db 100644 --- a/mlprec/mld_z_inner_mod.f90 +++ b/mlprec/mld_z_inner_mod.f90 @@ -44,7 +44,7 @@ ! The interfaces of the user level routines are defined in mld_prec_mod.f90. ! module mld_z_inner_mod -! use mld_z_prec_type, only : mld_z_prec_type + use psb_base_mod, only : psb_zspmat_type, psb_desc_type, psb_i_base_vect_type, & & psb_dpk_, psb_z_base_sparse_mat, psb_z_base_vect_type, psb_ipk_, & & psb_z_vect_type diff --git a/mlprec/mld_z_onelev_mod.f90 b/mlprec/mld_z_onelev_mod.f90 index be8eaaf3..0effdfeb 100644 --- a/mlprec/mld_z_onelev_mod.f90 +++ b/mlprec/mld_z_onelev_mod.f90 @@ -151,6 +151,9 @@ module mld_z_onelev_mod type(psb_zlinmap_type) :: map real(psb_dpk_) :: szratio contains + procedure, pass(lv) :: bld_tprol => z_base_onelev_bld_tprol + procedure, pass(lv) :: mat_asb => mld_z_base_onelev_mat_asb + procedure, pass(lv) :: update_aggr => z_base_onelev_update_aggr procedure, pass(lv) :: bld => mld_z_base_onelev_build procedure, pass(lv) :: clone => z_base_onelev_clone procedure, pass(lv) :: cnv => mld_z_base_onelev_cnv @@ -178,6 +181,7 @@ module mld_z_onelev_mod procedure, pass(lv) :: free_wrk => z_base_onelev_free_wrk procedure, nopass :: stringval => mld_stringval procedure, pass(lv) :: move_alloc => z_base_onelev_move_alloc + end type mld_z_onelev_type type mld_z_onelev_node @@ -191,7 +195,19 @@ module mld_z_onelev_mod & z_base_onelev_get_wrksize, z_base_onelev_allocate_wrk, & & z_base_onelev_free_wrk - + interface + subroutine mld_z_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: psb_zspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ + import :: mld_z_onelev_type + implicit none + class(mld_z_onelev_type), intent(inout), target :: lv + type(psb_zspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:),nlaggr(:) + type(psb_zspmat_type), intent(inout) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_z_base_onelev_mat_asb + end interface interface subroutine mld_z_base_onelev_build(lv,info,amold,vmold,imold) @@ -498,6 +514,29 @@ contains end subroutine z_base_onelev_default + subroutine z_base_onelev_bld_tprol(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) + implicit none + class(mld_z_onelev_type), intent(inout), target :: lv + type(psb_zspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_zspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + call lv%aggr%bld_tprol(lv%parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + + end subroutine z_base_onelev_bld_tprol + + + subroutine z_base_onelev_update_aggr(lv,lvnext,info) + implicit none + class(mld_z_onelev_type), intent(inout), target :: lv, lvnext + integer(psb_ipk_), intent(out) :: info + + call lv%aggr%update_next(lvnext%aggr,info) + + end subroutine z_base_onelev_update_aggr + subroutine z_base_onelev_clone(lv,lvout,info) From 6b87221ceaf59e40412c38bb6b2a299eaede0344 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 4 May 2018 21:16:21 +0100 Subject: [PATCH 13/33] Compilation works in aggregator. Cleanup needed. --- mlprec/impl/aggregator/Makefile | 3 +- mlprec/impl/aggregator/mld_c_dec_map_bld.f90 | 10 +- mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 | 10 +- mlprec/impl/aggregator/mld_d_dec_map_bld.f90 | 10 +- mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 | 10 +- mlprec/impl/aggregator/mld_s_dec_map_bld.f90 | 10 +- mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 | 10 +- mlprec/impl/aggregator/mld_z_dec_map_bld.f90 | 10 +- mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 | 10 +- mlprec/impl/mld_c_lev_aggrmap_bld.f90 | 157 ------------------- mlprec/impl/mld_d_lev_aggrmap_bld.f90 | 157 ------------------- mlprec/impl/mld_s_lev_aggrmap_bld.f90 | 157 ------------------- mlprec/impl/mld_z_lev_aggrmap_bld.f90 | 157 ------------------- 13 files changed, 41 insertions(+), 670 deletions(-) delete mode 100644 mlprec/impl/mld_c_lev_aggrmap_bld.f90 delete mode 100644 mlprec/impl/mld_d_lev_aggrmap_bld.f90 delete mode 100644 mlprec/impl/mld_s_lev_aggrmap_bld.f90 delete mode 100644 mlprec/impl/mld_z_lev_aggrmap_bld.f90 diff --git a/mlprec/impl/aggregator/Makefile b/mlprec/impl/aggregator/Makefile index d96b835b..b1f2e402 100644 --- a/mlprec/impl/aggregator/Makefile +++ b/mlprec/impl/aggregator/Makefile @@ -18,7 +18,6 @@ mld_saggrmat_biz_asb.o mld_saggrmat_minnrg_asb.o\ mld_saggrmat_nosmth_asb.o mld_saggrmat_smth_asb.o \ mld_d_base_aggregator_mat_asb.o \ mld_d_base_aggregator_tprol.o \ -mld_d_bcmatch_aggregator_tprol.o\ mld_d_hybrid_aggregator_tprol.o \ mld_d_symdec_aggregator_tprol.o \ mld_d_map_to_tprol.o mld_d_dec_map_bld.o mld_d_hyb_map_bld.o\ @@ -39,7 +38,7 @@ mld_z_map_to_tprol.o mld_z_dec_map_bld.o mld_z_hyb_map_bld.o\ mld_zaggrmat_biz_asb.o mld_zaggrmat_minnrg_asb.o\ mld_zaggrmat_nosmth_asb.o mld_zaggrmat_smth_asb.o -#bootCMatch_interface.o\ +#bootCMatch_interface.o mld_d_bcmatch_aggregator_tprol.o\ #mld_d_bcmatch_map_to_tprol.o mld_d_bcmatch_aggregator_mat_asb.o \ diff --git a/mlprec/impl/aggregator/mld_c_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_c_dec_map_bld.f90 index 4f98159a..110c5bbb 100644 --- a/mlprec/impl/aggregator/mld_c_dec_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_c_dec_map_bld.f90 @@ -4,12 +4,11 @@ ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions @@ -71,6 +70,7 @@ subroutine mld_c_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod + use mld_base_prec_type use mld_c_inner_mod, mld_protect_name => mld_c_dec_map_bld implicit none diff --git a/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 index 22ad0a2c..4bb25f4c 100644 --- a/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 @@ -4,12 +4,11 @@ ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions @@ -71,6 +70,7 @@ subroutine mld_c_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod + use mld_base_prec_type use mld_c_inner_mod, mld_protect_name => mld_c_hyb_map_bld implicit none diff --git a/mlprec/impl/aggregator/mld_d_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_d_dec_map_bld.f90 index d7576861..4925233c 100644 --- a/mlprec/impl/aggregator/mld_d_dec_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_d_dec_map_bld.f90 @@ -4,12 +4,11 @@ ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions @@ -71,6 +70,7 @@ subroutine mld_d_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod + use mld_base_prec_type use mld_d_inner_mod, mld_protect_name => mld_d_dec_map_bld implicit none diff --git a/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 index a0f7f7cb..d7d24589 100644 --- a/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 @@ -4,12 +4,11 @@ ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions @@ -71,6 +70,7 @@ subroutine mld_d_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod + use mld_base_prec_type use mld_d_inner_mod, mld_protect_name => mld_d_hyb_map_bld implicit none diff --git a/mlprec/impl/aggregator/mld_s_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_s_dec_map_bld.f90 index d9af2f5f..fc1c15ec 100644 --- a/mlprec/impl/aggregator/mld_s_dec_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_s_dec_map_bld.f90 @@ -4,12 +4,11 @@ ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions @@ -71,6 +70,7 @@ subroutine mld_s_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod + use mld_base_prec_type use mld_s_inner_mod, mld_protect_name => mld_s_dec_map_bld implicit none diff --git a/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 index 8331ae05..11744ea4 100644 --- a/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 @@ -4,12 +4,11 @@ ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions @@ -71,6 +70,7 @@ subroutine mld_s_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod + use mld_base_prec_type use mld_s_inner_mod, mld_protect_name => mld_s_hyb_map_bld implicit none diff --git a/mlprec/impl/aggregator/mld_z_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_z_dec_map_bld.f90 index 7c992167..6900b221 100644 --- a/mlprec/impl/aggregator/mld_z_dec_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_z_dec_map_bld.f90 @@ -4,12 +4,11 @@ ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions @@ -71,6 +70,7 @@ subroutine mld_z_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod + use mld_base_prec_type use mld_z_inner_mod, mld_protect_name => mld_z_dec_map_bld implicit none diff --git a/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 index cc795465..47d60179 100644 --- a/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 @@ -4,12 +4,11 @@ ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions @@ -71,6 +70,7 @@ subroutine mld_z_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod + use mld_base_prec_type use mld_z_inner_mod, mld_protect_name => mld_z_hyb_map_bld implicit none diff --git a/mlprec/impl/mld_c_lev_aggrmap_bld.f90 b/mlprec/impl/mld_c_lev_aggrmap_bld.f90 deleted file mode 100644 index 6485f38d..00000000 --- a/mlprec/impl/mld_c_lev_aggrmap_bld.f90 +++ /dev/null @@ -1,157 +0,0 @@ - -! -! -! MLD2P4 version 2.1 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_c_lev_aggrmap_bld.f90 -! -! Subroutine: mld_c_lev_aggrmap_bld -! Version: complex -! -! This routine is just an interface to aggrmap_bld where the real work is performed. -! It takes care of some consistency checking though. -! -! See mld_caggrmap_bld for constraints on input/oput arguments. -! -! -! Arguments: -! p - type(mld_c_onelev_type), input/output. -! The 'one-level' data structure containing the control -! parameters and (eventually) coarse matrix and prolongator/restrictors. -! -! a - type(psb_cspmat_type). -! The sparse matrix structure containing the local part of the -! fine-level matrix. -! desc_a - type(psb_desc_type), input. -! The communication descriptor of a. -! ilaggr - integer, dimension(:), allocatable, output -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that on exit the indices -! will be shifted so as to make sure the ranges on the various processes do not -! overlap. -! nlaggr - integer, dimension(:), allocatable, output -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_cspmat_type), output -! The tentative prolongator, based on ilaggr. -! -! info - integer, output. -! Error code. -! -subroutine mld_c_lev_aggrmap_bld(p,a,desc_a,ilaggr,nlaggr,op_prol,info) - - use psb_base_mod - use mld_base_prec_type - use mld_c_inner_mod, mld_protect_name => mld_c_lev_aggrmap_bld - - implicit none - - ! Arguments - type(mld_c_onelev_type), intent(inout), target :: p - type(psb_cspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - type(psb_cspmat_type), intent(out) :: op_prol - integer(psb_ipk_), intent(out) :: info - - - ! Local variables - character(len=20) :: name - integer(psb_mpik_) :: ictxt, np, me - integer(psb_ipk_) :: err_act - integer(psb_ipk_) :: nzl, ntaggr - integer(psb_ipk_) :: debug_level, debug_unit - - name='mld_c_lev_aggrmap_bld' - if (psb_get_errstatus().ne.0) return - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - info = psb_success_ - ictxt = desc_a%get_context() - call psb_info(ictxt,me,np) - - call mld_check_def(p%parms%ml_cycle,'Multilevel cycle',& - & mld_mult_ml_,is_legal_ml_cycle) - call mld_check_def(p%parms%par_aggr_alg,'Aggregation',& - & mld_dec_aggr_,is_legal_ml_par_aggr_alg) - call mld_check_def(p%parms%aggr_ord,'Ordering',& - & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) - call mld_check_def(p%parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) - - select case(p%parms%par_aggr_alg) - case (mld_dec_aggr_, mld_sym_dec_aggr_) - - ! - ! Build a mapping between the row indices of the fine-level matrix - ! and the row indices of the coarse-level matrix, according to a decoupled - ! aggregation algorithm. This also defines a tentative prolongator from - ! the coarse to the fine level. - ! - call mld_aggrmap_bld(p%parms%par_aggr_alg,p%parms%aggr_ord,p%parms%aggr_thresh,& - & a,desc_a,ilaggr,nlaggr,op_prol,info) - - if (info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='mld_aggrmap_bld') - goto 9999 - end if - - case (mld_bcmatch_aggr_) - write(0,*) 'Matching is not implemented yet ' - info = -1111 - call psb_errpush(psb_err_input_value_invalid_i_,name,& - & i_err=(/ione,p%parms%par_aggr_alg,izero,izero,izero/)) - goto 9999 - - case default - - info = -1 - call psb_errpush(psb_err_input_value_invalid_i_,name,& - & i_err=(/ione,p%parms%par_aggr_alg,izero,izero,izero/)) - goto 9999 - - end select - - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - return - -end subroutine mld_c_lev_aggrmap_bld diff --git a/mlprec/impl/mld_d_lev_aggrmap_bld.f90 b/mlprec/impl/mld_d_lev_aggrmap_bld.f90 deleted file mode 100644 index 118bfc66..00000000 --- a/mlprec/impl/mld_d_lev_aggrmap_bld.f90 +++ /dev/null @@ -1,157 +0,0 @@ - -! -! -! MLD2P4 version 2.1 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_d_lev_aggrmap_bld.f90 -! -! Subroutine: mld_d_lev_aggrmap_bld -! Version: real -! -! This routine is just an interface to aggrmap_bld where the real work is performed. -! It takes care of some consistency checking though. -! -! See mld_daggrmap_bld for constraints on input/oput arguments. -! -! -! Arguments: -! p - type(mld_d_onelev_type), input/output. -! The 'one-level' data structure containing the control -! parameters and (eventually) coarse matrix and prolongator/restrictors. -! -! a - type(psb_dspmat_type). -! The sparse matrix structure containing the local part of the -! fine-level matrix. -! desc_a - type(psb_desc_type), input. -! The communication descriptor of a. -! ilaggr - integer, dimension(:), allocatable, output -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that on exit the indices -! will be shifted so as to make sure the ranges on the various processes do not -! overlap. -! nlaggr - integer, dimension(:), allocatable, output -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_dspmat_type), output -! The tentative prolongator, based on ilaggr. -! -! info - integer, output. -! Error code. -! -subroutine mld_d_lev_aggrmap_bld(p,a,desc_a,ilaggr,nlaggr,op_prol,info) - - use psb_base_mod - use mld_base_prec_type - use mld_d_inner_mod, mld_protect_name => mld_d_lev_aggrmap_bld - - implicit none - - ! Arguments - type(mld_d_onelev_type), intent(inout), target :: p - type(psb_dspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - type(psb_dspmat_type), intent(out) :: op_prol - integer(psb_ipk_), intent(out) :: info - - - ! Local variables - character(len=20) :: name - integer(psb_mpik_) :: ictxt, np, me - integer(psb_ipk_) :: err_act - integer(psb_ipk_) :: nzl, ntaggr - integer(psb_ipk_) :: debug_level, debug_unit - - name='mld_d_lev_aggrmap_bld' - if (psb_get_errstatus().ne.0) return - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - info = psb_success_ - ictxt = desc_a%get_context() - call psb_info(ictxt,me,np) - - call mld_check_def(p%parms%ml_cycle,'Multilevel cycle',& - & mld_mult_ml_,is_legal_ml_cycle) - call mld_check_def(p%parms%par_aggr_alg,'Aggregation',& - & mld_dec_aggr_,is_legal_ml_par_aggr_alg) - call mld_check_def(p%parms%aggr_ord,'Ordering',& - & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) - call mld_check_def(p%parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) - - select case(p%parms%par_aggr_alg) - case (mld_dec_aggr_, mld_sym_dec_aggr_) - - ! - ! Build a mapping between the row indices of the fine-level matrix - ! and the row indices of the coarse-level matrix, according to a decoupled - ! aggregation algorithm. This also defines a tentative prolongator from - ! the coarse to the fine level. - ! - call mld_aggrmap_bld(p%parms%par_aggr_alg,p%parms%aggr_ord,p%parms%aggr_thresh,& - & a,desc_a,ilaggr,nlaggr,op_prol,info) - - if (info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='mld_aggrmap_bld') - goto 9999 - end if - - case (mld_bcmatch_aggr_) - write(0,*) 'Matching is not implemented yet ' - info = -1111 - call psb_errpush(psb_err_input_value_invalid_i_,name,& - & i_err=(/ione,p%parms%par_aggr_alg,izero,izero,izero/)) - goto 9999 - - case default - - info = -1 - call psb_errpush(psb_err_input_value_invalid_i_,name,& - & i_err=(/ione,p%parms%par_aggr_alg,izero,izero,izero/)) - goto 9999 - - end select - - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - return - -end subroutine mld_d_lev_aggrmap_bld diff --git a/mlprec/impl/mld_s_lev_aggrmap_bld.f90 b/mlprec/impl/mld_s_lev_aggrmap_bld.f90 deleted file mode 100644 index b1a00a3d..00000000 --- a/mlprec/impl/mld_s_lev_aggrmap_bld.f90 +++ /dev/null @@ -1,157 +0,0 @@ - -! -! -! MLD2P4 version 2.1 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_s_lev_aggrmap_bld.f90 -! -! Subroutine: mld_s_lev_aggrmap_bld -! Version: real -! -! This routine is just an interface to aggrmap_bld where the real work is performed. -! It takes care of some consistency checking though. -! -! See mld_saggrmap_bld for constraints on input/oput arguments. -! -! -! Arguments: -! p - type(mld_s_onelev_type), input/output. -! The 'one-level' data structure containing the control -! parameters and (eventually) coarse matrix and prolongator/restrictors. -! -! a - type(psb_sspmat_type). -! The sparse matrix structure containing the local part of the -! fine-level matrix. -! desc_a - type(psb_desc_type), input. -! The communication descriptor of a. -! ilaggr - integer, dimension(:), allocatable, output -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that on exit the indices -! will be shifted so as to make sure the ranges on the various processes do not -! overlap. -! nlaggr - integer, dimension(:), allocatable, output -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_sspmat_type), output -! The tentative prolongator, based on ilaggr. -! -! info - integer, output. -! Error code. -! -subroutine mld_s_lev_aggrmap_bld(p,a,desc_a,ilaggr,nlaggr,op_prol,info) - - use psb_base_mod - use mld_base_prec_type - use mld_s_inner_mod, mld_protect_name => mld_s_lev_aggrmap_bld - - implicit none - - ! Arguments - type(mld_s_onelev_type), intent(inout), target :: p - type(psb_sspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - type(psb_sspmat_type), intent(out) :: op_prol - integer(psb_ipk_), intent(out) :: info - - - ! Local variables - character(len=20) :: name - integer(psb_mpik_) :: ictxt, np, me - integer(psb_ipk_) :: err_act - integer(psb_ipk_) :: nzl, ntaggr - integer(psb_ipk_) :: debug_level, debug_unit - - name='mld_s_lev_aggrmap_bld' - if (psb_get_errstatus().ne.0) return - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - info = psb_success_ - ictxt = desc_a%get_context() - call psb_info(ictxt,me,np) - - call mld_check_def(p%parms%ml_cycle,'Multilevel cycle',& - & mld_mult_ml_,is_legal_ml_cycle) - call mld_check_def(p%parms%par_aggr_alg,'Aggregation',& - & mld_dec_aggr_,is_legal_ml_par_aggr_alg) - call mld_check_def(p%parms%aggr_ord,'Ordering',& - & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) - call mld_check_def(p%parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) - - select case(p%parms%par_aggr_alg) - case (mld_dec_aggr_, mld_sym_dec_aggr_) - - ! - ! Build a mapping between the row indices of the fine-level matrix - ! and the row indices of the coarse-level matrix, according to a decoupled - ! aggregation algorithm. This also defines a tentative prolongator from - ! the coarse to the fine level. - ! - call mld_aggrmap_bld(p%parms%par_aggr_alg,p%parms%aggr_ord,p%parms%aggr_thresh,& - & a,desc_a,ilaggr,nlaggr,op_prol,info) - - if (info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='mld_aggrmap_bld') - goto 9999 - end if - - case (mld_bcmatch_aggr_) - write(0,*) 'Matching is not implemented yet ' - info = -1111 - call psb_errpush(psb_err_input_value_invalid_i_,name,& - & i_err=(/ione,p%parms%par_aggr_alg,izero,izero,izero/)) - goto 9999 - - case default - - info = -1 - call psb_errpush(psb_err_input_value_invalid_i_,name,& - & i_err=(/ione,p%parms%par_aggr_alg,izero,izero,izero/)) - goto 9999 - - end select - - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - return - -end subroutine mld_s_lev_aggrmap_bld diff --git a/mlprec/impl/mld_z_lev_aggrmap_bld.f90 b/mlprec/impl/mld_z_lev_aggrmap_bld.f90 deleted file mode 100644 index 54a386e0..00000000 --- a/mlprec/impl/mld_z_lev_aggrmap_bld.f90 +++ /dev/null @@ -1,157 +0,0 @@ - -! -! -! MLD2P4 version 2.1 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_z_lev_aggrmap_bld.f90 -! -! Subroutine: mld_z_lev_aggrmap_bld -! Version: complex -! -! This routine is just an interface to aggrmap_bld where the real work is performed. -! It takes care of some consistency checking though. -! -! See mld_zaggrmap_bld for constraints on input/oput arguments. -! -! -! Arguments: -! p - type(mld_z_onelev_type), input/output. -! The 'one-level' data structure containing the control -! parameters and (eventually) coarse matrix and prolongator/restrictors. -! -! a - type(psb_zspmat_type). -! The sparse matrix structure containing the local part of the -! fine-level matrix. -! desc_a - type(psb_desc_type), input. -! The communication descriptor of a. -! ilaggr - integer, dimension(:), allocatable, output -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that on exit the indices -! will be shifted so as to make sure the ranges on the various processes do not -! overlap. -! nlaggr - integer, dimension(:), allocatable, output -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_zspmat_type), output -! The tentative prolongator, based on ilaggr. -! -! info - integer, output. -! Error code. -! -subroutine mld_z_lev_aggrmap_bld(p,a,desc_a,ilaggr,nlaggr,op_prol,info) - - use psb_base_mod - use mld_base_prec_type - use mld_z_inner_mod, mld_protect_name => mld_z_lev_aggrmap_bld - - implicit none - - ! Arguments - type(mld_z_onelev_type), intent(inout), target :: p - type(psb_zspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - type(psb_zspmat_type), intent(out) :: op_prol - integer(psb_ipk_), intent(out) :: info - - - ! Local variables - character(len=20) :: name - integer(psb_mpik_) :: ictxt, np, me - integer(psb_ipk_) :: err_act - integer(psb_ipk_) :: nzl, ntaggr - integer(psb_ipk_) :: debug_level, debug_unit - - name='mld_z_lev_aggrmap_bld' - if (psb_get_errstatus().ne.0) return - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - info = psb_success_ - ictxt = desc_a%get_context() - call psb_info(ictxt,me,np) - - call mld_check_def(p%parms%ml_cycle,'Multilevel cycle',& - & mld_mult_ml_,is_legal_ml_cycle) - call mld_check_def(p%parms%par_aggr_alg,'Aggregation',& - & mld_dec_aggr_,is_legal_ml_par_aggr_alg) - call mld_check_def(p%parms%aggr_ord,'Ordering',& - & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) - call mld_check_def(p%parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) - - select case(p%parms%par_aggr_alg) - case (mld_dec_aggr_, mld_sym_dec_aggr_) - - ! - ! Build a mapping between the row indices of the fine-level matrix - ! and the row indices of the coarse-level matrix, according to a decoupled - ! aggregation algorithm. This also defines a tentative prolongator from - ! the coarse to the fine level. - ! - call mld_aggrmap_bld(p%parms%par_aggr_alg,p%parms%aggr_ord,p%parms%aggr_thresh,& - & a,desc_a,ilaggr,nlaggr,op_prol,info) - - if (info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='mld_aggrmap_bld') - goto 9999 - end if - - case (mld_bcmatch_aggr_) - write(0,*) 'Matching is not implemented yet ' - info = -1111 - call psb_errpush(psb_err_input_value_invalid_i_,name,& - & i_err=(/ione,p%parms%par_aggr_alg,izero,izero,izero/)) - goto 9999 - - case default - - info = -1 - call psb_errpush(psb_err_input_value_invalid_i_,name,& - & i_err=(/ione,p%parms%par_aggr_alg,izero,izero,izero/)) - goto 9999 - - end select - - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - return - -end subroutine mld_z_lev_aggrmap_bld From e0b15f495ecb282b2771246d62742f8cac3d7954 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 4 May 2018 21:21:34 +0100 Subject: [PATCH 14/33] Fixed compilation in level. --- mlprec/impl/level/Makefile | 4 + .../impl/level/mld_c_base_onelev_mat_asb.f90 | 267 ++++++++++++++++++ mlprec/impl/level/mld_c_base_onelev_seti.F90 | 2 +- .../impl/level/mld_d_base_onelev_mat_asb.f90 | 267 ++++++++++++++++++ mlprec/impl/level/mld_d_base_onelev_seti.F90 | 2 +- .../impl/level/mld_s_base_onelev_mat_asb.f90 | 267 ++++++++++++++++++ mlprec/impl/level/mld_s_base_onelev_seti.F90 | 2 +- .../impl/level/mld_z_base_onelev_mat_asb.f90 | 267 ++++++++++++++++++ mlprec/impl/level/mld_z_base_onelev_seti.F90 | 2 +- 9 files changed, 1076 insertions(+), 4 deletions(-) create mode 100644 mlprec/impl/level/mld_c_base_onelev_mat_asb.f90 create mode 100644 mlprec/impl/level/mld_d_base_onelev_mat_asb.f90 create mode 100644 mlprec/impl/level/mld_s_base_onelev_mat_asb.f90 create mode 100644 mlprec/impl/level/mld_z_base_onelev_mat_asb.f90 diff --git a/mlprec/impl/level/Makefile b/mlprec/impl/level/Makefile index 0143f61b..6a484fe1 100644 --- a/mlprec/impl/level/Makefile +++ b/mlprec/impl/level/Makefile @@ -17,6 +17,7 @@ mld_c_base_onelev_csetr.o \ mld_c_base_onelev_descr.o \ mld_c_base_onelev_dump.o \ mld_c_base_onelev_free.o \ +mld_c_base_onelev_mat_asb.f90 \ mld_c_base_onelev_setc.o \ mld_c_base_onelev_seti.o \ mld_c_base_onelev_setr.o \ @@ -31,6 +32,7 @@ mld_d_base_onelev_csetr.o \ mld_d_base_onelev_descr.o \ mld_d_base_onelev_dump.o \ mld_d_base_onelev_free.o \ +mld_d_base_onelev_mat_asb.f90 \ mld_d_base_onelev_setc.o \ mld_d_base_onelev_seti.o \ mld_d_base_onelev_setr.o \ @@ -45,6 +47,7 @@ mld_s_base_onelev_csetr.o \ mld_s_base_onelev_descr.o \ mld_s_base_onelev_dump.o \ mld_s_base_onelev_free.o \ +mld_s_base_onelev_mat_asb.f90 \ mld_s_base_onelev_setc.o \ mld_s_base_onelev_seti.o \ mld_s_base_onelev_setr.o \ @@ -59,6 +62,7 @@ mld_z_base_onelev_csetr.o \ mld_z_base_onelev_descr.o \ mld_z_base_onelev_dump.o \ mld_z_base_onelev_free.o \ +mld_z_base_onelev_mat_asb.f90 \ mld_z_base_onelev_setc.o \ mld_z_base_onelev_seti.o \ mld_z_base_onelev_setr.o \ diff --git a/mlprec/impl/level/mld_c_base_onelev_mat_asb.f90 b/mlprec/impl/level/mld_c_base_onelev_mat_asb.f90 new file mode 100644 index 00000000..a1569265 --- /dev/null +++ b/mlprec/impl/level/mld_c_base_onelev_mat_asb.f90 @@ -0,0 +1,267 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008-2018 +! +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_c_onelev_mat_asb.f90 +! +! Subroutine: mld_c_onelev_mat_asb +! Version: complex +! +! This routine builds the matrix associated to the current level of the +! multilevel preconditioner from the matrix associated to the previous level, +! by using the user-specified aggregation technique (therefore, it also builds the +! prolongation and restriction operators mapping the current level to the +! previous one and vice versa). +! The current level is regarded as the coarse one, while the previous as +! the fine one. This is in agreement with the fact that the routine is called, +! by mld_mlprec_bld, only on levels >=2. +! The main structure is: +! 1. Perform sanity checks; +! 2. Call mld_Xaggrmat_asb to compute prolongator/restrictor/AC +! 3. According to the choice of DIST/REPL for AC, build a descriptor DESC_AC, +! and adjust the column numbering of AC/OP_PROL/OP_RESTR +! 4. Pack restrictor and prolongator into p%map +! 5. Fix base_a and base_desc pointers. +! +! +! Arguments: +! p - type(mld_c_onelev_type), input/output. +! The 'one-level' data structure containing the control +! parameters and (eventually) coarse matrix and prolongator/restrictors. +! +! a - type(psb_cspmat_type). +! The sparse matrix structure containing the local part of the +! fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of a. +! ilaggr - integer, dimension(:), input +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that the indices +! are assumed to be shifted so as to make sure the ranges on +! the various processes do not overlap. +! nlaggr - integer, dimension(:) input +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_cspmat_type), input/output +! The tentative prolongator on input, released on output. +! +! info - integer, output. +! Error code. +! +subroutine mld_c_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) + + use psb_base_mod + use mld_base_prec_type + use mld_c_inner_mod, mld_protect_name => mld_c_onelev_mat_asb + + implicit none + + ! Arguments + class(mld_c_onelev_type), intent(inout), target :: lv + type(psb_cspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:),nlaggr(:) + type(psb_cspmat_type), intent(inout) :: op_prol + integer(psb_ipk_), intent(out) :: info + + + ! Local variables + character(len=24) :: name + integer(psb_mpik_) :: ictxt, np, me + integer(psb_ipk_) :: err_act + type(psb_cspmat_type) :: ac, op_restr + type(psb_c_coo_sparse_mat) :: acoo, bcoo + type(psb_c_csr_sparse_mat) :: acsr1 + integer(psb_ipk_) :: nzl, ntaggr + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_c_onelev_mat_asb' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(lv%parms%aggr_prol,'Smoother',& + & mld_smooth_prol_,is_legal_ml_aggr_prol) + call mld_check_def(lv%parms%coarse_mat,'Coarse matrix',& + & mld_distr_mat_,is_legal_ml_coarse_mat) + call mld_check_def(lv%parms%aggr_filter,'Use filtered matrix',& + & mld_no_filter_mat_,is_legal_aggr_filter) + call mld_check_def(lv%parms%aggr_omega_alg,'Omega Alg.',& + & mld_eig_est_,is_legal_ml_aggr_omega_alg) + call mld_check_def(lv%parms%aggr_eig,'Eigenvalue estimate',& + & mld_max_norm_,is_legal_ml_aggr_eig) + call mld_check_def(lv%parms%aggr_omega_val,'Omega',szero,is_legal_s_omega) + + + ! + ! Build the coarse-level matrix from the fine-level one, starting from + ! the mapping defined by mld_aggrmap_bld and applying the aggregation + ! algorithm specified by lv%iprcparm(mld_aggr_prol_) + ! + call lv%aggr%mat_asb(a,desc_a,ilaggr,nlaggr,lv%parms,ac,op_prol,op_restr,info) + + if(info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='mld_aggrmat_asb') + goto 9999 + end if + + + ! Common code refactored here. + + ntaggr = sum(nlaggr) + + select case(lv%parms%coarse_mat) + + case(mld_distr_mat_) + + call ac%mv_to(bcoo) + nzl = bcoo%get_nzeros() + + if (info == psb_success_) call psb_cdall(ictxt,lv%desc_ac,info,nl=nlaggr(me+1)) + if (info == psb_success_) call psb_cdins(nzl,bcoo%ia,bcoo%ja,lv%desc_ac,info) + if (info == psb_success_) call psb_cdasb(lv%desc_ac,info) + if (info == psb_success_) call psb_glob_to_loc(bcoo%ia(1:nzl),lv%desc_ac,info,iact='I') + if (info == psb_success_) call psb_glob_to_loc(bcoo%ja(1:nzl),lv%desc_ac,info,iact='I') + if (info /= psb_success_) then + call psb_errpush(psb_err_internal_error_,name,& + & a_err='Creating lv%desc_ac and converting ac') + goto 9999 + end if + if (debug_level >= psb_debug_outer_) & + & write(debug_unit,*) me,' ',trim(name),& + & 'Assembld aux descr. distr.' + call lv%ac%mv_from(bcoo) + + call lv%ac%set_nrows(lv%desc_ac%get_local_rows()) + call lv%ac%set_ncols(lv%desc_ac%get_local_cols()) + call lv%ac%set_asb() + + if (info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_sp_free') + goto 9999 + end if + + if (np>1) then + call op_prol%mv_to(acsr1) + nzl = acsr1%get_nzeros() + call psb_glob_to_loc(acsr1%ja(1:nzl),lv%desc_ac,info,'I') + if(info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_glob_to_loc') + goto 9999 + end if + call op_prol%mv_from(acsr1) + endif + call op_prol%set_ncols(lv%desc_ac%get_local_cols()) + + if (np>1) then + call op_restr%cscnv(info,type='coo',dupl=psb_dupl_add_) + call op_restr%mv_to(acoo) + nzl = acoo%get_nzeros() + if (info == psb_success_) call psb_glob_to_loc(acoo%ia(1:nzl),lv%desc_ac,info,'I') + call acoo%set_dupl(psb_dupl_add_) + if (info == psb_success_) call op_restr%mv_from(acoo) + if (info == psb_success_) call op_restr%cscnv(info,type='csr') + if(info /= psb_success_) then + call psb_errpush(psb_err_internal_error_,name,& + & a_err='Converting op_restr to local') + goto 9999 + end if + end if + ! + ! Clip to local rows. + ! + call op_restr%set_nrows(lv%desc_ac%get_local_rows()) + + if (debug_level >= psb_debug_outer_) & + & write(debug_unit,*) me,' ',trim(name),& + & 'Done ac ' + + case(mld_repl_mat_) + ! + ! + call psb_cdall(ictxt,lv%desc_ac,info,mg=ntaggr,repl=.true.) + if (info == psb_success_) call psb_cdasb(lv%desc_ac,info) + if (info == psb_success_) & + & call psb_gather(lv%ac,ac,lv%desc_ac,info,dupl=psb_dupl_add_,keeploc=.false.) + + if (info /= psb_success_) goto 9999 + + case default + info = psb_err_internal_error_ + call psb_errpush(info,name,a_err='invalid mld_coarse_mat_') + goto 9999 + end select + + call lv%ac%cscnv(info,type='csr',dupl=psb_dupl_add_) + if(info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='spcnv') + goto 9999 + end if + + ! + ! Copy the prolongation/restriction matrices into the descriptor map. + ! op_restr => PR^T i.e. restriction operator + ! op_prol => PR i.e. prolongation operator + ! + + lv%map = psb_linmap(psb_map_aggr_,desc_a,& + & lv%desc_ac,op_restr,op_prol,ilaggr,nlaggr) + if (info == psb_success_) call op_prol%free() + if (info == psb_success_) call op_restr%free() + if(info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='sp_Free') + goto 9999 + end if + ! + ! Fix the base_a and base_desc pointers for handling of residuals. + ! This is correct because this routine is only called at levels >=2. + ! + lv%base_a => lv%ac + lv%base_desc => lv%desc_ac + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + +end subroutine mld_c_onelev_mat_asb diff --git a/mlprec/impl/level/mld_c_base_onelev_seti.F90 b/mlprec/impl/level/mld_c_base_onelev_seti.F90 index a85df1e5..b23c6b1a 100644 --- a/mlprec/impl/level/mld_c_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_c_base_onelev_seti.F90 @@ -116,7 +116,7 @@ subroutine mld_c_base_onelev_seti(lv,what,val,info,pos) case (mld_fbgs_) call lv%set(mld_c_jac_smoother_mold,info,pos='pre') if (info == 0) call lv%set(mld_c_gs_solver_mold,info,pos='pre') - call lv%set(mld_c_jac_smoother_mold,info,pos='post') + if (info == 0) call lv%set(mld_c_jac_smoother_mold,info,pos='post') if (info == 0) call lv%set(mld_c_bwgs_solver_mold,info,pos='post') diff --git a/mlprec/impl/level/mld_d_base_onelev_mat_asb.f90 b/mlprec/impl/level/mld_d_base_onelev_mat_asb.f90 new file mode 100644 index 00000000..d8105c63 --- /dev/null +++ b/mlprec/impl/level/mld_d_base_onelev_mat_asb.f90 @@ -0,0 +1,267 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008-2018 +! +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_d_onelev_mat_asb.f90 +! +! Subroutine: mld_d_onelev_mat_asb +! Version: real +! +! This routine builds the matrix associated to the current level of the +! multilevel preconditioner from the matrix associated to the previous level, +! by using the user-specified aggregation technique (therefore, it also builds the +! prolongation and restriction operators mapping the current level to the +! previous one and vice versa). +! The current level is regarded as the coarse one, while the previous as +! the fine one. This is in agreement with the fact that the routine is called, +! by mld_mlprec_bld, only on levels >=2. +! The main structure is: +! 1. Perform sanity checks; +! 2. Call mld_Xaggrmat_asb to compute prolongator/restrictor/AC +! 3. According to the choice of DIST/REPL for AC, build a descriptor DESC_AC, +! and adjust the column numbering of AC/OP_PROL/OP_RESTR +! 4. Pack restrictor and prolongator into p%map +! 5. Fix base_a and base_desc pointers. +! +! +! Arguments: +! p - type(mld_d_onelev_type), input/output. +! The 'one-level' data structure containing the control +! parameters and (eventually) coarse matrix and prolongator/restrictors. +! +! a - type(psb_dspmat_type). +! The sparse matrix structure containing the local part of the +! fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of a. +! ilaggr - integer, dimension(:), input +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that the indices +! are assumed to be shifted so as to make sure the ranges on +! the various processes do not overlap. +! nlaggr - integer, dimension(:) input +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_dspmat_type), input/output +! The tentative prolongator on input, released on output. +! +! info - integer, output. +! Error code. +! +subroutine mld_d_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) + + use psb_base_mod + use mld_base_prec_type + use mld_d_inner_mod, mld_protect_name => mld_d_onelev_mat_asb + + implicit none + + ! Arguments + class(mld_d_onelev_type), intent(inout), target :: lv + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:),nlaggr(:) + type(psb_dspmat_type), intent(inout) :: op_prol + integer(psb_ipk_), intent(out) :: info + + + ! Local variables + character(len=24) :: name + integer(psb_mpik_) :: ictxt, np, me + integer(psb_ipk_) :: err_act + type(psb_dspmat_type) :: ac, op_restr + type(psb_d_coo_sparse_mat) :: acoo, bcoo + type(psb_d_csr_sparse_mat) :: acsr1 + integer(psb_ipk_) :: nzl, ntaggr + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_d_onelev_mat_asb' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(lv%parms%aggr_prol,'Smoother',& + & mld_smooth_prol_,is_legal_ml_aggr_prol) + call mld_check_def(lv%parms%coarse_mat,'Coarse matrix',& + & mld_distr_mat_,is_legal_ml_coarse_mat) + call mld_check_def(lv%parms%aggr_filter,'Use filtered matrix',& + & mld_no_filter_mat_,is_legal_aggr_filter) + call mld_check_def(lv%parms%aggr_omega_alg,'Omega Alg.',& + & mld_eig_est_,is_legal_ml_aggr_omega_alg) + call mld_check_def(lv%parms%aggr_eig,'Eigenvalue estimate',& + & mld_max_norm_,is_legal_ml_aggr_eig) + call mld_check_def(lv%parms%aggr_omega_val,'Omega',dzero,is_legal_d_omega) + + + ! + ! Build the coarse-level matrix from the fine-level one, starting from + ! the mapping defined by mld_aggrmap_bld and applying the aggregation + ! algorithm specified by lv%iprcparm(mld_aggr_prol_) + ! + call lv%aggr%mat_asb(a,desc_a,ilaggr,nlaggr,lv%parms,ac,op_prol,op_restr,info) + + if(info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='mld_aggrmat_asb') + goto 9999 + end if + + + ! Common code refactored here. + + ntaggr = sum(nlaggr) + + select case(lv%parms%coarse_mat) + + case(mld_distr_mat_) + + call ac%mv_to(bcoo) + nzl = bcoo%get_nzeros() + + if (info == psb_success_) call psb_cdall(ictxt,lv%desc_ac,info,nl=nlaggr(me+1)) + if (info == psb_success_) call psb_cdins(nzl,bcoo%ia,bcoo%ja,lv%desc_ac,info) + if (info == psb_success_) call psb_cdasb(lv%desc_ac,info) + if (info == psb_success_) call psb_glob_to_loc(bcoo%ia(1:nzl),lv%desc_ac,info,iact='I') + if (info == psb_success_) call psb_glob_to_loc(bcoo%ja(1:nzl),lv%desc_ac,info,iact='I') + if (info /= psb_success_) then + call psb_errpush(psb_err_internal_error_,name,& + & a_err='Creating lv%desc_ac and converting ac') + goto 9999 + end if + if (debug_level >= psb_debug_outer_) & + & write(debug_unit,*) me,' ',trim(name),& + & 'Assembld aux descr. distr.' + call lv%ac%mv_from(bcoo) + + call lv%ac%set_nrows(lv%desc_ac%get_local_rows()) + call lv%ac%set_ncols(lv%desc_ac%get_local_cols()) + call lv%ac%set_asb() + + if (info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_sp_free') + goto 9999 + end if + + if (np>1) then + call op_prol%mv_to(acsr1) + nzl = acsr1%get_nzeros() + call psb_glob_to_loc(acsr1%ja(1:nzl),lv%desc_ac,info,'I') + if(info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_glob_to_loc') + goto 9999 + end if + call op_prol%mv_from(acsr1) + endif + call op_prol%set_ncols(lv%desc_ac%get_local_cols()) + + if (np>1) then + call op_restr%cscnv(info,type='coo',dupl=psb_dupl_add_) + call op_restr%mv_to(acoo) + nzl = acoo%get_nzeros() + if (info == psb_success_) call psb_glob_to_loc(acoo%ia(1:nzl),lv%desc_ac,info,'I') + call acoo%set_dupl(psb_dupl_add_) + if (info == psb_success_) call op_restr%mv_from(acoo) + if (info == psb_success_) call op_restr%cscnv(info,type='csr') + if(info /= psb_success_) then + call psb_errpush(psb_err_internal_error_,name,& + & a_err='Converting op_restr to local') + goto 9999 + end if + end if + ! + ! Clip to local rows. + ! + call op_restr%set_nrows(lv%desc_ac%get_local_rows()) + + if (debug_level >= psb_debug_outer_) & + & write(debug_unit,*) me,' ',trim(name),& + & 'Done ac ' + + case(mld_repl_mat_) + ! + ! + call psb_cdall(ictxt,lv%desc_ac,info,mg=ntaggr,repl=.true.) + if (info == psb_success_) call psb_cdasb(lv%desc_ac,info) + if (info == psb_success_) & + & call psb_gather(lv%ac,ac,lv%desc_ac,info,dupl=psb_dupl_add_,keeploc=.false.) + + if (info /= psb_success_) goto 9999 + + case default + info = psb_err_internal_error_ + call psb_errpush(info,name,a_err='invalid mld_coarse_mat_') + goto 9999 + end select + + call lv%ac%cscnv(info,type='csr',dupl=psb_dupl_add_) + if(info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='spcnv') + goto 9999 + end if + + ! + ! Copy the prolongation/restriction matrices into the descriptor map. + ! op_restr => PR^T i.e. restriction operator + ! op_prol => PR i.e. prolongation operator + ! + + lv%map = psb_linmap(psb_map_aggr_,desc_a,& + & lv%desc_ac,op_restr,op_prol,ilaggr,nlaggr) + if (info == psb_success_) call op_prol%free() + if (info == psb_success_) call op_restr%free() + if(info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='sp_Free') + goto 9999 + end if + ! + ! Fix the base_a and base_desc pointers for handling of residuals. + ! This is correct because this routine is only called at levels >=2. + ! + lv%base_a => lv%ac + lv%base_desc => lv%desc_ac + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + +end subroutine mld_d_onelev_mat_asb diff --git a/mlprec/impl/level/mld_d_base_onelev_seti.F90 b/mlprec/impl/level/mld_d_base_onelev_seti.F90 index 8fbe0ecc..6c3e7a22 100644 --- a/mlprec/impl/level/mld_d_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_d_base_onelev_seti.F90 @@ -128,7 +128,7 @@ subroutine mld_d_base_onelev_seti(lv,what,val,info,pos) case (mld_fbgs_) call lv%set(mld_d_jac_smoother_mold,info,pos='pre') if (info == 0) call lv%set(mld_d_gs_solver_mold,info,pos='pre') - call lv%set(mld_d_jac_smoother_mold,info,pos='post') + if (info == 0) call lv%set(mld_d_jac_smoother_mold,info,pos='post') if (info == 0) call lv%set(mld_d_bwgs_solver_mold,info,pos='post') diff --git a/mlprec/impl/level/mld_s_base_onelev_mat_asb.f90 b/mlprec/impl/level/mld_s_base_onelev_mat_asb.f90 new file mode 100644 index 00000000..13b43e42 --- /dev/null +++ b/mlprec/impl/level/mld_s_base_onelev_mat_asb.f90 @@ -0,0 +1,267 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008-2018 +! +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_s_onelev_mat_asb.f90 +! +! Subroutine: mld_s_onelev_mat_asb +! Version: real +! +! This routine builds the matrix associated to the current level of the +! multilevel preconditioner from the matrix associated to the previous level, +! by using the user-specified aggregation technique (therefore, it also builds the +! prolongation and restriction operators mapping the current level to the +! previous one and vice versa). +! The current level is regarded as the coarse one, while the previous as +! the fine one. This is in agreement with the fact that the routine is called, +! by mld_mlprec_bld, only on levels >=2. +! The main structure is: +! 1. Perform sanity checks; +! 2. Call mld_Xaggrmat_asb to compute prolongator/restrictor/AC +! 3. According to the choice of DIST/REPL for AC, build a descriptor DESC_AC, +! and adjust the column numbering of AC/OP_PROL/OP_RESTR +! 4. Pack restrictor and prolongator into p%map +! 5. Fix base_a and base_desc pointers. +! +! +! Arguments: +! p - type(mld_s_onelev_type), input/output. +! The 'one-level' data structure containing the control +! parameters and (eventually) coarse matrix and prolongator/restrictors. +! +! a - type(psb_sspmat_type). +! The sparse matrix structure containing the local part of the +! fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of a. +! ilaggr - integer, dimension(:), input +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that the indices +! are assumed to be shifted so as to make sure the ranges on +! the various processes do not overlap. +! nlaggr - integer, dimension(:) input +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_sspmat_type), input/output +! The tentative prolongator on input, released on output. +! +! info - integer, output. +! Error code. +! +subroutine mld_s_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) + + use psb_base_mod + use mld_base_prec_type + use mld_s_inner_mod, mld_protect_name => mld_s_onelev_mat_asb + + implicit none + + ! Arguments + class(mld_s_onelev_type), intent(inout), target :: lv + type(psb_sspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:),nlaggr(:) + type(psb_sspmat_type), intent(inout) :: op_prol + integer(psb_ipk_), intent(out) :: info + + + ! Local variables + character(len=24) :: name + integer(psb_mpik_) :: ictxt, np, me + integer(psb_ipk_) :: err_act + type(psb_sspmat_type) :: ac, op_restr + type(psb_s_coo_sparse_mat) :: acoo, bcoo + type(psb_s_csr_sparse_mat) :: acsr1 + integer(psb_ipk_) :: nzl, ntaggr + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_s_onelev_mat_asb' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(lv%parms%aggr_prol,'Smoother',& + & mld_smooth_prol_,is_legal_ml_aggr_prol) + call mld_check_def(lv%parms%coarse_mat,'Coarse matrix',& + & mld_distr_mat_,is_legal_ml_coarse_mat) + call mld_check_def(lv%parms%aggr_filter,'Use filtered matrix',& + & mld_no_filter_mat_,is_legal_aggr_filter) + call mld_check_def(lv%parms%aggr_omega_alg,'Omega Alg.',& + & mld_eig_est_,is_legal_ml_aggr_omega_alg) + call mld_check_def(lv%parms%aggr_eig,'Eigenvalue estimate',& + & mld_max_norm_,is_legal_ml_aggr_eig) + call mld_check_def(lv%parms%aggr_omega_val,'Omega',szero,is_legal_s_omega) + + + ! + ! Build the coarse-level matrix from the fine-level one, starting from + ! the mapping defined by mld_aggrmap_bld and applying the aggregation + ! algorithm specified by lv%iprcparm(mld_aggr_prol_) + ! + call lv%aggr%mat_asb(a,desc_a,ilaggr,nlaggr,lv%parms,ac,op_prol,op_restr,info) + + if(info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='mld_aggrmat_asb') + goto 9999 + end if + + + ! Common code refactored here. + + ntaggr = sum(nlaggr) + + select case(lv%parms%coarse_mat) + + case(mld_distr_mat_) + + call ac%mv_to(bcoo) + nzl = bcoo%get_nzeros() + + if (info == psb_success_) call psb_cdall(ictxt,lv%desc_ac,info,nl=nlaggr(me+1)) + if (info == psb_success_) call psb_cdins(nzl,bcoo%ia,bcoo%ja,lv%desc_ac,info) + if (info == psb_success_) call psb_cdasb(lv%desc_ac,info) + if (info == psb_success_) call psb_glob_to_loc(bcoo%ia(1:nzl),lv%desc_ac,info,iact='I') + if (info == psb_success_) call psb_glob_to_loc(bcoo%ja(1:nzl),lv%desc_ac,info,iact='I') + if (info /= psb_success_) then + call psb_errpush(psb_err_internal_error_,name,& + & a_err='Creating lv%desc_ac and converting ac') + goto 9999 + end if + if (debug_level >= psb_debug_outer_) & + & write(debug_unit,*) me,' ',trim(name),& + & 'Assembld aux descr. distr.' + call lv%ac%mv_from(bcoo) + + call lv%ac%set_nrows(lv%desc_ac%get_local_rows()) + call lv%ac%set_ncols(lv%desc_ac%get_local_cols()) + call lv%ac%set_asb() + + if (info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_sp_free') + goto 9999 + end if + + if (np>1) then + call op_prol%mv_to(acsr1) + nzl = acsr1%get_nzeros() + call psb_glob_to_loc(acsr1%ja(1:nzl),lv%desc_ac,info,'I') + if(info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_glob_to_loc') + goto 9999 + end if + call op_prol%mv_from(acsr1) + endif + call op_prol%set_ncols(lv%desc_ac%get_local_cols()) + + if (np>1) then + call op_restr%cscnv(info,type='coo',dupl=psb_dupl_add_) + call op_restr%mv_to(acoo) + nzl = acoo%get_nzeros() + if (info == psb_success_) call psb_glob_to_loc(acoo%ia(1:nzl),lv%desc_ac,info,'I') + call acoo%set_dupl(psb_dupl_add_) + if (info == psb_success_) call op_restr%mv_from(acoo) + if (info == psb_success_) call op_restr%cscnv(info,type='csr') + if(info /= psb_success_) then + call psb_errpush(psb_err_internal_error_,name,& + & a_err='Converting op_restr to local') + goto 9999 + end if + end if + ! + ! Clip to local rows. + ! + call op_restr%set_nrows(lv%desc_ac%get_local_rows()) + + if (debug_level >= psb_debug_outer_) & + & write(debug_unit,*) me,' ',trim(name),& + & 'Done ac ' + + case(mld_repl_mat_) + ! + ! + call psb_cdall(ictxt,lv%desc_ac,info,mg=ntaggr,repl=.true.) + if (info == psb_success_) call psb_cdasb(lv%desc_ac,info) + if (info == psb_success_) & + & call psb_gather(lv%ac,ac,lv%desc_ac,info,dupl=psb_dupl_add_,keeploc=.false.) + + if (info /= psb_success_) goto 9999 + + case default + info = psb_err_internal_error_ + call psb_errpush(info,name,a_err='invalid mld_coarse_mat_') + goto 9999 + end select + + call lv%ac%cscnv(info,type='csr',dupl=psb_dupl_add_) + if(info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='spcnv') + goto 9999 + end if + + ! + ! Copy the prolongation/restriction matrices into the descriptor map. + ! op_restr => PR^T i.e. restriction operator + ! op_prol => PR i.e. prolongation operator + ! + + lv%map = psb_linmap(psb_map_aggr_,desc_a,& + & lv%desc_ac,op_restr,op_prol,ilaggr,nlaggr) + if (info == psb_success_) call op_prol%free() + if (info == psb_success_) call op_restr%free() + if(info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='sp_Free') + goto 9999 + end if + ! + ! Fix the base_a and base_desc pointers for handling of residuals. + ! This is correct because this routine is only called at levels >=2. + ! + lv%base_a => lv%ac + lv%base_desc => lv%desc_ac + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + +end subroutine mld_s_onelev_mat_asb diff --git a/mlprec/impl/level/mld_s_base_onelev_seti.F90 b/mlprec/impl/level/mld_s_base_onelev_seti.F90 index d5e34645..fc690639 100644 --- a/mlprec/impl/level/mld_s_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_s_base_onelev_seti.F90 @@ -116,7 +116,7 @@ subroutine mld_s_base_onelev_seti(lv,what,val,info,pos) case (mld_fbgs_) call lv%set(mld_s_jac_smoother_mold,info,pos='pre') if (info == 0) call lv%set(mld_s_gs_solver_mold,info,pos='pre') - call lv%set(mld_s_jac_smoother_mold,info,pos='post') + if (info == 0) call lv%set(mld_s_jac_smoother_mold,info,pos='post') if (info == 0) call lv%set(mld_s_bwgs_solver_mold,info,pos='post') diff --git a/mlprec/impl/level/mld_z_base_onelev_mat_asb.f90 b/mlprec/impl/level/mld_z_base_onelev_mat_asb.f90 new file mode 100644 index 00000000..62e58069 --- /dev/null +++ b/mlprec/impl/level/mld_z_base_onelev_mat_asb.f90 @@ -0,0 +1,267 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008-2018 +! +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_z_onelev_mat_asb.f90 +! +! Subroutine: mld_z_onelev_mat_asb +! Version: complex +! +! This routine builds the matrix associated to the current level of the +! multilevel preconditioner from the matrix associated to the previous level, +! by using the user-specified aggregation technique (therefore, it also builds the +! prolongation and restriction operators mapping the current level to the +! previous one and vice versa). +! The current level is regarded as the coarse one, while the previous as +! the fine one. This is in agreement with the fact that the routine is called, +! by mld_mlprec_bld, only on levels >=2. +! The main structure is: +! 1. Perform sanity checks; +! 2. Call mld_Xaggrmat_asb to compute prolongator/restrictor/AC +! 3. According to the choice of DIST/REPL for AC, build a descriptor DESC_AC, +! and adjust the column numbering of AC/OP_PROL/OP_RESTR +! 4. Pack restrictor and prolongator into p%map +! 5. Fix base_a and base_desc pointers. +! +! +! Arguments: +! p - type(mld_z_onelev_type), input/output. +! The 'one-level' data structure containing the control +! parameters and (eventually) coarse matrix and prolongator/restrictors. +! +! a - type(psb_zspmat_type). +! The sparse matrix structure containing the local part of the +! fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of a. +! ilaggr - integer, dimension(:), input +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that the indices +! are assumed to be shifted so as to make sure the ranges on +! the various processes do not overlap. +! nlaggr - integer, dimension(:) input +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_zspmat_type), input/output +! The tentative prolongator on input, released on output. +! +! info - integer, output. +! Error code. +! +subroutine mld_z_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) + + use psb_base_mod + use mld_base_prec_type + use mld_z_inner_mod, mld_protect_name => mld_z_onelev_mat_asb + + implicit none + + ! Arguments + class(mld_z_onelev_type), intent(inout), target :: lv + type(psb_zspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:),nlaggr(:) + type(psb_zspmat_type), intent(inout) :: op_prol + integer(psb_ipk_), intent(out) :: info + + + ! Local variables + character(len=24) :: name + integer(psb_mpik_) :: ictxt, np, me + integer(psb_ipk_) :: err_act + type(psb_zspmat_type) :: ac, op_restr + type(psb_z_coo_sparse_mat) :: acoo, bcoo + type(psb_z_csr_sparse_mat) :: acsr1 + integer(psb_ipk_) :: nzl, ntaggr + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_z_onelev_mat_asb' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(lv%parms%aggr_prol,'Smoother',& + & mld_smooth_prol_,is_legal_ml_aggr_prol) + call mld_check_def(lv%parms%coarse_mat,'Coarse matrix',& + & mld_distr_mat_,is_legal_ml_coarse_mat) + call mld_check_def(lv%parms%aggr_filter,'Use filtered matrix',& + & mld_no_filter_mat_,is_legal_aggr_filter) + call mld_check_def(lv%parms%aggr_omega_alg,'Omega Alg.',& + & mld_eig_est_,is_legal_ml_aggr_omega_alg) + call mld_check_def(lv%parms%aggr_eig,'Eigenvalue estimate',& + & mld_max_norm_,is_legal_ml_aggr_eig) + call mld_check_def(lv%parms%aggr_omega_val,'Omega',dzero,is_legal_d_omega) + + + ! + ! Build the coarse-level matrix from the fine-level one, starting from + ! the mapping defined by mld_aggrmap_bld and applying the aggregation + ! algorithm specified by lv%iprcparm(mld_aggr_prol_) + ! + call lv%aggr%mat_asb(a,desc_a,ilaggr,nlaggr,lv%parms,ac,op_prol,op_restr,info) + + if(info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='mld_aggrmat_asb') + goto 9999 + end if + + + ! Common code refactored here. + + ntaggr = sum(nlaggr) + + select case(lv%parms%coarse_mat) + + case(mld_distr_mat_) + + call ac%mv_to(bcoo) + nzl = bcoo%get_nzeros() + + if (info == psb_success_) call psb_cdall(ictxt,lv%desc_ac,info,nl=nlaggr(me+1)) + if (info == psb_success_) call psb_cdins(nzl,bcoo%ia,bcoo%ja,lv%desc_ac,info) + if (info == psb_success_) call psb_cdasb(lv%desc_ac,info) + if (info == psb_success_) call psb_glob_to_loc(bcoo%ia(1:nzl),lv%desc_ac,info,iact='I') + if (info == psb_success_) call psb_glob_to_loc(bcoo%ja(1:nzl),lv%desc_ac,info,iact='I') + if (info /= psb_success_) then + call psb_errpush(psb_err_internal_error_,name,& + & a_err='Creating lv%desc_ac and converting ac') + goto 9999 + end if + if (debug_level >= psb_debug_outer_) & + & write(debug_unit,*) me,' ',trim(name),& + & 'Assembld aux descr. distr.' + call lv%ac%mv_from(bcoo) + + call lv%ac%set_nrows(lv%desc_ac%get_local_rows()) + call lv%ac%set_ncols(lv%desc_ac%get_local_cols()) + call lv%ac%set_asb() + + if (info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_sp_free') + goto 9999 + end if + + if (np>1) then + call op_prol%mv_to(acsr1) + nzl = acsr1%get_nzeros() + call psb_glob_to_loc(acsr1%ja(1:nzl),lv%desc_ac,info,'I') + if(info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_glob_to_loc') + goto 9999 + end if + call op_prol%mv_from(acsr1) + endif + call op_prol%set_ncols(lv%desc_ac%get_local_cols()) + + if (np>1) then + call op_restr%cscnv(info,type='coo',dupl=psb_dupl_add_) + call op_restr%mv_to(acoo) + nzl = acoo%get_nzeros() + if (info == psb_success_) call psb_glob_to_loc(acoo%ia(1:nzl),lv%desc_ac,info,'I') + call acoo%set_dupl(psb_dupl_add_) + if (info == psb_success_) call op_restr%mv_from(acoo) + if (info == psb_success_) call op_restr%cscnv(info,type='csr') + if(info /= psb_success_) then + call psb_errpush(psb_err_internal_error_,name,& + & a_err='Converting op_restr to local') + goto 9999 + end if + end if + ! + ! Clip to local rows. + ! + call op_restr%set_nrows(lv%desc_ac%get_local_rows()) + + if (debug_level >= psb_debug_outer_) & + & write(debug_unit,*) me,' ',trim(name),& + & 'Done ac ' + + case(mld_repl_mat_) + ! + ! + call psb_cdall(ictxt,lv%desc_ac,info,mg=ntaggr,repl=.true.) + if (info == psb_success_) call psb_cdasb(lv%desc_ac,info) + if (info == psb_success_) & + & call psb_gather(lv%ac,ac,lv%desc_ac,info,dupl=psb_dupl_add_,keeploc=.false.) + + if (info /= psb_success_) goto 9999 + + case default + info = psb_err_internal_error_ + call psb_errpush(info,name,a_err='invalid mld_coarse_mat_') + goto 9999 + end select + + call lv%ac%cscnv(info,type='csr',dupl=psb_dupl_add_) + if(info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='spcnv') + goto 9999 + end if + + ! + ! Copy the prolongation/restriction matrices into the descriptor map. + ! op_restr => PR^T i.e. restriction operator + ! op_prol => PR i.e. prolongation operator + ! + + lv%map = psb_linmap(psb_map_aggr_,desc_a,& + & lv%desc_ac,op_restr,op_prol,ilaggr,nlaggr) + if (info == psb_success_) call op_prol%free() + if (info == psb_success_) call op_restr%free() + if(info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='sp_Free') + goto 9999 + end if + ! + ! Fix the base_a and base_desc pointers for handling of residuals. + ! This is correct because this routine is only called at levels >=2. + ! + lv%base_a => lv%ac + lv%base_desc => lv%desc_ac + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + +end subroutine mld_z_onelev_mat_asb diff --git a/mlprec/impl/level/mld_z_base_onelev_seti.F90 b/mlprec/impl/level/mld_z_base_onelev_seti.F90 index 488d8845..af419a17 100644 --- a/mlprec/impl/level/mld_z_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_z_base_onelev_seti.F90 @@ -128,7 +128,7 @@ subroutine mld_z_base_onelev_seti(lv,what,val,info,pos) case (mld_fbgs_) call lv%set(mld_z_jac_smoother_mold,info,pos='pre') if (info == 0) call lv%set(mld_z_gs_solver_mold,info,pos='pre') - call lv%set(mld_z_jac_smoother_mold,info,pos='post') + if (info == 0) call lv%set(mld_z_jac_smoother_mold,info,pos='post') if (info == 0) call lv%set(mld_z_bwgs_solver_mold,info,pos='post') From 7092dc2063eaae2e6b0a0150970a34457a0d1961 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Sat, 5 May 2018 07:46:24 +0100 Subject: [PATCH 15/33] Fixed compilation process. --- mlprec/impl/level/Makefile | 12 ++- .../impl/level/mld_c_base_onelev_mat_asb.f90 | 8 +- mlprec/impl/level/mld_c_base_onelev_setag.f90 | 80 +++++++++++++++++++ .../impl/level/mld_d_base_onelev_mat_asb.f90 | 8 +- mlprec/impl/level/mld_d_base_onelev_setag.f90 | 80 +++++++++++++++++++ .../impl/level/mld_s_base_onelev_mat_asb.f90 | 8 +- mlprec/impl/level/mld_s_base_onelev_setag.f90 | 80 +++++++++++++++++++ .../impl/level/mld_z_base_onelev_mat_asb.f90 | 8 +- mlprec/impl/level/mld_z_base_onelev_setag.f90 | 80 +++++++++++++++++++ mlprec/impl/mld_cprecset.F90 | 64 +++++++++++++++ mlprec/impl/mld_dprecset.F90 | 64 +++++++++++++++ mlprec/impl/mld_sprecset.F90 | 64 +++++++++++++++ mlprec/impl/mld_zprecset.F90 | 64 +++++++++++++++ 13 files changed, 600 insertions(+), 20 deletions(-) create mode 100644 mlprec/impl/level/mld_c_base_onelev_setag.f90 create mode 100644 mlprec/impl/level/mld_d_base_onelev_setag.f90 create mode 100644 mlprec/impl/level/mld_s_base_onelev_setag.f90 create mode 100644 mlprec/impl/level/mld_z_base_onelev_setag.f90 diff --git a/mlprec/impl/level/Makefile b/mlprec/impl/level/Makefile index 6a484fe1..9cb12928 100644 --- a/mlprec/impl/level/Makefile +++ b/mlprec/impl/level/Makefile @@ -17,7 +17,8 @@ mld_c_base_onelev_csetr.o \ mld_c_base_onelev_descr.o \ mld_c_base_onelev_dump.o \ mld_c_base_onelev_free.o \ -mld_c_base_onelev_mat_asb.f90 \ +mld_c_base_onelev_mat_asb.o \ +mld_c_base_onelev_setag.o \ mld_c_base_onelev_setc.o \ mld_c_base_onelev_seti.o \ mld_c_base_onelev_setr.o \ @@ -32,7 +33,8 @@ mld_d_base_onelev_csetr.o \ mld_d_base_onelev_descr.o \ mld_d_base_onelev_dump.o \ mld_d_base_onelev_free.o \ -mld_d_base_onelev_mat_asb.f90 \ +mld_d_base_onelev_mat_asb.o \ +mld_d_base_onelev_setag.o \ mld_d_base_onelev_setc.o \ mld_d_base_onelev_seti.o \ mld_d_base_onelev_setr.o \ @@ -47,7 +49,8 @@ mld_s_base_onelev_csetr.o \ mld_s_base_onelev_descr.o \ mld_s_base_onelev_dump.o \ mld_s_base_onelev_free.o \ -mld_s_base_onelev_mat_asb.f90 \ +mld_s_base_onelev_mat_asb.o \ +mld_s_base_onelev_setag.o \ mld_s_base_onelev_setc.o \ mld_s_base_onelev_seti.o \ mld_s_base_onelev_setr.o \ @@ -62,7 +65,8 @@ mld_z_base_onelev_csetr.o \ mld_z_base_onelev_descr.o \ mld_z_base_onelev_dump.o \ mld_z_base_onelev_free.o \ -mld_z_base_onelev_mat_asb.f90 \ +mld_z_base_onelev_mat_asb.o \ +mld_z_base_onelev_setag.o \ mld_z_base_onelev_setc.o \ mld_z_base_onelev_seti.o \ mld_z_base_onelev_setr.o \ diff --git a/mlprec/impl/level/mld_c_base_onelev_mat_asb.f90 b/mlprec/impl/level/mld_c_base_onelev_mat_asb.f90 index a1569265..c9275dc8 100644 --- a/mlprec/impl/level/mld_c_base_onelev_mat_asb.f90 +++ b/mlprec/impl/level/mld_c_base_onelev_mat_asb.f90 @@ -83,11 +83,11 @@ ! info - integer, output. ! Error code. ! -subroutine mld_c_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) +subroutine mld_c_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod use mld_base_prec_type - use mld_c_inner_mod, mld_protect_name => mld_c_onelev_mat_asb + use mld_c_onelev_mod, mld_protect_name => mld_c_base_onelev_mat_asb implicit none @@ -137,7 +137,7 @@ subroutine mld_c_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) ! the mapping defined by mld_aggrmap_bld and applying the aggregation ! algorithm specified by lv%iprcparm(mld_aggr_prol_) ! - call lv%aggr%mat_asb(a,desc_a,ilaggr,nlaggr,lv%parms,ac,op_prol,op_restr,info) + call lv%aggr%mat_asb(lv%parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) if(info /= psb_success_) then call psb_errpush(psb_err_from_subroutine_,name,a_err='mld_aggrmat_asb') @@ -264,4 +264,4 @@ subroutine mld_c_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) 9999 call psb_error_handler(err_act) return -end subroutine mld_c_onelev_mat_asb +end subroutine mld_c_base_onelev_mat_asb diff --git a/mlprec/impl/level/mld_c_base_onelev_setag.f90 b/mlprec/impl/level/mld_c_base_onelev_setag.f90 new file mode 100644 index 00000000..9625b7e9 --- /dev/null +++ b/mlprec/impl/level/mld_c_base_onelev_setag.f90 @@ -0,0 +1,80 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +subroutine mld_c_base_onelev_setag(lev,val,info,pos) + + use psb_base_mod + use mld_c_onelev_mod, mld_protect_name => mld_c_base_onelev_setag + + implicit none + + ! Arguments + class(mld_c_onelev_type), target, intent(inout) :: lev + class(mld_c_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + character(len=*), optional, intent(in) :: pos + + ! Local variables + integer(psb_ipk_) :: ipos_ + character(len=*), parameter :: name='mld_base_onelev_setag' + + info = psb_success_ + + ! Ignore pos for aggregator + + if (allocated(lev%aggr)) then + if (.not.same_type_as(lev%aggr,val)) then + call lev%aggr%free(info) + deallocate(lev%aggr,stat=info) + if (info /= 0) then + info = 3111 + return + end if + end if + end if + + if (.not.allocated(lev%aggr)) then + allocate(lev%aggr,mold=val,stat=info) + if (info /= 0) then + info = 3111 + return + end if + end if + +end subroutine mld_c_base_onelev_setag + diff --git a/mlprec/impl/level/mld_d_base_onelev_mat_asb.f90 b/mlprec/impl/level/mld_d_base_onelev_mat_asb.f90 index d8105c63..84c81147 100644 --- a/mlprec/impl/level/mld_d_base_onelev_mat_asb.f90 +++ b/mlprec/impl/level/mld_d_base_onelev_mat_asb.f90 @@ -83,11 +83,11 @@ ! info - integer, output. ! Error code. ! -subroutine mld_d_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) +subroutine mld_d_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod use mld_base_prec_type - use mld_d_inner_mod, mld_protect_name => mld_d_onelev_mat_asb + use mld_d_onelev_mod, mld_protect_name => mld_d_base_onelev_mat_asb implicit none @@ -137,7 +137,7 @@ subroutine mld_d_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) ! the mapping defined by mld_aggrmap_bld and applying the aggregation ! algorithm specified by lv%iprcparm(mld_aggr_prol_) ! - call lv%aggr%mat_asb(a,desc_a,ilaggr,nlaggr,lv%parms,ac,op_prol,op_restr,info) + call lv%aggr%mat_asb(lv%parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) if(info /= psb_success_) then call psb_errpush(psb_err_from_subroutine_,name,a_err='mld_aggrmat_asb') @@ -264,4 +264,4 @@ subroutine mld_d_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) 9999 call psb_error_handler(err_act) return -end subroutine mld_d_onelev_mat_asb +end subroutine mld_d_base_onelev_mat_asb diff --git a/mlprec/impl/level/mld_d_base_onelev_setag.f90 b/mlprec/impl/level/mld_d_base_onelev_setag.f90 new file mode 100644 index 00000000..1ce8ed51 --- /dev/null +++ b/mlprec/impl/level/mld_d_base_onelev_setag.f90 @@ -0,0 +1,80 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +subroutine mld_d_base_onelev_setag(lev,val,info,pos) + + use psb_base_mod + use mld_d_onelev_mod, mld_protect_name => mld_d_base_onelev_setag + + implicit none + + ! Arguments + class(mld_d_onelev_type), target, intent(inout) :: lev + class(mld_d_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + character(len=*), optional, intent(in) :: pos + + ! Local variables + integer(psb_ipk_) :: ipos_ + character(len=*), parameter :: name='mld_base_onelev_setag' + + info = psb_success_ + + ! Ignore pos for aggregator + + if (allocated(lev%aggr)) then + if (.not.same_type_as(lev%aggr,val)) then + call lev%aggr%free(info) + deallocate(lev%aggr,stat=info) + if (info /= 0) then + info = 3111 + return + end if + end if + end if + + if (.not.allocated(lev%aggr)) then + allocate(lev%aggr,mold=val,stat=info) + if (info /= 0) then + info = 3111 + return + end if + end if + +end subroutine mld_d_base_onelev_setag + diff --git a/mlprec/impl/level/mld_s_base_onelev_mat_asb.f90 b/mlprec/impl/level/mld_s_base_onelev_mat_asb.f90 index 13b43e42..1e56b3f8 100644 --- a/mlprec/impl/level/mld_s_base_onelev_mat_asb.f90 +++ b/mlprec/impl/level/mld_s_base_onelev_mat_asb.f90 @@ -83,11 +83,11 @@ ! info - integer, output. ! Error code. ! -subroutine mld_s_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) +subroutine mld_s_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod use mld_base_prec_type - use mld_s_inner_mod, mld_protect_name => mld_s_onelev_mat_asb + use mld_s_onelev_mod, mld_protect_name => mld_s_base_onelev_mat_asb implicit none @@ -137,7 +137,7 @@ subroutine mld_s_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) ! the mapping defined by mld_aggrmap_bld and applying the aggregation ! algorithm specified by lv%iprcparm(mld_aggr_prol_) ! - call lv%aggr%mat_asb(a,desc_a,ilaggr,nlaggr,lv%parms,ac,op_prol,op_restr,info) + call lv%aggr%mat_asb(lv%parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) if(info /= psb_success_) then call psb_errpush(psb_err_from_subroutine_,name,a_err='mld_aggrmat_asb') @@ -264,4 +264,4 @@ subroutine mld_s_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) 9999 call psb_error_handler(err_act) return -end subroutine mld_s_onelev_mat_asb +end subroutine mld_s_base_onelev_mat_asb diff --git a/mlprec/impl/level/mld_s_base_onelev_setag.f90 b/mlprec/impl/level/mld_s_base_onelev_setag.f90 new file mode 100644 index 00000000..3c78aef1 --- /dev/null +++ b/mlprec/impl/level/mld_s_base_onelev_setag.f90 @@ -0,0 +1,80 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +subroutine mld_s_base_onelev_setag(lev,val,info,pos) + + use psb_base_mod + use mld_s_onelev_mod, mld_protect_name => mld_s_base_onelev_setag + + implicit none + + ! Arguments + class(mld_s_onelev_type), target, intent(inout) :: lev + class(mld_s_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + character(len=*), optional, intent(in) :: pos + + ! Local variables + integer(psb_ipk_) :: ipos_ + character(len=*), parameter :: name='mld_base_onelev_setag' + + info = psb_success_ + + ! Ignore pos for aggregator + + if (allocated(lev%aggr)) then + if (.not.same_type_as(lev%aggr,val)) then + call lev%aggr%free(info) + deallocate(lev%aggr,stat=info) + if (info /= 0) then + info = 3111 + return + end if + end if + end if + + if (.not.allocated(lev%aggr)) then + allocate(lev%aggr,mold=val,stat=info) + if (info /= 0) then + info = 3111 + return + end if + end if + +end subroutine mld_s_base_onelev_setag + diff --git a/mlprec/impl/level/mld_z_base_onelev_mat_asb.f90 b/mlprec/impl/level/mld_z_base_onelev_mat_asb.f90 index 62e58069..9ddc6749 100644 --- a/mlprec/impl/level/mld_z_base_onelev_mat_asb.f90 +++ b/mlprec/impl/level/mld_z_base_onelev_mat_asb.f90 @@ -83,11 +83,11 @@ ! info - integer, output. ! Error code. ! -subroutine mld_z_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) +subroutine mld_z_base_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod use mld_base_prec_type - use mld_z_inner_mod, mld_protect_name => mld_z_onelev_mat_asb + use mld_z_onelev_mod, mld_protect_name => mld_z_base_onelev_mat_asb implicit none @@ -137,7 +137,7 @@ subroutine mld_z_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) ! the mapping defined by mld_aggrmap_bld and applying the aggregation ! algorithm specified by lv%iprcparm(mld_aggr_prol_) ! - call lv%aggr%mat_asb(a,desc_a,ilaggr,nlaggr,lv%parms,ac,op_prol,op_restr,info) + call lv%aggr%mat_asb(lv%parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) if(info /= psb_success_) then call psb_errpush(psb_err_from_subroutine_,name,a_err='mld_aggrmat_asb') @@ -264,4 +264,4 @@ subroutine mld_z_onelev_mat_asb(lv,a,desc_a,ilaggr,nlaggr,op_prol,info) 9999 call psb_error_handler(err_act) return -end subroutine mld_z_onelev_mat_asb +end subroutine mld_z_base_onelev_mat_asb diff --git a/mlprec/impl/level/mld_z_base_onelev_setag.f90 b/mlprec/impl/level/mld_z_base_onelev_setag.f90 new file mode 100644 index 00000000..c69bb47a --- /dev/null +++ b/mlprec/impl/level/mld_z_base_onelev_setag.f90 @@ -0,0 +1,80 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +subroutine mld_z_base_onelev_setag(lev,val,info,pos) + + use psb_base_mod + use mld_z_onelev_mod, mld_protect_name => mld_z_base_onelev_setag + + implicit none + + ! Arguments + class(mld_z_onelev_type), target, intent(inout) :: lev + class(mld_z_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + character(len=*), optional, intent(in) :: pos + + ! Local variables + integer(psb_ipk_) :: ipos_ + character(len=*), parameter :: name='mld_base_onelev_setag' + + info = psb_success_ + + ! Ignore pos for aggregator + + if (allocated(lev%aggr)) then + if (.not.same_type_as(lev%aggr,val)) then + call lev%aggr%free(info) + deallocate(lev%aggr,stat=info) + if (info /= 0) then + info = 3111 + return + end if + end if + end if + + if (.not.allocated(lev%aggr)) then + allocate(lev%aggr,mold=val,stat=info) + if (info /= 0) then + info = 3111 + return + end if + end if + +end subroutine mld_z_base_onelev_setag + diff --git a/mlprec/impl/mld_cprecset.F90 b/mlprec/impl/mld_cprecset.F90 index d6f8c468..f785c6b7 100644 --- a/mlprec/impl/mld_cprecset.F90 +++ b/mlprec/impl/mld_cprecset.F90 @@ -542,6 +542,70 @@ subroutine mld_cprecsetsv(p,val,info,ilev,ilmax,pos) end subroutine mld_cprecsetsv +subroutine mld_cprecsetag(p,val,info,ilev,ilmax,pos) + + use psb_base_mod + use mld_c_prec_mod, mld_protect_name => mld_cprecsetag + + implicit none + + ! Arguments + class(mld_cprec_type), intent(inout) :: p + class(mld_c_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), optional, intent(in) :: ilev, ilmax + character(len=*), optional, intent(in) :: pos + + ! Local variables + integer(psb_ipk_) :: ilev_, nlev_, ilmin_, ilmax_ + character(len=*), parameter :: name='mld_precsetag' + + info = psb_success_ + + if (.not.allocated(p%precv)) then + info = 3111 + write(psb_err_unit,*) name,& + & ': Error: uninitialized preconditioner,',& + &' should call MLD_PRECINIT' + return + endif + nlev_ = size(p%precv) + + if (present(ilev)) then + ilev_ = ilev + ilmin_ = ilev + if (present(ilmax)) then + ilmax_ = ilmax + else + ilmax_ = ilev_ + end if + else + ilev_ = 1 + ilmin_ = 1 + ilmax_ = nlev_ + end if + + + if ((ilev_<1).or.(ilev_ > nlev_)) then + info = -1 + write(psb_err_unit,*) name,& + & ': Error: invalid ILEV/NLEV combination',ilev_, nlev_ + return + endif + if ((ilmax_<1).or.(ilmax_ > nlev_)) then + info = -1 + write(psb_err_unit,*) name,& + &': Error: invalid ILMAX/NLEV combination',ilmax_, nlev_ + return + endif + + do ilev_ = ilmin_, ilmax_ + call p%precv(ilev_)%set(val,info,pos=pos) + if (info /= 0) return + end do + +end subroutine mld_cprecsetag + ! ! Subroutine: mld_cprecsetc ! Version: complex diff --git a/mlprec/impl/mld_dprecset.F90 b/mlprec/impl/mld_dprecset.F90 index da732be5..8dfaa034 100644 --- a/mlprec/impl/mld_dprecset.F90 +++ b/mlprec/impl/mld_dprecset.F90 @@ -575,6 +575,70 @@ subroutine mld_dprecsetsv(p,val,info,ilev,ilmax,pos) end subroutine mld_dprecsetsv +subroutine mld_dprecsetag(p,val,info,ilev,ilmax,pos) + + use psb_base_mod + use mld_d_prec_mod, mld_protect_name => mld_dprecsetag + + implicit none + + ! Arguments + class(mld_dprec_type), intent(inout) :: p + class(mld_d_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), optional, intent(in) :: ilev, ilmax + character(len=*), optional, intent(in) :: pos + + ! Local variables + integer(psb_ipk_) :: ilev_, nlev_, ilmin_, ilmax_ + character(len=*), parameter :: name='mld_precsetag' + + info = psb_success_ + + if (.not.allocated(p%precv)) then + info = 3111 + write(psb_err_unit,*) name,& + & ': Error: uninitialized preconditioner,',& + &' should call MLD_PRECINIT' + return + endif + nlev_ = size(p%precv) + + if (present(ilev)) then + ilev_ = ilev + ilmin_ = ilev + if (present(ilmax)) then + ilmax_ = ilmax + else + ilmax_ = ilev_ + end if + else + ilev_ = 1 + ilmin_ = 1 + ilmax_ = nlev_ + end if + + + if ((ilev_<1).or.(ilev_ > nlev_)) then + info = -1 + write(psb_err_unit,*) name,& + & ': Error: invalid ILEV/NLEV combination',ilev_, nlev_ + return + endif + if ((ilmax_<1).or.(ilmax_ > nlev_)) then + info = -1 + write(psb_err_unit,*) name,& + &': Error: invalid ILMAX/NLEV combination',ilmax_, nlev_ + return + endif + + do ilev_ = ilmin_, ilmax_ + call p%precv(ilev_)%set(val,info,pos=pos) + if (info /= 0) return + end do + +end subroutine mld_dprecsetag + ! ! Subroutine: mld_dprecsetc ! Version: real diff --git a/mlprec/impl/mld_sprecset.F90 b/mlprec/impl/mld_sprecset.F90 index 30e6cc02..90752348 100644 --- a/mlprec/impl/mld_sprecset.F90 +++ b/mlprec/impl/mld_sprecset.F90 @@ -542,6 +542,70 @@ subroutine mld_sprecsetsv(p,val,info,ilev,ilmax,pos) end subroutine mld_sprecsetsv +subroutine mld_sprecsetag(p,val,info,ilev,ilmax,pos) + + use psb_base_mod + use mld_s_prec_mod, mld_protect_name => mld_sprecsetag + + implicit none + + ! Arguments + class(mld_sprec_type), intent(inout) :: p + class(mld_s_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), optional, intent(in) :: ilev, ilmax + character(len=*), optional, intent(in) :: pos + + ! Local variables + integer(psb_ipk_) :: ilev_, nlev_, ilmin_, ilmax_ + character(len=*), parameter :: name='mld_precsetag' + + info = psb_success_ + + if (.not.allocated(p%precv)) then + info = 3111 + write(psb_err_unit,*) name,& + & ': Error: uninitialized preconditioner,',& + &' should call MLD_PRECINIT' + return + endif + nlev_ = size(p%precv) + + if (present(ilev)) then + ilev_ = ilev + ilmin_ = ilev + if (present(ilmax)) then + ilmax_ = ilmax + else + ilmax_ = ilev_ + end if + else + ilev_ = 1 + ilmin_ = 1 + ilmax_ = nlev_ + end if + + + if ((ilev_<1).or.(ilev_ > nlev_)) then + info = -1 + write(psb_err_unit,*) name,& + & ': Error: invalid ILEV/NLEV combination',ilev_, nlev_ + return + endif + if ((ilmax_<1).or.(ilmax_ > nlev_)) then + info = -1 + write(psb_err_unit,*) name,& + &': Error: invalid ILMAX/NLEV combination',ilmax_, nlev_ + return + endif + + do ilev_ = ilmin_, ilmax_ + call p%precv(ilev_)%set(val,info,pos=pos) + if (info /= 0) return + end do + +end subroutine mld_sprecsetag + ! ! Subroutine: mld_sprecsetc ! Version: real diff --git a/mlprec/impl/mld_zprecset.F90 b/mlprec/impl/mld_zprecset.F90 index 3d1e7eb8..a3f74cad 100644 --- a/mlprec/impl/mld_zprecset.F90 +++ b/mlprec/impl/mld_zprecset.F90 @@ -575,6 +575,70 @@ subroutine mld_zprecsetsv(p,val,info,ilev,ilmax,pos) end subroutine mld_zprecsetsv +subroutine mld_zprecsetag(p,val,info,ilev,ilmax,pos) + + use psb_base_mod + use mld_z_prec_mod, mld_protect_name => mld_zprecsetag + + implicit none + + ! Arguments + class(mld_zprec_type), intent(inout) :: p + class(mld_z_base_aggregator_type), intent(in) :: val + integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), optional, intent(in) :: ilev, ilmax + character(len=*), optional, intent(in) :: pos + + ! Local variables + integer(psb_ipk_) :: ilev_, nlev_, ilmin_, ilmax_ + character(len=*), parameter :: name='mld_precsetag' + + info = psb_success_ + + if (.not.allocated(p%precv)) then + info = 3111 + write(psb_err_unit,*) name,& + & ': Error: uninitialized preconditioner,',& + &' should call MLD_PRECINIT' + return + endif + nlev_ = size(p%precv) + + if (present(ilev)) then + ilev_ = ilev + ilmin_ = ilev + if (present(ilmax)) then + ilmax_ = ilmax + else + ilmax_ = ilev_ + end if + else + ilev_ = 1 + ilmin_ = 1 + ilmax_ = nlev_ + end if + + + if ((ilev_<1).or.(ilev_ > nlev_)) then + info = -1 + write(psb_err_unit,*) name,& + & ': Error: invalid ILEV/NLEV combination',ilev_, nlev_ + return + endif + if ((ilmax_<1).or.(ilmax_ > nlev_)) then + info = -1 + write(psb_err_unit,*) name,& + &': Error: invalid ILMAX/NLEV combination',ilmax_, nlev_ + return + endif + + do ilev_ = ilmin_, ilmax_ + call p%precv(ilev_)%set(val,info,pos=pos) + if (info /= 0) return + end do + +end subroutine mld_zprecsetag + ! ! Subroutine: mld_zprecsetc ! Version: complex From ef5256b3b4ba04b3c8788f62893c6245caaff317 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Sat, 5 May 2018 08:09:25 +0100 Subject: [PATCH 16/33] Updated version number in headers. --- LICENSE | 2 +- examples/fileread/data_input.f90 | 2 +- examples/fileread/mld_cexample_1lev.f90 | 2 +- examples/fileread/mld_cexample_ml.f90 | 2 +- examples/fileread/mld_dexample_1lev.f90 | 2 +- examples/fileread/mld_dexample_ml.f90 | 2 +- examples/fileread/mld_sexample_1lev.f90 | 2 +- examples/fileread/mld_sexample_ml.f90 | 2 +- examples/fileread/mld_zexample_1lev.f90 | 2 +- examples/fileread/mld_zexample_ml.f90 | 2 +- examples/pdegen/data_input.f90 | 2 +- examples/pdegen/mld_dexample_1lev.f90 | 2 +- examples/pdegen/mld_dexample_ml.f90 | 2 +- examples/pdegen/mld_dpde_mod.f90 | 2 +- examples/pdegen/mld_sexample_1lev.f90 | 2 +- examples/pdegen/mld_sexample_ml.f90 | 2 +- examples/pdegen/mld_spde_mod.f90 | 2 +- .../aggregator/mld_c_base_aggregator_mat_asb.f90 | 11 +++++------ .../aggregator/mld_c_base_aggregator_tprol.f90 | 12 +++++------- mlprec/impl/aggregator/mld_c_dec_map_bld.f90 | 2 +- mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 | 2 +- .../aggregator/mld_c_hybrid_aggregator_tprol.f90 | 12 ++++++------ mlprec/impl/aggregator/mld_c_map_to_tprol.f90 | 14 +++++++------- .../aggregator/mld_c_symdec_aggregator_tprol.f90 | 11 +++++------ mlprec/impl/aggregator/mld_caggrmat_biz_asb.f90 | 2 +- mlprec/impl/aggregator/mld_caggrmat_minnrg_asb.f90 | 2 +- mlprec/impl/aggregator/mld_caggrmat_nosmth_asb.f90 | 2 +- mlprec/impl/aggregator/mld_caggrmat_smth_asb.f90 | 2 +- .../aggregator/mld_d_base_aggregator_mat_asb.f90 | 11 +++++------ .../aggregator/mld_d_base_aggregator_tprol.f90 | 12 +++++------- mlprec/impl/aggregator/mld_d_dec_map_bld.f90 | 2 +- mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 | 2 +- .../aggregator/mld_d_hybrid_aggregator_tprol.f90 | 12 ++++++------ mlprec/impl/aggregator/mld_d_map_to_tprol.f90 | 14 +++++++------- .../aggregator/mld_d_symdec_aggregator_tprol.f90 | 11 +++++------ mlprec/impl/aggregator/mld_daggrmat_biz_asb.f90 | 2 +- mlprec/impl/aggregator/mld_daggrmat_minnrg_asb.f90 | 2 +- mlprec/impl/aggregator/mld_daggrmat_nosmth_asb.f90 | 2 +- mlprec/impl/aggregator/mld_daggrmat_smth_asb.f90 | 2 +- .../aggregator/mld_s_base_aggregator_mat_asb.f90 | 11 +++++------ .../aggregator/mld_s_base_aggregator_tprol.f90 | 12 +++++------- mlprec/impl/aggregator/mld_s_dec_map_bld.f90 | 2 +- mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 | 2 +- .../aggregator/mld_s_hybrid_aggregator_tprol.f90 | 12 ++++++------ mlprec/impl/aggregator/mld_s_map_to_tprol.f90 | 14 +++++++------- .../aggregator/mld_s_symdec_aggregator_tprol.f90 | 11 +++++------ mlprec/impl/aggregator/mld_saggrmat_biz_asb.f90 | 2 +- mlprec/impl/aggregator/mld_saggrmat_minnrg_asb.f90 | 2 +- mlprec/impl/aggregator/mld_saggrmat_nosmth_asb.f90 | 2 +- mlprec/impl/aggregator/mld_saggrmat_smth_asb.f90 | 2 +- .../aggregator/mld_z_base_aggregator_mat_asb.f90 | 11 +++++------ .../aggregator/mld_z_base_aggregator_tprol.f90 | 12 +++++------- mlprec/impl/aggregator/mld_z_dec_map_bld.f90 | 2 +- mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 | 2 +- .../aggregator/mld_z_hybrid_aggregator_tprol.f90 | 12 ++++++------ mlprec/impl/aggregator/mld_z_map_to_tprol.f90 | 14 +++++++------- .../aggregator/mld_z_symdec_aggregator_tprol.f90 | 11 +++++------ mlprec/impl/aggregator/mld_zaggrmat_biz_asb.f90 | 2 +- mlprec/impl/aggregator/mld_zaggrmat_minnrg_asb.f90 | 2 +- mlprec/impl/aggregator/mld_zaggrmat_nosmth_asb.f90 | 2 +- mlprec/impl/aggregator/mld_zaggrmat_smth_asb.f90 | 2 +- mlprec/impl/level/mld_c_base_onelev_build.f90 | 2 +- mlprec/impl/level/mld_c_base_onelev_check.f90 | 2 +- mlprec/impl/level/mld_c_base_onelev_cnv.f90 | 2 +- mlprec/impl/level/mld_c_base_onelev_csetc.f90 | 2 +- mlprec/impl/level/mld_c_base_onelev_cseti.F90 | 2 +- mlprec/impl/level/mld_c_base_onelev_csetr.f90 | 2 +- mlprec/impl/level/mld_c_base_onelev_descr.f90 | 2 +- mlprec/impl/level/mld_c_base_onelev_dump.f90 | 2 +- mlprec/impl/level/mld_c_base_onelev_free.f90 | 2 +- mlprec/impl/level/mld_c_base_onelev_mat_asb.f90 | 2 +- mlprec/impl/level/mld_c_base_onelev_setag.f90 | 11 +++++------ mlprec/impl/level/mld_c_base_onelev_setc.f90 | 2 +- mlprec/impl/level/mld_c_base_onelev_seti.F90 | 2 +- mlprec/impl/level/mld_c_base_onelev_setr.f90 | 2 +- mlprec/impl/level/mld_c_base_onelev_setsm.F90 | 2 +- mlprec/impl/level/mld_c_base_onelev_setsv.F90 | 2 +- mlprec/impl/level/mld_d_base_onelev_build.f90 | 2 +- mlprec/impl/level/mld_d_base_onelev_check.f90 | 2 +- mlprec/impl/level/mld_d_base_onelev_cnv.f90 | 2 +- mlprec/impl/level/mld_d_base_onelev_csetc.f90 | 2 +- mlprec/impl/level/mld_d_base_onelev_cseti.F90 | 2 +- mlprec/impl/level/mld_d_base_onelev_csetr.f90 | 2 +- mlprec/impl/level/mld_d_base_onelev_descr.f90 | 2 +- mlprec/impl/level/mld_d_base_onelev_dump.f90 | 2 +- mlprec/impl/level/mld_d_base_onelev_free.f90 | 2 +- mlprec/impl/level/mld_d_base_onelev_mat_asb.f90 | 2 +- mlprec/impl/level/mld_d_base_onelev_setag.f90 | 11 +++++------ mlprec/impl/level/mld_d_base_onelev_setc.f90 | 2 +- mlprec/impl/level/mld_d_base_onelev_seti.F90 | 2 +- mlprec/impl/level/mld_d_base_onelev_setr.f90 | 2 +- mlprec/impl/level/mld_d_base_onelev_setsm.F90 | 2 +- mlprec/impl/level/mld_d_base_onelev_setsv.F90 | 2 +- mlprec/impl/level/mld_s_base_onelev_build.f90 | 2 +- mlprec/impl/level/mld_s_base_onelev_check.f90 | 2 +- mlprec/impl/level/mld_s_base_onelev_cnv.f90 | 2 +- mlprec/impl/level/mld_s_base_onelev_csetc.f90 | 2 +- mlprec/impl/level/mld_s_base_onelev_cseti.F90 | 2 +- mlprec/impl/level/mld_s_base_onelev_csetr.f90 | 2 +- mlprec/impl/level/mld_s_base_onelev_descr.f90 | 2 +- mlprec/impl/level/mld_s_base_onelev_dump.f90 | 2 +- mlprec/impl/level/mld_s_base_onelev_free.f90 | 2 +- mlprec/impl/level/mld_s_base_onelev_mat_asb.f90 | 2 +- mlprec/impl/level/mld_s_base_onelev_setag.f90 | 11 +++++------ mlprec/impl/level/mld_s_base_onelev_setc.f90 | 2 +- mlprec/impl/level/mld_s_base_onelev_seti.F90 | 2 +- mlprec/impl/level/mld_s_base_onelev_setr.f90 | 2 +- mlprec/impl/level/mld_s_base_onelev_setsm.F90 | 2 +- mlprec/impl/level/mld_s_base_onelev_setsv.F90 | 2 +- mlprec/impl/level/mld_z_base_onelev_build.f90 | 2 +- mlprec/impl/level/mld_z_base_onelev_check.f90 | 2 +- mlprec/impl/level/mld_z_base_onelev_cnv.f90 | 2 +- mlprec/impl/level/mld_z_base_onelev_csetc.f90 | 2 +- mlprec/impl/level/mld_z_base_onelev_cseti.F90 | 2 +- mlprec/impl/level/mld_z_base_onelev_csetr.f90 | 2 +- mlprec/impl/level/mld_z_base_onelev_descr.f90 | 2 +- mlprec/impl/level/mld_z_base_onelev_dump.f90 | 2 +- mlprec/impl/level/mld_z_base_onelev_free.f90 | 2 +- mlprec/impl/level/mld_z_base_onelev_mat_asb.f90 | 2 +- mlprec/impl/level/mld_z_base_onelev_setag.f90 | 11 +++++------ mlprec/impl/level/mld_z_base_onelev_setc.f90 | 2 +- mlprec/impl/level/mld_z_base_onelev_seti.F90 | 2 +- mlprec/impl/level/mld_z_base_onelev_setr.f90 | 2 +- mlprec/impl/level/mld_z_base_onelev_setsm.F90 | 2 +- mlprec/impl/level/mld_z_base_onelev_setsv.F90 | 2 +- mlprec/impl/mld_c_extprol_bld.f90 | 8 ++++---- mlprec/impl/mld_c_hierarchy_bld.f90 | 2 +- mlprec/impl/mld_c_smoothers_bld.f90 | 2 +- mlprec/impl/mld_ccprecset.F90 | 2 +- mlprec/impl/mld_cfile_prec_descr.f90 | 2 +- mlprec/impl/mld_cmlprec_aply.f90 | 2 +- mlprec/impl/mld_cmlprec_bld.f90 | 2 +- mlprec/impl/mld_cprecaply.f90 | 2 +- mlprec/impl/mld_cprecbld.f90 | 2 +- mlprec/impl/mld_cprecinit.F90 | 2 +- mlprec/impl/mld_cprecset.F90 | 2 +- mlprec/impl/mld_d_extprol_bld.f90 | 8 ++++---- mlprec/impl/mld_d_hierarchy_bld.f90 | 2 +- mlprec/impl/mld_d_smoothers_bld.f90 | 2 +- mlprec/impl/mld_dcprecset.F90 | 2 +- mlprec/impl/mld_dfile_prec_descr.f90 | 2 +- mlprec/impl/mld_dmlprec_aply.f90 | 2 +- mlprec/impl/mld_dmlprec_bld.f90 | 2 +- mlprec/impl/mld_dprecaply.f90 | 2 +- mlprec/impl/mld_dprecbld.f90 | 2 +- mlprec/impl/mld_dprecinit.F90 | 2 +- mlprec/impl/mld_dprecset.F90 | 2 +- mlprec/impl/mld_s_extprol_bld.f90 | 8 ++++---- mlprec/impl/mld_s_hierarchy_bld.f90 | 2 +- mlprec/impl/mld_s_smoothers_bld.f90 | 2 +- mlprec/impl/mld_scprecset.F90 | 2 +- mlprec/impl/mld_sfile_prec_descr.f90 | 2 +- mlprec/impl/mld_smlprec_aply.f90 | 2 +- mlprec/impl/mld_smlprec_bld.f90 | 2 +- mlprec/impl/mld_sprecaply.f90 | 2 +- mlprec/impl/mld_sprecbld.f90 | 2 +- mlprec/impl/mld_sprecinit.F90 | 2 +- mlprec/impl/mld_sprecset.F90 | 2 +- mlprec/impl/mld_z_extprol_bld.f90 | 8 ++++---- mlprec/impl/mld_z_hierarchy_bld.f90 | 2 +- mlprec/impl/mld_z_smoothers_bld.f90 | 2 +- mlprec/impl/mld_zcprecset.F90 | 2 +- mlprec/impl/mld_zfile_prec_descr.f90 | 2 +- mlprec/impl/mld_zmlprec_aply.f90 | 2 +- mlprec/impl/mld_zmlprec_bld.f90 | 2 +- mlprec/impl/mld_zprecaply.f90 | 2 +- mlprec/impl/mld_zprecbld.f90 | 2 +- mlprec/impl/mld_zprecinit.F90 | 2 +- mlprec/impl/mld_zprecset.F90 | 2 +- mlprec/impl/smoother/mld_c_as_smoother_apply.f90 | 2 +- .../impl/smoother/mld_c_as_smoother_apply_vect.f90 | 2 +- mlprec/impl/smoother/mld_c_as_smoother_bld.f90 | 2 +- mlprec/impl/smoother/mld_c_as_smoother_check.f90 | 2 +- mlprec/impl/smoother/mld_c_as_smoother_clone.f90 | 2 +- mlprec/impl/smoother/mld_c_as_smoother_cnv.f90 | 2 +- mlprec/impl/smoother/mld_c_as_smoother_csetc.f90 | 2 +- mlprec/impl/smoother/mld_c_as_smoother_cseti.f90 | 2 +- mlprec/impl/smoother/mld_c_as_smoother_csetr.f90 | 2 +- mlprec/impl/smoother/mld_c_as_smoother_dmp.f90 | 2 +- mlprec/impl/smoother/mld_c_as_smoother_free.f90 | 2 +- mlprec/impl/smoother/mld_c_as_smoother_prol_a.f90 | 2 +- mlprec/impl/smoother/mld_c_as_smoother_prol_v.f90 | 2 +- mlprec/impl/smoother/mld_c_as_smoother_restr_a.f90 | 2 +- mlprec/impl/smoother/mld_c_as_smoother_restr_v.f90 | 2 +- mlprec/impl/smoother/mld_c_as_smoother_setc.f90 | 2 +- mlprec/impl/smoother/mld_c_as_smoother_seti.f90 | 2 +- mlprec/impl/smoother/mld_c_as_smoother_setr.f90 | 2 +- mlprec/impl/smoother/mld_c_base_smoother_apply.f90 | 2 +- .../smoother/mld_c_base_smoother_apply_vect.f90 | 2 +- mlprec/impl/smoother/mld_c_base_smoother_bld.f90 | 2 +- mlprec/impl/smoother/mld_c_base_smoother_check.f90 | 2 +- mlprec/impl/smoother/mld_c_base_smoother_clone.f90 | 2 +- mlprec/impl/smoother/mld_c_base_smoother_cnv.f90 | 2 +- mlprec/impl/smoother/mld_c_base_smoother_csetc.f90 | 2 +- mlprec/impl/smoother/mld_c_base_smoother_cseti.f90 | 2 +- mlprec/impl/smoother/mld_c_base_smoother_csetr.f90 | 2 +- mlprec/impl/smoother/mld_c_base_smoother_descr.f90 | 2 +- mlprec/impl/smoother/mld_c_base_smoother_dmp.f90 | 2 +- mlprec/impl/smoother/mld_c_base_smoother_free.f90 | 2 +- mlprec/impl/smoother/mld_c_base_smoother_setc.f90 | 2 +- mlprec/impl/smoother/mld_c_base_smoother_seti.f90 | 2 +- mlprec/impl/smoother/mld_c_base_smoother_setr.f90 | 2 +- mlprec/impl/smoother/mld_c_jac_smoother_apply.f90 | 2 +- .../smoother/mld_c_jac_smoother_apply_vect.f90 | 2 +- mlprec/impl/smoother/mld_c_jac_smoother_bld.f90 | 2 +- mlprec/impl/smoother/mld_c_jac_smoother_clone.f90 | 2 +- mlprec/impl/smoother/mld_c_jac_smoother_cnv.f90 | 2 +- mlprec/impl/smoother/mld_c_jac_smoother_descr.f90 | 2 +- mlprec/impl/smoother/mld_c_jac_smoother_dmp.f90 | 2 +- mlprec/impl/smoother/mld_d_as_smoother_apply.f90 | 2 +- .../impl/smoother/mld_d_as_smoother_apply_vect.f90 | 2 +- mlprec/impl/smoother/mld_d_as_smoother_bld.f90 | 2 +- mlprec/impl/smoother/mld_d_as_smoother_check.f90 | 2 +- mlprec/impl/smoother/mld_d_as_smoother_clone.f90 | 2 +- mlprec/impl/smoother/mld_d_as_smoother_cnv.f90 | 2 +- mlprec/impl/smoother/mld_d_as_smoother_csetc.f90 | 2 +- mlprec/impl/smoother/mld_d_as_smoother_cseti.f90 | 2 +- mlprec/impl/smoother/mld_d_as_smoother_csetr.f90 | 2 +- mlprec/impl/smoother/mld_d_as_smoother_dmp.f90 | 2 +- mlprec/impl/smoother/mld_d_as_smoother_free.f90 | 2 +- mlprec/impl/smoother/mld_d_as_smoother_prol_a.f90 | 2 +- mlprec/impl/smoother/mld_d_as_smoother_prol_v.f90 | 2 +- mlprec/impl/smoother/mld_d_as_smoother_restr_a.f90 | 2 +- mlprec/impl/smoother/mld_d_as_smoother_restr_v.f90 | 2 +- mlprec/impl/smoother/mld_d_as_smoother_setc.f90 | 2 +- mlprec/impl/smoother/mld_d_as_smoother_seti.f90 | 2 +- mlprec/impl/smoother/mld_d_as_smoother_setr.f90 | 2 +- mlprec/impl/smoother/mld_d_base_smoother_apply.f90 | 2 +- .../smoother/mld_d_base_smoother_apply_vect.f90 | 2 +- mlprec/impl/smoother/mld_d_base_smoother_bld.f90 | 2 +- mlprec/impl/smoother/mld_d_base_smoother_check.f90 | 2 +- mlprec/impl/smoother/mld_d_base_smoother_clone.f90 | 2 +- mlprec/impl/smoother/mld_d_base_smoother_cnv.f90 | 2 +- mlprec/impl/smoother/mld_d_base_smoother_csetc.f90 | 2 +- mlprec/impl/smoother/mld_d_base_smoother_cseti.f90 | 2 +- mlprec/impl/smoother/mld_d_base_smoother_csetr.f90 | 2 +- mlprec/impl/smoother/mld_d_base_smoother_descr.f90 | 2 +- mlprec/impl/smoother/mld_d_base_smoother_dmp.f90 | 2 +- mlprec/impl/smoother/mld_d_base_smoother_free.f90 | 2 +- mlprec/impl/smoother/mld_d_base_smoother_setc.f90 | 2 +- mlprec/impl/smoother/mld_d_base_smoother_seti.f90 | 2 +- mlprec/impl/smoother/mld_d_base_smoother_setr.f90 | 2 +- mlprec/impl/smoother/mld_d_jac_smoother_apply.f90 | 2 +- .../smoother/mld_d_jac_smoother_apply_vect.f90 | 2 +- mlprec/impl/smoother/mld_d_jac_smoother_bld.f90 | 2 +- mlprec/impl/smoother/mld_d_jac_smoother_clone.f90 | 2 +- mlprec/impl/smoother/mld_d_jac_smoother_cnv.f90 | 2 +- mlprec/impl/smoother/mld_d_jac_smoother_descr.f90 | 2 +- mlprec/impl/smoother/mld_d_jac_smoother_dmp.f90 | 2 +- mlprec/impl/smoother/mld_s_as_smoother_apply.f90 | 2 +- .../impl/smoother/mld_s_as_smoother_apply_vect.f90 | 2 +- mlprec/impl/smoother/mld_s_as_smoother_bld.f90 | 2 +- mlprec/impl/smoother/mld_s_as_smoother_check.f90 | 2 +- mlprec/impl/smoother/mld_s_as_smoother_clone.f90 | 2 +- mlprec/impl/smoother/mld_s_as_smoother_cnv.f90 | 2 +- mlprec/impl/smoother/mld_s_as_smoother_csetc.f90 | 2 +- mlprec/impl/smoother/mld_s_as_smoother_cseti.f90 | 2 +- mlprec/impl/smoother/mld_s_as_smoother_csetr.f90 | 2 +- mlprec/impl/smoother/mld_s_as_smoother_dmp.f90 | 2 +- mlprec/impl/smoother/mld_s_as_smoother_free.f90 | 2 +- mlprec/impl/smoother/mld_s_as_smoother_prol_a.f90 | 2 +- mlprec/impl/smoother/mld_s_as_smoother_prol_v.f90 | 2 +- mlprec/impl/smoother/mld_s_as_smoother_restr_a.f90 | 2 +- mlprec/impl/smoother/mld_s_as_smoother_restr_v.f90 | 2 +- mlprec/impl/smoother/mld_s_as_smoother_setc.f90 | 2 +- mlprec/impl/smoother/mld_s_as_smoother_seti.f90 | 2 +- mlprec/impl/smoother/mld_s_as_smoother_setr.f90 | 2 +- mlprec/impl/smoother/mld_s_base_smoother_apply.f90 | 2 +- .../smoother/mld_s_base_smoother_apply_vect.f90 | 2 +- mlprec/impl/smoother/mld_s_base_smoother_bld.f90 | 2 +- mlprec/impl/smoother/mld_s_base_smoother_check.f90 | 2 +- mlprec/impl/smoother/mld_s_base_smoother_clone.f90 | 2 +- mlprec/impl/smoother/mld_s_base_smoother_cnv.f90 | 2 +- mlprec/impl/smoother/mld_s_base_smoother_csetc.f90 | 2 +- mlprec/impl/smoother/mld_s_base_smoother_cseti.f90 | 2 +- mlprec/impl/smoother/mld_s_base_smoother_csetr.f90 | 2 +- mlprec/impl/smoother/mld_s_base_smoother_descr.f90 | 2 +- mlprec/impl/smoother/mld_s_base_smoother_dmp.f90 | 2 +- mlprec/impl/smoother/mld_s_base_smoother_free.f90 | 2 +- mlprec/impl/smoother/mld_s_base_smoother_setc.f90 | 2 +- mlprec/impl/smoother/mld_s_base_smoother_seti.f90 | 2 +- mlprec/impl/smoother/mld_s_base_smoother_setr.f90 | 2 +- mlprec/impl/smoother/mld_s_jac_smoother_apply.f90 | 2 +- .../smoother/mld_s_jac_smoother_apply_vect.f90 | 2 +- mlprec/impl/smoother/mld_s_jac_smoother_bld.f90 | 2 +- mlprec/impl/smoother/mld_s_jac_smoother_clone.f90 | 2 +- mlprec/impl/smoother/mld_s_jac_smoother_cnv.f90 | 2 +- mlprec/impl/smoother/mld_s_jac_smoother_descr.f90 | 2 +- mlprec/impl/smoother/mld_s_jac_smoother_dmp.f90 | 2 +- mlprec/impl/smoother/mld_z_as_smoother_apply.f90 | 2 +- .../impl/smoother/mld_z_as_smoother_apply_vect.f90 | 2 +- mlprec/impl/smoother/mld_z_as_smoother_bld.f90 | 2 +- mlprec/impl/smoother/mld_z_as_smoother_check.f90 | 2 +- mlprec/impl/smoother/mld_z_as_smoother_clone.f90 | 2 +- mlprec/impl/smoother/mld_z_as_smoother_cnv.f90 | 2 +- mlprec/impl/smoother/mld_z_as_smoother_csetc.f90 | 2 +- mlprec/impl/smoother/mld_z_as_smoother_cseti.f90 | 2 +- mlprec/impl/smoother/mld_z_as_smoother_csetr.f90 | 2 +- mlprec/impl/smoother/mld_z_as_smoother_dmp.f90 | 2 +- mlprec/impl/smoother/mld_z_as_smoother_free.f90 | 2 +- mlprec/impl/smoother/mld_z_as_smoother_prol_a.f90 | 2 +- mlprec/impl/smoother/mld_z_as_smoother_prol_v.f90 | 2 +- mlprec/impl/smoother/mld_z_as_smoother_restr_a.f90 | 2 +- mlprec/impl/smoother/mld_z_as_smoother_restr_v.f90 | 2 +- mlprec/impl/smoother/mld_z_as_smoother_setc.f90 | 2 +- mlprec/impl/smoother/mld_z_as_smoother_seti.f90 | 2 +- mlprec/impl/smoother/mld_z_as_smoother_setr.f90 | 2 +- mlprec/impl/smoother/mld_z_base_smoother_apply.f90 | 2 +- .../smoother/mld_z_base_smoother_apply_vect.f90 | 2 +- mlprec/impl/smoother/mld_z_base_smoother_bld.f90 | 2 +- mlprec/impl/smoother/mld_z_base_smoother_check.f90 | 2 +- mlprec/impl/smoother/mld_z_base_smoother_clone.f90 | 2 +- mlprec/impl/smoother/mld_z_base_smoother_cnv.f90 | 2 +- mlprec/impl/smoother/mld_z_base_smoother_csetc.f90 | 2 +- mlprec/impl/smoother/mld_z_base_smoother_cseti.f90 | 2 +- mlprec/impl/smoother/mld_z_base_smoother_csetr.f90 | 2 +- mlprec/impl/smoother/mld_z_base_smoother_descr.f90 | 2 +- mlprec/impl/smoother/mld_z_base_smoother_dmp.f90 | 2 +- mlprec/impl/smoother/mld_z_base_smoother_free.f90 | 2 +- mlprec/impl/smoother/mld_z_base_smoother_setc.f90 | 2 +- mlprec/impl/smoother/mld_z_base_smoother_seti.f90 | 2 +- mlprec/impl/smoother/mld_z_base_smoother_setr.f90 | 2 +- mlprec/impl/smoother/mld_z_jac_smoother_apply.f90 | 2 +- .../smoother/mld_z_jac_smoother_apply_vect.f90 | 2 +- mlprec/impl/smoother/mld_z_jac_smoother_bld.f90 | 2 +- mlprec/impl/smoother/mld_z_jac_smoother_clone.f90 | 2 +- mlprec/impl/smoother/mld_z_jac_smoother_cnv.f90 | 2 +- mlprec/impl/smoother/mld_z_jac_smoother_descr.f90 | 2 +- mlprec/impl/smoother/mld_z_jac_smoother_dmp.f90 | 2 +- mlprec/impl/solver/mld_c_base_solver_apply.f90 | 2 +- .../impl/solver/mld_c_base_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_c_base_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_c_base_solver_check.f90 | 2 +- mlprec/impl/solver/mld_c_base_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_c_base_solver_cnv.f90 | 2 +- mlprec/impl/solver/mld_c_base_solver_csetc.f90 | 2 +- mlprec/impl/solver/mld_c_base_solver_cseti.f90 | 2 +- mlprec/impl/solver/mld_c_base_solver_csetr.f90 | 2 +- mlprec/impl/solver/mld_c_base_solver_descr.f90 | 2 +- mlprec/impl/solver/mld_c_base_solver_dmp.f90 | 2 +- mlprec/impl/solver/mld_c_base_solver_free.f90 | 2 +- mlprec/impl/solver/mld_c_base_solver_setc.f90 | 2 +- mlprec/impl/solver/mld_c_base_solver_seti.f90 | 2 +- mlprec/impl/solver/mld_c_base_solver_setr.f90 | 2 +- mlprec/impl/solver/mld_c_bwgs_solver_apply.f90 | 2 +- .../impl/solver/mld_c_bwgs_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_c_bwgs_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_c_diag_solver_apply.f90 | 2 +- .../impl/solver/mld_c_diag_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_c_diag_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_c_diag_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_c_diag_solver_cnv.f90 | 2 +- mlprec/impl/solver/mld_c_diag_solver_dmp.f90 | 2 +- mlprec/impl/solver/mld_c_gs_solver_apply.f90 | 2 +- mlprec/impl/solver/mld_c_gs_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_c_gs_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_c_gs_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_c_gs_solver_cnv.f90 | 2 +- mlprec/impl/solver/mld_c_gs_solver_dmp.f90 | 2 +- mlprec/impl/solver/mld_c_id_solver_apply.f90 | 2 +- mlprec/impl/solver/mld_c_id_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_c_id_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_c_ilu_solver_apply.f90 | 2 +- mlprec/impl/solver/mld_c_ilu_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_c_ilu_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_c_ilu_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_c_ilu_solver_cnv.f90 | 2 +- mlprec/impl/solver/mld_c_ilu_solver_dmp.f90 | 2 +- mlprec/impl/solver/mld_c_mumps_solver_apply.F90 | 2 +- .../impl/solver/mld_c_mumps_solver_apply_vect.F90 | 2 +- mlprec/impl/solver/mld_c_mumps_solver_bld.F90 | 2 +- mlprec/impl/solver/mld_cilu0_fact.f90 | 2 +- mlprec/impl/solver/mld_ciluk_fact.f90 | 2 +- mlprec/impl/solver/mld_cilut_fact.f90 | 2 +- mlprec/impl/solver/mld_d_base_solver_apply.f90 | 2 +- .../impl/solver/mld_d_base_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_d_base_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_d_base_solver_check.f90 | 2 +- mlprec/impl/solver/mld_d_base_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_d_base_solver_cnv.f90 | 2 +- mlprec/impl/solver/mld_d_base_solver_csetc.f90 | 2 +- mlprec/impl/solver/mld_d_base_solver_cseti.f90 | 2 +- mlprec/impl/solver/mld_d_base_solver_csetr.f90 | 2 +- mlprec/impl/solver/mld_d_base_solver_descr.f90 | 2 +- mlprec/impl/solver/mld_d_base_solver_dmp.f90 | 2 +- mlprec/impl/solver/mld_d_base_solver_free.f90 | 2 +- mlprec/impl/solver/mld_d_base_solver_setc.f90 | 2 +- mlprec/impl/solver/mld_d_base_solver_seti.f90 | 2 +- mlprec/impl/solver/mld_d_base_solver_setr.f90 | 2 +- mlprec/impl/solver/mld_d_bwgs_solver_apply.f90 | 2 +- .../impl/solver/mld_d_bwgs_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_d_bwgs_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_d_diag_solver_apply.f90 | 2 +- .../impl/solver/mld_d_diag_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_d_diag_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_d_diag_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_d_diag_solver_cnv.f90 | 2 +- mlprec/impl/solver/mld_d_diag_solver_dmp.f90 | 2 +- mlprec/impl/solver/mld_d_gs_solver_apply.f90 | 2 +- mlprec/impl/solver/mld_d_gs_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_d_gs_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_d_gs_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_d_gs_solver_cnv.f90 | 2 +- mlprec/impl/solver/mld_d_gs_solver_dmp.f90 | 2 +- mlprec/impl/solver/mld_d_id_solver_apply.f90 | 2 +- mlprec/impl/solver/mld_d_id_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_d_id_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_d_ilu_solver_apply.f90 | 2 +- mlprec/impl/solver/mld_d_ilu_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_d_ilu_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_d_ilu_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_d_ilu_solver_cnv.f90 | 2 +- mlprec/impl/solver/mld_d_ilu_solver_dmp.f90 | 2 +- mlprec/impl/solver/mld_d_mumps_solver_apply.F90 | 2 +- .../impl/solver/mld_d_mumps_solver_apply_vect.F90 | 2 +- mlprec/impl/solver/mld_d_mumps_solver_bld.F90 | 2 +- mlprec/impl/solver/mld_dilu0_fact.f90 | 2 +- mlprec/impl/solver/mld_diluk_fact.f90 | 2 +- mlprec/impl/solver/mld_dilut_fact.f90 | 2 +- mlprec/impl/solver/mld_s_base_solver_apply.f90 | 2 +- .../impl/solver/mld_s_base_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_s_base_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_s_base_solver_check.f90 | 2 +- mlprec/impl/solver/mld_s_base_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_s_base_solver_cnv.f90 | 2 +- mlprec/impl/solver/mld_s_base_solver_csetc.f90 | 2 +- mlprec/impl/solver/mld_s_base_solver_cseti.f90 | 2 +- mlprec/impl/solver/mld_s_base_solver_csetr.f90 | 2 +- mlprec/impl/solver/mld_s_base_solver_descr.f90 | 2 +- mlprec/impl/solver/mld_s_base_solver_dmp.f90 | 2 +- mlprec/impl/solver/mld_s_base_solver_free.f90 | 2 +- mlprec/impl/solver/mld_s_base_solver_setc.f90 | 2 +- mlprec/impl/solver/mld_s_base_solver_seti.f90 | 2 +- mlprec/impl/solver/mld_s_base_solver_setr.f90 | 2 +- mlprec/impl/solver/mld_s_bwgs_solver_apply.f90 | 2 +- .../impl/solver/mld_s_bwgs_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_s_bwgs_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_s_diag_solver_apply.f90 | 2 +- .../impl/solver/mld_s_diag_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_s_diag_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_s_diag_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_s_diag_solver_cnv.f90 | 2 +- mlprec/impl/solver/mld_s_diag_solver_dmp.f90 | 2 +- mlprec/impl/solver/mld_s_gs_solver_apply.f90 | 2 +- mlprec/impl/solver/mld_s_gs_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_s_gs_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_s_gs_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_s_gs_solver_cnv.f90 | 2 +- mlprec/impl/solver/mld_s_gs_solver_dmp.f90 | 2 +- mlprec/impl/solver/mld_s_id_solver_apply.f90 | 2 +- mlprec/impl/solver/mld_s_id_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_s_id_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_s_ilu_solver_apply.f90 | 2 +- mlprec/impl/solver/mld_s_ilu_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_s_ilu_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_s_ilu_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_s_ilu_solver_cnv.f90 | 2 +- mlprec/impl/solver/mld_s_ilu_solver_dmp.f90 | 2 +- mlprec/impl/solver/mld_s_mumps_solver_apply.F90 | 2 +- .../impl/solver/mld_s_mumps_solver_apply_vect.F90 | 2 +- mlprec/impl/solver/mld_s_mumps_solver_bld.F90 | 2 +- mlprec/impl/solver/mld_silu0_fact.f90 | 2 +- mlprec/impl/solver/mld_siluk_fact.f90 | 2 +- mlprec/impl/solver/mld_silut_fact.f90 | 2 +- mlprec/impl/solver/mld_z_base_solver_apply.f90 | 2 +- .../impl/solver/mld_z_base_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_z_base_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_z_base_solver_check.f90 | 2 +- mlprec/impl/solver/mld_z_base_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_z_base_solver_cnv.f90 | 2 +- mlprec/impl/solver/mld_z_base_solver_csetc.f90 | 2 +- mlprec/impl/solver/mld_z_base_solver_cseti.f90 | 2 +- mlprec/impl/solver/mld_z_base_solver_csetr.f90 | 2 +- mlprec/impl/solver/mld_z_base_solver_descr.f90 | 2 +- mlprec/impl/solver/mld_z_base_solver_dmp.f90 | 2 +- mlprec/impl/solver/mld_z_base_solver_free.f90 | 2 +- mlprec/impl/solver/mld_z_base_solver_setc.f90 | 2 +- mlprec/impl/solver/mld_z_base_solver_seti.f90 | 2 +- mlprec/impl/solver/mld_z_base_solver_setr.f90 | 2 +- mlprec/impl/solver/mld_z_bwgs_solver_apply.f90 | 2 +- .../impl/solver/mld_z_bwgs_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_z_bwgs_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_z_diag_solver_apply.f90 | 2 +- .../impl/solver/mld_z_diag_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_z_diag_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_z_diag_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_z_diag_solver_cnv.f90 | 2 +- mlprec/impl/solver/mld_z_diag_solver_dmp.f90 | 2 +- mlprec/impl/solver/mld_z_gs_solver_apply.f90 | 2 +- mlprec/impl/solver/mld_z_gs_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_z_gs_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_z_gs_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_z_gs_solver_cnv.f90 | 2 +- mlprec/impl/solver/mld_z_gs_solver_dmp.f90 | 2 +- mlprec/impl/solver/mld_z_id_solver_apply.f90 | 2 +- mlprec/impl/solver/mld_z_id_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_z_id_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_z_ilu_solver_apply.f90 | 2 +- mlprec/impl/solver/mld_z_ilu_solver_apply_vect.f90 | 2 +- mlprec/impl/solver/mld_z_ilu_solver_bld.f90 | 2 +- mlprec/impl/solver/mld_z_ilu_solver_clone.f90 | 2 +- mlprec/impl/solver/mld_z_ilu_solver_cnv.f90 | 2 +- mlprec/impl/solver/mld_z_ilu_solver_dmp.f90 | 2 +- mlprec/impl/solver/mld_z_mumps_solver_apply.F90 | 2 +- .../impl/solver/mld_z_mumps_solver_apply_vect.F90 | 2 +- mlprec/impl/solver/mld_z_mumps_solver_bld.F90 | 2 +- mlprec/impl/solver/mld_zilu0_fact.f90 | 2 +- mlprec/impl/solver/mld_ziluk_fact.f90 | 2 +- mlprec/impl/solver/mld_zilut_fact.f90 | 2 +- mlprec/mld_base_prec_type.F90 | 2 +- mlprec/mld_c_as_smoother.f90 | 2 +- mlprec/mld_c_base_aggregator_mod.f90 | 11 +++++------ mlprec/mld_c_base_smoother_mod.f90 | 2 +- mlprec/mld_c_base_solver_mod.f90 | 2 +- mlprec/mld_c_diag_solver.f90 | 2 +- mlprec/mld_c_gs_solver.f90 | 2 +- mlprec/mld_c_hybrid_aggregator_mod.F90 | 11 +++++------ mlprec/mld_c_id_solver.f90 | 2 +- mlprec/mld_c_ilu_fact_mod.f90 | 2 +- mlprec/mld_c_ilu_solver.f90 | 2 +- mlprec/mld_c_inner_mod.f90 | 2 +- mlprec/mld_c_jac_smoother.f90 | 2 +- mlprec/mld_c_mumps_solver.F90 | 6 +++--- mlprec/mld_c_onelev_mod.f90 | 2 +- mlprec/mld_c_prec_mod.f90 | 2 +- mlprec/mld_c_prec_type.f90 | 2 +- mlprec/mld_c_slu_solver.F90 | 2 +- mlprec/mld_c_symdec_aggregator_mod.f90 | 11 +++++------ mlprec/mld_d_as_smoother.f90 | 2 +- mlprec/mld_d_base_aggregator_mod.f90 | 11 +++++------ mlprec/mld_d_base_smoother_mod.f90 | 2 +- mlprec/mld_d_base_solver_mod.f90 | 2 +- mlprec/mld_d_bcmatch_aggregator_mod.F90 | 2 +- mlprec/mld_d_diag_solver.f90 | 2 +- mlprec/mld_d_gs_solver.f90 | 2 +- mlprec/mld_d_hybrid_aggregator_mod.F90 | 11 +++++------ mlprec/mld_d_id_solver.f90 | 2 +- mlprec/mld_d_ilu_fact_mod.f90 | 2 +- mlprec/mld_d_ilu_solver.f90 | 2 +- mlprec/mld_d_inner_mod.f90 | 2 +- mlprec/mld_d_jac_smoother.f90 | 2 +- mlprec/mld_d_mumps_solver.F90 | 6 +++--- mlprec/mld_d_onelev_mod.f90 | 2 +- mlprec/mld_d_prec_mod.f90 | 2 +- mlprec/mld_d_prec_type.f90 | 2 +- mlprec/mld_d_slu_solver.F90 | 2 +- mlprec/mld_d_sludist_solver.F90 | 2 +- mlprec/mld_d_symdec_aggregator_mod.f90 | 11 +++++------ mlprec/mld_d_umf_solver.F90 | 2 +- mlprec/mld_prec_mod.f90 | 2 +- mlprec/mld_prec_type.f90 | 2 +- mlprec/mld_s_as_smoother.f90 | 2 +- mlprec/mld_s_base_aggregator_mod.f90 | 11 +++++------ mlprec/mld_s_base_smoother_mod.f90 | 2 +- mlprec/mld_s_base_solver_mod.f90 | 2 +- mlprec/mld_s_diag_solver.f90 | 2 +- mlprec/mld_s_gs_solver.f90 | 2 +- mlprec/mld_s_hybrid_aggregator_mod.F90 | 11 +++++------ mlprec/mld_s_id_solver.f90 | 2 +- mlprec/mld_s_ilu_fact_mod.f90 | 2 +- mlprec/mld_s_ilu_solver.f90 | 2 +- mlprec/mld_s_inner_mod.f90 | 2 +- mlprec/mld_s_jac_smoother.f90 | 2 +- mlprec/mld_s_mumps_solver.F90 | 6 +++--- mlprec/mld_s_onelev_mod.f90 | 2 +- mlprec/mld_s_prec_mod.f90 | 2 +- mlprec/mld_s_prec_type.f90 | 2 +- mlprec/mld_s_slu_solver.F90 | 2 +- mlprec/mld_s_symdec_aggregator_mod.f90 | 11 +++++------ mlprec/mld_z_as_smoother.f90 | 2 +- mlprec/mld_z_base_aggregator_mod.f90 | 11 +++++------ mlprec/mld_z_base_smoother_mod.f90 | 2 +- mlprec/mld_z_base_solver_mod.f90 | 2 +- mlprec/mld_z_diag_solver.f90 | 2 +- mlprec/mld_z_gs_solver.f90 | 2 +- mlprec/mld_z_hybrid_aggregator_mod.F90 | 11 +++++------ mlprec/mld_z_id_solver.f90 | 2 +- mlprec/mld_z_ilu_fact_mod.f90 | 2 +- mlprec/mld_z_ilu_solver.f90 | 2 +- mlprec/mld_z_inner_mod.f90 | 2 +- mlprec/mld_z_jac_smoother.f90 | 2 +- mlprec/mld_z_mumps_solver.F90 | 6 +++--- mlprec/mld_z_onelev_mod.f90 | 2 +- mlprec/mld_z_prec_mod.f90 | 2 +- mlprec/mld_z_prec_type.f90 | 2 +- mlprec/mld_z_slu_solver.F90 | 2 +- mlprec/mld_z_sludist_solver.F90 | 2 +- mlprec/mld_z_symdec_aggregator_mod.f90 | 11 +++++------ mlprec/mld_z_umf_solver.F90 | 2 +- tests/fileread/data_input.f90 | 2 +- tests/fileread/mld_cf_sample.f90 | 2 +- tests/fileread/mld_df_sample.f90 | 2 +- tests/fileread/mld_sf_sample.f90 | 2 +- tests/fileread/mld_zf_sample.f90 | 2 +- tests/newslv/data_input.f90 | 2 +- tests/newslv/mld_d_tlu_solver.f90 | 2 +- tests/newslv/mld_d_tlu_solver_impl.f90 | 2 +- tests/newslv/mld_pde3d_newslv.f90 | 2 +- tests/pdegen/data_input.f90 | 2 +- tests/pdegen/mld_d_pde2d.f90 | 2 +- tests/pdegen/mld_d_pde3d.f90 | 2 +- tests/pdegen/mld_s_pde2d.f90 | 2 +- tests/pdegen/mld_s_pde3d.f90 | 2 +- 603 files changed, 779 insertions(+), 811 deletions(-) diff --git a/LICENSE b/LICENSE index 1a56c4c2..89dcff9b 100644 --- a/LICENSE +++ b/LICENSE @@ -1,6 +1,6 @@ - MLD2P4 version 2.1 + MLD2P4 version 2.2 MultiLevel Domain Decomposition Parallel Preconditioners Package based on PSBLAS (Parallel Sparse BLAS version 3.5) diff --git a/examples/fileread/data_input.f90 b/examples/fileread/data_input.f90 index 2366f448..b31a5f9a 100644 --- a/examples/fileread/data_input.f90 +++ b/examples/fileread/data_input.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/examples/fileread/mld_cexample_1lev.f90 b/examples/fileread/mld_cexample_1lev.f90 index 7d34d95d..f2522c4c 100644 --- a/examples/fileread/mld_cexample_1lev.f90 +++ b/examples/fileread/mld_cexample_1lev.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/examples/fileread/mld_cexample_ml.f90 b/examples/fileread/mld_cexample_ml.f90 index 1f2535ed..3cbc42d9 100644 --- a/examples/fileread/mld_cexample_ml.f90 +++ b/examples/fileread/mld_cexample_ml.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/examples/fileread/mld_dexample_1lev.f90 b/examples/fileread/mld_dexample_1lev.f90 index a178f596..900d070e 100644 --- a/examples/fileread/mld_dexample_1lev.f90 +++ b/examples/fileread/mld_dexample_1lev.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/examples/fileread/mld_dexample_ml.f90 b/examples/fileread/mld_dexample_ml.f90 index be0bbd48..7fe06f7e 100644 --- a/examples/fileread/mld_dexample_ml.f90 +++ b/examples/fileread/mld_dexample_ml.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/examples/fileread/mld_sexample_1lev.f90 b/examples/fileread/mld_sexample_1lev.f90 index ca39e65d..d4708e08 100644 --- a/examples/fileread/mld_sexample_1lev.f90 +++ b/examples/fileread/mld_sexample_1lev.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/examples/fileread/mld_sexample_ml.f90 b/examples/fileread/mld_sexample_ml.f90 index 027ed6f3..7b24bc31 100644 --- a/examples/fileread/mld_sexample_ml.f90 +++ b/examples/fileread/mld_sexample_ml.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/examples/fileread/mld_zexample_1lev.f90 b/examples/fileread/mld_zexample_1lev.f90 index 1a5da26d..cc659515 100644 --- a/examples/fileread/mld_zexample_1lev.f90 +++ b/examples/fileread/mld_zexample_1lev.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/examples/fileread/mld_zexample_ml.f90 b/examples/fileread/mld_zexample_ml.f90 index 453d3ecd..9c6cd54c 100644 --- a/examples/fileread/mld_zexample_ml.f90 +++ b/examples/fileread/mld_zexample_ml.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/examples/pdegen/data_input.f90 b/examples/pdegen/data_input.f90 index 2366f448..b31a5f9a 100644 --- a/examples/pdegen/data_input.f90 +++ b/examples/pdegen/data_input.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/examples/pdegen/mld_dexample_1lev.f90 b/examples/pdegen/mld_dexample_1lev.f90 index 9dd1a443..0b74503b 100644 --- a/examples/pdegen/mld_dexample_1lev.f90 +++ b/examples/pdegen/mld_dexample_1lev.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/examples/pdegen/mld_dexample_ml.f90 b/examples/pdegen/mld_dexample_ml.f90 index 4d924ac8..4df65dd5 100644 --- a/examples/pdegen/mld_dexample_ml.f90 +++ b/examples/pdegen/mld_dexample_ml.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/examples/pdegen/mld_dpde_mod.f90 b/examples/pdegen/mld_dpde_mod.f90 index 44f65ff2..ec06a599 100644 --- a/examples/pdegen/mld_dpde_mod.f90 +++ b/examples/pdegen/mld_dpde_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/examples/pdegen/mld_sexample_1lev.f90 b/examples/pdegen/mld_sexample_1lev.f90 index a60d61fd..7c7966bc 100644 --- a/examples/pdegen/mld_sexample_1lev.f90 +++ b/examples/pdegen/mld_sexample_1lev.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/examples/pdegen/mld_sexample_ml.f90 b/examples/pdegen/mld_sexample_ml.f90 index ccd7c9c9..5d5bc7f6 100644 --- a/examples/pdegen/mld_sexample_ml.f90 +++ b/examples/pdegen/mld_sexample_ml.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/examples/pdegen/mld_spde_mod.f90 b/examples/pdegen/mld_spde_mod.f90 index 6548fe00..ad0a7838 100644 --- a/examples/pdegen/mld_spde_mod.f90 +++ b/examples/pdegen/mld_spde_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_c_base_aggregator_mat_asb.f90 b/mlprec/impl/aggregator/mld_c_base_aggregator_mat_asb.f90 index d67f2e3e..69ca7c2e 100644 --- a/mlprec/impl/aggregator/mld_c_base_aggregator_mat_asb.f90 +++ b/mlprec/impl/aggregator/mld_c_base_aggregator_mat_asb.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/aggregator/mld_c_base_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_c_base_aggregator_tprol.f90 index 92a685a9..345ffcd1 100644 --- a/mlprec/impl/aggregator/mld_c_base_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_c_base_aggregator_tprol.f90 @@ -1,16 +1,14 @@ - ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/aggregator/mld_c_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_c_dec_map_bld.f90 index 110c5bbb..cc40d5fd 100644 --- a/mlprec/impl/aggregator/mld_c_dec_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_c_dec_map_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 index 4bb25f4c..33e50511 100644 --- a/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 index 291e17fc..997e0200 100644 --- a/mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 @@ -1,14 +1,14 @@ +! ! -! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University, UK -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/aggregator/mld_c_map_to_tprol.f90 b/mlprec/impl/aggregator/mld_c_map_to_tprol.f90 index ae2154c5..28ac347a 100644 --- a/mlprec/impl/aggregator/mld_c_map_to_tprol.f90 +++ b/mlprec/impl/aggregator/mld_c_map_to_tprol.f90 @@ -1,15 +1,15 @@ +! ! -! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 -! -! Salvatore Filippone Cranfield University, UK -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! (C) Copyright 2008-2018 ! +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino +! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions ! are met: diff --git a/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 index fc5c3611..2486de43 100644 --- a/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/aggregator/mld_caggrmat_biz_asb.f90 b/mlprec/impl/aggregator/mld_caggrmat_biz_asb.f90 index e0ab7e29..4944df2a 100644 --- a/mlprec/impl/aggregator/mld_caggrmat_biz_asb.f90 +++ b/mlprec/impl/aggregator/mld_caggrmat_biz_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_caggrmat_minnrg_asb.f90 b/mlprec/impl/aggregator/mld_caggrmat_minnrg_asb.f90 index 4af16a9e..60be7674 100644 --- a/mlprec/impl/aggregator/mld_caggrmat_minnrg_asb.f90 +++ b/mlprec/impl/aggregator/mld_caggrmat_minnrg_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_caggrmat_nosmth_asb.f90 b/mlprec/impl/aggregator/mld_caggrmat_nosmth_asb.f90 index bbf1f218..c029b562 100644 --- a/mlprec/impl/aggregator/mld_caggrmat_nosmth_asb.f90 +++ b/mlprec/impl/aggregator/mld_caggrmat_nosmth_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_caggrmat_smth_asb.f90 b/mlprec/impl/aggregator/mld_caggrmat_smth_asb.f90 index df5086b4..c4ee3bcc 100644 --- a/mlprec/impl/aggregator/mld_caggrmat_smth_asb.f90 +++ b/mlprec/impl/aggregator/mld_caggrmat_smth_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_d_base_aggregator_mat_asb.f90 b/mlprec/impl/aggregator/mld_d_base_aggregator_mat_asb.f90 index efbee053..36ab21b0 100644 --- a/mlprec/impl/aggregator/mld_d_base_aggregator_mat_asb.f90 +++ b/mlprec/impl/aggregator/mld_d_base_aggregator_mat_asb.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/aggregator/mld_d_base_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_d_base_aggregator_tprol.f90 index 61e7ba86..354a94da 100644 --- a/mlprec/impl/aggregator/mld_d_base_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_d_base_aggregator_tprol.f90 @@ -1,16 +1,14 @@ - ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/aggregator/mld_d_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_d_dec_map_bld.f90 index 4925233c..8d50c23e 100644 --- a/mlprec/impl/aggregator/mld_d_dec_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_d_dec_map_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 index d7d24589..5f3b5cbe 100644 --- a/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 index 98e43275..557082e4 100644 --- a/mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 @@ -1,14 +1,14 @@ +! ! -! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University, UK -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/aggregator/mld_d_map_to_tprol.f90 b/mlprec/impl/aggregator/mld_d_map_to_tprol.f90 index 1688b979..a8a53826 100644 --- a/mlprec/impl/aggregator/mld_d_map_to_tprol.f90 +++ b/mlprec/impl/aggregator/mld_d_map_to_tprol.f90 @@ -1,15 +1,15 @@ +! ! -! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 -! -! Salvatore Filippone Cranfield University, UK -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! (C) Copyright 2008-2018 ! +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino +! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions ! are met: diff --git a/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 index c9c00780..74bffe40 100644 --- a/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/aggregator/mld_daggrmat_biz_asb.f90 b/mlprec/impl/aggregator/mld_daggrmat_biz_asb.f90 index 90e35693..76d266d8 100644 --- a/mlprec/impl/aggregator/mld_daggrmat_biz_asb.f90 +++ b/mlprec/impl/aggregator/mld_daggrmat_biz_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_daggrmat_minnrg_asb.f90 b/mlprec/impl/aggregator/mld_daggrmat_minnrg_asb.f90 index 418ac112..391aefe1 100644 --- a/mlprec/impl/aggregator/mld_daggrmat_minnrg_asb.f90 +++ b/mlprec/impl/aggregator/mld_daggrmat_minnrg_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_daggrmat_nosmth_asb.f90 b/mlprec/impl/aggregator/mld_daggrmat_nosmth_asb.f90 index 8c507876..09989846 100644 --- a/mlprec/impl/aggregator/mld_daggrmat_nosmth_asb.f90 +++ b/mlprec/impl/aggregator/mld_daggrmat_nosmth_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_daggrmat_smth_asb.f90 b/mlprec/impl/aggregator/mld_daggrmat_smth_asb.f90 index 7605260d..7a147832 100644 --- a/mlprec/impl/aggregator/mld_daggrmat_smth_asb.f90 +++ b/mlprec/impl/aggregator/mld_daggrmat_smth_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_s_base_aggregator_mat_asb.f90 b/mlprec/impl/aggregator/mld_s_base_aggregator_mat_asb.f90 index 10285bfa..a77e8412 100644 --- a/mlprec/impl/aggregator/mld_s_base_aggregator_mat_asb.f90 +++ b/mlprec/impl/aggregator/mld_s_base_aggregator_mat_asb.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/aggregator/mld_s_base_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_s_base_aggregator_tprol.f90 index 786748d1..ca4b40dd 100644 --- a/mlprec/impl/aggregator/mld_s_base_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_s_base_aggregator_tprol.f90 @@ -1,16 +1,14 @@ - ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/aggregator/mld_s_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_s_dec_map_bld.f90 index fc1c15ec..be2212ad 100644 --- a/mlprec/impl/aggregator/mld_s_dec_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_s_dec_map_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 index 11744ea4..5f093685 100644 --- a/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 index 659c3f86..765f556c 100644 --- a/mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 @@ -1,14 +1,14 @@ +! ! -! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University, UK -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/aggregator/mld_s_map_to_tprol.f90 b/mlprec/impl/aggregator/mld_s_map_to_tprol.f90 index 0b41787c..8d237d34 100644 --- a/mlprec/impl/aggregator/mld_s_map_to_tprol.f90 +++ b/mlprec/impl/aggregator/mld_s_map_to_tprol.f90 @@ -1,15 +1,15 @@ +! ! -! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 -! -! Salvatore Filippone Cranfield University, UK -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! (C) Copyright 2008-2018 ! +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino +! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions ! are met: diff --git a/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 index e308ab5f..ea815091 100644 --- a/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/aggregator/mld_saggrmat_biz_asb.f90 b/mlprec/impl/aggregator/mld_saggrmat_biz_asb.f90 index dff9e720..93b3be0b 100644 --- a/mlprec/impl/aggregator/mld_saggrmat_biz_asb.f90 +++ b/mlprec/impl/aggregator/mld_saggrmat_biz_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_saggrmat_minnrg_asb.f90 b/mlprec/impl/aggregator/mld_saggrmat_minnrg_asb.f90 index d66af67b..6ceb0874 100644 --- a/mlprec/impl/aggregator/mld_saggrmat_minnrg_asb.f90 +++ b/mlprec/impl/aggregator/mld_saggrmat_minnrg_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_saggrmat_nosmth_asb.f90 b/mlprec/impl/aggregator/mld_saggrmat_nosmth_asb.f90 index c4805080..6678f775 100644 --- a/mlprec/impl/aggregator/mld_saggrmat_nosmth_asb.f90 +++ b/mlprec/impl/aggregator/mld_saggrmat_nosmth_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_saggrmat_smth_asb.f90 b/mlprec/impl/aggregator/mld_saggrmat_smth_asb.f90 index b95c9e93..e2c52d7f 100644 --- a/mlprec/impl/aggregator/mld_saggrmat_smth_asb.f90 +++ b/mlprec/impl/aggregator/mld_saggrmat_smth_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_z_base_aggregator_mat_asb.f90 b/mlprec/impl/aggregator/mld_z_base_aggregator_mat_asb.f90 index b9eda046..f7d4a926 100644 --- a/mlprec/impl/aggregator/mld_z_base_aggregator_mat_asb.f90 +++ b/mlprec/impl/aggregator/mld_z_base_aggregator_mat_asb.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/aggregator/mld_z_base_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_z_base_aggregator_tprol.f90 index 894e4e7a..4522bd8d 100644 --- a/mlprec/impl/aggregator/mld_z_base_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_z_base_aggregator_tprol.f90 @@ -1,16 +1,14 @@ - ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/aggregator/mld_z_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_z_dec_map_bld.f90 index 6900b221..80119809 100644 --- a/mlprec/impl/aggregator/mld_z_dec_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_z_dec_map_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 index 47d60179..57ae369c 100644 --- a/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 index 742dbc80..c31ed21c 100644 --- a/mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 @@ -1,14 +1,14 @@ +! ! -! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University, UK -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/aggregator/mld_z_map_to_tprol.f90 b/mlprec/impl/aggregator/mld_z_map_to_tprol.f90 index 5a9491e9..d01b2e75 100644 --- a/mlprec/impl/aggregator/mld_z_map_to_tprol.f90 +++ b/mlprec/impl/aggregator/mld_z_map_to_tprol.f90 @@ -1,15 +1,15 @@ +! ! -! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 -! -! Salvatore Filippone Cranfield University, UK -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! (C) Copyright 2008-2018 ! +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino +! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions ! are met: diff --git a/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 index 8f1e8ff8..a0de3a6a 100644 --- a/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/aggregator/mld_zaggrmat_biz_asb.f90 b/mlprec/impl/aggregator/mld_zaggrmat_biz_asb.f90 index 867ef775..297ea046 100644 --- a/mlprec/impl/aggregator/mld_zaggrmat_biz_asb.f90 +++ b/mlprec/impl/aggregator/mld_zaggrmat_biz_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_zaggrmat_minnrg_asb.f90 b/mlprec/impl/aggregator/mld_zaggrmat_minnrg_asb.f90 index b86af371..71add989 100644 --- a/mlprec/impl/aggregator/mld_zaggrmat_minnrg_asb.f90 +++ b/mlprec/impl/aggregator/mld_zaggrmat_minnrg_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_zaggrmat_nosmth_asb.f90 b/mlprec/impl/aggregator/mld_zaggrmat_nosmth_asb.f90 index 8dde35d7..27677ac4 100644 --- a/mlprec/impl/aggregator/mld_zaggrmat_nosmth_asb.f90 +++ b/mlprec/impl/aggregator/mld_zaggrmat_nosmth_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/aggregator/mld_zaggrmat_smth_asb.f90 b/mlprec/impl/aggregator/mld_zaggrmat_smth_asb.f90 index 165c2605..02f2ebe6 100644 --- a/mlprec/impl/aggregator/mld_zaggrmat_smth_asb.f90 +++ b/mlprec/impl/aggregator/mld_zaggrmat_smth_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_c_base_onelev_build.f90 b/mlprec/impl/level/mld_c_base_onelev_build.f90 index 6579af69..bc3c3a15 100644 --- a/mlprec/impl/level/mld_c_base_onelev_build.f90 +++ b/mlprec/impl/level/mld_c_base_onelev_build.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_c_base_onelev_check.f90 b/mlprec/impl/level/mld_c_base_onelev_check.f90 index 5f4f3f22..c47747b5 100644 --- a/mlprec/impl/level/mld_c_base_onelev_check.f90 +++ b/mlprec/impl/level/mld_c_base_onelev_check.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_c_base_onelev_cnv.f90 b/mlprec/impl/level/mld_c_base_onelev_cnv.f90 index 72837aed..e3d49b1b 100644 --- a/mlprec/impl/level/mld_c_base_onelev_cnv.f90 +++ b/mlprec/impl/level/mld_c_base_onelev_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_c_base_onelev_csetc.f90 b/mlprec/impl/level/mld_c_base_onelev_csetc.f90 index 8e3cc4a6..781ceef0 100644 --- a/mlprec/impl/level/mld_c_base_onelev_csetc.f90 +++ b/mlprec/impl/level/mld_c_base_onelev_csetc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_c_base_onelev_cseti.F90 b/mlprec/impl/level/mld_c_base_onelev_cseti.F90 index 2d8da26e..ea1ecc8e 100644 --- a/mlprec/impl/level/mld_c_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_c_base_onelev_cseti.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_c_base_onelev_csetr.f90 b/mlprec/impl/level/mld_c_base_onelev_csetr.f90 index fea5cef9..922496dd 100644 --- a/mlprec/impl/level/mld_c_base_onelev_csetr.f90 +++ b/mlprec/impl/level/mld_c_base_onelev_csetr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_c_base_onelev_descr.f90 b/mlprec/impl/level/mld_c_base_onelev_descr.f90 index 5dc4d610..c2698ddd 100644 --- a/mlprec/impl/level/mld_c_base_onelev_descr.f90 +++ b/mlprec/impl/level/mld_c_base_onelev_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_c_base_onelev_dump.f90 b/mlprec/impl/level/mld_c_base_onelev_dump.f90 index 52453416..5416dd63 100644 --- a/mlprec/impl/level/mld_c_base_onelev_dump.f90 +++ b/mlprec/impl/level/mld_c_base_onelev_dump.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_c_base_onelev_free.f90 b/mlprec/impl/level/mld_c_base_onelev_free.f90 index ae07b13e..e480e012 100644 --- a/mlprec/impl/level/mld_c_base_onelev_free.f90 +++ b/mlprec/impl/level/mld_c_base_onelev_free.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_c_base_onelev_mat_asb.f90 b/mlprec/impl/level/mld_c_base_onelev_mat_asb.f90 index c9275dc8..b02df225 100644 --- a/mlprec/impl/level/mld_c_base_onelev_mat_asb.f90 +++ b/mlprec/impl/level/mld_c_base_onelev_mat_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_c_base_onelev_setag.f90 b/mlprec/impl/level/mld_c_base_onelev_setag.f90 index 9625b7e9..2be2a0e5 100644 --- a/mlprec/impl/level/mld_c_base_onelev_setag.f90 +++ b/mlprec/impl/level/mld_c_base_onelev_setag.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/level/mld_c_base_onelev_setc.f90 b/mlprec/impl/level/mld_c_base_onelev_setc.f90 index 93dac171..93b8ff9c 100644 --- a/mlprec/impl/level/mld_c_base_onelev_setc.f90 +++ b/mlprec/impl/level/mld_c_base_onelev_setc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_c_base_onelev_seti.F90 b/mlprec/impl/level/mld_c_base_onelev_seti.F90 index b23c6b1a..27cceaa0 100644 --- a/mlprec/impl/level/mld_c_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_c_base_onelev_seti.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_c_base_onelev_setr.f90 b/mlprec/impl/level/mld_c_base_onelev_setr.f90 index 86c39ef3..adfd71ba 100644 --- a/mlprec/impl/level/mld_c_base_onelev_setr.f90 +++ b/mlprec/impl/level/mld_c_base_onelev_setr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_c_base_onelev_setsm.F90 b/mlprec/impl/level/mld_c_base_onelev_setsm.F90 index 6d970405..5f95daf7 100644 --- a/mlprec/impl/level/mld_c_base_onelev_setsm.F90 +++ b/mlprec/impl/level/mld_c_base_onelev_setsm.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_c_base_onelev_setsv.F90 b/mlprec/impl/level/mld_c_base_onelev_setsv.F90 index 4beb8b7b..16530915 100644 --- a/mlprec/impl/level/mld_c_base_onelev_setsv.F90 +++ b/mlprec/impl/level/mld_c_base_onelev_setsv.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_d_base_onelev_build.f90 b/mlprec/impl/level/mld_d_base_onelev_build.f90 index fe15bbb9..11e7fb5d 100644 --- a/mlprec/impl/level/mld_d_base_onelev_build.f90 +++ b/mlprec/impl/level/mld_d_base_onelev_build.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_d_base_onelev_check.f90 b/mlprec/impl/level/mld_d_base_onelev_check.f90 index f1a871c8..65c58a16 100644 --- a/mlprec/impl/level/mld_d_base_onelev_check.f90 +++ b/mlprec/impl/level/mld_d_base_onelev_check.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_d_base_onelev_cnv.f90 b/mlprec/impl/level/mld_d_base_onelev_cnv.f90 index d965c265..23ff2c26 100644 --- a/mlprec/impl/level/mld_d_base_onelev_cnv.f90 +++ b/mlprec/impl/level/mld_d_base_onelev_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_d_base_onelev_csetc.f90 b/mlprec/impl/level/mld_d_base_onelev_csetc.f90 index 23e2416e..1ac67d26 100644 --- a/mlprec/impl/level/mld_d_base_onelev_csetc.f90 +++ b/mlprec/impl/level/mld_d_base_onelev_csetc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_d_base_onelev_cseti.F90 b/mlprec/impl/level/mld_d_base_onelev_cseti.F90 index 713a31da..492eb9fb 100644 --- a/mlprec/impl/level/mld_d_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_d_base_onelev_cseti.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_d_base_onelev_csetr.f90 b/mlprec/impl/level/mld_d_base_onelev_csetr.f90 index 91af2d19..33f5a5a5 100644 --- a/mlprec/impl/level/mld_d_base_onelev_csetr.f90 +++ b/mlprec/impl/level/mld_d_base_onelev_csetr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_d_base_onelev_descr.f90 b/mlprec/impl/level/mld_d_base_onelev_descr.f90 index fdee2e93..fc602b40 100644 --- a/mlprec/impl/level/mld_d_base_onelev_descr.f90 +++ b/mlprec/impl/level/mld_d_base_onelev_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_d_base_onelev_dump.f90 b/mlprec/impl/level/mld_d_base_onelev_dump.f90 index 24e08b47..36b59197 100644 --- a/mlprec/impl/level/mld_d_base_onelev_dump.f90 +++ b/mlprec/impl/level/mld_d_base_onelev_dump.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_d_base_onelev_free.f90 b/mlprec/impl/level/mld_d_base_onelev_free.f90 index 68d44e74..24947988 100644 --- a/mlprec/impl/level/mld_d_base_onelev_free.f90 +++ b/mlprec/impl/level/mld_d_base_onelev_free.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_d_base_onelev_mat_asb.f90 b/mlprec/impl/level/mld_d_base_onelev_mat_asb.f90 index 84c81147..95b09136 100644 --- a/mlprec/impl/level/mld_d_base_onelev_mat_asb.f90 +++ b/mlprec/impl/level/mld_d_base_onelev_mat_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_d_base_onelev_setag.f90 b/mlprec/impl/level/mld_d_base_onelev_setag.f90 index 1ce8ed51..3303508b 100644 --- a/mlprec/impl/level/mld_d_base_onelev_setag.f90 +++ b/mlprec/impl/level/mld_d_base_onelev_setag.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/level/mld_d_base_onelev_setc.f90 b/mlprec/impl/level/mld_d_base_onelev_setc.f90 index d5002cc3..4b5f633b 100644 --- a/mlprec/impl/level/mld_d_base_onelev_setc.f90 +++ b/mlprec/impl/level/mld_d_base_onelev_setc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_d_base_onelev_seti.F90 b/mlprec/impl/level/mld_d_base_onelev_seti.F90 index 6c3e7a22..2a3914d0 100644 --- a/mlprec/impl/level/mld_d_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_d_base_onelev_seti.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_d_base_onelev_setr.f90 b/mlprec/impl/level/mld_d_base_onelev_setr.f90 index 4c28095c..dfd96da7 100644 --- a/mlprec/impl/level/mld_d_base_onelev_setr.f90 +++ b/mlprec/impl/level/mld_d_base_onelev_setr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_d_base_onelev_setsm.F90 b/mlprec/impl/level/mld_d_base_onelev_setsm.F90 index 5f5227eb..cc9d526b 100644 --- a/mlprec/impl/level/mld_d_base_onelev_setsm.F90 +++ b/mlprec/impl/level/mld_d_base_onelev_setsm.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_d_base_onelev_setsv.F90 b/mlprec/impl/level/mld_d_base_onelev_setsv.F90 index d6e1f2e6..65f219ca 100644 --- a/mlprec/impl/level/mld_d_base_onelev_setsv.F90 +++ b/mlprec/impl/level/mld_d_base_onelev_setsv.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_s_base_onelev_build.f90 b/mlprec/impl/level/mld_s_base_onelev_build.f90 index fdba5976..3e71496d 100644 --- a/mlprec/impl/level/mld_s_base_onelev_build.f90 +++ b/mlprec/impl/level/mld_s_base_onelev_build.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_s_base_onelev_check.f90 b/mlprec/impl/level/mld_s_base_onelev_check.f90 index 9fe3959f..ffa4c70d 100644 --- a/mlprec/impl/level/mld_s_base_onelev_check.f90 +++ b/mlprec/impl/level/mld_s_base_onelev_check.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_s_base_onelev_cnv.f90 b/mlprec/impl/level/mld_s_base_onelev_cnv.f90 index b518676b..89a3d087 100644 --- a/mlprec/impl/level/mld_s_base_onelev_cnv.f90 +++ b/mlprec/impl/level/mld_s_base_onelev_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_s_base_onelev_csetc.f90 b/mlprec/impl/level/mld_s_base_onelev_csetc.f90 index 5950034c..2443b4e5 100644 --- a/mlprec/impl/level/mld_s_base_onelev_csetc.f90 +++ b/mlprec/impl/level/mld_s_base_onelev_csetc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_s_base_onelev_cseti.F90 b/mlprec/impl/level/mld_s_base_onelev_cseti.F90 index 0a0ed792..b6552c5a 100644 --- a/mlprec/impl/level/mld_s_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_s_base_onelev_cseti.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_s_base_onelev_csetr.f90 b/mlprec/impl/level/mld_s_base_onelev_csetr.f90 index a010d029..f75849cc 100644 --- a/mlprec/impl/level/mld_s_base_onelev_csetr.f90 +++ b/mlprec/impl/level/mld_s_base_onelev_csetr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_s_base_onelev_descr.f90 b/mlprec/impl/level/mld_s_base_onelev_descr.f90 index 3ae878f0..254086cf 100644 --- a/mlprec/impl/level/mld_s_base_onelev_descr.f90 +++ b/mlprec/impl/level/mld_s_base_onelev_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_s_base_onelev_dump.f90 b/mlprec/impl/level/mld_s_base_onelev_dump.f90 index a4fca5eb..df93abe4 100644 --- a/mlprec/impl/level/mld_s_base_onelev_dump.f90 +++ b/mlprec/impl/level/mld_s_base_onelev_dump.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_s_base_onelev_free.f90 b/mlprec/impl/level/mld_s_base_onelev_free.f90 index 2cca2125..89588074 100644 --- a/mlprec/impl/level/mld_s_base_onelev_free.f90 +++ b/mlprec/impl/level/mld_s_base_onelev_free.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_s_base_onelev_mat_asb.f90 b/mlprec/impl/level/mld_s_base_onelev_mat_asb.f90 index 1e56b3f8..be91ae19 100644 --- a/mlprec/impl/level/mld_s_base_onelev_mat_asb.f90 +++ b/mlprec/impl/level/mld_s_base_onelev_mat_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_s_base_onelev_setag.f90 b/mlprec/impl/level/mld_s_base_onelev_setag.f90 index 3c78aef1..81af270b 100644 --- a/mlprec/impl/level/mld_s_base_onelev_setag.f90 +++ b/mlprec/impl/level/mld_s_base_onelev_setag.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/level/mld_s_base_onelev_setc.f90 b/mlprec/impl/level/mld_s_base_onelev_setc.f90 index 099412d5..1093ce9a 100644 --- a/mlprec/impl/level/mld_s_base_onelev_setc.f90 +++ b/mlprec/impl/level/mld_s_base_onelev_setc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_s_base_onelev_seti.F90 b/mlprec/impl/level/mld_s_base_onelev_seti.F90 index fc690639..52880ac6 100644 --- a/mlprec/impl/level/mld_s_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_s_base_onelev_seti.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_s_base_onelev_setr.f90 b/mlprec/impl/level/mld_s_base_onelev_setr.f90 index 874785a1..2aeee09c 100644 --- a/mlprec/impl/level/mld_s_base_onelev_setr.f90 +++ b/mlprec/impl/level/mld_s_base_onelev_setr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_s_base_onelev_setsm.F90 b/mlprec/impl/level/mld_s_base_onelev_setsm.F90 index 4d2a34e9..30cba813 100644 --- a/mlprec/impl/level/mld_s_base_onelev_setsm.F90 +++ b/mlprec/impl/level/mld_s_base_onelev_setsm.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_s_base_onelev_setsv.F90 b/mlprec/impl/level/mld_s_base_onelev_setsv.F90 index 4036194e..cbc4cacf 100644 --- a/mlprec/impl/level/mld_s_base_onelev_setsv.F90 +++ b/mlprec/impl/level/mld_s_base_onelev_setsv.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_z_base_onelev_build.f90 b/mlprec/impl/level/mld_z_base_onelev_build.f90 index 5a01daac..9c444715 100644 --- a/mlprec/impl/level/mld_z_base_onelev_build.f90 +++ b/mlprec/impl/level/mld_z_base_onelev_build.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_z_base_onelev_check.f90 b/mlprec/impl/level/mld_z_base_onelev_check.f90 index 5cfb4656..74f48256 100644 --- a/mlprec/impl/level/mld_z_base_onelev_check.f90 +++ b/mlprec/impl/level/mld_z_base_onelev_check.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_z_base_onelev_cnv.f90 b/mlprec/impl/level/mld_z_base_onelev_cnv.f90 index 758d4503..407fca8d 100644 --- a/mlprec/impl/level/mld_z_base_onelev_cnv.f90 +++ b/mlprec/impl/level/mld_z_base_onelev_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_z_base_onelev_csetc.f90 b/mlprec/impl/level/mld_z_base_onelev_csetc.f90 index ad68e3c2..a09be534 100644 --- a/mlprec/impl/level/mld_z_base_onelev_csetc.f90 +++ b/mlprec/impl/level/mld_z_base_onelev_csetc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_z_base_onelev_cseti.F90 b/mlprec/impl/level/mld_z_base_onelev_cseti.F90 index 2cf24546..d4d353da 100644 --- a/mlprec/impl/level/mld_z_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_z_base_onelev_cseti.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_z_base_onelev_csetr.f90 b/mlprec/impl/level/mld_z_base_onelev_csetr.f90 index f7914ee0..28a7d61a 100644 --- a/mlprec/impl/level/mld_z_base_onelev_csetr.f90 +++ b/mlprec/impl/level/mld_z_base_onelev_csetr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_z_base_onelev_descr.f90 b/mlprec/impl/level/mld_z_base_onelev_descr.f90 index 80053e38..795f8c4f 100644 --- a/mlprec/impl/level/mld_z_base_onelev_descr.f90 +++ b/mlprec/impl/level/mld_z_base_onelev_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_z_base_onelev_dump.f90 b/mlprec/impl/level/mld_z_base_onelev_dump.f90 index ecceb0f6..c1181e97 100644 --- a/mlprec/impl/level/mld_z_base_onelev_dump.f90 +++ b/mlprec/impl/level/mld_z_base_onelev_dump.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_z_base_onelev_free.f90 b/mlprec/impl/level/mld_z_base_onelev_free.f90 index 15fe3d0d..4e09b7f0 100644 --- a/mlprec/impl/level/mld_z_base_onelev_free.f90 +++ b/mlprec/impl/level/mld_z_base_onelev_free.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_z_base_onelev_mat_asb.f90 b/mlprec/impl/level/mld_z_base_onelev_mat_asb.f90 index 9ddc6749..f422eee5 100644 --- a/mlprec/impl/level/mld_z_base_onelev_mat_asb.f90 +++ b/mlprec/impl/level/mld_z_base_onelev_mat_asb.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_z_base_onelev_setag.f90 b/mlprec/impl/level/mld_z_base_onelev_setag.f90 index c69bb47a..a5c56bc7 100644 --- a/mlprec/impl/level/mld_z_base_onelev_setag.f90 +++ b/mlprec/impl/level/mld_z_base_onelev_setag.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/impl/level/mld_z_base_onelev_setc.f90 b/mlprec/impl/level/mld_z_base_onelev_setc.f90 index 24490ca3..137ee584 100644 --- a/mlprec/impl/level/mld_z_base_onelev_setc.f90 +++ b/mlprec/impl/level/mld_z_base_onelev_setc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_z_base_onelev_seti.F90 b/mlprec/impl/level/mld_z_base_onelev_seti.F90 index af419a17..f335b968 100644 --- a/mlprec/impl/level/mld_z_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_z_base_onelev_seti.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_z_base_onelev_setr.f90 b/mlprec/impl/level/mld_z_base_onelev_setr.f90 index c6ac932b..f2303e41 100644 --- a/mlprec/impl/level/mld_z_base_onelev_setr.f90 +++ b/mlprec/impl/level/mld_z_base_onelev_setr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_z_base_onelev_setsm.F90 b/mlprec/impl/level/mld_z_base_onelev_setsm.F90 index c42a309a..4f2081ef 100644 --- a/mlprec/impl/level/mld_z_base_onelev_setsm.F90 +++ b/mlprec/impl/level/mld_z_base_onelev_setsm.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/level/mld_z_base_onelev_setsv.F90 b/mlprec/impl/level/mld_z_base_onelev_setsv.F90 index 7a8dce05..30c68af4 100644 --- a/mlprec/impl/level/mld_z_base_onelev_setsv.F90 +++ b/mlprec/impl/level/mld_z_base_onelev_setsv.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_c_extprol_bld.f90 b/mlprec/impl/mld_c_extprol_bld.f90 index e25a6837..1058a6c4 100644 --- a/mlprec/impl/mld_c_extprol_bld.f90 +++ b/mlprec/impl/mld_c_extprol_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! @@ -35,9 +35,9 @@ ! POSSIBILITY OF SUCH DAMAGE. ! ! -! File: mld_c_hierarchy_bld.f90 +! File: mld_c_extprol_bld.f90 ! -! Subroutine: mld_c_hierarchy_bld +! Subroutine: mld_c_extprol_bld ! Version: real ! ! This routine builds the preconditioner according to the requirements made by @@ -312,7 +312,7 @@ subroutine mld_c_extprol_bld(a,desc_a,p,prolv,restrv,info,amold,vmold,imold) if (info /= psb_success_) then call psb_errpush(psb_err_internal_error_,name,& - & a_err='Internal hierarchy build' ) + & a_err='Internal extprol build' ) goto 9999 endif diff --git a/mlprec/impl/mld_c_hierarchy_bld.f90 b/mlprec/impl/mld_c_hierarchy_bld.f90 index 38684e6a..bc59c893 100644 --- a/mlprec/impl/mld_c_hierarchy_bld.f90 +++ b/mlprec/impl/mld_c_hierarchy_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_c_smoothers_bld.f90 b/mlprec/impl/mld_c_smoothers_bld.f90 index af364381..5fb30db5 100644 --- a/mlprec/impl/mld_c_smoothers_bld.f90 +++ b/mlprec/impl/mld_c_smoothers_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_ccprecset.F90 b/mlprec/impl/mld_ccprecset.F90 index 01a240d3..79bfdd29 100644 --- a/mlprec/impl/mld_ccprecset.F90 +++ b/mlprec/impl/mld_ccprecset.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_cfile_prec_descr.f90 b/mlprec/impl/mld_cfile_prec_descr.f90 index 690480bb..1f243756 100644 --- a/mlprec/impl/mld_cfile_prec_descr.f90 +++ b/mlprec/impl/mld_cfile_prec_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_cmlprec_aply.f90 b/mlprec/impl/mld_cmlprec_aply.f90 index b38b075a..6eac6b97 100644 --- a/mlprec/impl/mld_cmlprec_aply.f90 +++ b/mlprec/impl/mld_cmlprec_aply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_cmlprec_bld.f90 b/mlprec/impl/mld_cmlprec_bld.f90 index d34b157a..4330c49f 100644 --- a/mlprec/impl/mld_cmlprec_bld.f90 +++ b/mlprec/impl/mld_cmlprec_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_cprecaply.f90 b/mlprec/impl/mld_cprecaply.f90 index 170005c2..9ae6fcfd 100644 --- a/mlprec/impl/mld_cprecaply.f90 +++ b/mlprec/impl/mld_cprecaply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_cprecbld.f90 b/mlprec/impl/mld_cprecbld.f90 index 0e2f8e77..66a8cb84 100644 --- a/mlprec/impl/mld_cprecbld.f90 +++ b/mlprec/impl/mld_cprecbld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_cprecinit.F90 b/mlprec/impl/mld_cprecinit.F90 index e6733c3a..236a2e00 100644 --- a/mlprec/impl/mld_cprecinit.F90 +++ b/mlprec/impl/mld_cprecinit.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_cprecset.F90 b/mlprec/impl/mld_cprecset.F90 index f785c6b7..24e2d659 100644 --- a/mlprec/impl/mld_cprecset.F90 +++ b/mlprec/impl/mld_cprecset.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_d_extprol_bld.f90 b/mlprec/impl/mld_d_extprol_bld.f90 index dea4e243..9209c754 100644 --- a/mlprec/impl/mld_d_extprol_bld.f90 +++ b/mlprec/impl/mld_d_extprol_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! @@ -35,9 +35,9 @@ ! POSSIBILITY OF SUCH DAMAGE. ! ! -! File: mld_d_hierarchy_bld.f90 +! File: mld_d_extprol_bld.f90 ! -! Subroutine: mld_d_hierarchy_bld +! Subroutine: mld_d_extprol_bld ! Version: real ! ! This routine builds the preconditioner according to the requirements made by @@ -312,7 +312,7 @@ subroutine mld_d_extprol_bld(a,desc_a,p,prolv,restrv,info,amold,vmold,imold) if (info /= psb_success_) then call psb_errpush(psb_err_internal_error_,name,& - & a_err='Internal hierarchy build' ) + & a_err='Internal extprol build' ) goto 9999 endif diff --git a/mlprec/impl/mld_d_hierarchy_bld.f90 b/mlprec/impl/mld_d_hierarchy_bld.f90 index c7b882e3..715b3ad3 100644 --- a/mlprec/impl/mld_d_hierarchy_bld.f90 +++ b/mlprec/impl/mld_d_hierarchy_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_d_smoothers_bld.f90 b/mlprec/impl/mld_d_smoothers_bld.f90 index 81981b45..fbab6abd 100644 --- a/mlprec/impl/mld_d_smoothers_bld.f90 +++ b/mlprec/impl/mld_d_smoothers_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_dcprecset.F90 b/mlprec/impl/mld_dcprecset.F90 index 99776960..7838dea6 100644 --- a/mlprec/impl/mld_dcprecset.F90 +++ b/mlprec/impl/mld_dcprecset.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_dfile_prec_descr.f90 b/mlprec/impl/mld_dfile_prec_descr.f90 index ab5fc662..d129e434 100644 --- a/mlprec/impl/mld_dfile_prec_descr.f90 +++ b/mlprec/impl/mld_dfile_prec_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_dmlprec_aply.f90 b/mlprec/impl/mld_dmlprec_aply.f90 index 601c25a9..98a19c77 100644 --- a/mlprec/impl/mld_dmlprec_aply.f90 +++ b/mlprec/impl/mld_dmlprec_aply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_dmlprec_bld.f90 b/mlprec/impl/mld_dmlprec_bld.f90 index 5ce1fbf4..c19b8799 100644 --- a/mlprec/impl/mld_dmlprec_bld.f90 +++ b/mlprec/impl/mld_dmlprec_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_dprecaply.f90 b/mlprec/impl/mld_dprecaply.f90 index 27e78fc3..07c62d91 100644 --- a/mlprec/impl/mld_dprecaply.f90 +++ b/mlprec/impl/mld_dprecaply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_dprecbld.f90 b/mlprec/impl/mld_dprecbld.f90 index 6f6bd661..447d5a22 100644 --- a/mlprec/impl/mld_dprecbld.f90 +++ b/mlprec/impl/mld_dprecbld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_dprecinit.F90 b/mlprec/impl/mld_dprecinit.F90 index d86c32d4..0699fdd6 100644 --- a/mlprec/impl/mld_dprecinit.F90 +++ b/mlprec/impl/mld_dprecinit.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_dprecset.F90 b/mlprec/impl/mld_dprecset.F90 index 8dfaa034..aa4bf23c 100644 --- a/mlprec/impl/mld_dprecset.F90 +++ b/mlprec/impl/mld_dprecset.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_s_extprol_bld.f90 b/mlprec/impl/mld_s_extprol_bld.f90 index bfe54fbc..411c0bde 100644 --- a/mlprec/impl/mld_s_extprol_bld.f90 +++ b/mlprec/impl/mld_s_extprol_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! @@ -35,9 +35,9 @@ ! POSSIBILITY OF SUCH DAMAGE. ! ! -! File: mld_s_hierarchy_bld.f90 +! File: mld_s_extprol_bld.f90 ! -! Subroutine: mld_s_hierarchy_bld +! Subroutine: mld_s_extprol_bld ! Version: real ! ! This routine builds the preconditioner according to the requirements made by @@ -312,7 +312,7 @@ subroutine mld_s_extprol_bld(a,desc_a,p,prolv,restrv,info,amold,vmold,imold) if (info /= psb_success_) then call psb_errpush(psb_err_internal_error_,name,& - & a_err='Internal hierarchy build' ) + & a_err='Internal extprol build' ) goto 9999 endif diff --git a/mlprec/impl/mld_s_hierarchy_bld.f90 b/mlprec/impl/mld_s_hierarchy_bld.f90 index a579348b..f97e4472 100644 --- a/mlprec/impl/mld_s_hierarchy_bld.f90 +++ b/mlprec/impl/mld_s_hierarchy_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_s_smoothers_bld.f90 b/mlprec/impl/mld_s_smoothers_bld.f90 index 9191e791..e5b394bc 100644 --- a/mlprec/impl/mld_s_smoothers_bld.f90 +++ b/mlprec/impl/mld_s_smoothers_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_scprecset.F90 b/mlprec/impl/mld_scprecset.F90 index 2a355989..b887d878 100644 --- a/mlprec/impl/mld_scprecset.F90 +++ b/mlprec/impl/mld_scprecset.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_sfile_prec_descr.f90 b/mlprec/impl/mld_sfile_prec_descr.f90 index 1ce5bd14..c90976e2 100644 --- a/mlprec/impl/mld_sfile_prec_descr.f90 +++ b/mlprec/impl/mld_sfile_prec_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_smlprec_aply.f90 b/mlprec/impl/mld_smlprec_aply.f90 index 5967d42e..c9fef2b5 100644 --- a/mlprec/impl/mld_smlprec_aply.f90 +++ b/mlprec/impl/mld_smlprec_aply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_smlprec_bld.f90 b/mlprec/impl/mld_smlprec_bld.f90 index 442d8240..c22f0035 100644 --- a/mlprec/impl/mld_smlprec_bld.f90 +++ b/mlprec/impl/mld_smlprec_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_sprecaply.f90 b/mlprec/impl/mld_sprecaply.f90 index 79d6d8e3..34d7bee0 100644 --- a/mlprec/impl/mld_sprecaply.f90 +++ b/mlprec/impl/mld_sprecaply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_sprecbld.f90 b/mlprec/impl/mld_sprecbld.f90 index c55d344b..558e506b 100644 --- a/mlprec/impl/mld_sprecbld.f90 +++ b/mlprec/impl/mld_sprecbld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_sprecinit.F90 b/mlprec/impl/mld_sprecinit.F90 index 632f5706..72bd578e 100644 --- a/mlprec/impl/mld_sprecinit.F90 +++ b/mlprec/impl/mld_sprecinit.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_sprecset.F90 b/mlprec/impl/mld_sprecset.F90 index 90752348..3780e959 100644 --- a/mlprec/impl/mld_sprecset.F90 +++ b/mlprec/impl/mld_sprecset.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_z_extprol_bld.f90 b/mlprec/impl/mld_z_extprol_bld.f90 index 04805ade..4f856c69 100644 --- a/mlprec/impl/mld_z_extprol_bld.f90 +++ b/mlprec/impl/mld_z_extprol_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! @@ -35,9 +35,9 @@ ! POSSIBILITY OF SUCH DAMAGE. ! ! -! File: mld_z_hierarchy_bld.f90 +! File: mld_z_extprol_bld.f90 ! -! Subroutine: mld_z_hierarchy_bld +! Subroutine: mld_z_extprol_bld ! Version: real ! ! This routine builds the preconditioner according to the requirements made by @@ -312,7 +312,7 @@ subroutine mld_z_extprol_bld(a,desc_a,p,prolv,restrv,info,amold,vmold,imold) if (info /= psb_success_) then call psb_errpush(psb_err_internal_error_,name,& - & a_err='Internal hierarchy build' ) + & a_err='Internal extprol build' ) goto 9999 endif diff --git a/mlprec/impl/mld_z_hierarchy_bld.f90 b/mlprec/impl/mld_z_hierarchy_bld.f90 index eeafc9f7..cf6f2ad3 100644 --- a/mlprec/impl/mld_z_hierarchy_bld.f90 +++ b/mlprec/impl/mld_z_hierarchy_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_z_smoothers_bld.f90 b/mlprec/impl/mld_z_smoothers_bld.f90 index 24f99cd3..03d6c6f2 100644 --- a/mlprec/impl/mld_z_smoothers_bld.f90 +++ b/mlprec/impl/mld_z_smoothers_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_zcprecset.F90 b/mlprec/impl/mld_zcprecset.F90 index 1eedb04e..871a03d4 100644 --- a/mlprec/impl/mld_zcprecset.F90 +++ b/mlprec/impl/mld_zcprecset.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_zfile_prec_descr.f90 b/mlprec/impl/mld_zfile_prec_descr.f90 index 31faa261..e54e3a4f 100644 --- a/mlprec/impl/mld_zfile_prec_descr.f90 +++ b/mlprec/impl/mld_zfile_prec_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_zmlprec_aply.f90 b/mlprec/impl/mld_zmlprec_aply.f90 index 7f756c34..bbac15d1 100644 --- a/mlprec/impl/mld_zmlprec_aply.f90 +++ b/mlprec/impl/mld_zmlprec_aply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_zmlprec_bld.f90 b/mlprec/impl/mld_zmlprec_bld.f90 index cbf04032..11ce745d 100644 --- a/mlprec/impl/mld_zmlprec_bld.f90 +++ b/mlprec/impl/mld_zmlprec_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_zprecaply.f90 b/mlprec/impl/mld_zprecaply.f90 index ca5daccd..66c7a224 100644 --- a/mlprec/impl/mld_zprecaply.f90 +++ b/mlprec/impl/mld_zprecaply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_zprecbld.f90 b/mlprec/impl/mld_zprecbld.f90 index 0ffaa962..32306d6b 100644 --- a/mlprec/impl/mld_zprecbld.f90 +++ b/mlprec/impl/mld_zprecbld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_zprecinit.F90 b/mlprec/impl/mld_zprecinit.F90 index 22a585ef..0bf8ce05 100644 --- a/mlprec/impl/mld_zprecinit.F90 +++ b/mlprec/impl/mld_zprecinit.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/mld_zprecset.F90 b/mlprec/impl/mld_zprecset.F90 index a3f74cad..da553cb1 100644 --- a/mlprec/impl/mld_zprecset.F90 +++ b/mlprec/impl/mld_zprecset.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_as_smoother_apply.f90 b/mlprec/impl/smoother/mld_c_as_smoother_apply.f90 index 9af16fc1..b2687cce 100644 --- a/mlprec/impl/smoother/mld_c_as_smoother_apply.f90 +++ b/mlprec/impl/smoother/mld_c_as_smoother_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_as_smoother_apply_vect.f90 b/mlprec/impl/smoother/mld_c_as_smoother_apply_vect.f90 index c991652a..55b0d94a 100644 --- a/mlprec/impl/smoother/mld_c_as_smoother_apply_vect.f90 +++ b/mlprec/impl/smoother/mld_c_as_smoother_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_as_smoother_bld.f90 b/mlprec/impl/smoother/mld_c_as_smoother_bld.f90 index 3e39e298..2553354a 100644 --- a/mlprec/impl/smoother/mld_c_as_smoother_bld.f90 +++ b/mlprec/impl/smoother/mld_c_as_smoother_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_as_smoother_check.f90 b/mlprec/impl/smoother/mld_c_as_smoother_check.f90 index acb289ae..29172630 100644 --- a/mlprec/impl/smoother/mld_c_as_smoother_check.f90 +++ b/mlprec/impl/smoother/mld_c_as_smoother_check.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_as_smoother_clone.f90 b/mlprec/impl/smoother/mld_c_as_smoother_clone.f90 index 0c6be044..badcf5ca 100644 --- a/mlprec/impl/smoother/mld_c_as_smoother_clone.f90 +++ b/mlprec/impl/smoother/mld_c_as_smoother_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_as_smoother_cnv.f90 b/mlprec/impl/smoother/mld_c_as_smoother_cnv.f90 index 982f8bbf..a45259ea 100644 --- a/mlprec/impl/smoother/mld_c_as_smoother_cnv.f90 +++ b/mlprec/impl/smoother/mld_c_as_smoother_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_as_smoother_csetc.f90 b/mlprec/impl/smoother/mld_c_as_smoother_csetc.f90 index 25c9ab76..b48f58ed 100644 --- a/mlprec/impl/smoother/mld_c_as_smoother_csetc.f90 +++ b/mlprec/impl/smoother/mld_c_as_smoother_csetc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_as_smoother_cseti.f90 b/mlprec/impl/smoother/mld_c_as_smoother_cseti.f90 index 6ba123e3..6414ed84 100644 --- a/mlprec/impl/smoother/mld_c_as_smoother_cseti.f90 +++ b/mlprec/impl/smoother/mld_c_as_smoother_cseti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_as_smoother_csetr.f90 b/mlprec/impl/smoother/mld_c_as_smoother_csetr.f90 index 5453d6bd..ea438b55 100644 --- a/mlprec/impl/smoother/mld_c_as_smoother_csetr.f90 +++ b/mlprec/impl/smoother/mld_c_as_smoother_csetr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_as_smoother_dmp.f90 b/mlprec/impl/smoother/mld_c_as_smoother_dmp.f90 index 27b2981a..ada54775 100644 --- a/mlprec/impl/smoother/mld_c_as_smoother_dmp.f90 +++ b/mlprec/impl/smoother/mld_c_as_smoother_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_as_smoother_free.f90 b/mlprec/impl/smoother/mld_c_as_smoother_free.f90 index b251a40a..3f299a89 100644 --- a/mlprec/impl/smoother/mld_c_as_smoother_free.f90 +++ b/mlprec/impl/smoother/mld_c_as_smoother_free.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_as_smoother_prol_a.f90 b/mlprec/impl/smoother/mld_c_as_smoother_prol_a.f90 index 3155ba45..b2b0e775 100644 --- a/mlprec/impl/smoother/mld_c_as_smoother_prol_a.f90 +++ b/mlprec/impl/smoother/mld_c_as_smoother_prol_a.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_as_smoother_prol_v.f90 b/mlprec/impl/smoother/mld_c_as_smoother_prol_v.f90 index 83299dc6..218f519f 100644 --- a/mlprec/impl/smoother/mld_c_as_smoother_prol_v.f90 +++ b/mlprec/impl/smoother/mld_c_as_smoother_prol_v.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_as_smoother_restr_a.f90 b/mlprec/impl/smoother/mld_c_as_smoother_restr_a.f90 index 1dac43e4..bf404987 100644 --- a/mlprec/impl/smoother/mld_c_as_smoother_restr_a.f90 +++ b/mlprec/impl/smoother/mld_c_as_smoother_restr_a.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_as_smoother_restr_v.f90 b/mlprec/impl/smoother/mld_c_as_smoother_restr_v.f90 index f0bc9668..111d4f89 100644 --- a/mlprec/impl/smoother/mld_c_as_smoother_restr_v.f90 +++ b/mlprec/impl/smoother/mld_c_as_smoother_restr_v.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_as_smoother_setc.f90 b/mlprec/impl/smoother/mld_c_as_smoother_setc.f90 index ebfd3fbf..abf19e45 100644 --- a/mlprec/impl/smoother/mld_c_as_smoother_setc.f90 +++ b/mlprec/impl/smoother/mld_c_as_smoother_setc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_as_smoother_seti.f90 b/mlprec/impl/smoother/mld_c_as_smoother_seti.f90 index 2fe97834..d401f944 100644 --- a/mlprec/impl/smoother/mld_c_as_smoother_seti.f90 +++ b/mlprec/impl/smoother/mld_c_as_smoother_seti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_as_smoother_setr.f90 b/mlprec/impl/smoother/mld_c_as_smoother_setr.f90 index cbccad75..46f6c546 100644 --- a/mlprec/impl/smoother/mld_c_as_smoother_setr.f90 +++ b/mlprec/impl/smoother/mld_c_as_smoother_setr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_base_smoother_apply.f90 b/mlprec/impl/smoother/mld_c_base_smoother_apply.f90 index 0b1ff96c..db1ea5f5 100644 --- a/mlprec/impl/smoother/mld_c_base_smoother_apply.f90 +++ b/mlprec/impl/smoother/mld_c_base_smoother_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_base_smoother_apply_vect.f90 b/mlprec/impl/smoother/mld_c_base_smoother_apply_vect.f90 index c0fe128a..1cf7ad7d 100644 --- a/mlprec/impl/smoother/mld_c_base_smoother_apply_vect.f90 +++ b/mlprec/impl/smoother/mld_c_base_smoother_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_base_smoother_bld.f90 b/mlprec/impl/smoother/mld_c_base_smoother_bld.f90 index 1c8f0026..29cf9613 100644 --- a/mlprec/impl/smoother/mld_c_base_smoother_bld.f90 +++ b/mlprec/impl/smoother/mld_c_base_smoother_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_base_smoother_check.f90 b/mlprec/impl/smoother/mld_c_base_smoother_check.f90 index 18a36b41..d88b17fe 100644 --- a/mlprec/impl/smoother/mld_c_base_smoother_check.f90 +++ b/mlprec/impl/smoother/mld_c_base_smoother_check.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_base_smoother_clone.f90 b/mlprec/impl/smoother/mld_c_base_smoother_clone.f90 index aa4a428c..4b3ad865 100644 --- a/mlprec/impl/smoother/mld_c_base_smoother_clone.f90 +++ b/mlprec/impl/smoother/mld_c_base_smoother_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_base_smoother_cnv.f90 b/mlprec/impl/smoother/mld_c_base_smoother_cnv.f90 index e5d97561..c04a111f 100644 --- a/mlprec/impl/smoother/mld_c_base_smoother_cnv.f90 +++ b/mlprec/impl/smoother/mld_c_base_smoother_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_base_smoother_csetc.f90 b/mlprec/impl/smoother/mld_c_base_smoother_csetc.f90 index 2c2a3de4..94387853 100644 --- a/mlprec/impl/smoother/mld_c_base_smoother_csetc.f90 +++ b/mlprec/impl/smoother/mld_c_base_smoother_csetc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_base_smoother_cseti.f90 b/mlprec/impl/smoother/mld_c_base_smoother_cseti.f90 index 5b3a09b9..d04cc545 100644 --- a/mlprec/impl/smoother/mld_c_base_smoother_cseti.f90 +++ b/mlprec/impl/smoother/mld_c_base_smoother_cseti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_base_smoother_csetr.f90 b/mlprec/impl/smoother/mld_c_base_smoother_csetr.f90 index 6b905022..6890258e 100644 --- a/mlprec/impl/smoother/mld_c_base_smoother_csetr.f90 +++ b/mlprec/impl/smoother/mld_c_base_smoother_csetr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_base_smoother_descr.f90 b/mlprec/impl/smoother/mld_c_base_smoother_descr.f90 index f36d135c..d2710d1d 100644 --- a/mlprec/impl/smoother/mld_c_base_smoother_descr.f90 +++ b/mlprec/impl/smoother/mld_c_base_smoother_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_base_smoother_dmp.f90 b/mlprec/impl/smoother/mld_c_base_smoother_dmp.f90 index a5902b3c..5ab50a52 100644 --- a/mlprec/impl/smoother/mld_c_base_smoother_dmp.f90 +++ b/mlprec/impl/smoother/mld_c_base_smoother_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_base_smoother_free.f90 b/mlprec/impl/smoother/mld_c_base_smoother_free.f90 index db2c20b6..73e2a9fc 100644 --- a/mlprec/impl/smoother/mld_c_base_smoother_free.f90 +++ b/mlprec/impl/smoother/mld_c_base_smoother_free.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_base_smoother_setc.f90 b/mlprec/impl/smoother/mld_c_base_smoother_setc.f90 index 102584a9..88b82f78 100644 --- a/mlprec/impl/smoother/mld_c_base_smoother_setc.f90 +++ b/mlprec/impl/smoother/mld_c_base_smoother_setc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_base_smoother_seti.f90 b/mlprec/impl/smoother/mld_c_base_smoother_seti.f90 index 16f96f6f..9ea67f47 100644 --- a/mlprec/impl/smoother/mld_c_base_smoother_seti.f90 +++ b/mlprec/impl/smoother/mld_c_base_smoother_seti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_base_smoother_setr.f90 b/mlprec/impl/smoother/mld_c_base_smoother_setr.f90 index 63841822..eaf9ca24 100644 --- a/mlprec/impl/smoother/mld_c_base_smoother_setr.f90 +++ b/mlprec/impl/smoother/mld_c_base_smoother_setr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_jac_smoother_apply.f90 b/mlprec/impl/smoother/mld_c_jac_smoother_apply.f90 index 93038949..f6078ae4 100644 --- a/mlprec/impl/smoother/mld_c_jac_smoother_apply.f90 +++ b/mlprec/impl/smoother/mld_c_jac_smoother_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_jac_smoother_apply_vect.f90 b/mlprec/impl/smoother/mld_c_jac_smoother_apply_vect.f90 index 2dbfe8f7..33430696 100644 --- a/mlprec/impl/smoother/mld_c_jac_smoother_apply_vect.f90 +++ b/mlprec/impl/smoother/mld_c_jac_smoother_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_jac_smoother_bld.f90 b/mlprec/impl/smoother/mld_c_jac_smoother_bld.f90 index d2c45d76..86e6b659 100644 --- a/mlprec/impl/smoother/mld_c_jac_smoother_bld.f90 +++ b/mlprec/impl/smoother/mld_c_jac_smoother_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_jac_smoother_clone.f90 b/mlprec/impl/smoother/mld_c_jac_smoother_clone.f90 index 4ba9648b..39270332 100644 --- a/mlprec/impl/smoother/mld_c_jac_smoother_clone.f90 +++ b/mlprec/impl/smoother/mld_c_jac_smoother_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_jac_smoother_cnv.f90 b/mlprec/impl/smoother/mld_c_jac_smoother_cnv.f90 index 15693916..7b963511 100644 --- a/mlprec/impl/smoother/mld_c_jac_smoother_cnv.f90 +++ b/mlprec/impl/smoother/mld_c_jac_smoother_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_jac_smoother_descr.f90 b/mlprec/impl/smoother/mld_c_jac_smoother_descr.f90 index 9cc7c231..3f3c0725 100644 --- a/mlprec/impl/smoother/mld_c_jac_smoother_descr.f90 +++ b/mlprec/impl/smoother/mld_c_jac_smoother_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_c_jac_smoother_dmp.f90 b/mlprec/impl/smoother/mld_c_jac_smoother_dmp.f90 index e36794a8..bfa05ed4 100644 --- a/mlprec/impl/smoother/mld_c_jac_smoother_dmp.f90 +++ b/mlprec/impl/smoother/mld_c_jac_smoother_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_as_smoother_apply.f90 b/mlprec/impl/smoother/mld_d_as_smoother_apply.f90 index 3a74fdf5..4a8835d9 100644 --- a/mlprec/impl/smoother/mld_d_as_smoother_apply.f90 +++ b/mlprec/impl/smoother/mld_d_as_smoother_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_as_smoother_apply_vect.f90 b/mlprec/impl/smoother/mld_d_as_smoother_apply_vect.f90 index 7b4b119c..7ae8e8bf 100644 --- a/mlprec/impl/smoother/mld_d_as_smoother_apply_vect.f90 +++ b/mlprec/impl/smoother/mld_d_as_smoother_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_as_smoother_bld.f90 b/mlprec/impl/smoother/mld_d_as_smoother_bld.f90 index c2d62ac8..d385350f 100644 --- a/mlprec/impl/smoother/mld_d_as_smoother_bld.f90 +++ b/mlprec/impl/smoother/mld_d_as_smoother_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_as_smoother_check.f90 b/mlprec/impl/smoother/mld_d_as_smoother_check.f90 index d5b2c504..ef4be4e7 100644 --- a/mlprec/impl/smoother/mld_d_as_smoother_check.f90 +++ b/mlprec/impl/smoother/mld_d_as_smoother_check.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_as_smoother_clone.f90 b/mlprec/impl/smoother/mld_d_as_smoother_clone.f90 index 2f0c3d81..e84e670c 100644 --- a/mlprec/impl/smoother/mld_d_as_smoother_clone.f90 +++ b/mlprec/impl/smoother/mld_d_as_smoother_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_as_smoother_cnv.f90 b/mlprec/impl/smoother/mld_d_as_smoother_cnv.f90 index 22a42f9d..ce761966 100644 --- a/mlprec/impl/smoother/mld_d_as_smoother_cnv.f90 +++ b/mlprec/impl/smoother/mld_d_as_smoother_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_as_smoother_csetc.f90 b/mlprec/impl/smoother/mld_d_as_smoother_csetc.f90 index 0d01bcc3..13edd238 100644 --- a/mlprec/impl/smoother/mld_d_as_smoother_csetc.f90 +++ b/mlprec/impl/smoother/mld_d_as_smoother_csetc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_as_smoother_cseti.f90 b/mlprec/impl/smoother/mld_d_as_smoother_cseti.f90 index e148eba1..269e90ce 100644 --- a/mlprec/impl/smoother/mld_d_as_smoother_cseti.f90 +++ b/mlprec/impl/smoother/mld_d_as_smoother_cseti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_as_smoother_csetr.f90 b/mlprec/impl/smoother/mld_d_as_smoother_csetr.f90 index aa84ad3e..29324f20 100644 --- a/mlprec/impl/smoother/mld_d_as_smoother_csetr.f90 +++ b/mlprec/impl/smoother/mld_d_as_smoother_csetr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_as_smoother_dmp.f90 b/mlprec/impl/smoother/mld_d_as_smoother_dmp.f90 index e132ffd2..5929b06d 100644 --- a/mlprec/impl/smoother/mld_d_as_smoother_dmp.f90 +++ b/mlprec/impl/smoother/mld_d_as_smoother_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_as_smoother_free.f90 b/mlprec/impl/smoother/mld_d_as_smoother_free.f90 index 82b66be3..2b446d9d 100644 --- a/mlprec/impl/smoother/mld_d_as_smoother_free.f90 +++ b/mlprec/impl/smoother/mld_d_as_smoother_free.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_as_smoother_prol_a.f90 b/mlprec/impl/smoother/mld_d_as_smoother_prol_a.f90 index 4db22a62..97b1025e 100644 --- a/mlprec/impl/smoother/mld_d_as_smoother_prol_a.f90 +++ b/mlprec/impl/smoother/mld_d_as_smoother_prol_a.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_as_smoother_prol_v.f90 b/mlprec/impl/smoother/mld_d_as_smoother_prol_v.f90 index 1b587618..d616a16f 100644 --- a/mlprec/impl/smoother/mld_d_as_smoother_prol_v.f90 +++ b/mlprec/impl/smoother/mld_d_as_smoother_prol_v.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_as_smoother_restr_a.f90 b/mlprec/impl/smoother/mld_d_as_smoother_restr_a.f90 index 3e3f2e1e..f469ae6e 100644 --- a/mlprec/impl/smoother/mld_d_as_smoother_restr_a.f90 +++ b/mlprec/impl/smoother/mld_d_as_smoother_restr_a.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_as_smoother_restr_v.f90 b/mlprec/impl/smoother/mld_d_as_smoother_restr_v.f90 index 67f4a493..7c4eca48 100644 --- a/mlprec/impl/smoother/mld_d_as_smoother_restr_v.f90 +++ b/mlprec/impl/smoother/mld_d_as_smoother_restr_v.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_as_smoother_setc.f90 b/mlprec/impl/smoother/mld_d_as_smoother_setc.f90 index 50993348..c90c0cfb 100644 --- a/mlprec/impl/smoother/mld_d_as_smoother_setc.f90 +++ b/mlprec/impl/smoother/mld_d_as_smoother_setc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_as_smoother_seti.f90 b/mlprec/impl/smoother/mld_d_as_smoother_seti.f90 index 7bbfff48..2b84d5bb 100644 --- a/mlprec/impl/smoother/mld_d_as_smoother_seti.f90 +++ b/mlprec/impl/smoother/mld_d_as_smoother_seti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_as_smoother_setr.f90 b/mlprec/impl/smoother/mld_d_as_smoother_setr.f90 index 7fb75834..e87297a5 100644 --- a/mlprec/impl/smoother/mld_d_as_smoother_setr.f90 +++ b/mlprec/impl/smoother/mld_d_as_smoother_setr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_base_smoother_apply.f90 b/mlprec/impl/smoother/mld_d_base_smoother_apply.f90 index 7441ba8c..00b841c3 100644 --- a/mlprec/impl/smoother/mld_d_base_smoother_apply.f90 +++ b/mlprec/impl/smoother/mld_d_base_smoother_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_base_smoother_apply_vect.f90 b/mlprec/impl/smoother/mld_d_base_smoother_apply_vect.f90 index d81a6093..4a7dda3e 100644 --- a/mlprec/impl/smoother/mld_d_base_smoother_apply_vect.f90 +++ b/mlprec/impl/smoother/mld_d_base_smoother_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_base_smoother_bld.f90 b/mlprec/impl/smoother/mld_d_base_smoother_bld.f90 index f074ed6e..737c4a95 100644 --- a/mlprec/impl/smoother/mld_d_base_smoother_bld.f90 +++ b/mlprec/impl/smoother/mld_d_base_smoother_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_base_smoother_check.f90 b/mlprec/impl/smoother/mld_d_base_smoother_check.f90 index b0742813..339f2f3d 100644 --- a/mlprec/impl/smoother/mld_d_base_smoother_check.f90 +++ b/mlprec/impl/smoother/mld_d_base_smoother_check.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_base_smoother_clone.f90 b/mlprec/impl/smoother/mld_d_base_smoother_clone.f90 index 41a34afa..a596335a 100644 --- a/mlprec/impl/smoother/mld_d_base_smoother_clone.f90 +++ b/mlprec/impl/smoother/mld_d_base_smoother_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_base_smoother_cnv.f90 b/mlprec/impl/smoother/mld_d_base_smoother_cnv.f90 index e487b149..5518ac9b 100644 --- a/mlprec/impl/smoother/mld_d_base_smoother_cnv.f90 +++ b/mlprec/impl/smoother/mld_d_base_smoother_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_base_smoother_csetc.f90 b/mlprec/impl/smoother/mld_d_base_smoother_csetc.f90 index f6ae1630..64fb2902 100644 --- a/mlprec/impl/smoother/mld_d_base_smoother_csetc.f90 +++ b/mlprec/impl/smoother/mld_d_base_smoother_csetc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_base_smoother_cseti.f90 b/mlprec/impl/smoother/mld_d_base_smoother_cseti.f90 index ee9846b9..923288c8 100644 --- a/mlprec/impl/smoother/mld_d_base_smoother_cseti.f90 +++ b/mlprec/impl/smoother/mld_d_base_smoother_cseti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_base_smoother_csetr.f90 b/mlprec/impl/smoother/mld_d_base_smoother_csetr.f90 index de39a4b6..2048835f 100644 --- a/mlprec/impl/smoother/mld_d_base_smoother_csetr.f90 +++ b/mlprec/impl/smoother/mld_d_base_smoother_csetr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_base_smoother_descr.f90 b/mlprec/impl/smoother/mld_d_base_smoother_descr.f90 index a18d127e..da0a8bf1 100644 --- a/mlprec/impl/smoother/mld_d_base_smoother_descr.f90 +++ b/mlprec/impl/smoother/mld_d_base_smoother_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_base_smoother_dmp.f90 b/mlprec/impl/smoother/mld_d_base_smoother_dmp.f90 index dce0f67a..900a91ed 100644 --- a/mlprec/impl/smoother/mld_d_base_smoother_dmp.f90 +++ b/mlprec/impl/smoother/mld_d_base_smoother_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_base_smoother_free.f90 b/mlprec/impl/smoother/mld_d_base_smoother_free.f90 index f53452a6..624fd718 100644 --- a/mlprec/impl/smoother/mld_d_base_smoother_free.f90 +++ b/mlprec/impl/smoother/mld_d_base_smoother_free.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_base_smoother_setc.f90 b/mlprec/impl/smoother/mld_d_base_smoother_setc.f90 index 000bb1c8..cf5f34e8 100644 --- a/mlprec/impl/smoother/mld_d_base_smoother_setc.f90 +++ b/mlprec/impl/smoother/mld_d_base_smoother_setc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_base_smoother_seti.f90 b/mlprec/impl/smoother/mld_d_base_smoother_seti.f90 index 88d3e1d3..ea9deef4 100644 --- a/mlprec/impl/smoother/mld_d_base_smoother_seti.f90 +++ b/mlprec/impl/smoother/mld_d_base_smoother_seti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_base_smoother_setr.f90 b/mlprec/impl/smoother/mld_d_base_smoother_setr.f90 index 43041411..80f5ec7f 100644 --- a/mlprec/impl/smoother/mld_d_base_smoother_setr.f90 +++ b/mlprec/impl/smoother/mld_d_base_smoother_setr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_jac_smoother_apply.f90 b/mlprec/impl/smoother/mld_d_jac_smoother_apply.f90 index 1bee2bf3..fa5d27af 100644 --- a/mlprec/impl/smoother/mld_d_jac_smoother_apply.f90 +++ b/mlprec/impl/smoother/mld_d_jac_smoother_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_jac_smoother_apply_vect.f90 b/mlprec/impl/smoother/mld_d_jac_smoother_apply_vect.f90 index 92fe746a..11ab24b7 100644 --- a/mlprec/impl/smoother/mld_d_jac_smoother_apply_vect.f90 +++ b/mlprec/impl/smoother/mld_d_jac_smoother_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_jac_smoother_bld.f90 b/mlprec/impl/smoother/mld_d_jac_smoother_bld.f90 index 166b0e5c..033136cc 100644 --- a/mlprec/impl/smoother/mld_d_jac_smoother_bld.f90 +++ b/mlprec/impl/smoother/mld_d_jac_smoother_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_jac_smoother_clone.f90 b/mlprec/impl/smoother/mld_d_jac_smoother_clone.f90 index 180249fa..3408d225 100644 --- a/mlprec/impl/smoother/mld_d_jac_smoother_clone.f90 +++ b/mlprec/impl/smoother/mld_d_jac_smoother_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_jac_smoother_cnv.f90 b/mlprec/impl/smoother/mld_d_jac_smoother_cnv.f90 index 7bcfbe1b..0218e90c 100644 --- a/mlprec/impl/smoother/mld_d_jac_smoother_cnv.f90 +++ b/mlprec/impl/smoother/mld_d_jac_smoother_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_jac_smoother_descr.f90 b/mlprec/impl/smoother/mld_d_jac_smoother_descr.f90 index 5ade060c..4c738905 100644 --- a/mlprec/impl/smoother/mld_d_jac_smoother_descr.f90 +++ b/mlprec/impl/smoother/mld_d_jac_smoother_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_d_jac_smoother_dmp.f90 b/mlprec/impl/smoother/mld_d_jac_smoother_dmp.f90 index 44e63a35..811cee25 100644 --- a/mlprec/impl/smoother/mld_d_jac_smoother_dmp.f90 +++ b/mlprec/impl/smoother/mld_d_jac_smoother_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_as_smoother_apply.f90 b/mlprec/impl/smoother/mld_s_as_smoother_apply.f90 index b4a83811..0dbb467e 100644 --- a/mlprec/impl/smoother/mld_s_as_smoother_apply.f90 +++ b/mlprec/impl/smoother/mld_s_as_smoother_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_as_smoother_apply_vect.f90 b/mlprec/impl/smoother/mld_s_as_smoother_apply_vect.f90 index a25688fd..e20643ba 100644 --- a/mlprec/impl/smoother/mld_s_as_smoother_apply_vect.f90 +++ b/mlprec/impl/smoother/mld_s_as_smoother_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_as_smoother_bld.f90 b/mlprec/impl/smoother/mld_s_as_smoother_bld.f90 index 7ba5c86f..c1cb55c7 100644 --- a/mlprec/impl/smoother/mld_s_as_smoother_bld.f90 +++ b/mlprec/impl/smoother/mld_s_as_smoother_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_as_smoother_check.f90 b/mlprec/impl/smoother/mld_s_as_smoother_check.f90 index b381dfe3..06cbaf7f 100644 --- a/mlprec/impl/smoother/mld_s_as_smoother_check.f90 +++ b/mlprec/impl/smoother/mld_s_as_smoother_check.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_as_smoother_clone.f90 b/mlprec/impl/smoother/mld_s_as_smoother_clone.f90 index d423f28a..6076c287 100644 --- a/mlprec/impl/smoother/mld_s_as_smoother_clone.f90 +++ b/mlprec/impl/smoother/mld_s_as_smoother_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_as_smoother_cnv.f90 b/mlprec/impl/smoother/mld_s_as_smoother_cnv.f90 index e25ee374..a71dc5fe 100644 --- a/mlprec/impl/smoother/mld_s_as_smoother_cnv.f90 +++ b/mlprec/impl/smoother/mld_s_as_smoother_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_as_smoother_csetc.f90 b/mlprec/impl/smoother/mld_s_as_smoother_csetc.f90 index 130cfb81..08abf889 100644 --- a/mlprec/impl/smoother/mld_s_as_smoother_csetc.f90 +++ b/mlprec/impl/smoother/mld_s_as_smoother_csetc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_as_smoother_cseti.f90 b/mlprec/impl/smoother/mld_s_as_smoother_cseti.f90 index 27c76589..53950e47 100644 --- a/mlprec/impl/smoother/mld_s_as_smoother_cseti.f90 +++ b/mlprec/impl/smoother/mld_s_as_smoother_cseti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_as_smoother_csetr.f90 b/mlprec/impl/smoother/mld_s_as_smoother_csetr.f90 index 6d70cae9..5cdb1a35 100644 --- a/mlprec/impl/smoother/mld_s_as_smoother_csetr.f90 +++ b/mlprec/impl/smoother/mld_s_as_smoother_csetr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_as_smoother_dmp.f90 b/mlprec/impl/smoother/mld_s_as_smoother_dmp.f90 index ddcb0968..f35859b7 100644 --- a/mlprec/impl/smoother/mld_s_as_smoother_dmp.f90 +++ b/mlprec/impl/smoother/mld_s_as_smoother_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_as_smoother_free.f90 b/mlprec/impl/smoother/mld_s_as_smoother_free.f90 index 986f7eb4..5a632a42 100644 --- a/mlprec/impl/smoother/mld_s_as_smoother_free.f90 +++ b/mlprec/impl/smoother/mld_s_as_smoother_free.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_as_smoother_prol_a.f90 b/mlprec/impl/smoother/mld_s_as_smoother_prol_a.f90 index b15d9bee..caba1267 100644 --- a/mlprec/impl/smoother/mld_s_as_smoother_prol_a.f90 +++ b/mlprec/impl/smoother/mld_s_as_smoother_prol_a.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_as_smoother_prol_v.f90 b/mlprec/impl/smoother/mld_s_as_smoother_prol_v.f90 index d27e004a..f5516309 100644 --- a/mlprec/impl/smoother/mld_s_as_smoother_prol_v.f90 +++ b/mlprec/impl/smoother/mld_s_as_smoother_prol_v.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_as_smoother_restr_a.f90 b/mlprec/impl/smoother/mld_s_as_smoother_restr_a.f90 index bc5ca0b4..3055e987 100644 --- a/mlprec/impl/smoother/mld_s_as_smoother_restr_a.f90 +++ b/mlprec/impl/smoother/mld_s_as_smoother_restr_a.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_as_smoother_restr_v.f90 b/mlprec/impl/smoother/mld_s_as_smoother_restr_v.f90 index aed6bad2..f6a82d9d 100644 --- a/mlprec/impl/smoother/mld_s_as_smoother_restr_v.f90 +++ b/mlprec/impl/smoother/mld_s_as_smoother_restr_v.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_as_smoother_setc.f90 b/mlprec/impl/smoother/mld_s_as_smoother_setc.f90 index d9dccccc..842fa945 100644 --- a/mlprec/impl/smoother/mld_s_as_smoother_setc.f90 +++ b/mlprec/impl/smoother/mld_s_as_smoother_setc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_as_smoother_seti.f90 b/mlprec/impl/smoother/mld_s_as_smoother_seti.f90 index 64bce301..c4fee0fd 100644 --- a/mlprec/impl/smoother/mld_s_as_smoother_seti.f90 +++ b/mlprec/impl/smoother/mld_s_as_smoother_seti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_as_smoother_setr.f90 b/mlprec/impl/smoother/mld_s_as_smoother_setr.f90 index 1ea37d9e..1eb9fe99 100644 --- a/mlprec/impl/smoother/mld_s_as_smoother_setr.f90 +++ b/mlprec/impl/smoother/mld_s_as_smoother_setr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_base_smoother_apply.f90 b/mlprec/impl/smoother/mld_s_base_smoother_apply.f90 index 4197e7d1..e74a4d96 100644 --- a/mlprec/impl/smoother/mld_s_base_smoother_apply.f90 +++ b/mlprec/impl/smoother/mld_s_base_smoother_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_base_smoother_apply_vect.f90 b/mlprec/impl/smoother/mld_s_base_smoother_apply_vect.f90 index f9336a06..ab2fd275 100644 --- a/mlprec/impl/smoother/mld_s_base_smoother_apply_vect.f90 +++ b/mlprec/impl/smoother/mld_s_base_smoother_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_base_smoother_bld.f90 b/mlprec/impl/smoother/mld_s_base_smoother_bld.f90 index 2659f1bd..99e6ea78 100644 --- a/mlprec/impl/smoother/mld_s_base_smoother_bld.f90 +++ b/mlprec/impl/smoother/mld_s_base_smoother_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_base_smoother_check.f90 b/mlprec/impl/smoother/mld_s_base_smoother_check.f90 index 7bcd79dc..06a34223 100644 --- a/mlprec/impl/smoother/mld_s_base_smoother_check.f90 +++ b/mlprec/impl/smoother/mld_s_base_smoother_check.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_base_smoother_clone.f90 b/mlprec/impl/smoother/mld_s_base_smoother_clone.f90 index 43e51b24..231ec5a4 100644 --- a/mlprec/impl/smoother/mld_s_base_smoother_clone.f90 +++ b/mlprec/impl/smoother/mld_s_base_smoother_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_base_smoother_cnv.f90 b/mlprec/impl/smoother/mld_s_base_smoother_cnv.f90 index 2136eb5b..4dad645d 100644 --- a/mlprec/impl/smoother/mld_s_base_smoother_cnv.f90 +++ b/mlprec/impl/smoother/mld_s_base_smoother_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_base_smoother_csetc.f90 b/mlprec/impl/smoother/mld_s_base_smoother_csetc.f90 index 291f5db6..27c7d700 100644 --- a/mlprec/impl/smoother/mld_s_base_smoother_csetc.f90 +++ b/mlprec/impl/smoother/mld_s_base_smoother_csetc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_base_smoother_cseti.f90 b/mlprec/impl/smoother/mld_s_base_smoother_cseti.f90 index 792ff441..81808a41 100644 --- a/mlprec/impl/smoother/mld_s_base_smoother_cseti.f90 +++ b/mlprec/impl/smoother/mld_s_base_smoother_cseti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_base_smoother_csetr.f90 b/mlprec/impl/smoother/mld_s_base_smoother_csetr.f90 index b02c9b27..2e20b226 100644 --- a/mlprec/impl/smoother/mld_s_base_smoother_csetr.f90 +++ b/mlprec/impl/smoother/mld_s_base_smoother_csetr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_base_smoother_descr.f90 b/mlprec/impl/smoother/mld_s_base_smoother_descr.f90 index 876c8cd6..404e3829 100644 --- a/mlprec/impl/smoother/mld_s_base_smoother_descr.f90 +++ b/mlprec/impl/smoother/mld_s_base_smoother_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_base_smoother_dmp.f90 b/mlprec/impl/smoother/mld_s_base_smoother_dmp.f90 index c6819461..a9fcf074 100644 --- a/mlprec/impl/smoother/mld_s_base_smoother_dmp.f90 +++ b/mlprec/impl/smoother/mld_s_base_smoother_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_base_smoother_free.f90 b/mlprec/impl/smoother/mld_s_base_smoother_free.f90 index 5bd7c61b..048bec71 100644 --- a/mlprec/impl/smoother/mld_s_base_smoother_free.f90 +++ b/mlprec/impl/smoother/mld_s_base_smoother_free.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_base_smoother_setc.f90 b/mlprec/impl/smoother/mld_s_base_smoother_setc.f90 index a54efa36..0e04cddf 100644 --- a/mlprec/impl/smoother/mld_s_base_smoother_setc.f90 +++ b/mlprec/impl/smoother/mld_s_base_smoother_setc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_base_smoother_seti.f90 b/mlprec/impl/smoother/mld_s_base_smoother_seti.f90 index d4296cd0..b840ce5e 100644 --- a/mlprec/impl/smoother/mld_s_base_smoother_seti.f90 +++ b/mlprec/impl/smoother/mld_s_base_smoother_seti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_base_smoother_setr.f90 b/mlprec/impl/smoother/mld_s_base_smoother_setr.f90 index e4a20136..4a0d4936 100644 --- a/mlprec/impl/smoother/mld_s_base_smoother_setr.f90 +++ b/mlprec/impl/smoother/mld_s_base_smoother_setr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_jac_smoother_apply.f90 b/mlprec/impl/smoother/mld_s_jac_smoother_apply.f90 index 5880b124..73aa68b7 100644 --- a/mlprec/impl/smoother/mld_s_jac_smoother_apply.f90 +++ b/mlprec/impl/smoother/mld_s_jac_smoother_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_jac_smoother_apply_vect.f90 b/mlprec/impl/smoother/mld_s_jac_smoother_apply_vect.f90 index 1665050e..8d905796 100644 --- a/mlprec/impl/smoother/mld_s_jac_smoother_apply_vect.f90 +++ b/mlprec/impl/smoother/mld_s_jac_smoother_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_jac_smoother_bld.f90 b/mlprec/impl/smoother/mld_s_jac_smoother_bld.f90 index d96da7b3..5ab0b99e 100644 --- a/mlprec/impl/smoother/mld_s_jac_smoother_bld.f90 +++ b/mlprec/impl/smoother/mld_s_jac_smoother_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_jac_smoother_clone.f90 b/mlprec/impl/smoother/mld_s_jac_smoother_clone.f90 index 1ee27924..ecb850b5 100644 --- a/mlprec/impl/smoother/mld_s_jac_smoother_clone.f90 +++ b/mlprec/impl/smoother/mld_s_jac_smoother_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_jac_smoother_cnv.f90 b/mlprec/impl/smoother/mld_s_jac_smoother_cnv.f90 index d05cf8f5..792a7872 100644 --- a/mlprec/impl/smoother/mld_s_jac_smoother_cnv.f90 +++ b/mlprec/impl/smoother/mld_s_jac_smoother_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_jac_smoother_descr.f90 b/mlprec/impl/smoother/mld_s_jac_smoother_descr.f90 index d8e08461..820a246b 100644 --- a/mlprec/impl/smoother/mld_s_jac_smoother_descr.f90 +++ b/mlprec/impl/smoother/mld_s_jac_smoother_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_s_jac_smoother_dmp.f90 b/mlprec/impl/smoother/mld_s_jac_smoother_dmp.f90 index 13585519..e1c14975 100644 --- a/mlprec/impl/smoother/mld_s_jac_smoother_dmp.f90 +++ b/mlprec/impl/smoother/mld_s_jac_smoother_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_as_smoother_apply.f90 b/mlprec/impl/smoother/mld_z_as_smoother_apply.f90 index 9bc7dae4..a0e18c1a 100644 --- a/mlprec/impl/smoother/mld_z_as_smoother_apply.f90 +++ b/mlprec/impl/smoother/mld_z_as_smoother_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_as_smoother_apply_vect.f90 b/mlprec/impl/smoother/mld_z_as_smoother_apply_vect.f90 index e21ccf69..53bf90f6 100644 --- a/mlprec/impl/smoother/mld_z_as_smoother_apply_vect.f90 +++ b/mlprec/impl/smoother/mld_z_as_smoother_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_as_smoother_bld.f90 b/mlprec/impl/smoother/mld_z_as_smoother_bld.f90 index e92e78c9..43f97d1d 100644 --- a/mlprec/impl/smoother/mld_z_as_smoother_bld.f90 +++ b/mlprec/impl/smoother/mld_z_as_smoother_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_as_smoother_check.f90 b/mlprec/impl/smoother/mld_z_as_smoother_check.f90 index 5df26e1f..4fe4d6fe 100644 --- a/mlprec/impl/smoother/mld_z_as_smoother_check.f90 +++ b/mlprec/impl/smoother/mld_z_as_smoother_check.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_as_smoother_clone.f90 b/mlprec/impl/smoother/mld_z_as_smoother_clone.f90 index 2dc91fa6..c192cdc6 100644 --- a/mlprec/impl/smoother/mld_z_as_smoother_clone.f90 +++ b/mlprec/impl/smoother/mld_z_as_smoother_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_as_smoother_cnv.f90 b/mlprec/impl/smoother/mld_z_as_smoother_cnv.f90 index 5f53ea74..716fb2a7 100644 --- a/mlprec/impl/smoother/mld_z_as_smoother_cnv.f90 +++ b/mlprec/impl/smoother/mld_z_as_smoother_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_as_smoother_csetc.f90 b/mlprec/impl/smoother/mld_z_as_smoother_csetc.f90 index a79b08ed..553a2d20 100644 --- a/mlprec/impl/smoother/mld_z_as_smoother_csetc.f90 +++ b/mlprec/impl/smoother/mld_z_as_smoother_csetc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_as_smoother_cseti.f90 b/mlprec/impl/smoother/mld_z_as_smoother_cseti.f90 index ed0dbb75..0b7915be 100644 --- a/mlprec/impl/smoother/mld_z_as_smoother_cseti.f90 +++ b/mlprec/impl/smoother/mld_z_as_smoother_cseti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_as_smoother_csetr.f90 b/mlprec/impl/smoother/mld_z_as_smoother_csetr.f90 index faf31df3..c781b8ad 100644 --- a/mlprec/impl/smoother/mld_z_as_smoother_csetr.f90 +++ b/mlprec/impl/smoother/mld_z_as_smoother_csetr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_as_smoother_dmp.f90 b/mlprec/impl/smoother/mld_z_as_smoother_dmp.f90 index 339f0a8a..ecf10467 100644 --- a/mlprec/impl/smoother/mld_z_as_smoother_dmp.f90 +++ b/mlprec/impl/smoother/mld_z_as_smoother_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_as_smoother_free.f90 b/mlprec/impl/smoother/mld_z_as_smoother_free.f90 index 978dd459..6745ff10 100644 --- a/mlprec/impl/smoother/mld_z_as_smoother_free.f90 +++ b/mlprec/impl/smoother/mld_z_as_smoother_free.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_as_smoother_prol_a.f90 b/mlprec/impl/smoother/mld_z_as_smoother_prol_a.f90 index 892e7a2f..f320b923 100644 --- a/mlprec/impl/smoother/mld_z_as_smoother_prol_a.f90 +++ b/mlprec/impl/smoother/mld_z_as_smoother_prol_a.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_as_smoother_prol_v.f90 b/mlprec/impl/smoother/mld_z_as_smoother_prol_v.f90 index 7c2327c5..613c2005 100644 --- a/mlprec/impl/smoother/mld_z_as_smoother_prol_v.f90 +++ b/mlprec/impl/smoother/mld_z_as_smoother_prol_v.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_as_smoother_restr_a.f90 b/mlprec/impl/smoother/mld_z_as_smoother_restr_a.f90 index 21902f79..c56d72a5 100644 --- a/mlprec/impl/smoother/mld_z_as_smoother_restr_a.f90 +++ b/mlprec/impl/smoother/mld_z_as_smoother_restr_a.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_as_smoother_restr_v.f90 b/mlprec/impl/smoother/mld_z_as_smoother_restr_v.f90 index 2add349d..154c0572 100644 --- a/mlprec/impl/smoother/mld_z_as_smoother_restr_v.f90 +++ b/mlprec/impl/smoother/mld_z_as_smoother_restr_v.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_as_smoother_setc.f90 b/mlprec/impl/smoother/mld_z_as_smoother_setc.f90 index 20fe12b9..c928b1aa 100644 --- a/mlprec/impl/smoother/mld_z_as_smoother_setc.f90 +++ b/mlprec/impl/smoother/mld_z_as_smoother_setc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_as_smoother_seti.f90 b/mlprec/impl/smoother/mld_z_as_smoother_seti.f90 index bf61a7f0..ba29e8ec 100644 --- a/mlprec/impl/smoother/mld_z_as_smoother_seti.f90 +++ b/mlprec/impl/smoother/mld_z_as_smoother_seti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_as_smoother_setr.f90 b/mlprec/impl/smoother/mld_z_as_smoother_setr.f90 index cf322b20..88f54237 100644 --- a/mlprec/impl/smoother/mld_z_as_smoother_setr.f90 +++ b/mlprec/impl/smoother/mld_z_as_smoother_setr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_base_smoother_apply.f90 b/mlprec/impl/smoother/mld_z_base_smoother_apply.f90 index fd7521b1..b0013a85 100644 --- a/mlprec/impl/smoother/mld_z_base_smoother_apply.f90 +++ b/mlprec/impl/smoother/mld_z_base_smoother_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_base_smoother_apply_vect.f90 b/mlprec/impl/smoother/mld_z_base_smoother_apply_vect.f90 index ff339bf6..dc8c7578 100644 --- a/mlprec/impl/smoother/mld_z_base_smoother_apply_vect.f90 +++ b/mlprec/impl/smoother/mld_z_base_smoother_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_base_smoother_bld.f90 b/mlprec/impl/smoother/mld_z_base_smoother_bld.f90 index 01db6b89..52f061aa 100644 --- a/mlprec/impl/smoother/mld_z_base_smoother_bld.f90 +++ b/mlprec/impl/smoother/mld_z_base_smoother_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_base_smoother_check.f90 b/mlprec/impl/smoother/mld_z_base_smoother_check.f90 index 65c8ac46..ceb2fe37 100644 --- a/mlprec/impl/smoother/mld_z_base_smoother_check.f90 +++ b/mlprec/impl/smoother/mld_z_base_smoother_check.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_base_smoother_clone.f90 b/mlprec/impl/smoother/mld_z_base_smoother_clone.f90 index 45076f06..5a0efdc8 100644 --- a/mlprec/impl/smoother/mld_z_base_smoother_clone.f90 +++ b/mlprec/impl/smoother/mld_z_base_smoother_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_base_smoother_cnv.f90 b/mlprec/impl/smoother/mld_z_base_smoother_cnv.f90 index 53604e84..aed4fe2e 100644 --- a/mlprec/impl/smoother/mld_z_base_smoother_cnv.f90 +++ b/mlprec/impl/smoother/mld_z_base_smoother_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_base_smoother_csetc.f90 b/mlprec/impl/smoother/mld_z_base_smoother_csetc.f90 index da8977fa..361fc3a0 100644 --- a/mlprec/impl/smoother/mld_z_base_smoother_csetc.f90 +++ b/mlprec/impl/smoother/mld_z_base_smoother_csetc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_base_smoother_cseti.f90 b/mlprec/impl/smoother/mld_z_base_smoother_cseti.f90 index 0bb67086..f87f49c5 100644 --- a/mlprec/impl/smoother/mld_z_base_smoother_cseti.f90 +++ b/mlprec/impl/smoother/mld_z_base_smoother_cseti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_base_smoother_csetr.f90 b/mlprec/impl/smoother/mld_z_base_smoother_csetr.f90 index d0789793..730df7ad 100644 --- a/mlprec/impl/smoother/mld_z_base_smoother_csetr.f90 +++ b/mlprec/impl/smoother/mld_z_base_smoother_csetr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_base_smoother_descr.f90 b/mlprec/impl/smoother/mld_z_base_smoother_descr.f90 index 264bd877..589485db 100644 --- a/mlprec/impl/smoother/mld_z_base_smoother_descr.f90 +++ b/mlprec/impl/smoother/mld_z_base_smoother_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_base_smoother_dmp.f90 b/mlprec/impl/smoother/mld_z_base_smoother_dmp.f90 index a7b23e49..27f83a56 100644 --- a/mlprec/impl/smoother/mld_z_base_smoother_dmp.f90 +++ b/mlprec/impl/smoother/mld_z_base_smoother_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_base_smoother_free.f90 b/mlprec/impl/smoother/mld_z_base_smoother_free.f90 index 2170ab93..4e0bc66b 100644 --- a/mlprec/impl/smoother/mld_z_base_smoother_free.f90 +++ b/mlprec/impl/smoother/mld_z_base_smoother_free.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_base_smoother_setc.f90 b/mlprec/impl/smoother/mld_z_base_smoother_setc.f90 index c6536229..cb342510 100644 --- a/mlprec/impl/smoother/mld_z_base_smoother_setc.f90 +++ b/mlprec/impl/smoother/mld_z_base_smoother_setc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_base_smoother_seti.f90 b/mlprec/impl/smoother/mld_z_base_smoother_seti.f90 index 8af31ea5..0c089f6b 100644 --- a/mlprec/impl/smoother/mld_z_base_smoother_seti.f90 +++ b/mlprec/impl/smoother/mld_z_base_smoother_seti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_base_smoother_setr.f90 b/mlprec/impl/smoother/mld_z_base_smoother_setr.f90 index 05a38043..330b4093 100644 --- a/mlprec/impl/smoother/mld_z_base_smoother_setr.f90 +++ b/mlprec/impl/smoother/mld_z_base_smoother_setr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_jac_smoother_apply.f90 b/mlprec/impl/smoother/mld_z_jac_smoother_apply.f90 index c65c8d1e..90d3e8dc 100644 --- a/mlprec/impl/smoother/mld_z_jac_smoother_apply.f90 +++ b/mlprec/impl/smoother/mld_z_jac_smoother_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_jac_smoother_apply_vect.f90 b/mlprec/impl/smoother/mld_z_jac_smoother_apply_vect.f90 index 97f66e95..dc43087f 100644 --- a/mlprec/impl/smoother/mld_z_jac_smoother_apply_vect.f90 +++ b/mlprec/impl/smoother/mld_z_jac_smoother_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_jac_smoother_bld.f90 b/mlprec/impl/smoother/mld_z_jac_smoother_bld.f90 index 2ede4327..5bb2cf7e 100644 --- a/mlprec/impl/smoother/mld_z_jac_smoother_bld.f90 +++ b/mlprec/impl/smoother/mld_z_jac_smoother_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_jac_smoother_clone.f90 b/mlprec/impl/smoother/mld_z_jac_smoother_clone.f90 index dca98ad6..a9060305 100644 --- a/mlprec/impl/smoother/mld_z_jac_smoother_clone.f90 +++ b/mlprec/impl/smoother/mld_z_jac_smoother_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_jac_smoother_cnv.f90 b/mlprec/impl/smoother/mld_z_jac_smoother_cnv.f90 index 197bb18d..76ac02e0 100644 --- a/mlprec/impl/smoother/mld_z_jac_smoother_cnv.f90 +++ b/mlprec/impl/smoother/mld_z_jac_smoother_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_jac_smoother_descr.f90 b/mlprec/impl/smoother/mld_z_jac_smoother_descr.f90 index d13cd7e1..d89d0846 100644 --- a/mlprec/impl/smoother/mld_z_jac_smoother_descr.f90 +++ b/mlprec/impl/smoother/mld_z_jac_smoother_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/smoother/mld_z_jac_smoother_dmp.f90 b/mlprec/impl/smoother/mld_z_jac_smoother_dmp.f90 index fd3f9cb3..1c4f3f24 100644 --- a/mlprec/impl/smoother/mld_z_jac_smoother_dmp.f90 +++ b/mlprec/impl/smoother/mld_z_jac_smoother_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_base_solver_apply.f90 b/mlprec/impl/solver/mld_c_base_solver_apply.f90 index 32d84514..d15667d9 100644 --- a/mlprec/impl/solver/mld_c_base_solver_apply.f90 +++ b/mlprec/impl/solver/mld_c_base_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_base_solver_apply_vect.f90 b/mlprec/impl/solver/mld_c_base_solver_apply_vect.f90 index 73ff50fc..46531fbf 100644 --- a/mlprec/impl/solver/mld_c_base_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_c_base_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_base_solver_bld.f90 b/mlprec/impl/solver/mld_c_base_solver_bld.f90 index f64ffc0b..3cd33de6 100644 --- a/mlprec/impl/solver/mld_c_base_solver_bld.f90 +++ b/mlprec/impl/solver/mld_c_base_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_base_solver_check.f90 b/mlprec/impl/solver/mld_c_base_solver_check.f90 index a658e76b..a4f62967 100644 --- a/mlprec/impl/solver/mld_c_base_solver_check.f90 +++ b/mlprec/impl/solver/mld_c_base_solver_check.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_base_solver_clone.f90 b/mlprec/impl/solver/mld_c_base_solver_clone.f90 index cbd74849..fc158c5c 100644 --- a/mlprec/impl/solver/mld_c_base_solver_clone.f90 +++ b/mlprec/impl/solver/mld_c_base_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_base_solver_cnv.f90 b/mlprec/impl/solver/mld_c_base_solver_cnv.f90 index 3a1c0086..1c8b9416 100644 --- a/mlprec/impl/solver/mld_c_base_solver_cnv.f90 +++ b/mlprec/impl/solver/mld_c_base_solver_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_base_solver_csetc.f90 b/mlprec/impl/solver/mld_c_base_solver_csetc.f90 index a74fae11..c11c2a23 100644 --- a/mlprec/impl/solver/mld_c_base_solver_csetc.f90 +++ b/mlprec/impl/solver/mld_c_base_solver_csetc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_base_solver_cseti.f90 b/mlprec/impl/solver/mld_c_base_solver_cseti.f90 index f26ceb73..34bda825 100644 --- a/mlprec/impl/solver/mld_c_base_solver_cseti.f90 +++ b/mlprec/impl/solver/mld_c_base_solver_cseti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_base_solver_csetr.f90 b/mlprec/impl/solver/mld_c_base_solver_csetr.f90 index a18ce5e6..5a210ded 100644 --- a/mlprec/impl/solver/mld_c_base_solver_csetr.f90 +++ b/mlprec/impl/solver/mld_c_base_solver_csetr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_base_solver_descr.f90 b/mlprec/impl/solver/mld_c_base_solver_descr.f90 index 2204f932..e988194c 100644 --- a/mlprec/impl/solver/mld_c_base_solver_descr.f90 +++ b/mlprec/impl/solver/mld_c_base_solver_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_base_solver_dmp.f90 b/mlprec/impl/solver/mld_c_base_solver_dmp.f90 index 2dfa0c3e..530a7ce4 100644 --- a/mlprec/impl/solver/mld_c_base_solver_dmp.f90 +++ b/mlprec/impl/solver/mld_c_base_solver_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_base_solver_free.f90 b/mlprec/impl/solver/mld_c_base_solver_free.f90 index 51a521de..27577351 100644 --- a/mlprec/impl/solver/mld_c_base_solver_free.f90 +++ b/mlprec/impl/solver/mld_c_base_solver_free.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_base_solver_setc.f90 b/mlprec/impl/solver/mld_c_base_solver_setc.f90 index a4e57ec6..53f1201e 100644 --- a/mlprec/impl/solver/mld_c_base_solver_setc.f90 +++ b/mlprec/impl/solver/mld_c_base_solver_setc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_base_solver_seti.f90 b/mlprec/impl/solver/mld_c_base_solver_seti.f90 index ee583eba..3a461e05 100644 --- a/mlprec/impl/solver/mld_c_base_solver_seti.f90 +++ b/mlprec/impl/solver/mld_c_base_solver_seti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_base_solver_setr.f90 b/mlprec/impl/solver/mld_c_base_solver_setr.f90 index 5d0be970..f6ea6371 100644 --- a/mlprec/impl/solver/mld_c_base_solver_setr.f90 +++ b/mlprec/impl/solver/mld_c_base_solver_setr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_bwgs_solver_apply.f90 b/mlprec/impl/solver/mld_c_bwgs_solver_apply.f90 index fdc1a2b5..fcd0f93f 100644 --- a/mlprec/impl/solver/mld_c_bwgs_solver_apply.f90 +++ b/mlprec/impl/solver/mld_c_bwgs_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_bwgs_solver_apply_vect.f90 b/mlprec/impl/solver/mld_c_bwgs_solver_apply_vect.f90 index 26166333..33d21fd1 100644 --- a/mlprec/impl/solver/mld_c_bwgs_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_c_bwgs_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_bwgs_solver_bld.f90 b/mlprec/impl/solver/mld_c_bwgs_solver_bld.f90 index 0135fa9f..04a5f12e 100644 --- a/mlprec/impl/solver/mld_c_bwgs_solver_bld.f90 +++ b/mlprec/impl/solver/mld_c_bwgs_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_diag_solver_apply.f90 b/mlprec/impl/solver/mld_c_diag_solver_apply.f90 index f9734b89..120e4c29 100644 --- a/mlprec/impl/solver/mld_c_diag_solver_apply.f90 +++ b/mlprec/impl/solver/mld_c_diag_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_diag_solver_apply_vect.f90 b/mlprec/impl/solver/mld_c_diag_solver_apply_vect.f90 index 7bbcb448..05841f2d 100644 --- a/mlprec/impl/solver/mld_c_diag_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_c_diag_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_diag_solver_bld.f90 b/mlprec/impl/solver/mld_c_diag_solver_bld.f90 index 5e0e057c..d0e5c19f 100644 --- a/mlprec/impl/solver/mld_c_diag_solver_bld.f90 +++ b/mlprec/impl/solver/mld_c_diag_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_diag_solver_clone.f90 b/mlprec/impl/solver/mld_c_diag_solver_clone.f90 index b75bfba8..1fd53b26 100644 --- a/mlprec/impl/solver/mld_c_diag_solver_clone.f90 +++ b/mlprec/impl/solver/mld_c_diag_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_diag_solver_cnv.f90 b/mlprec/impl/solver/mld_c_diag_solver_cnv.f90 index 41503ed0..e1375a21 100644 --- a/mlprec/impl/solver/mld_c_diag_solver_cnv.f90 +++ b/mlprec/impl/solver/mld_c_diag_solver_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_diag_solver_dmp.f90 b/mlprec/impl/solver/mld_c_diag_solver_dmp.f90 index 606b37af..63846d37 100644 --- a/mlprec/impl/solver/mld_c_diag_solver_dmp.f90 +++ b/mlprec/impl/solver/mld_c_diag_solver_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_gs_solver_apply.f90 b/mlprec/impl/solver/mld_c_gs_solver_apply.f90 index a5f1af4c..c5b15321 100644 --- a/mlprec/impl/solver/mld_c_gs_solver_apply.f90 +++ b/mlprec/impl/solver/mld_c_gs_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_gs_solver_apply_vect.f90 b/mlprec/impl/solver/mld_c_gs_solver_apply_vect.f90 index 8c43b64d..d0c9c326 100644 --- a/mlprec/impl/solver/mld_c_gs_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_c_gs_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_gs_solver_bld.f90 b/mlprec/impl/solver/mld_c_gs_solver_bld.f90 index 56e35fd6..b1052f2a 100644 --- a/mlprec/impl/solver/mld_c_gs_solver_bld.f90 +++ b/mlprec/impl/solver/mld_c_gs_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_gs_solver_clone.f90 b/mlprec/impl/solver/mld_c_gs_solver_clone.f90 index 321e8920..a48a30d3 100644 --- a/mlprec/impl/solver/mld_c_gs_solver_clone.f90 +++ b/mlprec/impl/solver/mld_c_gs_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_gs_solver_cnv.f90 b/mlprec/impl/solver/mld_c_gs_solver_cnv.f90 index 2c094df2..143a6618 100644 --- a/mlprec/impl/solver/mld_c_gs_solver_cnv.f90 +++ b/mlprec/impl/solver/mld_c_gs_solver_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_gs_solver_dmp.f90 b/mlprec/impl/solver/mld_c_gs_solver_dmp.f90 index a8263b49..3459e594 100644 --- a/mlprec/impl/solver/mld_c_gs_solver_dmp.f90 +++ b/mlprec/impl/solver/mld_c_gs_solver_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_id_solver_apply.f90 b/mlprec/impl/solver/mld_c_id_solver_apply.f90 index ffb9e7b5..39142aec 100644 --- a/mlprec/impl/solver/mld_c_id_solver_apply.f90 +++ b/mlprec/impl/solver/mld_c_id_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_id_solver_apply_vect.f90 b/mlprec/impl/solver/mld_c_id_solver_apply_vect.f90 index 91e69ffb..e8de6596 100644 --- a/mlprec/impl/solver/mld_c_id_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_c_id_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_id_solver_clone.f90 b/mlprec/impl/solver/mld_c_id_solver_clone.f90 index 1b8290b4..9c108356 100644 --- a/mlprec/impl/solver/mld_c_id_solver_clone.f90 +++ b/mlprec/impl/solver/mld_c_id_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_ilu_solver_apply.f90 b/mlprec/impl/solver/mld_c_ilu_solver_apply.f90 index 17fc7f07..1b1606b8 100644 --- a/mlprec/impl/solver/mld_c_ilu_solver_apply.f90 +++ b/mlprec/impl/solver/mld_c_ilu_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_ilu_solver_apply_vect.f90 b/mlprec/impl/solver/mld_c_ilu_solver_apply_vect.f90 index 71afc102..617223c8 100644 --- a/mlprec/impl/solver/mld_c_ilu_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_c_ilu_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_ilu_solver_bld.f90 b/mlprec/impl/solver/mld_c_ilu_solver_bld.f90 index ea3f6279..1d1f2de8 100644 --- a/mlprec/impl/solver/mld_c_ilu_solver_bld.f90 +++ b/mlprec/impl/solver/mld_c_ilu_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_ilu_solver_clone.f90 b/mlprec/impl/solver/mld_c_ilu_solver_clone.f90 index d73b4435..f46d68a4 100644 --- a/mlprec/impl/solver/mld_c_ilu_solver_clone.f90 +++ b/mlprec/impl/solver/mld_c_ilu_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_ilu_solver_cnv.f90 b/mlprec/impl/solver/mld_c_ilu_solver_cnv.f90 index 857d4b0b..2578e0cb 100644 --- a/mlprec/impl/solver/mld_c_ilu_solver_cnv.f90 +++ b/mlprec/impl/solver/mld_c_ilu_solver_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_ilu_solver_dmp.f90 b/mlprec/impl/solver/mld_c_ilu_solver_dmp.f90 index d5b156a9..61e7d1f1 100644 --- a/mlprec/impl/solver/mld_c_ilu_solver_dmp.f90 +++ b/mlprec/impl/solver/mld_c_ilu_solver_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_c_mumps_solver_apply.F90 b/mlprec/impl/solver/mld_c_mumps_solver_apply.F90 index aa8e84c0..436c3bf9 100644 --- a/mlprec/impl/solver/mld_c_mumps_solver_apply.F90 +++ b/mlprec/impl/solver/mld_c_mumps_solver_apply.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.0) ! diff --git a/mlprec/impl/solver/mld_c_mumps_solver_apply_vect.F90 b/mlprec/impl/solver/mld_c_mumps_solver_apply_vect.F90 index 5e96f1dd..185970d5 100644 --- a/mlprec/impl/solver/mld_c_mumps_solver_apply_vect.F90 +++ b/mlprec/impl/solver/mld_c_mumps_solver_apply_vect.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.0) ! diff --git a/mlprec/impl/solver/mld_c_mumps_solver_bld.F90 b/mlprec/impl/solver/mld_c_mumps_solver_bld.F90 index f1361f87..8a4fc85b 100644 --- a/mlprec/impl/solver/mld_c_mumps_solver_bld.F90 +++ b/mlprec/impl/solver/mld_c_mumps_solver_bld.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.0) ! diff --git a/mlprec/impl/solver/mld_cilu0_fact.f90 b/mlprec/impl/solver/mld_cilu0_fact.f90 index 242aaa02..c6e646a2 100644 --- a/mlprec/impl/solver/mld_cilu0_fact.f90 +++ b/mlprec/impl/solver/mld_cilu0_fact.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_ciluk_fact.f90 b/mlprec/impl/solver/mld_ciluk_fact.f90 index a8502bbb..79fa2975 100644 --- a/mlprec/impl/solver/mld_ciluk_fact.f90 +++ b/mlprec/impl/solver/mld_ciluk_fact.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_cilut_fact.f90 b/mlprec/impl/solver/mld_cilut_fact.f90 index 2f76492a..b7557ce2 100644 --- a/mlprec/impl/solver/mld_cilut_fact.f90 +++ b/mlprec/impl/solver/mld_cilut_fact.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_base_solver_apply.f90 b/mlprec/impl/solver/mld_d_base_solver_apply.f90 index 8a25ebb7..170a10d5 100644 --- a/mlprec/impl/solver/mld_d_base_solver_apply.f90 +++ b/mlprec/impl/solver/mld_d_base_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_base_solver_apply_vect.f90 b/mlprec/impl/solver/mld_d_base_solver_apply_vect.f90 index 87265a45..b2208ba9 100644 --- a/mlprec/impl/solver/mld_d_base_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_d_base_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_base_solver_bld.f90 b/mlprec/impl/solver/mld_d_base_solver_bld.f90 index a6c7e065..b511aec7 100644 --- a/mlprec/impl/solver/mld_d_base_solver_bld.f90 +++ b/mlprec/impl/solver/mld_d_base_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_base_solver_check.f90 b/mlprec/impl/solver/mld_d_base_solver_check.f90 index 6ea2979f..fbd7264f 100644 --- a/mlprec/impl/solver/mld_d_base_solver_check.f90 +++ b/mlprec/impl/solver/mld_d_base_solver_check.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_base_solver_clone.f90 b/mlprec/impl/solver/mld_d_base_solver_clone.f90 index 829cfc38..6fdb6ef8 100644 --- a/mlprec/impl/solver/mld_d_base_solver_clone.f90 +++ b/mlprec/impl/solver/mld_d_base_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_base_solver_cnv.f90 b/mlprec/impl/solver/mld_d_base_solver_cnv.f90 index 571dd3eb..6f7774b8 100644 --- a/mlprec/impl/solver/mld_d_base_solver_cnv.f90 +++ b/mlprec/impl/solver/mld_d_base_solver_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_base_solver_csetc.f90 b/mlprec/impl/solver/mld_d_base_solver_csetc.f90 index 48f93b65..706d4ee1 100644 --- a/mlprec/impl/solver/mld_d_base_solver_csetc.f90 +++ b/mlprec/impl/solver/mld_d_base_solver_csetc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_base_solver_cseti.f90 b/mlprec/impl/solver/mld_d_base_solver_cseti.f90 index 6e811ed9..07cbd399 100644 --- a/mlprec/impl/solver/mld_d_base_solver_cseti.f90 +++ b/mlprec/impl/solver/mld_d_base_solver_cseti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_base_solver_csetr.f90 b/mlprec/impl/solver/mld_d_base_solver_csetr.f90 index 68faf968..1511eb26 100644 --- a/mlprec/impl/solver/mld_d_base_solver_csetr.f90 +++ b/mlprec/impl/solver/mld_d_base_solver_csetr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_base_solver_descr.f90 b/mlprec/impl/solver/mld_d_base_solver_descr.f90 index 5af62aa4..2254482d 100644 --- a/mlprec/impl/solver/mld_d_base_solver_descr.f90 +++ b/mlprec/impl/solver/mld_d_base_solver_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_base_solver_dmp.f90 b/mlprec/impl/solver/mld_d_base_solver_dmp.f90 index c094b619..fbbb5208 100644 --- a/mlprec/impl/solver/mld_d_base_solver_dmp.f90 +++ b/mlprec/impl/solver/mld_d_base_solver_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_base_solver_free.f90 b/mlprec/impl/solver/mld_d_base_solver_free.f90 index de40207c..386cbc30 100644 --- a/mlprec/impl/solver/mld_d_base_solver_free.f90 +++ b/mlprec/impl/solver/mld_d_base_solver_free.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_base_solver_setc.f90 b/mlprec/impl/solver/mld_d_base_solver_setc.f90 index 151a441a..e2664ce7 100644 --- a/mlprec/impl/solver/mld_d_base_solver_setc.f90 +++ b/mlprec/impl/solver/mld_d_base_solver_setc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_base_solver_seti.f90 b/mlprec/impl/solver/mld_d_base_solver_seti.f90 index f1549d21..4e18f78f 100644 --- a/mlprec/impl/solver/mld_d_base_solver_seti.f90 +++ b/mlprec/impl/solver/mld_d_base_solver_seti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_base_solver_setr.f90 b/mlprec/impl/solver/mld_d_base_solver_setr.f90 index 8399ca9d..a933cfd6 100644 --- a/mlprec/impl/solver/mld_d_base_solver_setr.f90 +++ b/mlprec/impl/solver/mld_d_base_solver_setr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_bwgs_solver_apply.f90 b/mlprec/impl/solver/mld_d_bwgs_solver_apply.f90 index af634e97..4ce02fea 100644 --- a/mlprec/impl/solver/mld_d_bwgs_solver_apply.f90 +++ b/mlprec/impl/solver/mld_d_bwgs_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_bwgs_solver_apply_vect.f90 b/mlprec/impl/solver/mld_d_bwgs_solver_apply_vect.f90 index 25a1aa87..fe4fdd7c 100644 --- a/mlprec/impl/solver/mld_d_bwgs_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_d_bwgs_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_bwgs_solver_bld.f90 b/mlprec/impl/solver/mld_d_bwgs_solver_bld.f90 index 68113294..3fcc4f75 100644 --- a/mlprec/impl/solver/mld_d_bwgs_solver_bld.f90 +++ b/mlprec/impl/solver/mld_d_bwgs_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_diag_solver_apply.f90 b/mlprec/impl/solver/mld_d_diag_solver_apply.f90 index 84c1b7a5..45ac95e0 100644 --- a/mlprec/impl/solver/mld_d_diag_solver_apply.f90 +++ b/mlprec/impl/solver/mld_d_diag_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_diag_solver_apply_vect.f90 b/mlprec/impl/solver/mld_d_diag_solver_apply_vect.f90 index 3f6d70fc..43012d16 100644 --- a/mlprec/impl/solver/mld_d_diag_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_d_diag_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_diag_solver_bld.f90 b/mlprec/impl/solver/mld_d_diag_solver_bld.f90 index bf89bb7b..8b7378bb 100644 --- a/mlprec/impl/solver/mld_d_diag_solver_bld.f90 +++ b/mlprec/impl/solver/mld_d_diag_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_diag_solver_clone.f90 b/mlprec/impl/solver/mld_d_diag_solver_clone.f90 index feeaab9b..15d29217 100644 --- a/mlprec/impl/solver/mld_d_diag_solver_clone.f90 +++ b/mlprec/impl/solver/mld_d_diag_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_diag_solver_cnv.f90 b/mlprec/impl/solver/mld_d_diag_solver_cnv.f90 index 666aa63a..951615a4 100644 --- a/mlprec/impl/solver/mld_d_diag_solver_cnv.f90 +++ b/mlprec/impl/solver/mld_d_diag_solver_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_diag_solver_dmp.f90 b/mlprec/impl/solver/mld_d_diag_solver_dmp.f90 index 72df7f32..21d58955 100644 --- a/mlprec/impl/solver/mld_d_diag_solver_dmp.f90 +++ b/mlprec/impl/solver/mld_d_diag_solver_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_gs_solver_apply.f90 b/mlprec/impl/solver/mld_d_gs_solver_apply.f90 index c08734c2..7e5e2da8 100644 --- a/mlprec/impl/solver/mld_d_gs_solver_apply.f90 +++ b/mlprec/impl/solver/mld_d_gs_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_gs_solver_apply_vect.f90 b/mlprec/impl/solver/mld_d_gs_solver_apply_vect.f90 index 34fdf152..5ed87f5b 100644 --- a/mlprec/impl/solver/mld_d_gs_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_d_gs_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_gs_solver_bld.f90 b/mlprec/impl/solver/mld_d_gs_solver_bld.f90 index 13ba9e5d..c9b23f4a 100644 --- a/mlprec/impl/solver/mld_d_gs_solver_bld.f90 +++ b/mlprec/impl/solver/mld_d_gs_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_gs_solver_clone.f90 b/mlprec/impl/solver/mld_d_gs_solver_clone.f90 index 72a602bf..5dae02e1 100644 --- a/mlprec/impl/solver/mld_d_gs_solver_clone.f90 +++ b/mlprec/impl/solver/mld_d_gs_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_gs_solver_cnv.f90 b/mlprec/impl/solver/mld_d_gs_solver_cnv.f90 index dc3b3c36..8253c863 100644 --- a/mlprec/impl/solver/mld_d_gs_solver_cnv.f90 +++ b/mlprec/impl/solver/mld_d_gs_solver_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_gs_solver_dmp.f90 b/mlprec/impl/solver/mld_d_gs_solver_dmp.f90 index 53ffc133..f1d3b5cb 100644 --- a/mlprec/impl/solver/mld_d_gs_solver_dmp.f90 +++ b/mlprec/impl/solver/mld_d_gs_solver_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_id_solver_apply.f90 b/mlprec/impl/solver/mld_d_id_solver_apply.f90 index 6df623a8..ee3209ea 100644 --- a/mlprec/impl/solver/mld_d_id_solver_apply.f90 +++ b/mlprec/impl/solver/mld_d_id_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_id_solver_apply_vect.f90 b/mlprec/impl/solver/mld_d_id_solver_apply_vect.f90 index ac117bff..9ab9f3af 100644 --- a/mlprec/impl/solver/mld_d_id_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_d_id_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_id_solver_clone.f90 b/mlprec/impl/solver/mld_d_id_solver_clone.f90 index d866edf3..895863a8 100644 --- a/mlprec/impl/solver/mld_d_id_solver_clone.f90 +++ b/mlprec/impl/solver/mld_d_id_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_ilu_solver_apply.f90 b/mlprec/impl/solver/mld_d_ilu_solver_apply.f90 index 56b15cdb..a2e589f2 100644 --- a/mlprec/impl/solver/mld_d_ilu_solver_apply.f90 +++ b/mlprec/impl/solver/mld_d_ilu_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_ilu_solver_apply_vect.f90 b/mlprec/impl/solver/mld_d_ilu_solver_apply_vect.f90 index fa6ce75d..2ca9b278 100644 --- a/mlprec/impl/solver/mld_d_ilu_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_d_ilu_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_ilu_solver_bld.f90 b/mlprec/impl/solver/mld_d_ilu_solver_bld.f90 index 5fc1f17c..ba28539f 100644 --- a/mlprec/impl/solver/mld_d_ilu_solver_bld.f90 +++ b/mlprec/impl/solver/mld_d_ilu_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_ilu_solver_clone.f90 b/mlprec/impl/solver/mld_d_ilu_solver_clone.f90 index ebd78e8b..5cc7ff72 100644 --- a/mlprec/impl/solver/mld_d_ilu_solver_clone.f90 +++ b/mlprec/impl/solver/mld_d_ilu_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_ilu_solver_cnv.f90 b/mlprec/impl/solver/mld_d_ilu_solver_cnv.f90 index 89f439b7..1e0d1089 100644 --- a/mlprec/impl/solver/mld_d_ilu_solver_cnv.f90 +++ b/mlprec/impl/solver/mld_d_ilu_solver_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_ilu_solver_dmp.f90 b/mlprec/impl/solver/mld_d_ilu_solver_dmp.f90 index 2ec0d74b..0a4c9b43 100644 --- a/mlprec/impl/solver/mld_d_ilu_solver_dmp.f90 +++ b/mlprec/impl/solver/mld_d_ilu_solver_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_d_mumps_solver_apply.F90 b/mlprec/impl/solver/mld_d_mumps_solver_apply.F90 index dd312e2a..3900d211 100644 --- a/mlprec/impl/solver/mld_d_mumps_solver_apply.F90 +++ b/mlprec/impl/solver/mld_d_mumps_solver_apply.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.0) ! diff --git a/mlprec/impl/solver/mld_d_mumps_solver_apply_vect.F90 b/mlprec/impl/solver/mld_d_mumps_solver_apply_vect.F90 index 47081248..56013ba7 100644 --- a/mlprec/impl/solver/mld_d_mumps_solver_apply_vect.F90 +++ b/mlprec/impl/solver/mld_d_mumps_solver_apply_vect.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.0) ! diff --git a/mlprec/impl/solver/mld_d_mumps_solver_bld.F90 b/mlprec/impl/solver/mld_d_mumps_solver_bld.F90 index c7b6494a..3f51d193 100644 --- a/mlprec/impl/solver/mld_d_mumps_solver_bld.F90 +++ b/mlprec/impl/solver/mld_d_mumps_solver_bld.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.0) ! diff --git a/mlprec/impl/solver/mld_dilu0_fact.f90 b/mlprec/impl/solver/mld_dilu0_fact.f90 index 144cd657..6dab06b5 100644 --- a/mlprec/impl/solver/mld_dilu0_fact.f90 +++ b/mlprec/impl/solver/mld_dilu0_fact.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_diluk_fact.f90 b/mlprec/impl/solver/mld_diluk_fact.f90 index 9fac8b38..53aa4cce 100644 --- a/mlprec/impl/solver/mld_diluk_fact.f90 +++ b/mlprec/impl/solver/mld_diluk_fact.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_dilut_fact.f90 b/mlprec/impl/solver/mld_dilut_fact.f90 index 1f44275e..d8dfddce 100644 --- a/mlprec/impl/solver/mld_dilut_fact.f90 +++ b/mlprec/impl/solver/mld_dilut_fact.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_base_solver_apply.f90 b/mlprec/impl/solver/mld_s_base_solver_apply.f90 index b1d101ec..5605f4f8 100644 --- a/mlprec/impl/solver/mld_s_base_solver_apply.f90 +++ b/mlprec/impl/solver/mld_s_base_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_base_solver_apply_vect.f90 b/mlprec/impl/solver/mld_s_base_solver_apply_vect.f90 index 4e831bd4..e1dac965 100644 --- a/mlprec/impl/solver/mld_s_base_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_s_base_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_base_solver_bld.f90 b/mlprec/impl/solver/mld_s_base_solver_bld.f90 index 1d76c6e9..8bf11961 100644 --- a/mlprec/impl/solver/mld_s_base_solver_bld.f90 +++ b/mlprec/impl/solver/mld_s_base_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_base_solver_check.f90 b/mlprec/impl/solver/mld_s_base_solver_check.f90 index 9bd3bbb7..0889c620 100644 --- a/mlprec/impl/solver/mld_s_base_solver_check.f90 +++ b/mlprec/impl/solver/mld_s_base_solver_check.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_base_solver_clone.f90 b/mlprec/impl/solver/mld_s_base_solver_clone.f90 index d093ac30..6e90e1af 100644 --- a/mlprec/impl/solver/mld_s_base_solver_clone.f90 +++ b/mlprec/impl/solver/mld_s_base_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_base_solver_cnv.f90 b/mlprec/impl/solver/mld_s_base_solver_cnv.f90 index a5ed05cc..acca2e24 100644 --- a/mlprec/impl/solver/mld_s_base_solver_cnv.f90 +++ b/mlprec/impl/solver/mld_s_base_solver_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_base_solver_csetc.f90 b/mlprec/impl/solver/mld_s_base_solver_csetc.f90 index 487c6ff0..0525d845 100644 --- a/mlprec/impl/solver/mld_s_base_solver_csetc.f90 +++ b/mlprec/impl/solver/mld_s_base_solver_csetc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_base_solver_cseti.f90 b/mlprec/impl/solver/mld_s_base_solver_cseti.f90 index 9d198638..73da04f4 100644 --- a/mlprec/impl/solver/mld_s_base_solver_cseti.f90 +++ b/mlprec/impl/solver/mld_s_base_solver_cseti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_base_solver_csetr.f90 b/mlprec/impl/solver/mld_s_base_solver_csetr.f90 index 1d19cf1c..4afcd3a8 100644 --- a/mlprec/impl/solver/mld_s_base_solver_csetr.f90 +++ b/mlprec/impl/solver/mld_s_base_solver_csetr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_base_solver_descr.f90 b/mlprec/impl/solver/mld_s_base_solver_descr.f90 index d2e1450c..67fa0d35 100644 --- a/mlprec/impl/solver/mld_s_base_solver_descr.f90 +++ b/mlprec/impl/solver/mld_s_base_solver_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_base_solver_dmp.f90 b/mlprec/impl/solver/mld_s_base_solver_dmp.f90 index 8c9112f3..77ae6492 100644 --- a/mlprec/impl/solver/mld_s_base_solver_dmp.f90 +++ b/mlprec/impl/solver/mld_s_base_solver_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_base_solver_free.f90 b/mlprec/impl/solver/mld_s_base_solver_free.f90 index 1bdadc18..7ba4a04c 100644 --- a/mlprec/impl/solver/mld_s_base_solver_free.f90 +++ b/mlprec/impl/solver/mld_s_base_solver_free.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_base_solver_setc.f90 b/mlprec/impl/solver/mld_s_base_solver_setc.f90 index 8b787f79..23e17ce5 100644 --- a/mlprec/impl/solver/mld_s_base_solver_setc.f90 +++ b/mlprec/impl/solver/mld_s_base_solver_setc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_base_solver_seti.f90 b/mlprec/impl/solver/mld_s_base_solver_seti.f90 index 982b3357..0a7fb9e6 100644 --- a/mlprec/impl/solver/mld_s_base_solver_seti.f90 +++ b/mlprec/impl/solver/mld_s_base_solver_seti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_base_solver_setr.f90 b/mlprec/impl/solver/mld_s_base_solver_setr.f90 index 6fe89e72..d0f25532 100644 --- a/mlprec/impl/solver/mld_s_base_solver_setr.f90 +++ b/mlprec/impl/solver/mld_s_base_solver_setr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_bwgs_solver_apply.f90 b/mlprec/impl/solver/mld_s_bwgs_solver_apply.f90 index ec9e052c..f6955fbd 100644 --- a/mlprec/impl/solver/mld_s_bwgs_solver_apply.f90 +++ b/mlprec/impl/solver/mld_s_bwgs_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_bwgs_solver_apply_vect.f90 b/mlprec/impl/solver/mld_s_bwgs_solver_apply_vect.f90 index f3fa7a12..a4565edb 100644 --- a/mlprec/impl/solver/mld_s_bwgs_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_s_bwgs_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_bwgs_solver_bld.f90 b/mlprec/impl/solver/mld_s_bwgs_solver_bld.f90 index 68f81b07..0d2eb1a3 100644 --- a/mlprec/impl/solver/mld_s_bwgs_solver_bld.f90 +++ b/mlprec/impl/solver/mld_s_bwgs_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_diag_solver_apply.f90 b/mlprec/impl/solver/mld_s_diag_solver_apply.f90 index b03b9c6e..4aab61c1 100644 --- a/mlprec/impl/solver/mld_s_diag_solver_apply.f90 +++ b/mlprec/impl/solver/mld_s_diag_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_diag_solver_apply_vect.f90 b/mlprec/impl/solver/mld_s_diag_solver_apply_vect.f90 index 86bcdd5d..2e28ccfd 100644 --- a/mlprec/impl/solver/mld_s_diag_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_s_diag_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_diag_solver_bld.f90 b/mlprec/impl/solver/mld_s_diag_solver_bld.f90 index 6b33cd82..7c1a8fa6 100644 --- a/mlprec/impl/solver/mld_s_diag_solver_bld.f90 +++ b/mlprec/impl/solver/mld_s_diag_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_diag_solver_clone.f90 b/mlprec/impl/solver/mld_s_diag_solver_clone.f90 index f02f1f45..f642e9f0 100644 --- a/mlprec/impl/solver/mld_s_diag_solver_clone.f90 +++ b/mlprec/impl/solver/mld_s_diag_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_diag_solver_cnv.f90 b/mlprec/impl/solver/mld_s_diag_solver_cnv.f90 index d9a02a19..fc4ff623 100644 --- a/mlprec/impl/solver/mld_s_diag_solver_cnv.f90 +++ b/mlprec/impl/solver/mld_s_diag_solver_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_diag_solver_dmp.f90 b/mlprec/impl/solver/mld_s_diag_solver_dmp.f90 index be962fca..ae3695b8 100644 --- a/mlprec/impl/solver/mld_s_diag_solver_dmp.f90 +++ b/mlprec/impl/solver/mld_s_diag_solver_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_gs_solver_apply.f90 b/mlprec/impl/solver/mld_s_gs_solver_apply.f90 index 70db86ad..adfd751d 100644 --- a/mlprec/impl/solver/mld_s_gs_solver_apply.f90 +++ b/mlprec/impl/solver/mld_s_gs_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_gs_solver_apply_vect.f90 b/mlprec/impl/solver/mld_s_gs_solver_apply_vect.f90 index 2928333f..74bfe835 100644 --- a/mlprec/impl/solver/mld_s_gs_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_s_gs_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_gs_solver_bld.f90 b/mlprec/impl/solver/mld_s_gs_solver_bld.f90 index f4fd37a4..24fedbc6 100644 --- a/mlprec/impl/solver/mld_s_gs_solver_bld.f90 +++ b/mlprec/impl/solver/mld_s_gs_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_gs_solver_clone.f90 b/mlprec/impl/solver/mld_s_gs_solver_clone.f90 index e49fdfc7..3aa18c4d 100644 --- a/mlprec/impl/solver/mld_s_gs_solver_clone.f90 +++ b/mlprec/impl/solver/mld_s_gs_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_gs_solver_cnv.f90 b/mlprec/impl/solver/mld_s_gs_solver_cnv.f90 index aae8704e..7e67b973 100644 --- a/mlprec/impl/solver/mld_s_gs_solver_cnv.f90 +++ b/mlprec/impl/solver/mld_s_gs_solver_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_gs_solver_dmp.f90 b/mlprec/impl/solver/mld_s_gs_solver_dmp.f90 index 0288a0f8..33af39a7 100644 --- a/mlprec/impl/solver/mld_s_gs_solver_dmp.f90 +++ b/mlprec/impl/solver/mld_s_gs_solver_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_id_solver_apply.f90 b/mlprec/impl/solver/mld_s_id_solver_apply.f90 index d7bed551..b7614844 100644 --- a/mlprec/impl/solver/mld_s_id_solver_apply.f90 +++ b/mlprec/impl/solver/mld_s_id_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_id_solver_apply_vect.f90 b/mlprec/impl/solver/mld_s_id_solver_apply_vect.f90 index 05844b36..00b56862 100644 --- a/mlprec/impl/solver/mld_s_id_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_s_id_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_id_solver_clone.f90 b/mlprec/impl/solver/mld_s_id_solver_clone.f90 index cf8fe453..8cc886a6 100644 --- a/mlprec/impl/solver/mld_s_id_solver_clone.f90 +++ b/mlprec/impl/solver/mld_s_id_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_ilu_solver_apply.f90 b/mlprec/impl/solver/mld_s_ilu_solver_apply.f90 index db2e9fb4..3e33c108 100644 --- a/mlprec/impl/solver/mld_s_ilu_solver_apply.f90 +++ b/mlprec/impl/solver/mld_s_ilu_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_ilu_solver_apply_vect.f90 b/mlprec/impl/solver/mld_s_ilu_solver_apply_vect.f90 index f64716b6..fb320a8d 100644 --- a/mlprec/impl/solver/mld_s_ilu_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_s_ilu_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_ilu_solver_bld.f90 b/mlprec/impl/solver/mld_s_ilu_solver_bld.f90 index aee3e501..2701a851 100644 --- a/mlprec/impl/solver/mld_s_ilu_solver_bld.f90 +++ b/mlprec/impl/solver/mld_s_ilu_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_ilu_solver_clone.f90 b/mlprec/impl/solver/mld_s_ilu_solver_clone.f90 index 6944a06f..2c742b74 100644 --- a/mlprec/impl/solver/mld_s_ilu_solver_clone.f90 +++ b/mlprec/impl/solver/mld_s_ilu_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_ilu_solver_cnv.f90 b/mlprec/impl/solver/mld_s_ilu_solver_cnv.f90 index 71407a73..eb55738f 100644 --- a/mlprec/impl/solver/mld_s_ilu_solver_cnv.f90 +++ b/mlprec/impl/solver/mld_s_ilu_solver_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_ilu_solver_dmp.f90 b/mlprec/impl/solver/mld_s_ilu_solver_dmp.f90 index 7268ef3a..5da73209 100644 --- a/mlprec/impl/solver/mld_s_ilu_solver_dmp.f90 +++ b/mlprec/impl/solver/mld_s_ilu_solver_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_s_mumps_solver_apply.F90 b/mlprec/impl/solver/mld_s_mumps_solver_apply.F90 index 384c4c5f..f0fae77d 100644 --- a/mlprec/impl/solver/mld_s_mumps_solver_apply.F90 +++ b/mlprec/impl/solver/mld_s_mumps_solver_apply.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.0) ! diff --git a/mlprec/impl/solver/mld_s_mumps_solver_apply_vect.F90 b/mlprec/impl/solver/mld_s_mumps_solver_apply_vect.F90 index 705892c6..59fad283 100644 --- a/mlprec/impl/solver/mld_s_mumps_solver_apply_vect.F90 +++ b/mlprec/impl/solver/mld_s_mumps_solver_apply_vect.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.0) ! diff --git a/mlprec/impl/solver/mld_s_mumps_solver_bld.F90 b/mlprec/impl/solver/mld_s_mumps_solver_bld.F90 index 78aec716..664823f5 100644 --- a/mlprec/impl/solver/mld_s_mumps_solver_bld.F90 +++ b/mlprec/impl/solver/mld_s_mumps_solver_bld.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.0) ! diff --git a/mlprec/impl/solver/mld_silu0_fact.f90 b/mlprec/impl/solver/mld_silu0_fact.f90 index b47c9c42..8065d4b1 100644 --- a/mlprec/impl/solver/mld_silu0_fact.f90 +++ b/mlprec/impl/solver/mld_silu0_fact.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_siluk_fact.f90 b/mlprec/impl/solver/mld_siluk_fact.f90 index 19ce3128..e91173df 100644 --- a/mlprec/impl/solver/mld_siluk_fact.f90 +++ b/mlprec/impl/solver/mld_siluk_fact.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_silut_fact.f90 b/mlprec/impl/solver/mld_silut_fact.f90 index c535d0cf..510321a1 100644 --- a/mlprec/impl/solver/mld_silut_fact.f90 +++ b/mlprec/impl/solver/mld_silut_fact.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_base_solver_apply.f90 b/mlprec/impl/solver/mld_z_base_solver_apply.f90 index 8eec5367..0c7a0f61 100644 --- a/mlprec/impl/solver/mld_z_base_solver_apply.f90 +++ b/mlprec/impl/solver/mld_z_base_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_base_solver_apply_vect.f90 b/mlprec/impl/solver/mld_z_base_solver_apply_vect.f90 index dc84cd7f..cc72e07d 100644 --- a/mlprec/impl/solver/mld_z_base_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_z_base_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_base_solver_bld.f90 b/mlprec/impl/solver/mld_z_base_solver_bld.f90 index 9f3a331a..9fbd81d1 100644 --- a/mlprec/impl/solver/mld_z_base_solver_bld.f90 +++ b/mlprec/impl/solver/mld_z_base_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_base_solver_check.f90 b/mlprec/impl/solver/mld_z_base_solver_check.f90 index ba893fc1..1fc6ccd8 100644 --- a/mlprec/impl/solver/mld_z_base_solver_check.f90 +++ b/mlprec/impl/solver/mld_z_base_solver_check.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_base_solver_clone.f90 b/mlprec/impl/solver/mld_z_base_solver_clone.f90 index 5c97abd9..7deb75eb 100644 --- a/mlprec/impl/solver/mld_z_base_solver_clone.f90 +++ b/mlprec/impl/solver/mld_z_base_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_base_solver_cnv.f90 b/mlprec/impl/solver/mld_z_base_solver_cnv.f90 index 8b3660e7..bd62c83d 100644 --- a/mlprec/impl/solver/mld_z_base_solver_cnv.f90 +++ b/mlprec/impl/solver/mld_z_base_solver_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_base_solver_csetc.f90 b/mlprec/impl/solver/mld_z_base_solver_csetc.f90 index c95f9510..048a4fdc 100644 --- a/mlprec/impl/solver/mld_z_base_solver_csetc.f90 +++ b/mlprec/impl/solver/mld_z_base_solver_csetc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_base_solver_cseti.f90 b/mlprec/impl/solver/mld_z_base_solver_cseti.f90 index 89e9c907..25ac8f67 100644 --- a/mlprec/impl/solver/mld_z_base_solver_cseti.f90 +++ b/mlprec/impl/solver/mld_z_base_solver_cseti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_base_solver_csetr.f90 b/mlprec/impl/solver/mld_z_base_solver_csetr.f90 index d2412eec..739586fc 100644 --- a/mlprec/impl/solver/mld_z_base_solver_csetr.f90 +++ b/mlprec/impl/solver/mld_z_base_solver_csetr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_base_solver_descr.f90 b/mlprec/impl/solver/mld_z_base_solver_descr.f90 index 7cc4c049..01050fdd 100644 --- a/mlprec/impl/solver/mld_z_base_solver_descr.f90 +++ b/mlprec/impl/solver/mld_z_base_solver_descr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_base_solver_dmp.f90 b/mlprec/impl/solver/mld_z_base_solver_dmp.f90 index b6749cfd..a85cd64c 100644 --- a/mlprec/impl/solver/mld_z_base_solver_dmp.f90 +++ b/mlprec/impl/solver/mld_z_base_solver_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_base_solver_free.f90 b/mlprec/impl/solver/mld_z_base_solver_free.f90 index 10cd4a58..21a8099f 100644 --- a/mlprec/impl/solver/mld_z_base_solver_free.f90 +++ b/mlprec/impl/solver/mld_z_base_solver_free.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_base_solver_setc.f90 b/mlprec/impl/solver/mld_z_base_solver_setc.f90 index ceebe541..a0d60a99 100644 --- a/mlprec/impl/solver/mld_z_base_solver_setc.f90 +++ b/mlprec/impl/solver/mld_z_base_solver_setc.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_base_solver_seti.f90 b/mlprec/impl/solver/mld_z_base_solver_seti.f90 index 4ba74e10..ebeec939 100644 --- a/mlprec/impl/solver/mld_z_base_solver_seti.f90 +++ b/mlprec/impl/solver/mld_z_base_solver_seti.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_base_solver_setr.f90 b/mlprec/impl/solver/mld_z_base_solver_setr.f90 index 8d190d99..a31ba30d 100644 --- a/mlprec/impl/solver/mld_z_base_solver_setr.f90 +++ b/mlprec/impl/solver/mld_z_base_solver_setr.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_bwgs_solver_apply.f90 b/mlprec/impl/solver/mld_z_bwgs_solver_apply.f90 index 28958ccd..02dce73c 100644 --- a/mlprec/impl/solver/mld_z_bwgs_solver_apply.f90 +++ b/mlprec/impl/solver/mld_z_bwgs_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_bwgs_solver_apply_vect.f90 b/mlprec/impl/solver/mld_z_bwgs_solver_apply_vect.f90 index 3ade70df..9454046f 100644 --- a/mlprec/impl/solver/mld_z_bwgs_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_z_bwgs_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_bwgs_solver_bld.f90 b/mlprec/impl/solver/mld_z_bwgs_solver_bld.f90 index 81fddcfb..38454e18 100644 --- a/mlprec/impl/solver/mld_z_bwgs_solver_bld.f90 +++ b/mlprec/impl/solver/mld_z_bwgs_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_diag_solver_apply.f90 b/mlprec/impl/solver/mld_z_diag_solver_apply.f90 index c7e76900..bdedc0f0 100644 --- a/mlprec/impl/solver/mld_z_diag_solver_apply.f90 +++ b/mlprec/impl/solver/mld_z_diag_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_diag_solver_apply_vect.f90 b/mlprec/impl/solver/mld_z_diag_solver_apply_vect.f90 index 19fb79d4..840e14a6 100644 --- a/mlprec/impl/solver/mld_z_diag_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_z_diag_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_diag_solver_bld.f90 b/mlprec/impl/solver/mld_z_diag_solver_bld.f90 index d1655bfd..59eb6fa4 100644 --- a/mlprec/impl/solver/mld_z_diag_solver_bld.f90 +++ b/mlprec/impl/solver/mld_z_diag_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_diag_solver_clone.f90 b/mlprec/impl/solver/mld_z_diag_solver_clone.f90 index c98beae1..508b503e 100644 --- a/mlprec/impl/solver/mld_z_diag_solver_clone.f90 +++ b/mlprec/impl/solver/mld_z_diag_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_diag_solver_cnv.f90 b/mlprec/impl/solver/mld_z_diag_solver_cnv.f90 index f13d9c3a..1f432bc1 100644 --- a/mlprec/impl/solver/mld_z_diag_solver_cnv.f90 +++ b/mlprec/impl/solver/mld_z_diag_solver_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_diag_solver_dmp.f90 b/mlprec/impl/solver/mld_z_diag_solver_dmp.f90 index 6e7b67c2..fe69026d 100644 --- a/mlprec/impl/solver/mld_z_diag_solver_dmp.f90 +++ b/mlprec/impl/solver/mld_z_diag_solver_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_gs_solver_apply.f90 b/mlprec/impl/solver/mld_z_gs_solver_apply.f90 index 7ca49e8d..4acfff15 100644 --- a/mlprec/impl/solver/mld_z_gs_solver_apply.f90 +++ b/mlprec/impl/solver/mld_z_gs_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_gs_solver_apply_vect.f90 b/mlprec/impl/solver/mld_z_gs_solver_apply_vect.f90 index 4c64ca42..5174ddc9 100644 --- a/mlprec/impl/solver/mld_z_gs_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_z_gs_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_gs_solver_bld.f90 b/mlprec/impl/solver/mld_z_gs_solver_bld.f90 index ea1076fd..a3934cd5 100644 --- a/mlprec/impl/solver/mld_z_gs_solver_bld.f90 +++ b/mlprec/impl/solver/mld_z_gs_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_gs_solver_clone.f90 b/mlprec/impl/solver/mld_z_gs_solver_clone.f90 index ffb2954f..0691846b 100644 --- a/mlprec/impl/solver/mld_z_gs_solver_clone.f90 +++ b/mlprec/impl/solver/mld_z_gs_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_gs_solver_cnv.f90 b/mlprec/impl/solver/mld_z_gs_solver_cnv.f90 index d9e25943..212a733d 100644 --- a/mlprec/impl/solver/mld_z_gs_solver_cnv.f90 +++ b/mlprec/impl/solver/mld_z_gs_solver_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_gs_solver_dmp.f90 b/mlprec/impl/solver/mld_z_gs_solver_dmp.f90 index b3a02f28..3449cdd1 100644 --- a/mlprec/impl/solver/mld_z_gs_solver_dmp.f90 +++ b/mlprec/impl/solver/mld_z_gs_solver_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_id_solver_apply.f90 b/mlprec/impl/solver/mld_z_id_solver_apply.f90 index caca1ca2..ab728ab2 100644 --- a/mlprec/impl/solver/mld_z_id_solver_apply.f90 +++ b/mlprec/impl/solver/mld_z_id_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_id_solver_apply_vect.f90 b/mlprec/impl/solver/mld_z_id_solver_apply_vect.f90 index 97ed7dcf..43ef0442 100644 --- a/mlprec/impl/solver/mld_z_id_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_z_id_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_id_solver_clone.f90 b/mlprec/impl/solver/mld_z_id_solver_clone.f90 index f9094e14..3dafb3ff 100644 --- a/mlprec/impl/solver/mld_z_id_solver_clone.f90 +++ b/mlprec/impl/solver/mld_z_id_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_ilu_solver_apply.f90 b/mlprec/impl/solver/mld_z_ilu_solver_apply.f90 index 23eaac57..5d70536d 100644 --- a/mlprec/impl/solver/mld_z_ilu_solver_apply.f90 +++ b/mlprec/impl/solver/mld_z_ilu_solver_apply.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_ilu_solver_apply_vect.f90 b/mlprec/impl/solver/mld_z_ilu_solver_apply_vect.f90 index 7c6fcaf9..5cf4d013 100644 --- a/mlprec/impl/solver/mld_z_ilu_solver_apply_vect.f90 +++ b/mlprec/impl/solver/mld_z_ilu_solver_apply_vect.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_ilu_solver_bld.f90 b/mlprec/impl/solver/mld_z_ilu_solver_bld.f90 index 7d685c92..18c069fb 100644 --- a/mlprec/impl/solver/mld_z_ilu_solver_bld.f90 +++ b/mlprec/impl/solver/mld_z_ilu_solver_bld.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_ilu_solver_clone.f90 b/mlprec/impl/solver/mld_z_ilu_solver_clone.f90 index 156f8363..a754b969 100644 --- a/mlprec/impl/solver/mld_z_ilu_solver_clone.f90 +++ b/mlprec/impl/solver/mld_z_ilu_solver_clone.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_ilu_solver_cnv.f90 b/mlprec/impl/solver/mld_z_ilu_solver_cnv.f90 index 6364b796..bbfcca7f 100644 --- a/mlprec/impl/solver/mld_z_ilu_solver_cnv.f90 +++ b/mlprec/impl/solver/mld_z_ilu_solver_cnv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_ilu_solver_dmp.f90 b/mlprec/impl/solver/mld_z_ilu_solver_dmp.f90 index 5c9cc0d0..8c40336d 100644 --- a/mlprec/impl/solver/mld_z_ilu_solver_dmp.f90 +++ b/mlprec/impl/solver/mld_z_ilu_solver_dmp.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_z_mumps_solver_apply.F90 b/mlprec/impl/solver/mld_z_mumps_solver_apply.F90 index 11050f9d..252e4c3a 100644 --- a/mlprec/impl/solver/mld_z_mumps_solver_apply.F90 +++ b/mlprec/impl/solver/mld_z_mumps_solver_apply.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.0) ! diff --git a/mlprec/impl/solver/mld_z_mumps_solver_apply_vect.F90 b/mlprec/impl/solver/mld_z_mumps_solver_apply_vect.F90 index 987a828f..29db13b8 100644 --- a/mlprec/impl/solver/mld_z_mumps_solver_apply_vect.F90 +++ b/mlprec/impl/solver/mld_z_mumps_solver_apply_vect.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.0) ! diff --git a/mlprec/impl/solver/mld_z_mumps_solver_bld.F90 b/mlprec/impl/solver/mld_z_mumps_solver_bld.F90 index 96b38b7b..77bc4682 100644 --- a/mlprec/impl/solver/mld_z_mumps_solver_bld.F90 +++ b/mlprec/impl/solver/mld_z_mumps_solver_bld.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.0) ! diff --git a/mlprec/impl/solver/mld_zilu0_fact.f90 b/mlprec/impl/solver/mld_zilu0_fact.f90 index f7dd71b8..5a89e785 100644 --- a/mlprec/impl/solver/mld_zilu0_fact.f90 +++ b/mlprec/impl/solver/mld_zilu0_fact.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_ziluk_fact.f90 b/mlprec/impl/solver/mld_ziluk_fact.f90 index 151b4c45..daf52dc9 100644 --- a/mlprec/impl/solver/mld_ziluk_fact.f90 +++ b/mlprec/impl/solver/mld_ziluk_fact.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/impl/solver/mld_zilut_fact.f90 b/mlprec/impl/solver/mld_zilut_fact.f90 index d7957aef..7554b35a 100644 --- a/mlprec/impl/solver/mld_zilut_fact.f90 +++ b/mlprec/impl/solver/mld_zilut_fact.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_base_prec_type.F90 b/mlprec/mld_base_prec_type.F90 index d473cb2d..26987979 100644 --- a/mlprec/mld_base_prec_type.F90 +++ b/mlprec/mld_base_prec_type.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_c_as_smoother.f90 b/mlprec/mld_c_as_smoother.f90 index 1c186c55..2da8aedb 100644 --- a/mlprec/mld_c_as_smoother.f90 +++ b/mlprec/mld_c_as_smoother.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_c_base_aggregator_mod.f90 b/mlprec/mld_c_base_aggregator_mod.f90 index 7bfb4428..6383f507 100644 --- a/mlprec/mld_c_base_aggregator_mod.f90 +++ b/mlprec/mld_c_base_aggregator_mod.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/mld_c_base_smoother_mod.f90 b/mlprec/mld_c_base_smoother_mod.f90 index 7477455c..caf92d49 100644 --- a/mlprec/mld_c_base_smoother_mod.f90 +++ b/mlprec/mld_c_base_smoother_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_c_base_solver_mod.f90 b/mlprec/mld_c_base_solver_mod.f90 index 894f8d03..c4dc7f35 100644 --- a/mlprec/mld_c_base_solver_mod.f90 +++ b/mlprec/mld_c_base_solver_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_c_diag_solver.f90 b/mlprec/mld_c_diag_solver.f90 index c6da0670..2f9ce680 100644 --- a/mlprec/mld_c_diag_solver.f90 +++ b/mlprec/mld_c_diag_solver.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_c_gs_solver.f90 b/mlprec/mld_c_gs_solver.f90 index 9ccb5be9..0ce986b2 100644 --- a/mlprec/mld_c_gs_solver.f90 +++ b/mlprec/mld_c_gs_solver.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_c_hybrid_aggregator_mod.F90 b/mlprec/mld_c_hybrid_aggregator_mod.F90 index bbc62953..f44a4f60 100644 --- a/mlprec/mld_c_hybrid_aggregator_mod.F90 +++ b/mlprec/mld_c_hybrid_aggregator_mod.F90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/mld_c_id_solver.f90 b/mlprec/mld_c_id_solver.f90 index ce03a91c..4bcba672 100644 --- a/mlprec/mld_c_id_solver.f90 +++ b/mlprec/mld_c_id_solver.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_c_ilu_fact_mod.f90 b/mlprec/mld_c_ilu_fact_mod.f90 index b8c9a55d..e61ae28a 100644 --- a/mlprec/mld_c_ilu_fact_mod.f90 +++ b/mlprec/mld_c_ilu_fact_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_c_ilu_solver.f90 b/mlprec/mld_c_ilu_solver.f90 index 919ddc18..8ee43c46 100644 --- a/mlprec/mld_c_ilu_solver.f90 +++ b/mlprec/mld_c_ilu_solver.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_c_inner_mod.f90 b/mlprec/mld_c_inner_mod.f90 index 432c73b5..2b4c9fd7 100644 --- a/mlprec/mld_c_inner_mod.f90 +++ b/mlprec/mld_c_inner_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_c_jac_smoother.f90 b/mlprec/mld_c_jac_smoother.f90 index ac0cd36e..fd66e696 100644 --- a/mlprec/mld_c_jac_smoother.f90 +++ b/mlprec/mld_c_jac_smoother.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_c_mumps_solver.F90 b/mlprec/mld_c_mumps_solver.F90 index 522b5ae3..cf4b2db8 100644 --- a/mlprec/mld_c_mumps_solver.F90 +++ b/mlprec/mld_c_mumps_solver.F90 @@ -1,10 +1,10 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.0) +! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008,2009,2010,2012,2013 +! (C) Copyright 2008-2018 ! ! Salvatore Filippone ! Pasqua D'Ambra diff --git a/mlprec/mld_c_onelev_mod.f90 b/mlprec/mld_c_onelev_mod.f90 index de6ec194..a9b456d2 100644 --- a/mlprec/mld_c_onelev_mod.f90 +++ b/mlprec/mld_c_onelev_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_c_prec_mod.f90 b/mlprec/mld_c_prec_mod.f90 index a06680b8..682b0548 100644 --- a/mlprec/mld_c_prec_mod.f90 +++ b/mlprec/mld_c_prec_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_c_prec_type.f90 b/mlprec/mld_c_prec_type.f90 index 073f303c..a6f37391 100644 --- a/mlprec/mld_c_prec_type.f90 +++ b/mlprec/mld_c_prec_type.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_c_slu_solver.F90 b/mlprec/mld_c_slu_solver.F90 index 3978b91d..dd544aaf 100644 --- a/mlprec/mld_c_slu_solver.F90 +++ b/mlprec/mld_c_slu_solver.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_c_symdec_aggregator_mod.f90 b/mlprec/mld_c_symdec_aggregator_mod.f90 index 4738c595..1cf69096 100644 --- a/mlprec/mld_c_symdec_aggregator_mod.f90 +++ b/mlprec/mld_c_symdec_aggregator_mod.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/mld_d_as_smoother.f90 b/mlprec/mld_d_as_smoother.f90 index baa3f424..7dcb6641 100644 --- a/mlprec/mld_d_as_smoother.f90 +++ b/mlprec/mld_d_as_smoother.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_d_base_aggregator_mod.f90 b/mlprec/mld_d_base_aggregator_mod.f90 index 876e36d4..a07c2da0 100644 --- a/mlprec/mld_d_base_aggregator_mod.f90 +++ b/mlprec/mld_d_base_aggregator_mod.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/mld_d_base_smoother_mod.f90 b/mlprec/mld_d_base_smoother_mod.f90 index d0e2519c..b382d100 100644 --- a/mlprec/mld_d_base_smoother_mod.f90 +++ b/mlprec/mld_d_base_smoother_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_d_base_solver_mod.f90 b/mlprec/mld_d_base_solver_mod.f90 index 8b9f73a6..26e860e2 100644 --- a/mlprec/mld_d_base_solver_mod.f90 +++ b/mlprec/mld_d_base_solver_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_d_bcmatch_aggregator_mod.F90 b/mlprec/mld_d_bcmatch_aggregator_mod.F90 index 5f43ac91..489b7b10 100644 --- a/mlprec/mld_d_bcmatch_aggregator_mod.F90 +++ b/mlprec/mld_d_bcmatch_aggregator_mod.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_d_diag_solver.f90 b/mlprec/mld_d_diag_solver.f90 index 1349f062..f62bf3e8 100644 --- a/mlprec/mld_d_diag_solver.f90 +++ b/mlprec/mld_d_diag_solver.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_d_gs_solver.f90 b/mlprec/mld_d_gs_solver.f90 index a9029530..35c818dc 100644 --- a/mlprec/mld_d_gs_solver.f90 +++ b/mlprec/mld_d_gs_solver.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_d_hybrid_aggregator_mod.F90 b/mlprec/mld_d_hybrid_aggregator_mod.F90 index 50e3215c..4cdde8bd 100644 --- a/mlprec/mld_d_hybrid_aggregator_mod.F90 +++ b/mlprec/mld_d_hybrid_aggregator_mod.F90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/mld_d_id_solver.f90 b/mlprec/mld_d_id_solver.f90 index 0bae0f90..50aaf2bd 100644 --- a/mlprec/mld_d_id_solver.f90 +++ b/mlprec/mld_d_id_solver.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_d_ilu_fact_mod.f90 b/mlprec/mld_d_ilu_fact_mod.f90 index 3ce83f41..cb8c4bbe 100644 --- a/mlprec/mld_d_ilu_fact_mod.f90 +++ b/mlprec/mld_d_ilu_fact_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_d_ilu_solver.f90 b/mlprec/mld_d_ilu_solver.f90 index 5237c72b..2f435a35 100644 --- a/mlprec/mld_d_ilu_solver.f90 +++ b/mlprec/mld_d_ilu_solver.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_d_inner_mod.f90 b/mlprec/mld_d_inner_mod.f90 index ed052f69..454d934a 100644 --- a/mlprec/mld_d_inner_mod.f90 +++ b/mlprec/mld_d_inner_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_d_jac_smoother.f90 b/mlprec/mld_d_jac_smoother.f90 index 64e57e6f..2d9f0a58 100644 --- a/mlprec/mld_d_jac_smoother.f90 +++ b/mlprec/mld_d_jac_smoother.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_d_mumps_solver.F90 b/mlprec/mld_d_mumps_solver.F90 index 66336f0c..2f2dab5f 100644 --- a/mlprec/mld_d_mumps_solver.F90 +++ b/mlprec/mld_d_mumps_solver.F90 @@ -1,10 +1,10 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.0) +! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008,2009,2010,2012,2013 +! (C) Copyright 2008-2018 ! ! Salvatore Filippone ! Pasqua D'Ambra diff --git a/mlprec/mld_d_onelev_mod.f90 b/mlprec/mld_d_onelev_mod.f90 index 1c5da02a..13fcc688 100644 --- a/mlprec/mld_d_onelev_mod.f90 +++ b/mlprec/mld_d_onelev_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_d_prec_mod.f90 b/mlprec/mld_d_prec_mod.f90 index 7e695111..e9ffb466 100644 --- a/mlprec/mld_d_prec_mod.f90 +++ b/mlprec/mld_d_prec_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_d_prec_type.f90 b/mlprec/mld_d_prec_type.f90 index f62f4760..64036b94 100644 --- a/mlprec/mld_d_prec_type.f90 +++ b/mlprec/mld_d_prec_type.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_d_slu_solver.F90 b/mlprec/mld_d_slu_solver.F90 index 9cec715b..493a0e03 100644 --- a/mlprec/mld_d_slu_solver.F90 +++ b/mlprec/mld_d_slu_solver.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_d_sludist_solver.F90 b/mlprec/mld_d_sludist_solver.F90 index 87834f39..9e69eaaa 100644 --- a/mlprec/mld_d_sludist_solver.F90 +++ b/mlprec/mld_d_sludist_solver.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_d_symdec_aggregator_mod.f90 b/mlprec/mld_d_symdec_aggregator_mod.f90 index 2532fac9..927ad60f 100644 --- a/mlprec/mld_d_symdec_aggregator_mod.f90 +++ b/mlprec/mld_d_symdec_aggregator_mod.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/mld_d_umf_solver.F90 b/mlprec/mld_d_umf_solver.F90 index 64ea392a..1222979c 100644 --- a/mlprec/mld_d_umf_solver.F90 +++ b/mlprec/mld_d_umf_solver.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_prec_mod.f90 b/mlprec/mld_prec_mod.f90 index 5dc5a011..91995d85 100644 --- a/mlprec/mld_prec_mod.f90 +++ b/mlprec/mld_prec_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_prec_type.f90 b/mlprec/mld_prec_type.f90 index 6a1b4a25..cf1b8ff2 100644 --- a/mlprec/mld_prec_type.f90 +++ b/mlprec/mld_prec_type.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_s_as_smoother.f90 b/mlprec/mld_s_as_smoother.f90 index bae1e982..a9ef488d 100644 --- a/mlprec/mld_s_as_smoother.f90 +++ b/mlprec/mld_s_as_smoother.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_s_base_aggregator_mod.f90 b/mlprec/mld_s_base_aggregator_mod.f90 index 79eb9ca7..b9a67239 100644 --- a/mlprec/mld_s_base_aggregator_mod.f90 +++ b/mlprec/mld_s_base_aggregator_mod.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/mld_s_base_smoother_mod.f90 b/mlprec/mld_s_base_smoother_mod.f90 index 10583ffb..25b35dae 100644 --- a/mlprec/mld_s_base_smoother_mod.f90 +++ b/mlprec/mld_s_base_smoother_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_s_base_solver_mod.f90 b/mlprec/mld_s_base_solver_mod.f90 index 9c564b67..1282a8c7 100644 --- a/mlprec/mld_s_base_solver_mod.f90 +++ b/mlprec/mld_s_base_solver_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_s_diag_solver.f90 b/mlprec/mld_s_diag_solver.f90 index 541496f0..3af49116 100644 --- a/mlprec/mld_s_diag_solver.f90 +++ b/mlprec/mld_s_diag_solver.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_s_gs_solver.f90 b/mlprec/mld_s_gs_solver.f90 index 82959cfd..a9cb146a 100644 --- a/mlprec/mld_s_gs_solver.f90 +++ b/mlprec/mld_s_gs_solver.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_s_hybrid_aggregator_mod.F90 b/mlprec/mld_s_hybrid_aggregator_mod.F90 index 5db38098..c7619e98 100644 --- a/mlprec/mld_s_hybrid_aggregator_mod.F90 +++ b/mlprec/mld_s_hybrid_aggregator_mod.F90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/mld_s_id_solver.f90 b/mlprec/mld_s_id_solver.f90 index e6ffa7d2..f483935a 100644 --- a/mlprec/mld_s_id_solver.f90 +++ b/mlprec/mld_s_id_solver.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_s_ilu_fact_mod.f90 b/mlprec/mld_s_ilu_fact_mod.f90 index fc109093..0722a423 100644 --- a/mlprec/mld_s_ilu_fact_mod.f90 +++ b/mlprec/mld_s_ilu_fact_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_s_ilu_solver.f90 b/mlprec/mld_s_ilu_solver.f90 index e2fb0fa3..a8d0e919 100644 --- a/mlprec/mld_s_ilu_solver.f90 +++ b/mlprec/mld_s_ilu_solver.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_s_inner_mod.f90 b/mlprec/mld_s_inner_mod.f90 index 42317490..512d60c7 100644 --- a/mlprec/mld_s_inner_mod.f90 +++ b/mlprec/mld_s_inner_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_s_jac_smoother.f90 b/mlprec/mld_s_jac_smoother.f90 index 5a9c292b..561232bf 100644 --- a/mlprec/mld_s_jac_smoother.f90 +++ b/mlprec/mld_s_jac_smoother.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_s_mumps_solver.F90 b/mlprec/mld_s_mumps_solver.F90 index 676a54db..464f0a75 100644 --- a/mlprec/mld_s_mumps_solver.F90 +++ b/mlprec/mld_s_mumps_solver.F90 @@ -1,10 +1,10 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.0) +! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008,2009,2010,2012,2013 +! (C) Copyright 2008-2018 ! ! Salvatore Filippone ! Pasqua D'Ambra diff --git a/mlprec/mld_s_onelev_mod.f90 b/mlprec/mld_s_onelev_mod.f90 index 0c6b653d..3bfb50c3 100644 --- a/mlprec/mld_s_onelev_mod.f90 +++ b/mlprec/mld_s_onelev_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_s_prec_mod.f90 b/mlprec/mld_s_prec_mod.f90 index 27e9c75a..f7cd86bb 100644 --- a/mlprec/mld_s_prec_mod.f90 +++ b/mlprec/mld_s_prec_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_s_prec_type.f90 b/mlprec/mld_s_prec_type.f90 index a53c65e8..20adde41 100644 --- a/mlprec/mld_s_prec_type.f90 +++ b/mlprec/mld_s_prec_type.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_s_slu_solver.F90 b/mlprec/mld_s_slu_solver.F90 index 1f5a3b0e..ae70454b 100644 --- a/mlprec/mld_s_slu_solver.F90 +++ b/mlprec/mld_s_slu_solver.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_s_symdec_aggregator_mod.f90 b/mlprec/mld_s_symdec_aggregator_mod.f90 index fbc89303..de5c46d7 100644 --- a/mlprec/mld_s_symdec_aggregator_mod.f90 +++ b/mlprec/mld_s_symdec_aggregator_mod.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/mld_z_as_smoother.f90 b/mlprec/mld_z_as_smoother.f90 index 851ad738..4e11a61a 100644 --- a/mlprec/mld_z_as_smoother.f90 +++ b/mlprec/mld_z_as_smoother.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_z_base_aggregator_mod.f90 b/mlprec/mld_z_base_aggregator_mod.f90 index b3bd3cf2..cd99cf1a 100644 --- a/mlprec/mld_z_base_aggregator_mod.f90 +++ b/mlprec/mld_z_base_aggregator_mod.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/mld_z_base_smoother_mod.f90 b/mlprec/mld_z_base_smoother_mod.f90 index 0758eceb..c73473e1 100644 --- a/mlprec/mld_z_base_smoother_mod.f90 +++ b/mlprec/mld_z_base_smoother_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_z_base_solver_mod.f90 b/mlprec/mld_z_base_solver_mod.f90 index ede7477d..37d2b03c 100644 --- a/mlprec/mld_z_base_solver_mod.f90 +++ b/mlprec/mld_z_base_solver_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_z_diag_solver.f90 b/mlprec/mld_z_diag_solver.f90 index b8f6f60a..ee1c6562 100644 --- a/mlprec/mld_z_diag_solver.f90 +++ b/mlprec/mld_z_diag_solver.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_z_gs_solver.f90 b/mlprec/mld_z_gs_solver.f90 index 21016387..fe14eb15 100644 --- a/mlprec/mld_z_gs_solver.f90 +++ b/mlprec/mld_z_gs_solver.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_z_hybrid_aggregator_mod.F90 b/mlprec/mld_z_hybrid_aggregator_mod.F90 index be353fc4..4e74d5bb 100644 --- a/mlprec/mld_z_hybrid_aggregator_mod.F90 +++ b/mlprec/mld_z_hybrid_aggregator_mod.F90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/mld_z_id_solver.f90 b/mlprec/mld_z_id_solver.f90 index 561cd0fa..8775c5a4 100644 --- a/mlprec/mld_z_id_solver.f90 +++ b/mlprec/mld_z_id_solver.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_z_ilu_fact_mod.f90 b/mlprec/mld_z_ilu_fact_mod.f90 index 6bed0435..80edcf81 100644 --- a/mlprec/mld_z_ilu_fact_mod.f90 +++ b/mlprec/mld_z_ilu_fact_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_z_ilu_solver.f90 b/mlprec/mld_z_ilu_solver.f90 index 5966151b..1e7f563a 100644 --- a/mlprec/mld_z_ilu_solver.f90 +++ b/mlprec/mld_z_ilu_solver.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_z_inner_mod.f90 b/mlprec/mld_z_inner_mod.f90 index b512d3db..2100d576 100644 --- a/mlprec/mld_z_inner_mod.f90 +++ b/mlprec/mld_z_inner_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_z_jac_smoother.f90 b/mlprec/mld_z_jac_smoother.f90 index af68bc9a..d3316f17 100644 --- a/mlprec/mld_z_jac_smoother.f90 +++ b/mlprec/mld_z_jac_smoother.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_z_mumps_solver.F90 b/mlprec/mld_z_mumps_solver.F90 index b9c64a6c..5558ec2d 100644 --- a/mlprec/mld_z_mumps_solver.F90 +++ b/mlprec/mld_z_mumps_solver.F90 @@ -1,10 +1,10 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.0) +! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008,2009,2010,2012,2013 +! (C) Copyright 2008-2018 ! ! Salvatore Filippone ! Pasqua D'Ambra diff --git a/mlprec/mld_z_onelev_mod.f90 b/mlprec/mld_z_onelev_mod.f90 index 0effdfeb..b5d873a9 100644 --- a/mlprec/mld_z_onelev_mod.f90 +++ b/mlprec/mld_z_onelev_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_z_prec_mod.f90 b/mlprec/mld_z_prec_mod.f90 index 374a41b2..2c402d10 100644 --- a/mlprec/mld_z_prec_mod.f90 +++ b/mlprec/mld_z_prec_mod.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_z_prec_type.f90 b/mlprec/mld_z_prec_type.f90 index 3def4f30..880085f1 100644 --- a/mlprec/mld_z_prec_type.f90 +++ b/mlprec/mld_z_prec_type.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_z_slu_solver.F90 b/mlprec/mld_z_slu_solver.F90 index 78d3b3c0..77151a11 100644 --- a/mlprec/mld_z_slu_solver.F90 +++ b/mlprec/mld_z_slu_solver.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_z_sludist_solver.F90 b/mlprec/mld_z_sludist_solver.F90 index 5f4b1a79..be0c56e5 100644 --- a/mlprec/mld_z_sludist_solver.F90 +++ b/mlprec/mld_z_sludist_solver.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/mlprec/mld_z_symdec_aggregator_mod.f90 b/mlprec/mld_z_symdec_aggregator_mod.f90 index f1f08e7d..a16fd1a3 100644 --- a/mlprec/mld_z_symdec_aggregator_mod.f90 +++ b/mlprec/mld_z_symdec_aggregator_mod.f90 @@ -1,15 +1,14 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! -! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! (C) Copyright 2008-2018 ! -! Salvatore Filippone Cranfield University -! Ambra Abdullahi Hassan University of Rome Tor Vergata -! Pasqua D'Ambra IAC-CNR, Naples, IT -! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino ! ! Redistribution and use in source and binary forms, with or without ! modification, are permitted provided that the following conditions diff --git a/mlprec/mld_z_umf_solver.F90 b/mlprec/mld_z_umf_solver.F90 index 4ca6445f..da955d5d 100644 --- a/mlprec/mld_z_umf_solver.F90 +++ b/mlprec/mld_z_umf_solver.F90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/tests/fileread/data_input.f90 b/tests/fileread/data_input.f90 index fe548526..b25cdeb0 100644 --- a/tests/fileread/data_input.f90 +++ b/tests/fileread/data_input.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/tests/fileread/mld_cf_sample.f90 b/tests/fileread/mld_cf_sample.f90 index 8883d18a..c494301b 100644 --- a/tests/fileread/mld_cf_sample.f90 +++ b/tests/fileread/mld_cf_sample.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/tests/fileread/mld_df_sample.f90 b/tests/fileread/mld_df_sample.f90 index 3a9a77dd..7a84e045 100644 --- a/tests/fileread/mld_df_sample.f90 +++ b/tests/fileread/mld_df_sample.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/tests/fileread/mld_sf_sample.f90 b/tests/fileread/mld_sf_sample.f90 index f08aa486..58ace825 100644 --- a/tests/fileread/mld_sf_sample.f90 +++ b/tests/fileread/mld_sf_sample.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/tests/fileread/mld_zf_sample.f90 b/tests/fileread/mld_zf_sample.f90 index 3f6533ce..5474305f 100644 --- a/tests/fileread/mld_zf_sample.f90 +++ b/tests/fileread/mld_zf_sample.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/tests/newslv/data_input.f90 b/tests/newslv/data_input.f90 index a8733b56..e6a8582b 100644 --- a/tests/newslv/data_input.f90 +++ b/tests/newslv/data_input.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/tests/newslv/mld_d_tlu_solver.f90 b/tests/newslv/mld_d_tlu_solver.f90 index cf04d546..af6fb6bd 100644 --- a/tests/newslv/mld_d_tlu_solver.f90 +++ b/tests/newslv/mld_d_tlu_solver.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/tests/newslv/mld_d_tlu_solver_impl.f90 b/tests/newslv/mld_d_tlu_solver_impl.f90 index 8369443d..086a1c80 100644 --- a/tests/newslv/mld_d_tlu_solver_impl.f90 +++ b/tests/newslv/mld_d_tlu_solver_impl.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/tests/newslv/mld_pde3d_newslv.f90 b/tests/newslv/mld_pde3d_newslv.f90 index 9281909d..c0533508 100644 --- a/tests/newslv/mld_pde3d_newslv.f90 +++ b/tests/newslv/mld_pde3d_newslv.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/tests/pdegen/data_input.f90 b/tests/pdegen/data_input.f90 index fe548526..b25cdeb0 100644 --- a/tests/pdegen/data_input.f90 +++ b/tests/pdegen/data_input.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/tests/pdegen/mld_d_pde2d.f90 b/tests/pdegen/mld_d_pde2d.f90 index b8fe23cb..1c35cb52 100644 --- a/tests/pdegen/mld_d_pde2d.f90 +++ b/tests/pdegen/mld_d_pde2d.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/tests/pdegen/mld_d_pde3d.f90 b/tests/pdegen/mld_d_pde3d.f90 index a0976844..50c77756 100644 --- a/tests/pdegen/mld_d_pde3d.f90 +++ b/tests/pdegen/mld_d_pde3d.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/tests/pdegen/mld_s_pde2d.f90 b/tests/pdegen/mld_s_pde2d.f90 index bd5670e7..cf30ffdb 100644 --- a/tests/pdegen/mld_s_pde2d.f90 +++ b/tests/pdegen/mld_s_pde2d.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! diff --git a/tests/pdegen/mld_s_pde3d.f90 b/tests/pdegen/mld_s_pde3d.f90 index 3e2f8c32..540ea723 100644 --- a/tests/pdegen/mld_s_pde3d.f90 +++ b/tests/pdegen/mld_s_pde3d.f90 @@ -1,6 +1,6 @@ ! ! -! MLD2P4 version 2.1 +! MLD2P4 version 2.2 ! MultiLevel Domain Decomposition Parallel Preconditioners Package ! based on PSBLAS (Parallel Sparse BLAS version 3.5) ! From 24988bcfc5ac1385d852741352f561c24d273731 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Sat, 5 May 2018 14:35:47 +0100 Subject: [PATCH 17/33] Moved BootCMatch interface to tests; to be reviewed later. --- mlprec/Makefile | 3 +- .../mld_d_bcmatch_aggregator_mat_asb.f90 | 225 +++++++++++ .../Bcmatch}/mld_d_bcmatch_aggregator_mod.F90 | 0 .../mld_d_bcmatch_aggregator_tprol.f90 | 355 ++++++++++++++++++ tests/Bcmatch/mld_d_bcmatch_map_bld.f90 | 0 tests/Bcmatch/mld_d_bcmatch_map_to_tprol.f90 | 158 ++++++++ tests/pdegen/runs/mld_pde3d.inp | 2 +- 7 files changed, 741 insertions(+), 2 deletions(-) create mode 100644 tests/Bcmatch/mld_d_bcmatch_aggregator_mat_asb.f90 rename {mlprec => tests/Bcmatch}/mld_d_bcmatch_aggregator_mod.F90 (100%) create mode 100644 tests/Bcmatch/mld_d_bcmatch_aggregator_tprol.f90 create mode 100644 tests/Bcmatch/mld_d_bcmatch_map_bld.f90 create mode 100644 tests/Bcmatch/mld_d_bcmatch_map_to_tprol.f90 diff --git a/mlprec/Makefile b/mlprec/Makefile index d89347b7..5de506ee 100644 --- a/mlprec/Makefile +++ b/mlprec/Makefile @@ -13,7 +13,8 @@ DMODOBJS=mld_d_prec_type.o mld_d_ilu_fact_mod.o \ mld_d_base_solver_mod.o mld_d_base_smoother_mod.o mld_d_onelev_mod.o \ mld_d_gs_solver.o mld_d_mumps_solver.o \ mld_d_base_aggregator_mod.o mld_d_hybrid_aggregator_mod.o \ - mld_d_symdec_aggregator_mod.o mld_d_bcmatch_aggregator_mod.o + mld_d_symdec_aggregator_mod.o +#mld_d_bcmatch_aggregator_mod.o SMODOBJS=mld_s_prec_type.o mld_s_ilu_fact_mod.o \ mld_s_inner_mod.o mld_s_ilu_solver.o mld_s_diag_solver.o mld_s_jac_smoother.o mld_s_as_smoother.o \ diff --git a/tests/Bcmatch/mld_d_bcmatch_aggregator_mat_asb.f90 b/tests/Bcmatch/mld_d_bcmatch_aggregator_mat_asb.f90 new file mode 100644 index 00000000..750c068b --- /dev/null +++ b/tests/Bcmatch/mld_d_bcmatch_aggregator_mat_asb.f90 @@ -0,0 +1,225 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_d_base_aggregator_mat_asb.f90 +! +! Subroutine: mld_d_base_aggregator_mat_asb +! Version: real +! +! This routine builds the matrix associated to the current level of the +! multilevel preconditioner from the matrix associated to the previous level, +! by using the user-specified aggregation technique (therefore, it also builds the +! prolongation and restriction operators mapping the current level to the +! previous one and vice versa). +! The current level is regarded as the coarse one, while the previous as +! the fine one. This is in agreement with the fact that the routine is called, +! by mld_mlprec_bld, only on levels >=2. +! The coarse-level matrix A_C is built from a fine-level matrix A +! by using the Galerkin approach, i.e. +! +! A_C = P_C^T A P_C, +! +! where P_C is a prolongator from the coarse level to the fine one. +! +! A mapping from the nodes of the adjacency graph of A to the nodes of the +! adjacency graph of A_C has been computed by the mld_aggrmap_bld subroutine. +! The prolongator P_C is built here from this mapping, according to the +! value of p%iprcparm(mld_aggr_kind_), specified by the user through +! mld_dprecinit and mld_zprecset. +! On output from this routine the entries of AC, op_prol, op_restr +! are still in "global numbering" mode; this is fixed in the calling routine +! mld_d_lev_aggrmat_asb. +! +! Currently four different prolongators are implemented, corresponding to +! four aggregation algorithms: +! 1. un-smoothed aggregation, +! 2. smoothed aggregation, +! 3. "bizarre" aggregation. +! 4. minimum energy +! 1. The non-smoothed aggregation uses as prolongator the piecewise constant +! interpolation operator corresponding to the fine-to-coarse level mapping built +! by p%aggr%bld_tprol. This is called tentative prolongator. +! 2. The smoothed aggregation uses as prolongator the operator obtained by applying +! a damped Jacobi smoother to the tentative prolongator. +! 3. The "bizarre" aggregation uses a prolongator proposed by the authors of MLD2P4. +! This prolongator still requires a deep analysis and testing and its use is +! not recommended. +! 4. Minimum energy aggregation +! +! For more details see +! M. Brezina and P. Vanek, A black-box iterative solver based on a two-level +! Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of PSBLAS-based +! parallel two-level Schwarz preconditioners, Appl. Num. Math., 57 (2007), +! 1181-1196. +! M. Sala, R. Tuminaro: A new Petrov-Galerkin smoothed aggregation preconditioner +! for nonsymmetric linear systems, SIAM J. Sci. Comput., 31(1):143-166 (2008) +! +! +! The main structure is: +! 1. Perform sanity checks; +! 2. Compute prolongator/restrictor/AC +! +! +! Arguments: +! ag - type(mld_d_base_aggregator_type), input/output. +! The aggregator object +! parms - type(mld_dml_parms), input +! The aggregation parameters +! 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. +! The communication descriptor of the fine-level matrix. +! The 'one-level' data structure that will contain the local +! part of the matrix to be built as well as the information +! concerning the prolongator and its transpose. +! ilaggr - integer, dimension(:), input +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that the indices +! are assumed to be shifted so as to make sure the ranges on +! the various processes do not overlap. +! nlaggr - integer, dimension(:) input +! nlaggr(i) contains the aggregates held by process i. +! ac - type(psb_dspmat_type), output +! The coarse matrix on output +! +! op_prol - type(psb_dspmat_type), input/output +! The tentative prolongator on input, the computed prolongator on output +! +! op_restr - type(psb_dspmat_type), output +! The restrictor operator; normally, it is the transpose of the prolongator. +! +! info - integer, output. +! Error code. +! +subroutine mld_d_bcmatch_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) + use psb_base_mod + use mld_d_inner_mod!, mld_protect_name => mld_d_base_aggregator_mat_asb + implicit none + + class(mld_d_base_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) + type(psb_dspmat_type), intent(inout) :: op_prol + type(psb_dspmat_type), intent(out) :: ac,op_restr + integer(psb_ipk_), intent(out) :: info + + ! Local variables + character(len=20) :: name + integer(psb_mpik_) :: ictxt, np, me + type(psb_d_coo_sparse_mat) :: acoo, bcoo + type(psb_d_csr_sparse_mat) :: acsr1 + integer(psb_ipk_) :: nzl,ntaggr + integer(psb_ipk_) :: err_act + integer(psb_ipk_) :: debug_level, debug_unit + + name='mld_d_base_aggregator_mat_asb' + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + + call mld_check_def(parms%aggr_kind,'Smoother',& + & mld_smooth_prol_,is_legal_ml_aggr_kind) + call mld_check_def(parms%coarse_mat,'Coarse matrix',& + & mld_distr_mat_,is_legal_ml_coarse_mat) + call mld_check_def(parms%aggr_filter,'Use filtered matrix',& + & mld_no_filter_mat_,is_legal_aggr_filter) + call mld_check_def(parms%smoother_pos,'smooth_pos',& + & mld_pre_smooth_,is_legal_ml_smooth_pos) + call mld_check_def(parms%aggr_omega_alg,'Omega Alg.',& + & mld_eig_est_,is_legal_ml_aggr_omega_alg) + call mld_check_def(parms%aggr_eig,'Eigenvalue estimate',& + & mld_max_norm_,is_legal_ml_aggr_eig) + call mld_check_def(parms%aggr_omega_val,'Omega',dzero,is_legal_d_omega) + + ! + ! Build the coarse-level matrix from the fine-level one, starting from + ! the mapping defined by mld_aggrmap_bld and applying the aggregation + ! algorithm specified by p%iprcparm(mld_aggr_kind_) + ! + select case (parms%aggr_kind) + case (mld_no_smooth_) + + call mld_daggrmat_unsmth_spmm_asb(a,desc_a,ilaggr,nlaggr,& + & parms,ac,op_prol,op_restr,info) + + case(mld_smooth_prol_) + + call mld_daggrmat_smth_asb(a,desc_a,ilaggr,nlaggr, & + & parms,ac,op_prol,op_restr,info) + + case(mld_biz_prol_) + + call mld_daggrmat_biz_asb(a,desc_a,ilaggr,nlaggr, & + & parms,ac,op_prol,op_restr,info) + + case(mld_min_energy_) + + call mld_daggrmat_minnrg_asb(a,desc_a,ilaggr,nlaggr, & + & parms,ac,op_prol,op_restr,info) + + case default + info = psb_err_internal_error_ + call psb_errpush(info,name,a_err='Invalid aggr kind') + goto 9999 + + end select + if (info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='Inner aggrmat asb') + goto 9999 + end if + + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + + +end subroutine mld_d_bcmatch_aggregator_mat_asb diff --git a/mlprec/mld_d_bcmatch_aggregator_mod.F90 b/tests/Bcmatch/mld_d_bcmatch_aggregator_mod.F90 similarity index 100% rename from mlprec/mld_d_bcmatch_aggregator_mod.F90 rename to tests/Bcmatch/mld_d_bcmatch_aggregator_mod.F90 diff --git a/tests/Bcmatch/mld_d_bcmatch_aggregator_tprol.f90 b/tests/Bcmatch/mld_d_bcmatch_aggregator_tprol.f90 new file mode 100644 index 00000000..d6b511fe --- /dev/null +++ b/tests/Bcmatch/mld_d_bcmatch_aggregator_tprol.f90 @@ -0,0 +1,355 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_d_bcmatch_aggregator_tprol.f90 +! +! Subroutine: mld_d_bcmatch_aggregator_tprol +! Version: real +! +! +! This routine is mainly an interface to hyb_map_bld where the real work is performed. +! It takes care of some consistency checking, and calls map_to_tprol, which is +! refactored and shared among all the aggregation methods that produce a simple +! integer mapping. +! +! +! Arguments: +! p - type(mld_d_onelev_type), input/output. +! The 'one-level' data structure containing the control +! parameters and (eventually) coarse matrix and prolongator/restrictors. +! +! a - type(psb_dspmat_type). +! The sparse matrix structure containing the local part of the +! fine-level matrix. +! desc_a - type(psb_desc_type), input. +! The communication descriptor of a. +! ilaggr - integer, dimension(:), allocatable, output +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that on exit the indices +! will be shifted so as to make sure the ranges on the various processes do not +! overlap. +! nlaggr - integer, dimension(:), allocatable, output +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_dspmat_type), output +! The tentative prolongator, based on ilaggr. +! +! info - integer, output. +! Error code. +! + +module bcm_CSRMatrix_mod +use psb_base_mod +use psb_util_mod +use iso_c_binding +use bcm_csr_type_mod +implicit none + +contains + subroutine MLD_to_CSR(a,csr_ia, csr_ja, csr_val, C, info) + type(psb_dspmat_type), intent(in) :: a + type(bcm_CSRMatrix), intent(out) :: C + real(c_double), allocatable, target, intent(out) :: csr_val(:) + integer(c_int), allocatable, target, intent(out) :: csr_ia(:), csr_ja(:) + + !Local variable + character(len=20) :: name + integer(psb_ipk_) :: info + real(psb_dpk_), allocatable :: coo_val(:) + integer(psb_ipk_), allocatable :: coo_ia(:), coo_ja(:) + integer(psb_ipk_) :: x, nz, num_rows, num_cols , i , j, iad, k , k0 + type(psb_d_csr_sparse_mat) :: acsr + + name="MLD_to_CSR" + num_rows= a%get_nrows() + num_cols= a%get_ncols() + nz= a%get_nzeros() + call a%csgetrow(1,num_rows,nz,coo_ia,coo_ja,coo_val,info) + !allocate(csr_ia(0:nz-1), csr_ja(0:nz-1), csr_val(0:nz-1), STAT=info) + if (info /= psb_success_) then + info=psb_err_alloc_request_ + call psb_errpush(info,name,i_err=(/nz,izero,izero,izero,izero/),& + & a_err='integer') + return + end if + + call a%cp_to(acsr) + allocate(csr_ia(0:nz-1), csr_ja(0:nz-1), csr_val(0:nz-1), STAT=info) + + + csr_ia(0:min(nz,size(acsr%irp,1))-1)=acsr%irp(1:min(nz,size(acsr%irp,1)))-1 + csr_ja(0:nz-1)=acsr%ja(1:nz)-1 + csr_val(0:nz-1)=acsr%val(1:nz) + + call acsr%free() + + C%num_rows=num_rows + C%num_cols=num_cols + C%num_nonzeros=nz + C%owns_data=0 + C%i=c_loc(csr_ia) + C%j=c_loc(csr_ja) + C%data=c_loc(csr_val) + end subroutine MLD_to_CSR + + subroutine bcm_to_op_prol(P, ilaggr, valaggr, info) + type(bcm_CSRMatrix), intent(in) :: P + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:) + integer(psb_ipk_), intent(out) :: info + real(psb_dpk_), allocatable, intent(out) :: valaggr(:) + + ! Local variables + integer(psb_ipk_), pointer :: point_ia(:), point_ja(:) + real(psb_dpk_), pointer :: point_val(:) + integer(psb_ipk_) :: i, j, k + integer(psb_ipk_) :: n, num_rows, num_cols, num_nz + character(len=20) :: name + integer(c_int), allocatable, target :: coo_ia(:),coo_ja(:) + real(c_double), allocatable, target :: coo_val(:) + + name="bcm_to_op_prol" + num_nz = P%num_nonzeros + num_rows = P%num_rows + num_cols = P%num_cols + call c_f_pointer(P%i,point_ia,(/num_rows+1/)) + call c_f_pointer(P%j,point_ja,(/num_nz/)) + call c_f_pointer(P%data,point_val,(/num_nz/)) + + !These are I, J, VAL. + !These are I, J, VAL. + if (allocated(coo_ia)) deallocate(coo_ia) + if (allocated(coo_ja)) deallocate(coo_ja) + if (allocated(coo_val)) deallocate(coo_val) + allocate(coo_ia(num_nz),coo_ja(num_nz),coo_val(num_nz), STAT=info) +!!$ write(0,*) num_rows,num_cols,num_nz,info,size(coo_val) + if (info /= psb_success_) then + info=psb_err_alloc_request_ + call psb_errpush(info,name,i_err=(/num_nz,izero,izero,izero,izero/),& + & a_err='integer') + return + end if + + n = 1 + !coo_ia=-123 + !coo_ja=-123 + coo_val(1:num_nz)=point_val(1:num_nz) + do i=1, num_rows + do j=point_ia(i)+1, point_ia(i+1) + coo_ia(n)=i + coo_ja(n)=point_ja(j) + 1 + n = n + 1 + enddo + enddo + if (allocated(ilaggr)) deallocate(ilaggr) + if (allocated(valaggr)) deallocate(valaggr) + allocate(ilaggr(num_rows),valaggr(num_rows), STAT=info) + ilaggr=0 + if (info /= psb_success_) then + info=psb_err_alloc_request_ + call psb_errpush(info,name,i_err=(/num_rows,izero,izero,izero,izero/),& + & a_err='integer') + return + end if + + do k=1,num_nz + i=coo_ia(k) + j=coo_ja(k) + ilaggr(i)=j + valaggr(i)=coo_val(i) + enddo + if (allocated(coo_ia)) deallocate(coo_ia) + if (allocated(coo_ja)) deallocate(coo_ja) + if (allocated(coo_val)) deallocate(coo_val) + nullify(point_ia) + nullify(point_ja) + nullify(point_val) + end subroutine bcm_to_op_prol +end module bcm_CSRMatrix_mod + + +subroutine mld_d_bcmatch_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod + use mld_d_bcmatch_aggregator_mod, mld_protect_name => mld_d_bcmatch_aggregator_build_tprol + use mld_d_inner_mod + !use bcm_CSRMatrix_mod + use bcm_csr_type_mod + use iso_c_binding + implicit none + class(mld_d_bcmatch_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + real(psb_dpk_), allocatable:: valaggr(:) + type(psb_dspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + + ! Local variables + type(psb_dspmat_type) :: a_tmp + type(bcm_CSRMatrix) :: C, P + integer(c_int) :: match_algorithm, n_sweeps, max_csize, max_nlevels + character(len=20) :: name, ch_err + integer(psb_mpik_) :: ictxt, np, me + integer(psb_ipk_) :: err_act, ierr + integer(psb_ipk_) :: debug_level, debug_unit + integer(psb_ipk_) :: i, j, k, nr, nc, isz, num_pcols + type(psb_d_csr_sparse_mat), target :: acsr + integer(psb_ipk_), allocatable, target :: csr_ia(:), csr_ja(:) + integer(psb_ipk_), allocatable :: aux(:) + real(psb_dpk_), allocatable, target:: csr_val(:) + interface + function bootCMatch(C,match_alg,n_sweeps,max_nlevels,max_csize,w)bind(c,name='bootCMatch') result(P) + use iso_c_binding + use bcm_CSRMatrix_mod + implicit none + type(bcm_CSRMatrix) :: C, P + type(bcm_Vector) :: w + integer(c_int) :: match_alg + integer(c_int) :: n_sweeps + integer(c_int) :: max_nlevels + integer(c_int) :: max_csize + end function bootCMatch + end interface + + interface + function mld_bootCMatch_if(C,match_alg,n_sweeps,max_nlevels,max_csize,& + & w,isz,ilaggr,valaggr, num_cols) & + & bind(c,name='mld_bootCMatch_if') result(iret) + use iso_c_binding + use bcm_CSRMatrix_mod + implicit none + type(bcm_CSRMatrix) :: C, P + type(bcm_Vector) :: w + integer(c_int), value :: match_alg + integer(c_int), value :: n_sweeps + integer(c_int), value :: max_nlevels + integer(c_int), value :: max_csize + integer(c_int), value :: isz + integer(c_int) :: num_cols + integer(c_int) :: ilaggr(*) + real(c_double) :: valaggr(*) + integer(c_int) :: iret + end function mld_bootCMatch_if + end interface + + name='mld_d_bcmatch_aggregator_tprol' + ictxt = desc_a%get_context() + call psb_info(ictxt,me,np) + if (psb_get_errstatus().ne.0) return + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + info = psb_success_ + + + call mld_check_def(parms%ml_type,'Multilevel type',& + & mld_mult_ml_,is_legal_ml_type) + call mld_check_def(parms%aggr_alg,'Aggregation',& + & mld_dec_aggr_,is_legal_ml_aggr_alg) + call mld_check_def(parms%aggr_ord,'Ordering',& + & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) + call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) + + call a%csclip(b=a_tmp, info=info, jmax=a%get_nrows(), imax=a%get_nrows()) + + call a_tmp%mv_to(acsr) + + !write(*,*) 'Build_tprol:',acsr%get_nrows(),acsr%get_ncols() + C%num_rows=acsr%get_nrows() + C%num_cols=acsr%get_ncols() + C%num_nonzeros=acsr%get_nzeros() + C%owns_data=0 + acsr%irp = acsr%irp - 1 + acsr%ja = acsr%ja - 1 + C%i=c_loc(acsr%irp) + C%j=c_loc(acsr%ja) + C%data=c_loc(acsr%val) + + isz = a%get_ncols() + call psb_realloc(isz,ilaggr,info) + if (info == psb_success_) call psb_realloc(isz,valaggr,info) + if (info /= psb_success_) then + info=psb_err_from_subroutine_ + ch_err='psb_realloc' + call psb_errpush(info,name,a_err=ch_err) + goto 9999 + end if + + match_algorithm = ag%matching_alg + n_sweeps = ag%n_sweeps + max_csize = ag%max_csize + max_nlevels = ag%max_nlevels + + info = mld_bootCMatch_if(C,match_algorithm,n_sweeps,max_nlevels,max_csize,& + & ag%w_par, isz, ilaggr, valaggr, num_pcols) + if (info /= psb_success_) then +!!$ write(0,*) 'On return from bootCMatch_if:',info + call psb_errpush(psb_err_from_subroutine_,name,a_err='mld_bootCMatch_if') + goto 9999 + end if + + call psb_realloc(np,nlaggr,info) + if (info /= psb_success_) then + info=psb_err_alloc_request_ + call psb_errpush(info,name,i_err=(/np,izero,izero,izero,izero/),& + & a_err='integer') + goto 9999 + end if + call acsr%free() + + nlaggr(:)=0 + nlaggr(me+1) = num_pcols + call psb_sum(ictxt,nlaggr(1:np)) + + + call mld_bcmatch_map_to_tprol(desc_a,ilaggr,nlaggr,valaggr,op_prol,info) + if (info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='mld_bcmatch_map_to_tprol') + goto 9999 + end if + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + return + +end subroutine mld_d_bcmatch_aggregator_build_tprol diff --git a/tests/Bcmatch/mld_d_bcmatch_map_bld.f90 b/tests/Bcmatch/mld_d_bcmatch_map_bld.f90 new file mode 100644 index 00000000..e69de29b diff --git a/tests/Bcmatch/mld_d_bcmatch_map_to_tprol.f90 b/tests/Bcmatch/mld_d_bcmatch_map_to_tprol.f90 new file mode 100644 index 00000000..960f9cb9 --- /dev/null +++ b/tests/Bcmatch/mld_d_bcmatch_map_to_tprol.f90 @@ -0,0 +1,158 @@ +! +! +! MLD2P4 version 2.1 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008, 2010, 2012, 2015, 2017 , 2017 +! +! Salvatore Filippone Cranfield University +! Ambra Abdullahi Hassan University of Rome Tor Vergata +! Pasqua D'Ambra IAC-CNR, Naples, IT +! Daniela di Serafino University of Campania "L. Vanvitelli", Caserta, IT +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! File: mld_d_bcmatch_map_to_tprol.f90 +! +! Subroutine: mld_d_bcmatch_map_to_tprol +! Version: real +! +! This routine uses a mapping from the row indices of the fine-level matrix +! to the row indices of the coarse-level matrix to build a tentative +! prolongator, i.e. a piecewise constant operator. +! This is later used to build the final operator; the code has been refactored here +! to be shared among all the methods that provide the tentative prolongator +! through a simple integer mapping. +! +! The aggregation algorithm is a parallel version of that described in +! * M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! * P. Vanek, J. Mandel and M. Brezina, Algebraic Multigrid by Smoothed +! Aggregation for Second and Fourth Order Elliptic Problems, Computing, 56 +! (1996), 179-196. +! For more details see +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +! +! Arguments: +! aggr_type - integer, input. +! The scalar used to identify the aggregation algorithm. +! theta - real, input. +! The aggregation threshold used in the aggregation algorithm. +! 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. +! The communication descriptor of the fine-level matrix. +! ilaggr - integer, dimension(:), allocatable. +! The mapping between the row indices of the coarse-level +! matrix and the row indices of the fine-level matrix. +! ilaggr(i)=j means that node i in the adjacency graph +! of the fine-level matrix is mapped onto node j in the +! adjacency graph of the coarse-level matrix. Note that on exit the indices +! will be shifted so as to make sure the ranges on the various processes do not +! overlap. +! nlaggr - integer, dimension(:), allocatable. +! nlaggr(i) contains the aggregates held by process i. +! op_prol - type(psb_dspmat_type). +! The tentative prolongator, based on ilaggr. +! +! info - integer, output. +! Error code. +! +subroutine mld_d_bcmatch_map_to_tprol(desc_a,ilaggr,nlaggr,valaggr, op_prol,info) + + use psb_base_mod + use mld_d_inner_mod, mld_protect_name => mld_d_bcmatch_map_to_tprol + + implicit none + + ! Arguments + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(inout) :: ilaggr(:),nlaggr(:) + real(psb_dpk_), allocatable, intent(inout) :: valaggr(:) + type(psb_dspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + ! Local variables + integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m,naggrm1, naggrp1, ntaggr + type(psb_d_coo_sparse_mat) :: tmpcoo + integer(psb_ipk_) :: debug_level, debug_unit,err_act + integer(psb_ipk_) :: ictxt,np,me + integer(psb_ipk_) :: nrow, ncol, n_ne + character(len=20) :: name, ch_err + + if(psb_get_errstatus() /= 0) return + info=psb_success_ + name = 'mld_d_bcmatch_map_to_tprol' + call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() + ! + ictxt=desc_a%get_context() + call psb_info(ictxt,me,np) + nrow = desc_a%get_local_rows() + ncol = desc_a%get_local_cols() + + naggr = nlaggr(me+1) + ntaggr = sum(nlaggr) + naggrm1 = sum(nlaggr(1:me)) + naggrp1 = sum(nlaggr(1:me+1)) + ilaggr(1:nrow) = ilaggr(1:nrow) + naggrm1 + call psb_halo(ilaggr,desc_a,info) + if (info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_halo') + goto 9999 + end if + + call psb_halo(valaggr,desc_a,info) + if (info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='psb_halo') + goto 9999 + end if + + call tmpcoo%allocate(ncol,ntaggr,ncol) + do i=1,ncol + tmpcoo%val(i) = valaggr(i) + tmpcoo%ia(i) = i + tmpcoo%ja(i) = ilaggr(i) + end do + call tmpcoo%set_nzeros(ncol) + call tmpcoo%set_dupl(psb_dupl_add_) + call tmpcoo%set_sorted() ! At this point this is in row-major + call op_prol%mv_from(tmpcoo) + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + +end subroutine mld_d_bcmatch_map_to_tprol diff --git a/tests/pdegen/runs/mld_pde3d.inp b/tests/pdegen/runs/mld_pde3d.inp index 316edc63..7d1bcbb7 100644 --- a/tests/pdegen/runs/mld_pde3d.inp +++ b/tests/pdegen/runs/mld_pde3d.inp @@ -1,7 +1,7 @@ %%%%%%%%%%% General arguments % Lines starting with % are ignored. CSR ! Storage format CSR COO JAD 0080 ! IDIM; domain size. Linear system size is IDIM**3 -CG ! Iterative method: BiCGSTAB BiCGSTABL BiCG CG CGS FCG GCR RGMRES +BICGSTAB ! Iterative method: BiCGSTAB BiCGSTABL BiCG CG CGS FCG GCR RGMRES 2 ! ISTOPC 00500 ! ITMAX 1 ! ITRACE From 7aadb73bd6d6c1a2d1b13ac33b592aa2bdfdc718 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Thu, 10 May 2018 14:00:47 +0100 Subject: [PATCH 18/33] New inheritance structure for aggregator object. --- mlprec/impl/aggregator/Makefile | 16 ++-- ...b.f90 => mld_c_dec_aggregator_mat_asb.f90} | 16 ++-- ...rol.f90 => mld_c_dec_aggregator_tprol.f90} | 14 +-- ...b.f90 => mld_d_dec_aggregator_mat_asb.f90} | 16 ++-- ...rol.f90 => mld_d_dec_aggregator_tprol.f90} | 14 +-- ...b.f90 => mld_s_dec_aggregator_mat_asb.f90} | 16 ++-- ...rol.f90 => mld_s_dec_aggregator_tprol.f90} | 14 +-- ...b.f90 => mld_z_dec_aggregator_mat_asb.f90} | 16 ++-- ...rol.f90 => mld_z_dec_aggregator_tprol.f90} | 14 +-- mlprec/impl/level/mld_c_base_onelev_cseti.F90 | 23 +++++ mlprec/impl/level/mld_c_base_onelev_seti.F90 | 23 +++++ mlprec/impl/level/mld_d_base_onelev_cseti.F90 | 23 +++++ mlprec/impl/level/mld_d_base_onelev_seti.F90 | 23 +++++ mlprec/impl/level/mld_s_base_onelev_cseti.F90 | 23 +++++ mlprec/impl/level/mld_s_base_onelev_seti.F90 | 23 +++++ mlprec/impl/level/mld_z_base_onelev_cseti.F90 | 23 +++++ mlprec/impl/level/mld_z_base_onelev_seti.F90 | 23 +++++ mlprec/mld_base_prec_type.F90 | 58 +++++++----- mlprec/mld_c_base_aggregator_mod.f90 | 94 ++++++++++++------- mlprec/mld_c_onelev_mod.f90 | 2 +- mlprec/mld_c_symdec_aggregator_mod.f90 | 4 +- mlprec/mld_d_base_aggregator_mod.f90 | 94 ++++++++++++------- mlprec/mld_d_onelev_mod.f90 | 2 +- mlprec/mld_d_symdec_aggregator_mod.f90 | 4 +- mlprec/mld_s_base_aggregator_mod.f90 | 94 ++++++++++++------- mlprec/mld_s_onelev_mod.f90 | 2 +- mlprec/mld_s_symdec_aggregator_mod.f90 | 4 +- mlprec/mld_z_base_aggregator_mod.f90 | 94 ++++++++++++------- mlprec/mld_z_onelev_mod.f90 | 2 +- mlprec/mld_z_symdec_aggregator_mod.f90 | 4 +- 30 files changed, 540 insertions(+), 238 deletions(-) rename mlprec/impl/aggregator/{mld_c_base_aggregator_mat_asb.f90 => mld_c_dec_aggregator_mat_asb.f90} (94%) rename mlprec/impl/aggregator/{mld_c_base_aggregator_tprol.f90 => mld_c_dec_aggregator_tprol.f90} (92%) rename mlprec/impl/aggregator/{mld_d_base_aggregator_mat_asb.f90 => mld_d_dec_aggregator_mat_asb.f90} (94%) rename mlprec/impl/aggregator/{mld_d_base_aggregator_tprol.f90 => mld_d_dec_aggregator_tprol.f90} (92%) rename mlprec/impl/aggregator/{mld_s_base_aggregator_mat_asb.f90 => mld_s_dec_aggregator_mat_asb.f90} (94%) rename mlprec/impl/aggregator/{mld_s_base_aggregator_tprol.f90 => mld_s_dec_aggregator_tprol.f90} (92%) rename mlprec/impl/aggregator/{mld_z_base_aggregator_mat_asb.f90 => mld_z_dec_aggregator_mat_asb.f90} (94%) rename mlprec/impl/aggregator/{mld_z_base_aggregator_tprol.f90 => mld_z_dec_aggregator_tprol.f90} (92%) diff --git a/mlprec/impl/aggregator/Makefile b/mlprec/impl/aggregator/Makefile index b1f2e402..ba217c1c 100644 --- a/mlprec/impl/aggregator/Makefile +++ b/mlprec/impl/aggregator/Makefile @@ -9,29 +9,29 @@ FINCLUDES=$(FMFLAG)$(HERE) $(FMFLAG)$(MODDIR) $(FMFLAG)$(INCDIR) $(PSBLAS_INCLUD #CINCLUDES= -I${SUPERLU_INCDIR} -I${HSL_INCDIR} -I${SPRAL_INCDIR} -I/home/users/pasqua/Ambra/BootCMatch/include -lBCM -L/home/users/pasqua/Ambra/BootCMatch/lib -lm OBJS= \ -mld_s_base_aggregator_mat_asb.o \ -mld_s_base_aggregator_tprol.o \ +mld_s_dec_aggregator_mat_asb.o \ +mld_s_dec_aggregator_tprol.o \ mld_s_hybrid_aggregator_tprol.o \ mld_s_symdec_aggregator_tprol.o \ mld_s_map_to_tprol.o mld_s_dec_map_bld.o mld_s_hyb_map_bld.o\ mld_saggrmat_biz_asb.o mld_saggrmat_minnrg_asb.o\ mld_saggrmat_nosmth_asb.o mld_saggrmat_smth_asb.o \ -mld_d_base_aggregator_mat_asb.o \ -mld_d_base_aggregator_tprol.o \ +mld_d_dec_aggregator_mat_asb.o \ +mld_d_dec_aggregator_tprol.o \ mld_d_hybrid_aggregator_tprol.o \ mld_d_symdec_aggregator_tprol.o \ mld_d_map_to_tprol.o mld_d_dec_map_bld.o mld_d_hyb_map_bld.o\ mld_daggrmat_biz_asb.o mld_daggrmat_minnrg_asb.o\ mld_daggrmat_nosmth_asb.o mld_daggrmat_smth_asb.o \ -mld_c_base_aggregator_mat_asb.o \ -mld_c_base_aggregator_tprol.o \ +mld_c_dec_aggregator_mat_asb.o \ +mld_c_dec_aggregator_tprol.o \ mld_c_hybrid_aggregator_tprol.o \ mld_c_symdec_aggregator_tprol.o \ mld_c_map_to_tprol.o mld_c_dec_map_bld.o mld_c_hyb_map_bld.o\ mld_caggrmat_biz_asb.o mld_caggrmat_minnrg_asb.o\ mld_caggrmat_nosmth_asb.o mld_caggrmat_smth_asb.o \ -mld_z_base_aggregator_mat_asb.o \ -mld_z_base_aggregator_tprol.o \ +mld_z_dec_aggregator_mat_asb.o \ +mld_z_dec_aggregator_tprol.o \ mld_z_hybrid_aggregator_tprol.o \ mld_z_symdec_aggregator_tprol.o \ mld_z_map_to_tprol.o mld_z_dec_map_bld.o mld_z_hyb_map_bld.o\ diff --git a/mlprec/impl/aggregator/mld_c_base_aggregator_mat_asb.f90 b/mlprec/impl/aggregator/mld_c_dec_aggregator_mat_asb.f90 similarity index 94% rename from mlprec/impl/aggregator/mld_c_base_aggregator_mat_asb.f90 rename to mlprec/impl/aggregator/mld_c_dec_aggregator_mat_asb.f90 index 69ca7c2e..0cce1101 100644 --- a/mlprec/impl/aggregator/mld_c_base_aggregator_mat_asb.f90 +++ b/mlprec/impl/aggregator/mld_c_dec_aggregator_mat_asb.f90 @@ -35,9 +35,9 @@ ! POSSIBILITY OF SUCH DAMAGE. ! ! -! File: mld_c_base_aggregator_mat_asb.f90 +! File: mld_c_dec_aggregator_mat_asb.f90 ! -! Subroutine: mld_c_base_aggregator_mat_asb +! Subroutine: mld_c_dec_aggregator_mat_asb ! Version: complex ! ! This routine builds the matrix associated to the current level of the @@ -96,7 +96,7 @@ ! ! ! Arguments: -! ag - type(mld_c_base_aggregator_type), input/output. +! ag - type(mld_c_dec_aggregator_type), input/output. ! The aggregator object ! parms - type(mld_sml_parms), input ! The aggregation parameters @@ -130,13 +130,13 @@ ! info - integer, output. ! Error code. ! -subroutine mld_c_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) +subroutine mld_c_dec_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) use psb_base_mod - use mld_c_prec_type, mld_protect_name => mld_c_base_aggregator_mat_asb + use mld_c_prec_type, mld_protect_name => mld_c_dec_aggregator_mat_asb use mld_c_inner_mod implicit none - class(mld_c_base_aggregator_type), target, intent(inout) :: ag + class(mld_c_dec_aggregator_type), target, intent(inout) :: ag type(mld_sml_parms), intent(inout) :: parms type(psb_cspmat_type), intent(in) :: a type(psb_desc_type), intent(in) :: desc_a @@ -154,7 +154,7 @@ subroutine mld_c_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_ integer(psb_ipk_) :: err_act integer(psb_ipk_) :: debug_level, debug_unit - name='mld_c_base_aggregator_mat_asb' + name='mld_c_dec_aggregator_mat_asb' if (psb_get_errstatus().ne.0) return call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() @@ -208,4 +208,4 @@ subroutine mld_c_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_ return -end subroutine mld_c_base_aggregator_mat_asb +end subroutine mld_c_dec_aggregator_mat_asb diff --git a/mlprec/impl/aggregator/mld_c_base_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_c_dec_aggregator_tprol.f90 similarity index 92% rename from mlprec/impl/aggregator/mld_c_base_aggregator_tprol.f90 rename to mlprec/impl/aggregator/mld_c_dec_aggregator_tprol.f90 index 345ffcd1..cd978972 100644 --- a/mlprec/impl/aggregator/mld_c_base_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_c_dec_aggregator_tprol.f90 @@ -35,9 +35,9 @@ ! POSSIBILITY OF SUCH DAMAGE. ! ! -! File: mld_c_base_aggregator_tprol.f90 +! File: mld_c_dec_aggregator_tprol.f90 ! -! Subroutine: mld_c_base_aggregator_tprol +! Subroutine: mld_c_dec_aggregator_tprol ! Version: complex ! ! This routine is mainly an interface to dec_map_bld where the real work is performed. @@ -72,12 +72,12 @@ ! info - integer, output. ! Error code. ! -subroutine mld_c_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) +subroutine mld_c_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod - use mld_c_prec_type, mld_protect_name => mld_c_base_aggregator_build_tprol + use mld_c_prec_type, mld_protect_name => mld_c_dec_aggregator_build_tprol use mld_c_inner_mod implicit none - class(mld_c_base_aggregator_type), target, intent(inout) :: ag + class(mld_c_dec_aggregator_type), target, intent(inout) :: ag type(mld_sml_parms), intent(inout) :: parms type(psb_cspmat_type), intent(in) :: a type(psb_desc_type), intent(in) :: desc_a @@ -92,7 +92,7 @@ subroutine mld_c_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op integer(psb_ipk_) :: ntaggr integer(psb_ipk_) :: debug_level, debug_unit - name='mld_c_base_aggregator_tprol' + name='mld_c_dec_aggregator_tprol' if (psb_get_errstatus().ne.0) return call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() @@ -125,4 +125,4 @@ subroutine mld_c_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op 9999 call psb_error_handler(err_act) return -end subroutine mld_c_base_aggregator_build_tprol +end subroutine mld_c_dec_aggregator_build_tprol diff --git a/mlprec/impl/aggregator/mld_d_base_aggregator_mat_asb.f90 b/mlprec/impl/aggregator/mld_d_dec_aggregator_mat_asb.f90 similarity index 94% rename from mlprec/impl/aggregator/mld_d_base_aggregator_mat_asb.f90 rename to mlprec/impl/aggregator/mld_d_dec_aggregator_mat_asb.f90 index 36ab21b0..9f14fad1 100644 --- a/mlprec/impl/aggregator/mld_d_base_aggregator_mat_asb.f90 +++ b/mlprec/impl/aggregator/mld_d_dec_aggregator_mat_asb.f90 @@ -35,9 +35,9 @@ ! POSSIBILITY OF SUCH DAMAGE. ! ! -! File: mld_d_base_aggregator_mat_asb.f90 +! File: mld_d_dec_aggregator_mat_asb.f90 ! -! Subroutine: mld_d_base_aggregator_mat_asb +! Subroutine: mld_d_dec_aggregator_mat_asb ! Version: real ! ! This routine builds the matrix associated to the current level of the @@ -96,7 +96,7 @@ ! ! ! Arguments: -! ag - type(mld_d_base_aggregator_type), input/output. +! ag - type(mld_d_dec_aggregator_type), input/output. ! The aggregator object ! parms - type(mld_dml_parms), input ! The aggregation parameters @@ -130,13 +130,13 @@ ! info - integer, output. ! Error code. ! -subroutine mld_d_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) +subroutine mld_d_dec_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) use psb_base_mod - use mld_d_prec_type, mld_protect_name => mld_d_base_aggregator_mat_asb + use mld_d_prec_type, mld_protect_name => mld_d_dec_aggregator_mat_asb use mld_d_inner_mod implicit none - class(mld_d_base_aggregator_type), target, intent(inout) :: ag + class(mld_d_dec_aggregator_type), target, intent(inout) :: ag type(mld_dml_parms), intent(inout) :: parms type(psb_dspmat_type), intent(in) :: a type(psb_desc_type), intent(in) :: desc_a @@ -154,7 +154,7 @@ subroutine mld_d_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_ integer(psb_ipk_) :: err_act integer(psb_ipk_) :: debug_level, debug_unit - name='mld_d_base_aggregator_mat_asb' + name='mld_d_dec_aggregator_mat_asb' if (psb_get_errstatus().ne.0) return call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() @@ -208,4 +208,4 @@ subroutine mld_d_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_ return -end subroutine mld_d_base_aggregator_mat_asb +end subroutine mld_d_dec_aggregator_mat_asb diff --git a/mlprec/impl/aggregator/mld_d_base_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_d_dec_aggregator_tprol.f90 similarity index 92% rename from mlprec/impl/aggregator/mld_d_base_aggregator_tprol.f90 rename to mlprec/impl/aggregator/mld_d_dec_aggregator_tprol.f90 index 354a94da..a919f55b 100644 --- a/mlprec/impl/aggregator/mld_d_base_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_d_dec_aggregator_tprol.f90 @@ -35,9 +35,9 @@ ! POSSIBILITY OF SUCH DAMAGE. ! ! -! File: mld_d_base_aggregator_tprol.f90 +! File: mld_d_dec_aggregator_tprol.f90 ! -! Subroutine: mld_d_base_aggregator_tprol +! Subroutine: mld_d_dec_aggregator_tprol ! Version: real ! ! This routine is mainly an interface to dec_map_bld where the real work is performed. @@ -72,12 +72,12 @@ ! info - integer, output. ! Error code. ! -subroutine mld_d_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) +subroutine mld_d_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod - use mld_d_prec_type, mld_protect_name => mld_d_base_aggregator_build_tprol + use mld_d_prec_type, mld_protect_name => mld_d_dec_aggregator_build_tprol use mld_d_inner_mod implicit none - class(mld_d_base_aggregator_type), target, intent(inout) :: ag + class(mld_d_dec_aggregator_type), target, intent(inout) :: ag type(mld_dml_parms), intent(inout) :: parms type(psb_dspmat_type), intent(in) :: a type(psb_desc_type), intent(in) :: desc_a @@ -92,7 +92,7 @@ subroutine mld_d_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op integer(psb_ipk_) :: ntaggr integer(psb_ipk_) :: debug_level, debug_unit - name='mld_d_base_aggregator_tprol' + name='mld_d_dec_aggregator_tprol' if (psb_get_errstatus().ne.0) return call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() @@ -125,4 +125,4 @@ subroutine mld_d_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op 9999 call psb_error_handler(err_act) return -end subroutine mld_d_base_aggregator_build_tprol +end subroutine mld_d_dec_aggregator_build_tprol diff --git a/mlprec/impl/aggregator/mld_s_base_aggregator_mat_asb.f90 b/mlprec/impl/aggregator/mld_s_dec_aggregator_mat_asb.f90 similarity index 94% rename from mlprec/impl/aggregator/mld_s_base_aggregator_mat_asb.f90 rename to mlprec/impl/aggregator/mld_s_dec_aggregator_mat_asb.f90 index a77e8412..e632f8fa 100644 --- a/mlprec/impl/aggregator/mld_s_base_aggregator_mat_asb.f90 +++ b/mlprec/impl/aggregator/mld_s_dec_aggregator_mat_asb.f90 @@ -35,9 +35,9 @@ ! POSSIBILITY OF SUCH DAMAGE. ! ! -! File: mld_s_base_aggregator_mat_asb.f90 +! File: mld_s_dec_aggregator_mat_asb.f90 ! -! Subroutine: mld_s_base_aggregator_mat_asb +! Subroutine: mld_s_dec_aggregator_mat_asb ! Version: real ! ! This routine builds the matrix associated to the current level of the @@ -96,7 +96,7 @@ ! ! ! Arguments: -! ag - type(mld_s_base_aggregator_type), input/output. +! ag - type(mld_s_dec_aggregator_type), input/output. ! The aggregator object ! parms - type(mld_sml_parms), input ! The aggregation parameters @@ -130,13 +130,13 @@ ! info - integer, output. ! Error code. ! -subroutine mld_s_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) +subroutine mld_s_dec_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) use psb_base_mod - use mld_s_prec_type, mld_protect_name => mld_s_base_aggregator_mat_asb + use mld_s_prec_type, mld_protect_name => mld_s_dec_aggregator_mat_asb use mld_s_inner_mod implicit none - class(mld_s_base_aggregator_type), target, intent(inout) :: ag + class(mld_s_dec_aggregator_type), target, intent(inout) :: ag type(mld_sml_parms), intent(inout) :: parms type(psb_sspmat_type), intent(in) :: a type(psb_desc_type), intent(in) :: desc_a @@ -154,7 +154,7 @@ subroutine mld_s_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_ integer(psb_ipk_) :: err_act integer(psb_ipk_) :: debug_level, debug_unit - name='mld_s_base_aggregator_mat_asb' + name='mld_s_dec_aggregator_mat_asb' if (psb_get_errstatus().ne.0) return call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() @@ -208,4 +208,4 @@ subroutine mld_s_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_ return -end subroutine mld_s_base_aggregator_mat_asb +end subroutine mld_s_dec_aggregator_mat_asb diff --git a/mlprec/impl/aggregator/mld_s_base_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_s_dec_aggregator_tprol.f90 similarity index 92% rename from mlprec/impl/aggregator/mld_s_base_aggregator_tprol.f90 rename to mlprec/impl/aggregator/mld_s_dec_aggregator_tprol.f90 index ca4b40dd..78bce133 100644 --- a/mlprec/impl/aggregator/mld_s_base_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_s_dec_aggregator_tprol.f90 @@ -35,9 +35,9 @@ ! POSSIBILITY OF SUCH DAMAGE. ! ! -! File: mld_s_base_aggregator_tprol.f90 +! File: mld_s_dec_aggregator_tprol.f90 ! -! Subroutine: mld_s_base_aggregator_tprol +! Subroutine: mld_s_dec_aggregator_tprol ! Version: real ! ! This routine is mainly an interface to dec_map_bld where the real work is performed. @@ -72,12 +72,12 @@ ! info - integer, output. ! Error code. ! -subroutine mld_s_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) +subroutine mld_s_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod - use mld_s_prec_type, mld_protect_name => mld_s_base_aggregator_build_tprol + use mld_s_prec_type, mld_protect_name => mld_s_dec_aggregator_build_tprol use mld_s_inner_mod implicit none - class(mld_s_base_aggregator_type), target, intent(inout) :: ag + class(mld_s_dec_aggregator_type), target, intent(inout) :: ag type(mld_sml_parms), intent(inout) :: parms type(psb_sspmat_type), intent(in) :: a type(psb_desc_type), intent(in) :: desc_a @@ -92,7 +92,7 @@ subroutine mld_s_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op integer(psb_ipk_) :: ntaggr integer(psb_ipk_) :: debug_level, debug_unit - name='mld_s_base_aggregator_tprol' + name='mld_s_dec_aggregator_tprol' if (psb_get_errstatus().ne.0) return call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() @@ -125,4 +125,4 @@ subroutine mld_s_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op 9999 call psb_error_handler(err_act) return -end subroutine mld_s_base_aggregator_build_tprol +end subroutine mld_s_dec_aggregator_build_tprol diff --git a/mlprec/impl/aggregator/mld_z_base_aggregator_mat_asb.f90 b/mlprec/impl/aggregator/mld_z_dec_aggregator_mat_asb.f90 similarity index 94% rename from mlprec/impl/aggregator/mld_z_base_aggregator_mat_asb.f90 rename to mlprec/impl/aggregator/mld_z_dec_aggregator_mat_asb.f90 index f7d4a926..6d85871b 100644 --- a/mlprec/impl/aggregator/mld_z_base_aggregator_mat_asb.f90 +++ b/mlprec/impl/aggregator/mld_z_dec_aggregator_mat_asb.f90 @@ -35,9 +35,9 @@ ! POSSIBILITY OF SUCH DAMAGE. ! ! -! File: mld_z_base_aggregator_mat_asb.f90 +! File: mld_z_dec_aggregator_mat_asb.f90 ! -! Subroutine: mld_z_base_aggregator_mat_asb +! Subroutine: mld_z_dec_aggregator_mat_asb ! Version: complex ! ! This routine builds the matrix associated to the current level of the @@ -96,7 +96,7 @@ ! ! ! Arguments: -! ag - type(mld_z_base_aggregator_type), input/output. +! ag - type(mld_z_dec_aggregator_type), input/output. ! The aggregator object ! parms - type(mld_dml_parms), input ! The aggregation parameters @@ -130,13 +130,13 @@ ! info - integer, output. ! Error code. ! -subroutine mld_z_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) +subroutine mld_z_dec_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_prol,op_restr,info) use psb_base_mod - use mld_z_prec_type, mld_protect_name => mld_z_base_aggregator_mat_asb + use mld_z_prec_type, mld_protect_name => mld_z_dec_aggregator_mat_asb use mld_z_inner_mod implicit none - class(mld_z_base_aggregator_type), target, intent(inout) :: ag + class(mld_z_dec_aggregator_type), target, intent(inout) :: ag type(mld_dml_parms), intent(inout) :: parms type(psb_zspmat_type), intent(in) :: a type(psb_desc_type), intent(in) :: desc_a @@ -154,7 +154,7 @@ subroutine mld_z_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_ integer(psb_ipk_) :: err_act integer(psb_ipk_) :: debug_level, debug_unit - name='mld_z_base_aggregator_mat_asb' + name='mld_z_dec_aggregator_mat_asb' if (psb_get_errstatus().ne.0) return call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() @@ -208,4 +208,4 @@ subroutine mld_z_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,op_ return -end subroutine mld_z_base_aggregator_mat_asb +end subroutine mld_z_dec_aggregator_mat_asb diff --git a/mlprec/impl/aggregator/mld_z_base_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_z_dec_aggregator_tprol.f90 similarity index 92% rename from mlprec/impl/aggregator/mld_z_base_aggregator_tprol.f90 rename to mlprec/impl/aggregator/mld_z_dec_aggregator_tprol.f90 index 4522bd8d..cc3f23cb 100644 --- a/mlprec/impl/aggregator/mld_z_base_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_z_dec_aggregator_tprol.f90 @@ -35,9 +35,9 @@ ! POSSIBILITY OF SUCH DAMAGE. ! ! -! File: mld_z_base_aggregator_tprol.f90 +! File: mld_z_dec_aggregator_tprol.f90 ! -! Subroutine: mld_z_base_aggregator_tprol +! Subroutine: mld_z_dec_aggregator_tprol ! Version: complex ! ! This routine is mainly an interface to dec_map_bld where the real work is performed. @@ -72,12 +72,12 @@ ! info - integer, output. ! Error code. ! -subroutine mld_z_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) +subroutine mld_z_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod - use mld_z_prec_type, mld_protect_name => mld_z_base_aggregator_build_tprol + use mld_z_prec_type, mld_protect_name => mld_z_dec_aggregator_build_tprol use mld_z_inner_mod implicit none - class(mld_z_base_aggregator_type), target, intent(inout) :: ag + class(mld_z_dec_aggregator_type), target, intent(inout) :: ag type(mld_dml_parms), intent(inout) :: parms type(psb_zspmat_type), intent(in) :: a type(psb_desc_type), intent(in) :: desc_a @@ -92,7 +92,7 @@ subroutine mld_z_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op integer(psb_ipk_) :: ntaggr integer(psb_ipk_) :: debug_level, debug_unit - name='mld_z_base_aggregator_tprol' + name='mld_z_dec_aggregator_tprol' if (psb_get_errstatus().ne.0) return call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() @@ -125,4 +125,4 @@ subroutine mld_z_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op 9999 call psb_error_handler(err_act) return -end subroutine mld_z_base_aggregator_build_tprol +end subroutine mld_z_dec_aggregator_build_tprol diff --git a/mlprec/impl/level/mld_c_base_onelev_cseti.F90 b/mlprec/impl/level/mld_c_base_onelev_cseti.F90 index ea1ecc8e..48e98d7d 100644 --- a/mlprec/impl/level/mld_c_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_c_base_onelev_cseti.F90 @@ -39,6 +39,10 @@ subroutine mld_c_base_onelev_cseti(lv,what,val,info,pos) use psb_base_mod use mld_c_onelev_mod, mld_protect_name => mld_c_base_onelev_cseti + use mld_c_base_aggregator_mod + use mld_c_dec_aggregator_mod + use mld_c_symdec_aggregator_mod + use mld_c_hybrid_aggregator_mod use mld_c_jac_smoother use mld_c_as_smoother use mld_c_diag_solver @@ -182,6 +186,25 @@ subroutine mld_c_base_onelev_cseti(lv,what,val,info,pos) case ('PAR_AGGR_ALG') lv%parms%par_aggr_alg = val + if (allocated(lv%aggr)) then + call lv%aggr%free(info) + if (info == 0) deallocate(lv%aggr,stat=info) + if (info /= 0) then + info = psb_err_internal_error_ + return + end if + end if + + select case(val) + case(mld_dec_aggr_) + allocate(mld_c_dec_aggregator_type :: lv%aggr, stat=info) + case(mld_sym_dec_aggr_) + allocate(mld_c_symdec_aggregator_type :: lv%aggr, stat=info) + case(mld_hybrid_aggr_) + allocate(mld_c_hybrid_aggregator_type :: lv%aggr, stat=info) + case default + info = psb_err_internal_error_ + end select case ('AGGR_ORD') lv%parms%aggr_ord = val diff --git a/mlprec/impl/level/mld_c_base_onelev_seti.F90 b/mlprec/impl/level/mld_c_base_onelev_seti.F90 index 27cceaa0..dcaa19dc 100644 --- a/mlprec/impl/level/mld_c_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_c_base_onelev_seti.F90 @@ -39,6 +39,10 @@ subroutine mld_c_base_onelev_seti(lv,what,val,info,pos) use psb_base_mod use mld_c_onelev_mod, mld_protect_name => mld_c_base_onelev_seti + use mld_c_base_aggregator_mod + use mld_c_dec_aggregator_mod + use mld_c_symdec_aggregator_mod + use mld_c_hybrid_aggregator_mod use mld_c_jac_smoother use mld_c_as_smoother use mld_c_diag_solver @@ -182,6 +186,25 @@ subroutine mld_c_base_onelev_seti(lv,what,val,info,pos) case (mld_par_aggr_alg_) lv%parms%par_aggr_alg = val + if (allocated(lv%aggr)) then + call lv%aggr%free(info) + if (info == 0) deallocate(lv%aggr,stat=info) + if (info /= 0) then + info = psb_err_internal_error_ + return + end if + end if + + select case(val) + case(mld_dec_aggr_) + allocate(mld_c_dec_aggregator_type :: lv%aggr, stat=info) + case(mld_sym_dec_aggr_) + allocate(mld_c_symdec_aggregator_type :: lv%aggr, stat=info) + case(mld_hybrid_aggr_) + allocate(mld_c_hybrid_aggregator_type :: lv%aggr, stat=info) + case default + info = psb_err_internal_error_ + end select case (mld_aggr_ord_) lv%parms%aggr_ord = val diff --git a/mlprec/impl/level/mld_d_base_onelev_cseti.F90 b/mlprec/impl/level/mld_d_base_onelev_cseti.F90 index 492eb9fb..a4ca7838 100644 --- a/mlprec/impl/level/mld_d_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_d_base_onelev_cseti.F90 @@ -39,6 +39,10 @@ subroutine mld_d_base_onelev_cseti(lv,what,val,info,pos) use psb_base_mod use mld_d_onelev_mod, mld_protect_name => mld_d_base_onelev_cseti + use mld_d_base_aggregator_mod + use mld_d_dec_aggregator_mod + use mld_d_symdec_aggregator_mod + use mld_d_hybrid_aggregator_mod use mld_d_jac_smoother use mld_d_as_smoother use mld_d_diag_solver @@ -202,6 +206,25 @@ subroutine mld_d_base_onelev_cseti(lv,what,val,info,pos) case ('PAR_AGGR_ALG') lv%parms%par_aggr_alg = val + if (allocated(lv%aggr)) then + call lv%aggr%free(info) + if (info == 0) deallocate(lv%aggr,stat=info) + if (info /= 0) then + info = psb_err_internal_error_ + return + end if + end if + + select case(val) + case(mld_dec_aggr_) + allocate(mld_d_dec_aggregator_type :: lv%aggr, stat=info) + case(mld_sym_dec_aggr_) + allocate(mld_d_symdec_aggregator_type :: lv%aggr, stat=info) + case(mld_hybrid_aggr_) + allocate(mld_d_hybrid_aggregator_type :: lv%aggr, stat=info) + case default + info = psb_err_internal_error_ + end select case ('AGGR_ORD') lv%parms%aggr_ord = val diff --git a/mlprec/impl/level/mld_d_base_onelev_seti.F90 b/mlprec/impl/level/mld_d_base_onelev_seti.F90 index 2a3914d0..38610bd1 100644 --- a/mlprec/impl/level/mld_d_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_d_base_onelev_seti.F90 @@ -39,6 +39,10 @@ subroutine mld_d_base_onelev_seti(lv,what,val,info,pos) use psb_base_mod use mld_d_onelev_mod, mld_protect_name => mld_d_base_onelev_seti + use mld_d_base_aggregator_mod + use mld_d_dec_aggregator_mod + use mld_d_symdec_aggregator_mod + use mld_d_hybrid_aggregator_mod use mld_d_jac_smoother use mld_d_as_smoother use mld_d_diag_solver @@ -202,6 +206,25 @@ subroutine mld_d_base_onelev_seti(lv,what,val,info,pos) case (mld_par_aggr_alg_) lv%parms%par_aggr_alg = val + if (allocated(lv%aggr)) then + call lv%aggr%free(info) + if (info == 0) deallocate(lv%aggr,stat=info) + if (info /= 0) then + info = psb_err_internal_error_ + return + end if + end if + + select case(val) + case(mld_dec_aggr_) + allocate(mld_d_dec_aggregator_type :: lv%aggr, stat=info) + case(mld_sym_dec_aggr_) + allocate(mld_d_symdec_aggregator_type :: lv%aggr, stat=info) + case(mld_hybrid_aggr_) + allocate(mld_d_hybrid_aggregator_type :: lv%aggr, stat=info) + case default + info = psb_err_internal_error_ + end select case (mld_aggr_ord_) lv%parms%aggr_ord = val diff --git a/mlprec/impl/level/mld_s_base_onelev_cseti.F90 b/mlprec/impl/level/mld_s_base_onelev_cseti.F90 index b6552c5a..882bae1a 100644 --- a/mlprec/impl/level/mld_s_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_s_base_onelev_cseti.F90 @@ -39,6 +39,10 @@ subroutine mld_s_base_onelev_cseti(lv,what,val,info,pos) use psb_base_mod use mld_s_onelev_mod, mld_protect_name => mld_s_base_onelev_cseti + use mld_s_base_aggregator_mod + use mld_s_dec_aggregator_mod + use mld_s_symdec_aggregator_mod + use mld_s_hybrid_aggregator_mod use mld_s_jac_smoother use mld_s_as_smoother use mld_s_diag_solver @@ -182,6 +186,25 @@ subroutine mld_s_base_onelev_cseti(lv,what,val,info,pos) case ('PAR_AGGR_ALG') lv%parms%par_aggr_alg = val + if (allocated(lv%aggr)) then + call lv%aggr%free(info) + if (info == 0) deallocate(lv%aggr,stat=info) + if (info /= 0) then + info = psb_err_internal_error_ + return + end if + end if + + select case(val) + case(mld_dec_aggr_) + allocate(mld_s_dec_aggregator_type :: lv%aggr, stat=info) + case(mld_sym_dec_aggr_) + allocate(mld_s_symdec_aggregator_type :: lv%aggr, stat=info) + case(mld_hybrid_aggr_) + allocate(mld_s_hybrid_aggregator_type :: lv%aggr, stat=info) + case default + info = psb_err_internal_error_ + end select case ('AGGR_ORD') lv%parms%aggr_ord = val diff --git a/mlprec/impl/level/mld_s_base_onelev_seti.F90 b/mlprec/impl/level/mld_s_base_onelev_seti.F90 index 52880ac6..54ed838f 100644 --- a/mlprec/impl/level/mld_s_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_s_base_onelev_seti.F90 @@ -39,6 +39,10 @@ subroutine mld_s_base_onelev_seti(lv,what,val,info,pos) use psb_base_mod use mld_s_onelev_mod, mld_protect_name => mld_s_base_onelev_seti + use mld_s_base_aggregator_mod + use mld_s_dec_aggregator_mod + use mld_s_symdec_aggregator_mod + use mld_s_hybrid_aggregator_mod use mld_s_jac_smoother use mld_s_as_smoother use mld_s_diag_solver @@ -182,6 +186,25 @@ subroutine mld_s_base_onelev_seti(lv,what,val,info,pos) case (mld_par_aggr_alg_) lv%parms%par_aggr_alg = val + if (allocated(lv%aggr)) then + call lv%aggr%free(info) + if (info == 0) deallocate(lv%aggr,stat=info) + if (info /= 0) then + info = psb_err_internal_error_ + return + end if + end if + + select case(val) + case(mld_dec_aggr_) + allocate(mld_s_dec_aggregator_type :: lv%aggr, stat=info) + case(mld_sym_dec_aggr_) + allocate(mld_s_symdec_aggregator_type :: lv%aggr, stat=info) + case(mld_hybrid_aggr_) + allocate(mld_s_hybrid_aggregator_type :: lv%aggr, stat=info) + case default + info = psb_err_internal_error_ + end select case (mld_aggr_ord_) lv%parms%aggr_ord = val diff --git a/mlprec/impl/level/mld_z_base_onelev_cseti.F90 b/mlprec/impl/level/mld_z_base_onelev_cseti.F90 index d4d353da..1418b3ac 100644 --- a/mlprec/impl/level/mld_z_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_z_base_onelev_cseti.F90 @@ -39,6 +39,10 @@ subroutine mld_z_base_onelev_cseti(lv,what,val,info,pos) use psb_base_mod use mld_z_onelev_mod, mld_protect_name => mld_z_base_onelev_cseti + use mld_z_base_aggregator_mod + use mld_z_dec_aggregator_mod + use mld_z_symdec_aggregator_mod + use mld_z_hybrid_aggregator_mod use mld_z_jac_smoother use mld_z_as_smoother use mld_z_diag_solver @@ -202,6 +206,25 @@ subroutine mld_z_base_onelev_cseti(lv,what,val,info,pos) case ('PAR_AGGR_ALG') lv%parms%par_aggr_alg = val + if (allocated(lv%aggr)) then + call lv%aggr%free(info) + if (info == 0) deallocate(lv%aggr,stat=info) + if (info /= 0) then + info = psb_err_internal_error_ + return + end if + end if + + select case(val) + case(mld_dec_aggr_) + allocate(mld_z_dec_aggregator_type :: lv%aggr, stat=info) + case(mld_sym_dec_aggr_) + allocate(mld_z_symdec_aggregator_type :: lv%aggr, stat=info) + case(mld_hybrid_aggr_) + allocate(mld_z_hybrid_aggregator_type :: lv%aggr, stat=info) + case default + info = psb_err_internal_error_ + end select case ('AGGR_ORD') lv%parms%aggr_ord = val diff --git a/mlprec/impl/level/mld_z_base_onelev_seti.F90 b/mlprec/impl/level/mld_z_base_onelev_seti.F90 index f335b968..73bc2d2d 100644 --- a/mlprec/impl/level/mld_z_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_z_base_onelev_seti.F90 @@ -39,6 +39,10 @@ subroutine mld_z_base_onelev_seti(lv,what,val,info,pos) use psb_base_mod use mld_z_onelev_mod, mld_protect_name => mld_z_base_onelev_seti + use mld_z_base_aggregator_mod + use mld_z_dec_aggregator_mod + use mld_z_symdec_aggregator_mod + use mld_z_hybrid_aggregator_mod use mld_z_jac_smoother use mld_z_as_smoother use mld_z_diag_solver @@ -202,6 +206,25 @@ subroutine mld_z_base_onelev_seti(lv,what,val,info,pos) case (mld_par_aggr_alg_) lv%parms%par_aggr_alg = val + if (allocated(lv%aggr)) then + call lv%aggr%free(info) + if (info == 0) deallocate(lv%aggr,stat=info) + if (info /= 0) then + info = psb_err_internal_error_ + return + end if + end if + + select case(val) + case(mld_dec_aggr_) + allocate(mld_z_dec_aggregator_type :: lv%aggr, stat=info) + case(mld_sym_dec_aggr_) + allocate(mld_z_symdec_aggregator_type :: lv%aggr, stat=info) + case(mld_hybrid_aggr_) + allocate(mld_z_hybrid_aggregator_type :: lv%aggr, stat=info) + case default + info = psb_err_internal_error_ + end select case (mld_aggr_ord_) lv%parms%aggr_ord = val diff --git a/mlprec/mld_base_prec_type.F90 b/mlprec/mld_base_prec_type.F90 index 26987979..28cda2db 100644 --- a/mlprec/mld_base_prec_type.F90 +++ b/mlprec/mld_base_prec_type.F90 @@ -97,6 +97,7 @@ module mld_base_prec_type procedure, pass(pm) :: get_coarse => ml_parms_get_coarse procedure, pass(pm) :: clone => ml_parms_clone procedure, pass(pm) :: descr => ml_parms_descr + procedure, pass(pm) :: mlcycledsc => ml_parms_mlcycledsc procedure, pass(pm) :: mldescr => ml_parms_mldescr procedure, pass(pm) :: coarsedescr => ml_parms_coarsedescr procedure, pass(pm) :: printout => ml_parms_printout @@ -222,6 +223,13 @@ module mld_base_prec_type integer(psb_ipk_), parameter :: mld_new_ml_prec_ = 7 integer(psb_ipk_), parameter :: mld_mult_dev_ml_ = 7 integer(psb_ipk_), parameter :: mld_max_ml_cycle_ = 8 + ! + ! Legal values for entry: mld_par_aggr_alg_ + ! + integer(psb_ipk_), parameter :: mld_dec_aggr_ = 0 + integer(psb_ipk_), parameter :: mld_sym_dec_aggr_ = 1 + integer(psb_ipk_), parameter :: mld_ext_aggr_ = 2 + integer(psb_ipk_), parameter :: mld_max_par_aggr_alg_ = mld_ext_aggr_ ! ! Legal values for entry: mld_aggr_type_ ! @@ -244,14 +252,6 @@ module mld_base_prec_type integer(psb_ipk_), parameter :: mld_filter_mat_ = 1 integer(psb_ipk_), parameter :: mld_max_filter_mat_ = mld_filter_mat_ ! - ! Legal values for entry: mld_par_aggr_alg_ - ! - integer(psb_ipk_), parameter :: mld_dec_aggr_ = 0 - integer(psb_ipk_), parameter :: mld_sym_dec_aggr_ = 1 - integer(psb_ipk_), parameter :: mld_ext_aggr_ = 2 - integer(psb_ipk_), parameter :: mld_bcmatch_aggr_ = 3 - integer(psb_ipk_), parameter :: mld_max_par_aggr_alg_ = mld_ext_aggr_ - ! ! Legal values for entry: mld_aggr_ord_ ! integer(psb_ipk_), parameter :: mld_aggr_ord_nat_ = 0 @@ -322,12 +322,12 @@ module mld_base_prec_type character(len=15), parameter, private :: & & matrix_names(0:1)=(/'distributed ','replicated '/) character(len=18), parameter, private :: & - & aggr_type_names(0:2)=(/'No aggregation ',& + & aggr_type_names(0:2)=(/'None ',& & 'VMB aggregation ', 'Hybrid aggregation'/) character(len=18), parameter, private :: & - & par_aggr_alg_names(0:3)=(/'decoupled aggr. ',& - & 'sym. dec. aggr. ',& - & 'user defined aggr.', 'matching aggr. '/) + & par_aggr_alg_names(0:2)=(/& + & 'decoupled aggr. ', 'sym. dec. aggr. ',& + & 'user defined aggr.'/) character(len=18), parameter, private :: & & ord_names(0:1)=(/'Natural ordering ','Desc. degree ord. '/) character(len=6), parameter, private :: & @@ -446,8 +446,6 @@ contains val = mld_dec_aggr_ case('SYMDEC') val = mld_sym_dec_aggr_ - case('BCMATCH') - val = mld_bcmatch_aggr_ case('NAT','NATURAL') val = mld_aggr_ord_nat_ case('DESC','RDEGREE','DEGREE') @@ -533,8 +531,7 @@ contains ! ! Routines printing out a description of the preconditioner ! - - subroutine ml_parms_mldescr(pm,iout,info,aggr_name) + subroutine ml_parms_mlcycledsc(pm,iout,info) Implicit None @@ -542,7 +539,6 @@ contains class(mld_ml_parms), intent(in) :: pm integer(psb_ipk_), intent(in) :: iout integer(psb_ipk_), intent(out) :: info - character(len=*), intent(in), optional :: aggr_name info = psb_success_ if ((pm%ml_cycle>=mld_no_ml_).and.(pm%ml_cycle<=mld_max_ml_cycle_)) then @@ -557,14 +553,24 @@ contains write(iout,*) ' Number of smoother sweeps : pre: ',& & pm%sweeps_pre ,' post: ', pm%sweeps_post end select + + end if + end subroutine ml_parms_mlcycledsc + + subroutine ml_parms_mldescr(pm,iout,info) + + Implicit None + + ! Arguments + class(mld_ml_parms), intent(in) :: pm + integer(psb_ipk_), intent(in) :: iout + integer(psb_ipk_), intent(out) :: info + info = psb_success_ + if ((pm%ml_cycle>=mld_no_ml_).and.(pm%ml_cycle<=mld_max_ml_cycle_)) then + - if (present(aggr_name)) then - write(iout,*) ' Aggregation type: ', & - & aggr_name - else - write(iout,*) ' Aggregation type: ',& - & aggr_type_names(pm%aggr_type) - end if + write(iout,*) ' Aggregation type: ',& + & aggr_type_names(pm%aggr_type) write(iout,*) ' parallel algorithm: ',& & par_aggr_alg_names(pm%par_aggr_alg) if (pm%par_aggr_alg /= mld_ext_aggr_) then @@ -574,7 +580,7 @@ contains write(iout,*) ' Aggregation prolongator: ', & & aggr_prols(pm%aggr_prol) if (pm%aggr_prol /= mld_no_smooth_) then - write(iout,*) ' with: ', aggr_filters(pm%aggr_filter) + write(iout,*) ' with: ', aggr_filters(pm%aggr_filter) if (pm%aggr_omega_alg == mld_eig_est_) then write(iout,*) ' Damping omega computation: spectral radius estimate' write(iout,*) ' Spectral radius estimate: ', & @@ -587,7 +593,7 @@ contains end if end if else - write(iout,*) ' Multilevel type: Unkonwn value. Something is amis....',& + write(iout,*) ' Multilevel type: Unkonwn value. Something is amiss....',& & pm%ml_cycle end if diff --git a/mlprec/mld_c_base_aggregator_mod.f90 b/mlprec/mld_c_base_aggregator_mod.f90 index 6383f507..4576af81 100644 --- a/mlprec/mld_c_base_aggregator_mod.f90 +++ b/mlprec/mld_c_base_aggregator_mod.f90 @@ -107,38 +107,6 @@ module mld_c_base_aggregator_mod end type mld_c_base_aggregator_type - interface - subroutine mld_c_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) - import :: mld_c_base_aggregator_type, psb_desc_type, psb_cspmat_type, psb_spk_, & - & psb_ipk_, psb_long_int_k_, mld_sml_parms - implicit none - class(mld_c_base_aggregator_type), target, intent(inout) :: ag - type(mld_sml_parms), intent(inout) :: parms - type(psb_cspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - type(psb_cspmat_type), intent(out) :: op_prol - integer(psb_ipk_), intent(out) :: info - end subroutine mld_c_base_aggregator_build_tprol - end interface - - interface - subroutine mld_c_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,& - & op_prol,op_restr,info) - import :: mld_c_base_aggregator_type, psb_desc_type, psb_cspmat_type, psb_spk_, & - & psb_ipk_, psb_long_int_k_, mld_sml_parms - implicit none - class(mld_c_base_aggregator_type), target, intent(inout) :: ag - type(mld_sml_parms), intent(inout) :: parms - type(psb_cspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) - type(psb_cspmat_type), intent(inout) :: op_prol - type(psb_cspmat_type), intent(out) :: ac,op_restr - integer(psb_ipk_), intent(out) :: info - end subroutine mld_c_base_aggregator_mat_asb - end interface - contains subroutine mld_c_base_aggregator_update_next(ag,agnext,info) @@ -190,7 +158,7 @@ contains implicit none character(len=32) :: val - val = "Decoupled aggregation" + val = "Null " end function mld_c_base_aggregator_fmt subroutine mld_c_base_aggregator_descr(ag,parms,iout,info) @@ -205,4 +173,64 @@ contains return end subroutine mld_c_base_aggregator_descr + subroutine mld_c_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod + implicit none + class(mld_c_base_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_cspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_cspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + integer(psb_ipk_) :: err_act + character(len=20) :: name='c_base_aggregator_build_tprol' + + call psb_erractionsave(err_act) + + info = psb_err_missing_override_method_ + call psb_errpush(info,name) + goto 9999 + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + + end subroutine mld_c_base_aggregator_build_tprol + + + subroutine mld_c_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,& + & op_prol,op_restr,info) + use psb_base_mod + implicit none + class(mld_c_base_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_cspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) + type(psb_cspmat_type), intent(inout) :: op_prol + type(psb_cspmat_type), intent(out) :: ac,op_restr + integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_) :: err_act + character(len=20) :: name='c_base_aggregator_mat_asb' + + call psb_erractionsave(err_act) + + info = psb_err_missing_override_method_ + call psb_errpush(info,name) + goto 9999 + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + end subroutine mld_c_base_aggregator_mat_asb + + end module mld_c_base_aggregator_mod diff --git a/mlprec/mld_c_onelev_mod.f90 b/mlprec/mld_c_onelev_mod.f90 index a9b456d2..db9a64cc 100644 --- a/mlprec/mld_c_onelev_mod.f90 +++ b/mlprec/mld_c_onelev_mod.f90 @@ -507,7 +507,7 @@ contains else lv%sm2 => lv%sm end if - if (.not.allocated(lv%aggr)) allocate(mld_c_base_aggregator_type :: lv%aggr,stat=info) + if (.not.allocated(lv%aggr)) allocate(mld_c_dec_aggregator_type :: lv%aggr,stat=info) if (allocated(lv%aggr)) call lv%aggr%default() return diff --git a/mlprec/mld_c_symdec_aggregator_mod.f90 b/mlprec/mld_c_symdec_aggregator_mod.f90 index 1cf69096..0fffcf7a 100644 --- a/mlprec/mld_c_symdec_aggregator_mod.f90 +++ b/mlprec/mld_c_symdec_aggregator_mod.f90 @@ -50,7 +50,7 @@ ! module mld_c_symdec_aggregator_mod - use mld_c_base_aggregator_mod + use mld_c_dec_aggregator_mod ! ! sm - class(mld_T_base_smoother_type), allocatable ! The current level preconditioner (aka smoother). @@ -91,7 +91,7 @@ module mld_c_symdec_aggregator_mod ! get_nzeros - Number of nonzeros ! ! - type, extends(mld_c_base_aggregator_type) :: mld_c_symdec_aggregator_type + type, extends(mld_c_dec_aggregator_type) :: mld_c_symdec_aggregator_type contains procedure, pass(ag) :: tprol => mld_c_symdec_aggregator_build_tprol diff --git a/mlprec/mld_d_base_aggregator_mod.f90 b/mlprec/mld_d_base_aggregator_mod.f90 index a07c2da0..85dc972e 100644 --- a/mlprec/mld_d_base_aggregator_mod.f90 +++ b/mlprec/mld_d_base_aggregator_mod.f90 @@ -107,38 +107,6 @@ module mld_d_base_aggregator_mod end type mld_d_base_aggregator_type - interface - subroutine mld_d_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) - import :: mld_d_base_aggregator_type, psb_desc_type, psb_dspmat_type, psb_dpk_, & - & psb_ipk_, psb_long_int_k_, mld_dml_parms - implicit none - class(mld_d_base_aggregator_type), target, intent(inout) :: ag - type(mld_dml_parms), intent(inout) :: parms - type(psb_dspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - type(psb_dspmat_type), intent(out) :: op_prol - integer(psb_ipk_), intent(out) :: info - end subroutine mld_d_base_aggregator_build_tprol - end interface - - interface - subroutine mld_d_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,& - & op_prol,op_restr,info) - import :: mld_d_base_aggregator_type, psb_desc_type, psb_dspmat_type, psb_dpk_, & - & psb_ipk_, psb_long_int_k_, mld_dml_parms - implicit none - class(mld_d_base_aggregator_type), target, intent(inout) :: ag - type(mld_dml_parms), intent(inout) :: parms - type(psb_dspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) - type(psb_dspmat_type), intent(inout) :: op_prol - type(psb_dspmat_type), intent(out) :: ac,op_restr - integer(psb_ipk_), intent(out) :: info - end subroutine mld_d_base_aggregator_mat_asb - end interface - contains subroutine mld_d_base_aggregator_update_next(ag,agnext,info) @@ -190,7 +158,7 @@ contains implicit none character(len=32) :: val - val = "Decoupled aggregation" + val = "Null " end function mld_d_base_aggregator_fmt subroutine mld_d_base_aggregator_descr(ag,parms,iout,info) @@ -205,4 +173,64 @@ contains return end subroutine mld_d_base_aggregator_descr + subroutine mld_d_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod + implicit none + class(mld_d_base_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_dspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + integer(psb_ipk_) :: err_act + character(len=20) :: name='d_base_aggregator_build_tprol' + + call psb_erractionsave(err_act) + + info = psb_err_missing_override_method_ + call psb_errpush(info,name) + goto 9999 + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + + end subroutine mld_d_base_aggregator_build_tprol + + + subroutine mld_d_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,& + & op_prol,op_restr,info) + use psb_base_mod + implicit none + class(mld_d_base_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) + type(psb_dspmat_type), intent(inout) :: op_prol + type(psb_dspmat_type), intent(out) :: ac,op_restr + integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_) :: err_act + character(len=20) :: name='d_base_aggregator_mat_asb' + + call psb_erractionsave(err_act) + + info = psb_err_missing_override_method_ + call psb_errpush(info,name) + goto 9999 + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + end subroutine mld_d_base_aggregator_mat_asb + + end module mld_d_base_aggregator_mod diff --git a/mlprec/mld_d_onelev_mod.f90 b/mlprec/mld_d_onelev_mod.f90 index 13fcc688..c8e7630d 100644 --- a/mlprec/mld_d_onelev_mod.f90 +++ b/mlprec/mld_d_onelev_mod.f90 @@ -507,7 +507,7 @@ contains else lv%sm2 => lv%sm end if - if (.not.allocated(lv%aggr)) allocate(mld_d_base_aggregator_type :: lv%aggr,stat=info) + if (.not.allocated(lv%aggr)) allocate(mld_d_dec_aggregator_type :: lv%aggr,stat=info) if (allocated(lv%aggr)) call lv%aggr%default() return diff --git a/mlprec/mld_d_symdec_aggregator_mod.f90 b/mlprec/mld_d_symdec_aggregator_mod.f90 index 927ad60f..893cfbf2 100644 --- a/mlprec/mld_d_symdec_aggregator_mod.f90 +++ b/mlprec/mld_d_symdec_aggregator_mod.f90 @@ -50,7 +50,7 @@ ! module mld_d_symdec_aggregator_mod - use mld_d_base_aggregator_mod + use mld_d_dec_aggregator_mod ! ! sm - class(mld_T_base_smoother_type), allocatable ! The current level preconditioner (aka smoother). @@ -91,7 +91,7 @@ module mld_d_symdec_aggregator_mod ! get_nzeros - Number of nonzeros ! ! - type, extends(mld_d_base_aggregator_type) :: mld_d_symdec_aggregator_type + type, extends(mld_d_dec_aggregator_type) :: mld_d_symdec_aggregator_type contains procedure, pass(ag) :: tprol => mld_d_symdec_aggregator_build_tprol diff --git a/mlprec/mld_s_base_aggregator_mod.f90 b/mlprec/mld_s_base_aggregator_mod.f90 index b9a67239..4b7a5fd4 100644 --- a/mlprec/mld_s_base_aggregator_mod.f90 +++ b/mlprec/mld_s_base_aggregator_mod.f90 @@ -107,38 +107,6 @@ module mld_s_base_aggregator_mod end type mld_s_base_aggregator_type - interface - subroutine mld_s_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) - import :: mld_s_base_aggregator_type, psb_desc_type, psb_sspmat_type, psb_spk_, & - & psb_ipk_, psb_long_int_k_, mld_sml_parms - implicit none - class(mld_s_base_aggregator_type), target, intent(inout) :: ag - type(mld_sml_parms), intent(inout) :: parms - type(psb_sspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - type(psb_sspmat_type), intent(out) :: op_prol - integer(psb_ipk_), intent(out) :: info - end subroutine mld_s_base_aggregator_build_tprol - end interface - - interface - subroutine mld_s_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,& - & op_prol,op_restr,info) - import :: mld_s_base_aggregator_type, psb_desc_type, psb_sspmat_type, psb_spk_, & - & psb_ipk_, psb_long_int_k_, mld_sml_parms - implicit none - class(mld_s_base_aggregator_type), target, intent(inout) :: ag - type(mld_sml_parms), intent(inout) :: parms - type(psb_sspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) - type(psb_sspmat_type), intent(inout) :: op_prol - type(psb_sspmat_type), intent(out) :: ac,op_restr - integer(psb_ipk_), intent(out) :: info - end subroutine mld_s_base_aggregator_mat_asb - end interface - contains subroutine mld_s_base_aggregator_update_next(ag,agnext,info) @@ -190,7 +158,7 @@ contains implicit none character(len=32) :: val - val = "Decoupled aggregation" + val = "Null " end function mld_s_base_aggregator_fmt subroutine mld_s_base_aggregator_descr(ag,parms,iout,info) @@ -205,4 +173,64 @@ contains return end subroutine mld_s_base_aggregator_descr + subroutine mld_s_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod + implicit none + class(mld_s_base_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_sspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_sspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + integer(psb_ipk_) :: err_act + character(len=20) :: name='s_base_aggregator_build_tprol' + + call psb_erractionsave(err_act) + + info = psb_err_missing_override_method_ + call psb_errpush(info,name) + goto 9999 + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + + end subroutine mld_s_base_aggregator_build_tprol + + + subroutine mld_s_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,& + & op_prol,op_restr,info) + use psb_base_mod + implicit none + class(mld_s_base_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_sspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) + type(psb_sspmat_type), intent(inout) :: op_prol + type(psb_sspmat_type), intent(out) :: ac,op_restr + integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_) :: err_act + character(len=20) :: name='s_base_aggregator_mat_asb' + + call psb_erractionsave(err_act) + + info = psb_err_missing_override_method_ + call psb_errpush(info,name) + goto 9999 + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + end subroutine mld_s_base_aggregator_mat_asb + + end module mld_s_base_aggregator_mod diff --git a/mlprec/mld_s_onelev_mod.f90 b/mlprec/mld_s_onelev_mod.f90 index 3bfb50c3..a3bf3cb5 100644 --- a/mlprec/mld_s_onelev_mod.f90 +++ b/mlprec/mld_s_onelev_mod.f90 @@ -507,7 +507,7 @@ contains else lv%sm2 => lv%sm end if - if (.not.allocated(lv%aggr)) allocate(mld_s_base_aggregator_type :: lv%aggr,stat=info) + if (.not.allocated(lv%aggr)) allocate(mld_s_dec_aggregator_type :: lv%aggr,stat=info) if (allocated(lv%aggr)) call lv%aggr%default() return diff --git a/mlprec/mld_s_symdec_aggregator_mod.f90 b/mlprec/mld_s_symdec_aggregator_mod.f90 index de5c46d7..0e980885 100644 --- a/mlprec/mld_s_symdec_aggregator_mod.f90 +++ b/mlprec/mld_s_symdec_aggregator_mod.f90 @@ -50,7 +50,7 @@ ! module mld_s_symdec_aggregator_mod - use mld_s_base_aggregator_mod + use mld_s_dec_aggregator_mod ! ! sm - class(mld_T_base_smoother_type), allocatable ! The current level preconditioner (aka smoother). @@ -91,7 +91,7 @@ module mld_s_symdec_aggregator_mod ! get_nzeros - Number of nonzeros ! ! - type, extends(mld_s_base_aggregator_type) :: mld_s_symdec_aggregator_type + type, extends(mld_s_dec_aggregator_type) :: mld_s_symdec_aggregator_type contains procedure, pass(ag) :: tprol => mld_s_symdec_aggregator_build_tprol diff --git a/mlprec/mld_z_base_aggregator_mod.f90 b/mlprec/mld_z_base_aggregator_mod.f90 index cd99cf1a..e737c7df 100644 --- a/mlprec/mld_z_base_aggregator_mod.f90 +++ b/mlprec/mld_z_base_aggregator_mod.f90 @@ -107,38 +107,6 @@ module mld_z_base_aggregator_mod end type mld_z_base_aggregator_type - interface - subroutine mld_z_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) - import :: mld_z_base_aggregator_type, psb_desc_type, psb_zspmat_type, psb_dpk_, & - & psb_ipk_, psb_long_int_k_, mld_dml_parms - implicit none - class(mld_z_base_aggregator_type), target, intent(inout) :: ag - type(mld_dml_parms), intent(inout) :: parms - type(psb_zspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - type(psb_zspmat_type), intent(out) :: op_prol - integer(psb_ipk_), intent(out) :: info - end subroutine mld_z_base_aggregator_build_tprol - end interface - - interface - subroutine mld_z_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,& - & op_prol,op_restr,info) - import :: mld_z_base_aggregator_type, psb_desc_type, psb_zspmat_type, psb_dpk_, & - & psb_ipk_, psb_long_int_k_, mld_dml_parms - implicit none - class(mld_z_base_aggregator_type), target, intent(inout) :: ag - type(mld_dml_parms), intent(inout) :: parms - type(psb_zspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) - type(psb_zspmat_type), intent(inout) :: op_prol - type(psb_zspmat_type), intent(out) :: ac,op_restr - integer(psb_ipk_), intent(out) :: info - end subroutine mld_z_base_aggregator_mat_asb - end interface - contains subroutine mld_z_base_aggregator_update_next(ag,agnext,info) @@ -190,7 +158,7 @@ contains implicit none character(len=32) :: val - val = "Decoupled aggregation" + val = "Null " end function mld_z_base_aggregator_fmt subroutine mld_z_base_aggregator_descr(ag,parms,iout,info) @@ -205,4 +173,64 @@ contains return end subroutine mld_z_base_aggregator_descr + subroutine mld_z_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + use psb_base_mod + implicit none + class(mld_z_base_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_zspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_zspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + + integer(psb_ipk_) :: err_act + character(len=20) :: name='z_base_aggregator_build_tprol' + + call psb_erractionsave(err_act) + + info = psb_err_missing_override_method_ + call psb_errpush(info,name) + goto 9999 + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + + end subroutine mld_z_base_aggregator_build_tprol + + + subroutine mld_z_base_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,& + & op_prol,op_restr,info) + use psb_base_mod + implicit none + class(mld_z_base_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_zspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) + type(psb_zspmat_type), intent(inout) :: op_prol + type(psb_zspmat_type), intent(out) :: ac,op_restr + integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_) :: err_act + character(len=20) :: name='z_base_aggregator_mat_asb' + + call psb_erractionsave(err_act) + + info = psb_err_missing_override_method_ + call psb_errpush(info,name) + goto 9999 + + call psb_erractionrestore(err_act) + return + +9999 call psb_error_handler(err_act) + + return + end subroutine mld_z_base_aggregator_mat_asb + + end module mld_z_base_aggregator_mod diff --git a/mlprec/mld_z_onelev_mod.f90 b/mlprec/mld_z_onelev_mod.f90 index b5d873a9..5256cc6f 100644 --- a/mlprec/mld_z_onelev_mod.f90 +++ b/mlprec/mld_z_onelev_mod.f90 @@ -507,7 +507,7 @@ contains else lv%sm2 => lv%sm end if - if (.not.allocated(lv%aggr)) allocate(mld_z_base_aggregator_type :: lv%aggr,stat=info) + if (.not.allocated(lv%aggr)) allocate(mld_z_dec_aggregator_type :: lv%aggr,stat=info) if (allocated(lv%aggr)) call lv%aggr%default() return diff --git a/mlprec/mld_z_symdec_aggregator_mod.f90 b/mlprec/mld_z_symdec_aggregator_mod.f90 index a16fd1a3..ae7916b2 100644 --- a/mlprec/mld_z_symdec_aggregator_mod.f90 +++ b/mlprec/mld_z_symdec_aggregator_mod.f90 @@ -50,7 +50,7 @@ ! module mld_z_symdec_aggregator_mod - use mld_z_base_aggregator_mod + use mld_z_dec_aggregator_mod ! ! sm - class(mld_T_base_smoother_type), allocatable ! The current level preconditioner (aka smoother). @@ -91,7 +91,7 @@ module mld_z_symdec_aggregator_mod ! get_nzeros - Number of nonzeros ! ! - type, extends(mld_z_base_aggregator_type) :: mld_z_symdec_aggregator_type + type, extends(mld_z_dec_aggregator_type) :: mld_z_symdec_aggregator_type contains procedure, pass(ag) :: tprol => mld_z_symdec_aggregator_build_tprol From 036c072ebcf6d50e53b94c5757b87fe56b595ac4 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Thu, 10 May 2018 14:09:15 +0100 Subject: [PATCH 19/33] Fixed setup of aggregators. --- mlprec/Makefile | 28 +++--- mlprec/mld_c_base_aggregator_mod.f90 | 2 +- mlprec/mld_c_dec_aggregator_mod.f90 | 143 +++++++++++++++++++++++++++ mlprec/mld_c_onelev_mod.f90 | 2 +- mlprec/mld_d_base_aggregator_mod.f90 | 2 +- mlprec/mld_d_dec_aggregator_mod.f90 | 143 +++++++++++++++++++++++++++ mlprec/mld_d_onelev_mod.f90 | 2 +- mlprec/mld_s_base_aggregator_mod.f90 | 2 +- mlprec/mld_s_dec_aggregator_mod.f90 | 143 +++++++++++++++++++++++++++ mlprec/mld_s_onelev_mod.f90 | 2 +- mlprec/mld_z_base_aggregator_mod.f90 | 2 +- mlprec/mld_z_dec_aggregator_mod.f90 | 143 +++++++++++++++++++++++++++ mlprec/mld_z_onelev_mod.f90 | 2 +- 13 files changed, 596 insertions(+), 20 deletions(-) create mode 100644 mlprec/mld_c_dec_aggregator_mod.f90 create mode 100644 mlprec/mld_d_dec_aggregator_mod.f90 create mode 100644 mlprec/mld_s_dec_aggregator_mod.f90 create mode 100644 mlprec/mld_z_dec_aggregator_mod.f90 diff --git a/mlprec/Makefile b/mlprec/Makefile index 5de506ee..f683e3e4 100644 --- a/mlprec/Makefile +++ b/mlprec/Makefile @@ -13,7 +13,7 @@ DMODOBJS=mld_d_prec_type.o mld_d_ilu_fact_mod.o \ mld_d_base_solver_mod.o mld_d_base_smoother_mod.o mld_d_onelev_mod.o \ mld_d_gs_solver.o mld_d_mumps_solver.o \ mld_d_base_aggregator_mod.o mld_d_hybrid_aggregator_mod.o \ - mld_d_symdec_aggregator_mod.o + mld_d_dec_aggregator_mod.o mld_d_symdec_aggregator_mod.o #mld_d_bcmatch_aggregator_mod.o SMODOBJS=mld_s_prec_type.o mld_s_ilu_fact_mod.o \ @@ -22,7 +22,7 @@ SMODOBJS=mld_s_prec_type.o mld_s_ilu_fact_mod.o \ mld_s_base_solver_mod.o mld_s_base_smoother_mod.o mld_s_onelev_mod.o \ mld_s_gs_solver.o mld_s_mumps_solver.o \ mld_s_base_aggregator_mod.o mld_s_hybrid_aggregator_mod.o \ - mld_s_symdec_aggregator_mod.o + mld_s_dec_aggregator_mod.o mld_s_symdec_aggregator_mod.o ZMODOBJS=mld_z_prec_type.o mld_z_ilu_fact_mod.o \ mld_z_inner_mod.o mld_z_ilu_solver.o mld_z_diag_solver.o mld_z_jac_smoother.o mld_z_as_smoother.o \ @@ -30,7 +30,7 @@ ZMODOBJS=mld_z_prec_type.o mld_z_ilu_fact_mod.o \ mld_z_base_solver_mod.o mld_z_base_smoother_mod.o mld_z_onelev_mod.o \ mld_z_gs_solver.o mld_z_mumps_solver.o \ mld_z_base_aggregator_mod.o mld_z_hybrid_aggregator_mod.o \ - mld_z_symdec_aggregator_mod.o + mld_z_dec_aggregator_mod.o mld_z_symdec_aggregator_mod.o CMODOBJS=mld_c_prec_type.o mld_c_ilu_fact_mod.o \ mld_c_inner_mod.o mld_c_ilu_solver.o mld_c_diag_solver.o mld_c_jac_smoother.o mld_c_as_smoother.o \ @@ -38,7 +38,7 @@ CMODOBJS=mld_c_prec_type.o mld_c_ilu_fact_mod.o \ mld_c_base_solver_mod.o mld_c_base_smoother_mod.o mld_c_onelev_mod.o \ mld_c_gs_solver.o mld_c_mumps_solver.o \ mld_c_base_aggregator_mod.o mld_c_hybrid_aggregator_mod.o \ - mld_c_symdec_aggregator_mod.o + mld_c_dec_aggregator_mod.o mld_c_symdec_aggregator_mod.o @@ -93,22 +93,26 @@ mld_d_prec_type.o: mld_d_onelev_mod.o mld_c_prec_type.o: mld_c_onelev_mod.o mld_z_prec_type.o: mld_z_onelev_mod.o -mld_s_onelev_mod.o: mld_s_base_smoother_mod.o mld_s_base_aggregator_mod.o -mld_d_onelev_mod.o: mld_d_base_smoother_mod.o mld_d_base_aggregator_mod.o -mld_c_onelev_mod.o: mld_c_base_smoother_mod.o mld_c_base_aggregator_mod.o -mld_z_onelev_mod.o: mld_z_base_smoother_mod.o mld_z_base_aggregator_mod.o +mld_s_onelev_mod.o: mld_s_base_smoother_mod.o mld_s_dec_aggregator_mod.o +mld_d_onelev_mod.o: mld_d_base_smoother_mod.o mld_d_dec_aggregator_mod.o +mld_c_onelev_mod.o: mld_c_base_smoother_mod.o mld_c_dec_aggregator_mod.o +mld_z_onelev_mod.o: mld_z_base_smoother_mod.o mld_z_dec_aggregator_mod.o mld_s_base_aggregator_mod.o: mld_base_prec_type.o -mld_s_hybrid_aggregator_mod.o mld_s_symdec_aggregator_mod.o: mld_s_base_aggregator_mod.o +mld_s_hybrid_aggregator_mod.o mld_s_dec_aggregator_mod.o: mld_s_base_aggregator_mod.o +mld_s_symdec_aggregator_mod.o: mld_s_dec_aggregator_mod.o mld_d_base_aggregator_mod.o: mld_base_prec_type.o -mld_d_bcmatch_aggregator_mod.o mld_d_hybrid_aggregator_mod.o mld_d_symdec_aggregator_mod.o: mld_d_base_aggregator_mod.o +mld_d_hybrid_aggregator_mod.o mld_d_dec_aggregator_mod.o: mld_d_base_aggregator_mod.o +mld_d_symdec_aggregator_mod.o: mld_d_dec_aggregator_mod.o mld_c_base_aggregator_mod.o: mld_base_prec_type.o -mld_c_hybrid_aggregator_mod.o mld_c_symdec_aggregator_mod.o: mld_c_base_aggregator_mod.o +mld_c_hybrid_aggregator_mod.o mld_c_dec_aggregator_mod.o: mld_c_base_aggregator_mod.o +mld_c_symdec_aggregator_mod.o: mld_c_dec_aggregator_mod.o mld_z_base_aggregator_mod.o: mld_base_prec_type.o -mld_z_hybrid_aggregator_mod.o mld_z_symdec_aggregator_mod.o: mld_z_base_aggregator_mod.o +mld_z_hybrid_aggregator_mod.o mld_z_dec_aggregator_mod.o: mld_z_base_aggregator_mod.o +mld_z_symdec_aggregator_mod.o: mld_z_dec_aggregator_mod.o mld_s_base_smoother_mod.o: mld_s_base_solver_mod.o mld_d_base_smoother_mod.o: mld_d_base_solver_mod.o diff --git a/mlprec/mld_c_base_aggregator_mod.f90 b/mlprec/mld_c_base_aggregator_mod.f90 index 4576af81..85d16d4d 100644 --- a/mlprec/mld_c_base_aggregator_mod.f90 +++ b/mlprec/mld_c_base_aggregator_mod.f90 @@ -168,7 +168,7 @@ contains integer(psb_ipk_), intent(in) :: iout integer(psb_ipk_), intent(out) :: info - call parms%mldescr(iout,info,aggr_name=ag%fmt()) + call parms%mldescr(iout,info) return end subroutine mld_c_base_aggregator_descr diff --git a/mlprec/mld_c_dec_aggregator_mod.f90 b/mlprec/mld_c_dec_aggregator_mod.f90 new file mode 100644 index 00000000..8c6df140 --- /dev/null +++ b/mlprec/mld_c_dec_aggregator_mod.f90 @@ -0,0 +1,143 @@ +! +! +! MLD2P4 version 2.2 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008-2018 +! +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. +! +! M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +module mld_c_dec_aggregator_mod + + use mld_c_base_aggregator_mod + ! + ! sm - class(mld_T_base_smoother_type), allocatable + ! The current level preconditioner (aka smoother). + ! parms - type(mld_RTml_parms) + ! The parameters defining the multilevel strategy. + ! ac - The local part of the current-level matrix, built by + ! coarsening the previous-level matrix. + ! desc_ac - type(psb_desc_type). + ! The communication descriptor associated to the matrix + ! stored in ac. + ! base_a - type(psb_Tspmat_type), pointer. + ! Pointer (really a pointer!) to the local part of the current + ! matrix (so we have a unified treatment of residuals). + ! We need this to avoid passing explicitly the current matrix + ! to the routine which applies the preconditioner. + ! base_desc - type(psb_desc_type), pointer. + ! Pointer to the communication descriptor associated to the + ! matrix pointed by base_a. + ! map - Stores the maps (restriction and prolongation) between the + ! vector spaces associated to the index spaces of the previous + ! and current levels. + ! + ! Methods: + ! Most methods follow the encapsulation hierarchy: they take whatever action + ! is appropriate for the current object, then call the corresponding method for + ! the contained object. + ! As an example: the descr() method prints out a description of the + ! level. It starts by invoking the descr() method of the parms object, + ! then calls the descr() method of the smoother object. + ! + ! descr - Prints a description of the object. + ! default - Set default values + ! dump - Dump to file object contents + ! set - Sets various parameters; when a request is unknown + ! it is passed to the smoother object for further processing. + ! check - Sanity checks. + ! sizeof - Total memory occupation in bytes + ! get_nzeros - Number of nonzeros + ! + ! + type, extends(mld_c_base_aggregator_type) :: mld_c_dec_aggregator_type + + contains + procedure, pass(ag) :: tprol => mld_c_dec_aggregator_build_tprol + procedure, pass(ag) :: mat_asb => mld_c_dec_aggregator_mat_asb + procedure, nopass :: fmt => mld_c_dec_aggregator_fmt + end type mld_c_dec_aggregator_type + + + interface + subroutine mld_c_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: mld_c_dec_aggregator_type, psb_desc_type, psb_cspmat_type, psb_spk_, & + & psb_ipk_, psb_long_int_k_, mld_sml_parms + implicit none + class(mld_c_dec_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_cspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_cspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_c_dec_aggregator_build_tprol + end interface + + interface + subroutine mld_c_dec_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,& + & op_prol,op_restr,info) + import :: mld_c_dec_aggregator_type, psb_desc_type, psb_cspmat_type, psb_spk_, & + & psb_ipk_, psb_long_int_k_, mld_sml_parms + implicit none + class(mld_c_dec_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_cspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) + type(psb_cspmat_type), intent(inout) :: op_prol + type(psb_cspmat_type), intent(out) :: ac,op_restr + integer(psb_ipk_), intent(out) :: info + end subroutine mld_c_dec_aggregator_mat_asb + end interface + + +contains + + function mld_c_dec_aggregator_fmt() result(val) + implicit none + character(len=32) :: val + + val = "Decoupled aggregation" + end function mld_c_dec_aggregator_fmt + +end module mld_c_dec_aggregator_mod diff --git a/mlprec/mld_c_onelev_mod.f90 b/mlprec/mld_c_onelev_mod.f90 index db9a64cc..8ddbed4e 100644 --- a/mlprec/mld_c_onelev_mod.f90 +++ b/mlprec/mld_c_onelev_mod.f90 @@ -55,7 +55,7 @@ module mld_c_onelev_mod use mld_base_prec_type use mld_c_base_smoother_mod - use mld_c_base_aggregator_mod + use mld_c_dec_aggregator_mod use psb_base_mod, only : psb_cspmat_type, psb_c_vect_type, & & psb_c_base_vect_type, psb_clinmap_type, psb_spk_, & & psb_ipk_, psb_long_int_k_, psb_desc_type, psb_i_base_vect_type, & diff --git a/mlprec/mld_d_base_aggregator_mod.f90 b/mlprec/mld_d_base_aggregator_mod.f90 index 85dc972e..f89b636a 100644 --- a/mlprec/mld_d_base_aggregator_mod.f90 +++ b/mlprec/mld_d_base_aggregator_mod.f90 @@ -168,7 +168,7 @@ contains integer(psb_ipk_), intent(in) :: iout integer(psb_ipk_), intent(out) :: info - call parms%mldescr(iout,info,aggr_name=ag%fmt()) + call parms%mldescr(iout,info) return end subroutine mld_d_base_aggregator_descr diff --git a/mlprec/mld_d_dec_aggregator_mod.f90 b/mlprec/mld_d_dec_aggregator_mod.f90 new file mode 100644 index 00000000..ec25f574 --- /dev/null +++ b/mlprec/mld_d_dec_aggregator_mod.f90 @@ -0,0 +1,143 @@ +! +! +! MLD2P4 version 2.2 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008-2018 +! +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. +! +! M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +module mld_d_dec_aggregator_mod + + use mld_d_base_aggregator_mod + ! + ! sm - class(mld_T_base_smoother_type), allocatable + ! The current level preconditioner (aka smoother). + ! parms - type(mld_RTml_parms) + ! The parameters defining the multilevel strategy. + ! ac - The local part of the current-level matrix, built by + ! coarsening the previous-level matrix. + ! desc_ac - type(psb_desc_type). + ! The communication descriptor associated to the matrix + ! stored in ac. + ! base_a - type(psb_Tspmat_type), pointer. + ! Pointer (really a pointer!) to the local part of the current + ! matrix (so we have a unified treatment of residuals). + ! We need this to avoid passing explicitly the current matrix + ! to the routine which applies the preconditioner. + ! base_desc - type(psb_desc_type), pointer. + ! Pointer to the communication descriptor associated to the + ! matrix pointed by base_a. + ! map - Stores the maps (restriction and prolongation) between the + ! vector spaces associated to the index spaces of the previous + ! and current levels. + ! + ! Methods: + ! Most methods follow the encapsulation hierarchy: they take whatever action + ! is appropriate for the current object, then call the corresponding method for + ! the contained object. + ! As an example: the descr() method prints out a description of the + ! level. It starts by invoking the descr() method of the parms object, + ! then calls the descr() method of the smoother object. + ! + ! descr - Prints a description of the object. + ! default - Set default values + ! dump - Dump to file object contents + ! set - Sets various parameters; when a request is unknown + ! it is passed to the smoother object for further processing. + ! check - Sanity checks. + ! sizeof - Total memory occupation in bytes + ! get_nzeros - Number of nonzeros + ! + ! + type, extends(mld_d_base_aggregator_type) :: mld_d_dec_aggregator_type + + contains + procedure, pass(ag) :: tprol => mld_d_dec_aggregator_build_tprol + procedure, pass(ag) :: mat_asb => mld_d_dec_aggregator_mat_asb + procedure, nopass :: fmt => mld_d_dec_aggregator_fmt + end type mld_d_dec_aggregator_type + + + interface + subroutine mld_d_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: mld_d_dec_aggregator_type, psb_desc_type, psb_dspmat_type, psb_dpk_, & + & psb_ipk_, psb_long_int_k_, mld_dml_parms + implicit none + class(mld_d_dec_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_dspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_d_dec_aggregator_build_tprol + end interface + + interface + subroutine mld_d_dec_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,& + & op_prol,op_restr,info) + import :: mld_d_dec_aggregator_type, psb_desc_type, psb_dspmat_type, psb_dpk_, & + & psb_ipk_, psb_long_int_k_, mld_dml_parms + implicit none + class(mld_d_dec_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) + type(psb_dspmat_type), intent(inout) :: op_prol + type(psb_dspmat_type), intent(out) :: ac,op_restr + integer(psb_ipk_), intent(out) :: info + end subroutine mld_d_dec_aggregator_mat_asb + end interface + + +contains + + function mld_d_dec_aggregator_fmt() result(val) + implicit none + character(len=32) :: val + + val = "Decoupled aggregation" + end function mld_d_dec_aggregator_fmt + +end module mld_d_dec_aggregator_mod diff --git a/mlprec/mld_d_onelev_mod.f90 b/mlprec/mld_d_onelev_mod.f90 index c8e7630d..a109e6eb 100644 --- a/mlprec/mld_d_onelev_mod.f90 +++ b/mlprec/mld_d_onelev_mod.f90 @@ -55,7 +55,7 @@ module mld_d_onelev_mod use mld_base_prec_type use mld_d_base_smoother_mod - use mld_d_base_aggregator_mod + use mld_d_dec_aggregator_mod use psb_base_mod, only : psb_dspmat_type, psb_d_vect_type, & & psb_d_base_vect_type, psb_dlinmap_type, psb_dpk_, & & psb_ipk_, psb_long_int_k_, psb_desc_type, psb_i_base_vect_type, & diff --git a/mlprec/mld_s_base_aggregator_mod.f90 b/mlprec/mld_s_base_aggregator_mod.f90 index 4b7a5fd4..6128df62 100644 --- a/mlprec/mld_s_base_aggregator_mod.f90 +++ b/mlprec/mld_s_base_aggregator_mod.f90 @@ -168,7 +168,7 @@ contains integer(psb_ipk_), intent(in) :: iout integer(psb_ipk_), intent(out) :: info - call parms%mldescr(iout,info,aggr_name=ag%fmt()) + call parms%mldescr(iout,info) return end subroutine mld_s_base_aggregator_descr diff --git a/mlprec/mld_s_dec_aggregator_mod.f90 b/mlprec/mld_s_dec_aggregator_mod.f90 new file mode 100644 index 00000000..63cdd6ea --- /dev/null +++ b/mlprec/mld_s_dec_aggregator_mod.f90 @@ -0,0 +1,143 @@ +! +! +! MLD2P4 version 2.2 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008-2018 +! +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. +! +! M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +module mld_s_dec_aggregator_mod + + use mld_s_base_aggregator_mod + ! + ! sm - class(mld_T_base_smoother_type), allocatable + ! The current level preconditioner (aka smoother). + ! parms - type(mld_RTml_parms) + ! The parameters defining the multilevel strategy. + ! ac - The local part of the current-level matrix, built by + ! coarsening the previous-level matrix. + ! desc_ac - type(psb_desc_type). + ! The communication descriptor associated to the matrix + ! stored in ac. + ! base_a - type(psb_Tspmat_type), pointer. + ! Pointer (really a pointer!) to the local part of the current + ! matrix (so we have a unified treatment of residuals). + ! We need this to avoid passing explicitly the current matrix + ! to the routine which applies the preconditioner. + ! base_desc - type(psb_desc_type), pointer. + ! Pointer to the communication descriptor associated to the + ! matrix pointed by base_a. + ! map - Stores the maps (restriction and prolongation) between the + ! vector spaces associated to the index spaces of the previous + ! and current levels. + ! + ! Methods: + ! Most methods follow the encapsulation hierarchy: they take whatever action + ! is appropriate for the current object, then call the corresponding method for + ! the contained object. + ! As an example: the descr() method prints out a description of the + ! level. It starts by invoking the descr() method of the parms object, + ! then calls the descr() method of the smoother object. + ! + ! descr - Prints a description of the object. + ! default - Set default values + ! dump - Dump to file object contents + ! set - Sets various parameters; when a request is unknown + ! it is passed to the smoother object for further processing. + ! check - Sanity checks. + ! sizeof - Total memory occupation in bytes + ! get_nzeros - Number of nonzeros + ! + ! + type, extends(mld_s_base_aggregator_type) :: mld_s_dec_aggregator_type + + contains + procedure, pass(ag) :: tprol => mld_s_dec_aggregator_build_tprol + procedure, pass(ag) :: mat_asb => mld_s_dec_aggregator_mat_asb + procedure, nopass :: fmt => mld_s_dec_aggregator_fmt + end type mld_s_dec_aggregator_type + + + interface + subroutine mld_s_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: mld_s_dec_aggregator_type, psb_desc_type, psb_sspmat_type, psb_spk_, & + & psb_ipk_, psb_long_int_k_, mld_sml_parms + implicit none + class(mld_s_dec_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_sspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_sspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_s_dec_aggregator_build_tprol + end interface + + interface + subroutine mld_s_dec_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,& + & op_prol,op_restr,info) + import :: mld_s_dec_aggregator_type, psb_desc_type, psb_sspmat_type, psb_spk_, & + & psb_ipk_, psb_long_int_k_, mld_sml_parms + implicit none + class(mld_s_dec_aggregator_type), target, intent(inout) :: ag + type(mld_sml_parms), intent(inout) :: parms + type(psb_sspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) + type(psb_sspmat_type), intent(inout) :: op_prol + type(psb_sspmat_type), intent(out) :: ac,op_restr + integer(psb_ipk_), intent(out) :: info + end subroutine mld_s_dec_aggregator_mat_asb + end interface + + +contains + + function mld_s_dec_aggregator_fmt() result(val) + implicit none + character(len=32) :: val + + val = "Decoupled aggregation" + end function mld_s_dec_aggregator_fmt + +end module mld_s_dec_aggregator_mod diff --git a/mlprec/mld_s_onelev_mod.f90 b/mlprec/mld_s_onelev_mod.f90 index a3bf3cb5..e1c7bd01 100644 --- a/mlprec/mld_s_onelev_mod.f90 +++ b/mlprec/mld_s_onelev_mod.f90 @@ -55,7 +55,7 @@ module mld_s_onelev_mod use mld_base_prec_type use mld_s_base_smoother_mod - use mld_s_base_aggregator_mod + use mld_s_dec_aggregator_mod use psb_base_mod, only : psb_sspmat_type, psb_s_vect_type, & & psb_s_base_vect_type, psb_slinmap_type, psb_spk_, & & psb_ipk_, psb_long_int_k_, psb_desc_type, psb_i_base_vect_type, & diff --git a/mlprec/mld_z_base_aggregator_mod.f90 b/mlprec/mld_z_base_aggregator_mod.f90 index e737c7df..e76f4561 100644 --- a/mlprec/mld_z_base_aggregator_mod.f90 +++ b/mlprec/mld_z_base_aggregator_mod.f90 @@ -168,7 +168,7 @@ contains integer(psb_ipk_), intent(in) :: iout integer(psb_ipk_), intent(out) :: info - call parms%mldescr(iout,info,aggr_name=ag%fmt()) + call parms%mldescr(iout,info) return end subroutine mld_z_base_aggregator_descr diff --git a/mlprec/mld_z_dec_aggregator_mod.f90 b/mlprec/mld_z_dec_aggregator_mod.f90 new file mode 100644 index 00000000..61f9bcbd --- /dev/null +++ b/mlprec/mld_z_dec_aggregator_mod.f90 @@ -0,0 +1,143 @@ +! +! +! MLD2P4 version 2.2 +! MultiLevel Domain Decomposition Parallel Preconditioners Package +! based on PSBLAS (Parallel Sparse BLAS version 3.5) +! +! (C) Copyright 2008-2018 +! +! Salvatore Filippone +! Pasqua D'Ambra +! Daniela di Serafino +! +! Redistribution and use in source and binary forms, with or without +! modification, are permitted provided that the following conditions +! are met: +! 1. Redistributions of source code must retain the above copyright +! notice, this list of conditions and the following disclaimer. +! 2. Redistributions in binary form must reproduce the above copyright +! notice, this list of conditions, and the following disclaimer in the +! documentation and/or other materials provided with the distribution. +! 3. The name of the MLD2P4 group or the names of its contributors may +! not be used to endorse or promote products derived from this +! software without specific written permission. +! +! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED +! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS +! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +! POSSIBILITY OF SUCH DAMAGE. +! +! +! +! +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. +! +! M. Brezina and P. Vanek, A black-box iterative solver based on a +! two-level Schwarz method, Computing, 63 (1999), 233-263. +! P. D'Ambra, D. di Serafino and S. Filippone, On the development of +! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. +! 57 (2007), 1181-1196. +! +module mld_z_dec_aggregator_mod + + use mld_z_base_aggregator_mod + ! + ! sm - class(mld_T_base_smoother_type), allocatable + ! The current level preconditioner (aka smoother). + ! parms - type(mld_RTml_parms) + ! The parameters defining the multilevel strategy. + ! ac - The local part of the current-level matrix, built by + ! coarsening the previous-level matrix. + ! desc_ac - type(psb_desc_type). + ! The communication descriptor associated to the matrix + ! stored in ac. + ! base_a - type(psb_Tspmat_type), pointer. + ! Pointer (really a pointer!) to the local part of the current + ! matrix (so we have a unified treatment of residuals). + ! We need this to avoid passing explicitly the current matrix + ! to the routine which applies the preconditioner. + ! base_desc - type(psb_desc_type), pointer. + ! Pointer to the communication descriptor associated to the + ! matrix pointed by base_a. + ! map - Stores the maps (restriction and prolongation) between the + ! vector spaces associated to the index spaces of the previous + ! and current levels. + ! + ! Methods: + ! Most methods follow the encapsulation hierarchy: they take whatever action + ! is appropriate for the current object, then call the corresponding method for + ! the contained object. + ! As an example: the descr() method prints out a description of the + ! level. It starts by invoking the descr() method of the parms object, + ! then calls the descr() method of the smoother object. + ! + ! descr - Prints a description of the object. + ! default - Set default values + ! dump - Dump to file object contents + ! set - Sets various parameters; when a request is unknown + ! it is passed to the smoother object for further processing. + ! check - Sanity checks. + ! sizeof - Total memory occupation in bytes + ! get_nzeros - Number of nonzeros + ! + ! + type, extends(mld_z_base_aggregator_type) :: mld_z_dec_aggregator_type + + contains + procedure, pass(ag) :: tprol => mld_z_dec_aggregator_build_tprol + procedure, pass(ag) :: mat_asb => mld_z_dec_aggregator_mat_asb + procedure, nopass :: fmt => mld_z_dec_aggregator_fmt + end type mld_z_dec_aggregator_type + + + interface + subroutine mld_z_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) + import :: mld_z_dec_aggregator_type, psb_desc_type, psb_zspmat_type, psb_dpk_, & + & psb_ipk_, psb_long_int_k_, mld_dml_parms + implicit none + class(mld_z_dec_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_zspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + type(psb_zspmat_type), intent(out) :: op_prol + integer(psb_ipk_), intent(out) :: info + end subroutine mld_z_dec_aggregator_build_tprol + end interface + + interface + subroutine mld_z_dec_aggregator_mat_asb(ag,parms,a,desc_a,ilaggr,nlaggr,ac,& + & op_prol,op_restr,info) + import :: mld_z_dec_aggregator_type, psb_desc_type, psb_zspmat_type, psb_dpk_, & + & psb_ipk_, psb_long_int_k_, mld_dml_parms + implicit none + class(mld_z_dec_aggregator_type), target, intent(inout) :: ag + type(mld_dml_parms), intent(inout) :: parms + type(psb_zspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + integer(psb_ipk_), intent(inout) :: ilaggr(:), nlaggr(:) + type(psb_zspmat_type), intent(inout) :: op_prol + type(psb_zspmat_type), intent(out) :: ac,op_restr + integer(psb_ipk_), intent(out) :: info + end subroutine mld_z_dec_aggregator_mat_asb + end interface + + +contains + + function mld_z_dec_aggregator_fmt() result(val) + implicit none + character(len=32) :: val + + val = "Decoupled aggregation" + end function mld_z_dec_aggregator_fmt + +end module mld_z_dec_aggregator_mod diff --git a/mlprec/mld_z_onelev_mod.f90 b/mlprec/mld_z_onelev_mod.f90 index 5256cc6f..bfc59dde 100644 --- a/mlprec/mld_z_onelev_mod.f90 +++ b/mlprec/mld_z_onelev_mod.f90 @@ -55,7 +55,7 @@ module mld_z_onelev_mod use mld_base_prec_type use mld_z_base_smoother_mod - use mld_z_base_aggregator_mod + use mld_z_dec_aggregator_mod use psb_base_mod, only : psb_zspmat_type, psb_z_vect_type, & & psb_z_base_vect_type, psb_zlinmap_type, psb_dpk_, & & psb_ipk_, psb_long_int_k_, psb_desc_type, psb_i_base_vect_type, & From f131e0d86dd73d06a070b9fe4ec9f0bb98bdef2c Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Thu, 10 May 2018 15:38:48 +0100 Subject: [PATCH 20/33] Clear par_aggr_alg when setting from external aggregator. --- mlprec/impl/level/mld_c_base_onelev_setag.f90 | 2 ++ mlprec/impl/level/mld_d_base_onelev_setag.f90 | 2 ++ mlprec/impl/level/mld_s_base_onelev_setag.f90 | 2 ++ mlprec/impl/level/mld_z_base_onelev_setag.f90 | 2 ++ 4 files changed, 8 insertions(+) diff --git a/mlprec/impl/level/mld_c_base_onelev_setag.f90 b/mlprec/impl/level/mld_c_base_onelev_setag.f90 index 2be2a0e5..8c7af8eb 100644 --- a/mlprec/impl/level/mld_c_base_onelev_setag.f90 +++ b/mlprec/impl/level/mld_c_base_onelev_setag.f90 @@ -73,6 +73,8 @@ subroutine mld_c_base_onelev_setag(lev,val,info,pos) info = 3111 return end if + lv%parms%par_aggr_alg = mld_ext_aggr_ + lv%parms%aggr_type = mld_ext_noalg_ end if end subroutine mld_c_base_onelev_setag diff --git a/mlprec/impl/level/mld_d_base_onelev_setag.f90 b/mlprec/impl/level/mld_d_base_onelev_setag.f90 index 3303508b..397ecdef 100644 --- a/mlprec/impl/level/mld_d_base_onelev_setag.f90 +++ b/mlprec/impl/level/mld_d_base_onelev_setag.f90 @@ -73,6 +73,8 @@ subroutine mld_d_base_onelev_setag(lev,val,info,pos) info = 3111 return end if + lv%parms%par_aggr_alg = mld_ext_aggr_ + lv%parms%aggr_type = mld_ext_noalg_ end if end subroutine mld_d_base_onelev_setag diff --git a/mlprec/impl/level/mld_s_base_onelev_setag.f90 b/mlprec/impl/level/mld_s_base_onelev_setag.f90 index 81af270b..41b7e0de 100644 --- a/mlprec/impl/level/mld_s_base_onelev_setag.f90 +++ b/mlprec/impl/level/mld_s_base_onelev_setag.f90 @@ -73,6 +73,8 @@ subroutine mld_s_base_onelev_setag(lev,val,info,pos) info = 3111 return end if + lv%parms%par_aggr_alg = mld_ext_aggr_ + lv%parms%aggr_type = mld_ext_noalg_ end if end subroutine mld_s_base_onelev_setag diff --git a/mlprec/impl/level/mld_z_base_onelev_setag.f90 b/mlprec/impl/level/mld_z_base_onelev_setag.f90 index a5c56bc7..4d7702ba 100644 --- a/mlprec/impl/level/mld_z_base_onelev_setag.f90 +++ b/mlprec/impl/level/mld_z_base_onelev_setag.f90 @@ -73,6 +73,8 @@ subroutine mld_z_base_onelev_setag(lev,val,info,pos) info = 3111 return end if + lv%parms%par_aggr_alg = mld_ext_aggr_ + lv%parms%aggr_type = mld_ext_noalg_ end if end subroutine mld_z_base_onelev_setag From 13dc38307962f71dfb51899434a708ab2a2617a6 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Thu, 10 May 2018 21:16:44 +0100 Subject: [PATCH 21/33] Fixed inheritance and setup of aggregators. --- mlprec/Makefile | 16 ++++++++-------- mlprec/impl/level/mld_c_base_onelev_cseti.F90 | 4 ++-- mlprec/impl/level/mld_c_base_onelev_setag.f90 | 18 +++++++++--------- mlprec/impl/level/mld_c_base_onelev_seti.F90 | 4 ++-- mlprec/impl/level/mld_d_base_onelev_cseti.F90 | 4 ++-- mlprec/impl/level/mld_d_base_onelev_setag.f90 | 18 +++++++++--------- mlprec/impl/level/mld_d_base_onelev_seti.F90 | 4 ++-- mlprec/impl/level/mld_s_base_onelev_cseti.F90 | 4 ++-- mlprec/impl/level/mld_s_base_onelev_setag.f90 | 18 +++++++++--------- mlprec/impl/level/mld_s_base_onelev_seti.F90 | 4 ++-- mlprec/impl/level/mld_z_base_onelev_cseti.F90 | 4 ++-- mlprec/impl/level/mld_z_base_onelev_setag.f90 | 18 +++++++++--------- mlprec/impl/level/mld_z_base_onelev_seti.F90 | 4 ++-- mlprec/mld_c_dec_aggregator_mod.f90 | 2 +- mlprec/mld_c_hybrid_aggregator_mod.F90 | 11 +++-------- mlprec/mld_c_symdec_aggregator_mod.f90 | 2 +- mlprec/mld_d_dec_aggregator_mod.f90 | 2 +- mlprec/mld_d_hybrid_aggregator_mod.F90 | 11 +++-------- mlprec/mld_d_symdec_aggregator_mod.f90 | 2 +- mlprec/mld_s_dec_aggregator_mod.f90 | 2 +- mlprec/mld_s_hybrid_aggregator_mod.F90 | 11 +++-------- mlprec/mld_s_symdec_aggregator_mod.f90 | 2 +- mlprec/mld_z_dec_aggregator_mod.f90 | 2 +- mlprec/mld_z_hybrid_aggregator_mod.F90 | 11 +++-------- mlprec/mld_z_symdec_aggregator_mod.f90 | 2 +- 25 files changed, 80 insertions(+), 100 deletions(-) diff --git a/mlprec/Makefile b/mlprec/Makefile index f683e3e4..134d26e7 100644 --- a/mlprec/Makefile +++ b/mlprec/Makefile @@ -99,20 +99,20 @@ mld_c_onelev_mod.o: mld_c_base_smoother_mod.o mld_c_dec_aggregator_mod.o mld_z_onelev_mod.o: mld_z_base_smoother_mod.o mld_z_dec_aggregator_mod.o mld_s_base_aggregator_mod.o: mld_base_prec_type.o -mld_s_hybrid_aggregator_mod.o mld_s_dec_aggregator_mod.o: mld_s_base_aggregator_mod.o -mld_s_symdec_aggregator_mod.o: mld_s_dec_aggregator_mod.o +mld_s_dec_aggregator_mod.o: mld_s_base_aggregator_mod.o +mld_s_hybrid_aggregator_mod.o mld_s_symdec_aggregator_mod.o: mld_s_dec_aggregator_mod.o mld_d_base_aggregator_mod.o: mld_base_prec_type.o -mld_d_hybrid_aggregator_mod.o mld_d_dec_aggregator_mod.o: mld_d_base_aggregator_mod.o -mld_d_symdec_aggregator_mod.o: mld_d_dec_aggregator_mod.o +mld_d_dec_aggregator_mod.o: mld_d_base_aggregator_mod.o +mld_d_hybrid_aggregator_mod.o mld_d_symdec_aggregator_mod.o: mld_d_dec_aggregator_mod.o mld_c_base_aggregator_mod.o: mld_base_prec_type.o -mld_c_hybrid_aggregator_mod.o mld_c_dec_aggregator_mod.o: mld_c_base_aggregator_mod.o -mld_c_symdec_aggregator_mod.o: mld_c_dec_aggregator_mod.o +mld_c_dec_aggregator_mod.o: mld_c_base_aggregator_mod.o +mld_c_hybrid_aggregator_mod.o mld_c_symdec_aggregator_mod.o: mld_c_dec_aggregator_mod.o mld_z_base_aggregator_mod.o: mld_base_prec_type.o -mld_z_hybrid_aggregator_mod.o mld_z_dec_aggregator_mod.o: mld_z_base_aggregator_mod.o -mld_z_symdec_aggregator_mod.o: mld_z_dec_aggregator_mod.o +mld_z_dec_aggregator_mod.o: mld_z_base_aggregator_mod.o +mld_z_hybrid_aggregator_mod.o mld_z_symdec_aggregator_mod.o: mld_z_dec_aggregator_mod.o mld_s_base_smoother_mod.o: mld_s_base_solver_mod.o mld_d_base_smoother_mod.o: mld_d_base_solver_mod.o diff --git a/mlprec/impl/level/mld_c_base_onelev_cseti.F90 b/mlprec/impl/level/mld_c_base_onelev_cseti.F90 index 48e98d7d..a2cf8bfc 100644 --- a/mlprec/impl/level/mld_c_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_c_base_onelev_cseti.F90 @@ -200,8 +200,8 @@ subroutine mld_c_base_onelev_cseti(lv,what,val,info,pos) allocate(mld_c_dec_aggregator_type :: lv%aggr, stat=info) case(mld_sym_dec_aggr_) allocate(mld_c_symdec_aggregator_type :: lv%aggr, stat=info) - case(mld_hybrid_aggr_) - allocate(mld_c_hybrid_aggregator_type :: lv%aggr, stat=info) +!!$ case(mld_hybrid_aggr_) +!!$ allocate(mld_c_hybrid_aggregator_type :: lv%aggr, stat=info) case default info = psb_err_internal_error_ end select diff --git a/mlprec/impl/level/mld_c_base_onelev_setag.f90 b/mlprec/impl/level/mld_c_base_onelev_setag.f90 index 8c7af8eb..25da1459 100644 --- a/mlprec/impl/level/mld_c_base_onelev_setag.f90 +++ b/mlprec/impl/level/mld_c_base_onelev_setag.f90 @@ -35,7 +35,7 @@ ! POSSIBILITY OF SUCH DAMAGE. ! ! -subroutine mld_c_base_onelev_setag(lev,val,info,pos) +subroutine mld_c_base_onelev_setag(lv,val,info,pos) use psb_base_mod use mld_c_onelev_mod, mld_protect_name => mld_c_base_onelev_setag @@ -43,7 +43,7 @@ subroutine mld_c_base_onelev_setag(lev,val,info,pos) implicit none ! Arguments - class(mld_c_onelev_type), target, intent(inout) :: lev + class(mld_c_onelev_type), target, intent(inout) :: lv class(mld_c_base_aggregator_type), intent(in) :: val integer(psb_ipk_), intent(out) :: info character(len=*), optional, intent(in) :: pos @@ -56,10 +56,10 @@ subroutine mld_c_base_onelev_setag(lev,val,info,pos) ! Ignore pos for aggregator - if (allocated(lev%aggr)) then - if (.not.same_type_as(lev%aggr,val)) then - call lev%aggr%free(info) - deallocate(lev%aggr,stat=info) + if (allocated(lv%aggr)) then + if (.not.same_type_as(lv%aggr,val)) then + call lv%aggr%free(info) + deallocate(lv%aggr,stat=info) if (info /= 0) then info = 3111 return @@ -67,14 +67,14 @@ subroutine mld_c_base_onelev_setag(lev,val,info,pos) end if end if - if (.not.allocated(lev%aggr)) then - allocate(lev%aggr,mold=val,stat=info) + if (.not.allocated(lv%aggr)) then + allocate(lv%aggr,mold=val,stat=info) if (info /= 0) then info = 3111 return end if lv%parms%par_aggr_alg = mld_ext_aggr_ - lv%parms%aggr_type = mld_ext_noalg_ + lv%parms%aggr_type = mld_noalg_ end if end subroutine mld_c_base_onelev_setag diff --git a/mlprec/impl/level/mld_c_base_onelev_seti.F90 b/mlprec/impl/level/mld_c_base_onelev_seti.F90 index dcaa19dc..583bf2f1 100644 --- a/mlprec/impl/level/mld_c_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_c_base_onelev_seti.F90 @@ -200,8 +200,8 @@ subroutine mld_c_base_onelev_seti(lv,what,val,info,pos) allocate(mld_c_dec_aggregator_type :: lv%aggr, stat=info) case(mld_sym_dec_aggr_) allocate(mld_c_symdec_aggregator_type :: lv%aggr, stat=info) - case(mld_hybrid_aggr_) - allocate(mld_c_hybrid_aggregator_type :: lv%aggr, stat=info) +!!$ case(mld_hybrid_aggr_) +!!$ allocate(mld_c_hybrid_aggregator_type :: lv%aggr, stat=info) case default info = psb_err_internal_error_ end select diff --git a/mlprec/impl/level/mld_d_base_onelev_cseti.F90 b/mlprec/impl/level/mld_d_base_onelev_cseti.F90 index a4ca7838..ea44e7de 100644 --- a/mlprec/impl/level/mld_d_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_d_base_onelev_cseti.F90 @@ -220,8 +220,8 @@ subroutine mld_d_base_onelev_cseti(lv,what,val,info,pos) allocate(mld_d_dec_aggregator_type :: lv%aggr, stat=info) case(mld_sym_dec_aggr_) allocate(mld_d_symdec_aggregator_type :: lv%aggr, stat=info) - case(mld_hybrid_aggr_) - allocate(mld_d_hybrid_aggregator_type :: lv%aggr, stat=info) +!!$ case(mld_hybrid_aggr_) +!!$ allocate(mld_d_hybrid_aggregator_type :: lv%aggr, stat=info) case default info = psb_err_internal_error_ end select diff --git a/mlprec/impl/level/mld_d_base_onelev_setag.f90 b/mlprec/impl/level/mld_d_base_onelev_setag.f90 index 397ecdef..c4c26cca 100644 --- a/mlprec/impl/level/mld_d_base_onelev_setag.f90 +++ b/mlprec/impl/level/mld_d_base_onelev_setag.f90 @@ -35,7 +35,7 @@ ! POSSIBILITY OF SUCH DAMAGE. ! ! -subroutine mld_d_base_onelev_setag(lev,val,info,pos) +subroutine mld_d_base_onelev_setag(lv,val,info,pos) use psb_base_mod use mld_d_onelev_mod, mld_protect_name => mld_d_base_onelev_setag @@ -43,7 +43,7 @@ subroutine mld_d_base_onelev_setag(lev,val,info,pos) implicit none ! Arguments - class(mld_d_onelev_type), target, intent(inout) :: lev + class(mld_d_onelev_type), target, intent(inout) :: lv class(mld_d_base_aggregator_type), intent(in) :: val integer(psb_ipk_), intent(out) :: info character(len=*), optional, intent(in) :: pos @@ -56,10 +56,10 @@ subroutine mld_d_base_onelev_setag(lev,val,info,pos) ! Ignore pos for aggregator - if (allocated(lev%aggr)) then - if (.not.same_type_as(lev%aggr,val)) then - call lev%aggr%free(info) - deallocate(lev%aggr,stat=info) + if (allocated(lv%aggr)) then + if (.not.same_type_as(lv%aggr,val)) then + call lv%aggr%free(info) + deallocate(lv%aggr,stat=info) if (info /= 0) then info = 3111 return @@ -67,14 +67,14 @@ subroutine mld_d_base_onelev_setag(lev,val,info,pos) end if end if - if (.not.allocated(lev%aggr)) then - allocate(lev%aggr,mold=val,stat=info) + if (.not.allocated(lv%aggr)) then + allocate(lv%aggr,mold=val,stat=info) if (info /= 0) then info = 3111 return end if lv%parms%par_aggr_alg = mld_ext_aggr_ - lv%parms%aggr_type = mld_ext_noalg_ + lv%parms%aggr_type = mld_noalg_ end if end subroutine mld_d_base_onelev_setag diff --git a/mlprec/impl/level/mld_d_base_onelev_seti.F90 b/mlprec/impl/level/mld_d_base_onelev_seti.F90 index 38610bd1..82234b51 100644 --- a/mlprec/impl/level/mld_d_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_d_base_onelev_seti.F90 @@ -220,8 +220,8 @@ subroutine mld_d_base_onelev_seti(lv,what,val,info,pos) allocate(mld_d_dec_aggregator_type :: lv%aggr, stat=info) case(mld_sym_dec_aggr_) allocate(mld_d_symdec_aggregator_type :: lv%aggr, stat=info) - case(mld_hybrid_aggr_) - allocate(mld_d_hybrid_aggregator_type :: lv%aggr, stat=info) +!!$ case(mld_hybrid_aggr_) +!!$ allocate(mld_d_hybrid_aggregator_type :: lv%aggr, stat=info) case default info = psb_err_internal_error_ end select diff --git a/mlprec/impl/level/mld_s_base_onelev_cseti.F90 b/mlprec/impl/level/mld_s_base_onelev_cseti.F90 index 882bae1a..fc95bc22 100644 --- a/mlprec/impl/level/mld_s_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_s_base_onelev_cseti.F90 @@ -200,8 +200,8 @@ subroutine mld_s_base_onelev_cseti(lv,what,val,info,pos) allocate(mld_s_dec_aggregator_type :: lv%aggr, stat=info) case(mld_sym_dec_aggr_) allocate(mld_s_symdec_aggregator_type :: lv%aggr, stat=info) - case(mld_hybrid_aggr_) - allocate(mld_s_hybrid_aggregator_type :: lv%aggr, stat=info) +!!$ case(mld_hybrid_aggr_) +!!$ allocate(mld_s_hybrid_aggregator_type :: lv%aggr, stat=info) case default info = psb_err_internal_error_ end select diff --git a/mlprec/impl/level/mld_s_base_onelev_setag.f90 b/mlprec/impl/level/mld_s_base_onelev_setag.f90 index 41b7e0de..36bf2871 100644 --- a/mlprec/impl/level/mld_s_base_onelev_setag.f90 +++ b/mlprec/impl/level/mld_s_base_onelev_setag.f90 @@ -35,7 +35,7 @@ ! POSSIBILITY OF SUCH DAMAGE. ! ! -subroutine mld_s_base_onelev_setag(lev,val,info,pos) +subroutine mld_s_base_onelev_setag(lv,val,info,pos) use psb_base_mod use mld_s_onelev_mod, mld_protect_name => mld_s_base_onelev_setag @@ -43,7 +43,7 @@ subroutine mld_s_base_onelev_setag(lev,val,info,pos) implicit none ! Arguments - class(mld_s_onelev_type), target, intent(inout) :: lev + class(mld_s_onelev_type), target, intent(inout) :: lv class(mld_s_base_aggregator_type), intent(in) :: val integer(psb_ipk_), intent(out) :: info character(len=*), optional, intent(in) :: pos @@ -56,10 +56,10 @@ subroutine mld_s_base_onelev_setag(lev,val,info,pos) ! Ignore pos for aggregator - if (allocated(lev%aggr)) then - if (.not.same_type_as(lev%aggr,val)) then - call lev%aggr%free(info) - deallocate(lev%aggr,stat=info) + if (allocated(lv%aggr)) then + if (.not.same_type_as(lv%aggr,val)) then + call lv%aggr%free(info) + deallocate(lv%aggr,stat=info) if (info /= 0) then info = 3111 return @@ -67,14 +67,14 @@ subroutine mld_s_base_onelev_setag(lev,val,info,pos) end if end if - if (.not.allocated(lev%aggr)) then - allocate(lev%aggr,mold=val,stat=info) + if (.not.allocated(lv%aggr)) then + allocate(lv%aggr,mold=val,stat=info) if (info /= 0) then info = 3111 return end if lv%parms%par_aggr_alg = mld_ext_aggr_ - lv%parms%aggr_type = mld_ext_noalg_ + lv%parms%aggr_type = mld_noalg_ end if end subroutine mld_s_base_onelev_setag diff --git a/mlprec/impl/level/mld_s_base_onelev_seti.F90 b/mlprec/impl/level/mld_s_base_onelev_seti.F90 index 54ed838f..ad241194 100644 --- a/mlprec/impl/level/mld_s_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_s_base_onelev_seti.F90 @@ -200,8 +200,8 @@ subroutine mld_s_base_onelev_seti(lv,what,val,info,pos) allocate(mld_s_dec_aggregator_type :: lv%aggr, stat=info) case(mld_sym_dec_aggr_) allocate(mld_s_symdec_aggregator_type :: lv%aggr, stat=info) - case(mld_hybrid_aggr_) - allocate(mld_s_hybrid_aggregator_type :: lv%aggr, stat=info) +!!$ case(mld_hybrid_aggr_) +!!$ allocate(mld_s_hybrid_aggregator_type :: lv%aggr, stat=info) case default info = psb_err_internal_error_ end select diff --git a/mlprec/impl/level/mld_z_base_onelev_cseti.F90 b/mlprec/impl/level/mld_z_base_onelev_cseti.F90 index 1418b3ac..d519e8a6 100644 --- a/mlprec/impl/level/mld_z_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_z_base_onelev_cseti.F90 @@ -220,8 +220,8 @@ subroutine mld_z_base_onelev_cseti(lv,what,val,info,pos) allocate(mld_z_dec_aggregator_type :: lv%aggr, stat=info) case(mld_sym_dec_aggr_) allocate(mld_z_symdec_aggregator_type :: lv%aggr, stat=info) - case(mld_hybrid_aggr_) - allocate(mld_z_hybrid_aggregator_type :: lv%aggr, stat=info) +!!$ case(mld_hybrid_aggr_) +!!$ allocate(mld_z_hybrid_aggregator_type :: lv%aggr, stat=info) case default info = psb_err_internal_error_ end select diff --git a/mlprec/impl/level/mld_z_base_onelev_setag.f90 b/mlprec/impl/level/mld_z_base_onelev_setag.f90 index 4d7702ba..e6c7d51b 100644 --- a/mlprec/impl/level/mld_z_base_onelev_setag.f90 +++ b/mlprec/impl/level/mld_z_base_onelev_setag.f90 @@ -35,7 +35,7 @@ ! POSSIBILITY OF SUCH DAMAGE. ! ! -subroutine mld_z_base_onelev_setag(lev,val,info,pos) +subroutine mld_z_base_onelev_setag(lv,val,info,pos) use psb_base_mod use mld_z_onelev_mod, mld_protect_name => mld_z_base_onelev_setag @@ -43,7 +43,7 @@ subroutine mld_z_base_onelev_setag(lev,val,info,pos) implicit none ! Arguments - class(mld_z_onelev_type), target, intent(inout) :: lev + class(mld_z_onelev_type), target, intent(inout) :: lv class(mld_z_base_aggregator_type), intent(in) :: val integer(psb_ipk_), intent(out) :: info character(len=*), optional, intent(in) :: pos @@ -56,10 +56,10 @@ subroutine mld_z_base_onelev_setag(lev,val,info,pos) ! Ignore pos for aggregator - if (allocated(lev%aggr)) then - if (.not.same_type_as(lev%aggr,val)) then - call lev%aggr%free(info) - deallocate(lev%aggr,stat=info) + if (allocated(lv%aggr)) then + if (.not.same_type_as(lv%aggr,val)) then + call lv%aggr%free(info) + deallocate(lv%aggr,stat=info) if (info /= 0) then info = 3111 return @@ -67,14 +67,14 @@ subroutine mld_z_base_onelev_setag(lev,val,info,pos) end if end if - if (.not.allocated(lev%aggr)) then - allocate(lev%aggr,mold=val,stat=info) + if (.not.allocated(lv%aggr)) then + allocate(lv%aggr,mold=val,stat=info) if (info /= 0) then info = 3111 return end if lv%parms%par_aggr_alg = mld_ext_aggr_ - lv%parms%aggr_type = mld_ext_noalg_ + lv%parms%aggr_type = mld_noalg_ end if end subroutine mld_z_base_onelev_setag diff --git a/mlprec/impl/level/mld_z_base_onelev_seti.F90 b/mlprec/impl/level/mld_z_base_onelev_seti.F90 index 73bc2d2d..1d1505f4 100644 --- a/mlprec/impl/level/mld_z_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_z_base_onelev_seti.F90 @@ -220,8 +220,8 @@ subroutine mld_z_base_onelev_seti(lv,what,val,info,pos) allocate(mld_z_dec_aggregator_type :: lv%aggr, stat=info) case(mld_sym_dec_aggr_) allocate(mld_z_symdec_aggregator_type :: lv%aggr, stat=info) - case(mld_hybrid_aggr_) - allocate(mld_z_hybrid_aggregator_type :: lv%aggr, stat=info) +!!$ case(mld_hybrid_aggr_) +!!$ allocate(mld_z_hybrid_aggregator_type :: lv%aggr, stat=info) case default info = psb_err_internal_error_ end select diff --git a/mlprec/mld_c_dec_aggregator_mod.f90 b/mlprec/mld_c_dec_aggregator_mod.f90 index 8c6df140..4548b4b0 100644 --- a/mlprec/mld_c_dec_aggregator_mod.f90 +++ b/mlprec/mld_c_dec_aggregator_mod.f90 @@ -92,7 +92,7 @@ module mld_c_dec_aggregator_mod type, extends(mld_c_base_aggregator_type) :: mld_c_dec_aggregator_type contains - procedure, pass(ag) :: tprol => mld_c_dec_aggregator_build_tprol + procedure, pass(ag) :: bld_tprol => mld_c_dec_aggregator_build_tprol procedure, pass(ag) :: mat_asb => mld_c_dec_aggregator_mat_asb procedure, nopass :: fmt => mld_c_dec_aggregator_fmt end type mld_c_dec_aggregator_type diff --git a/mlprec/mld_c_hybrid_aggregator_mod.F90 b/mlprec/mld_c_hybrid_aggregator_mod.F90 index f44a4f60..e616eb87 100644 --- a/mlprec/mld_c_hybrid_aggregator_mod.F90 +++ b/mlprec/mld_c_hybrid_aggregator_mod.F90 @@ -47,7 +47,7 @@ ! module mld_c_hybrid_aggregator_mod - use mld_c_base_aggregator_mod + use mld_c_dec_aggregator_mod ! ! sm - class(mld_T_base_smoother_type), allocatable ! The current level preconditioner (aka smoother). @@ -88,15 +88,10 @@ module mld_c_hybrid_aggregator_mod ! get_nzeros - Number of nonzeros ! ! - type, extends(mld_c_base_aggregator_type) :: mld_c_hybrid_aggregator_type + type, extends(mld_c_dec_aggregator_type) :: mld_c_hybrid_aggregator_type contains - procedure, pass(ag) :: bld_tprol => mld_c_hybrid_aggregator_build_tprol -!!$ procedure, pass(ag) :: mat_asb => mld_c_base_aggregator_mat_asb -!!$ procedure, pass(ag) :: update_level => mld_c_base_aggregator_update_level -!!$ procedure, pass(ag) :: clone => mld_c_base_aggregator_clone -!!$ procedure, pass(ag) :: free => mld_c_base_aggregator_free -!!$ procedure, pass(ag) :: default => mld_c_base_aggregator_default + procedure, pass(ag) :: bld_tprol => mld_c_hybrid_aggregator_build_tprol procedure, nopass :: fmt => mld_c_hybrid_aggregator_fmt end type mld_c_hybrid_aggregator_type diff --git a/mlprec/mld_c_symdec_aggregator_mod.f90 b/mlprec/mld_c_symdec_aggregator_mod.f90 index 0fffcf7a..f3df179e 100644 --- a/mlprec/mld_c_symdec_aggregator_mod.f90 +++ b/mlprec/mld_c_symdec_aggregator_mod.f90 @@ -94,7 +94,7 @@ module mld_c_symdec_aggregator_mod type, extends(mld_c_dec_aggregator_type) :: mld_c_symdec_aggregator_type contains - procedure, pass(ag) :: tprol => mld_c_symdec_aggregator_build_tprol + procedure, pass(ag) :: bld_tprol => mld_c_symdec_aggregator_build_tprol procedure, nopass :: fmt => mld_c_symdec_aggregator_fmt end type mld_c_symdec_aggregator_type diff --git a/mlprec/mld_d_dec_aggregator_mod.f90 b/mlprec/mld_d_dec_aggregator_mod.f90 index ec25f574..4ddb8f5a 100644 --- a/mlprec/mld_d_dec_aggregator_mod.f90 +++ b/mlprec/mld_d_dec_aggregator_mod.f90 @@ -92,7 +92,7 @@ module mld_d_dec_aggregator_mod type, extends(mld_d_base_aggregator_type) :: mld_d_dec_aggregator_type contains - procedure, pass(ag) :: tprol => mld_d_dec_aggregator_build_tprol + procedure, pass(ag) :: bld_tprol => mld_d_dec_aggregator_build_tprol procedure, pass(ag) :: mat_asb => mld_d_dec_aggregator_mat_asb procedure, nopass :: fmt => mld_d_dec_aggregator_fmt end type mld_d_dec_aggregator_type diff --git a/mlprec/mld_d_hybrid_aggregator_mod.F90 b/mlprec/mld_d_hybrid_aggregator_mod.F90 index 4cdde8bd..7acb7942 100644 --- a/mlprec/mld_d_hybrid_aggregator_mod.F90 +++ b/mlprec/mld_d_hybrid_aggregator_mod.F90 @@ -47,7 +47,7 @@ ! module mld_d_hybrid_aggregator_mod - use mld_d_base_aggregator_mod + use mld_d_dec_aggregator_mod ! ! sm - class(mld_T_base_smoother_type), allocatable ! The current level preconditioner (aka smoother). @@ -88,15 +88,10 @@ module mld_d_hybrid_aggregator_mod ! get_nzeros - Number of nonzeros ! ! - type, extends(mld_d_base_aggregator_type) :: mld_d_hybrid_aggregator_type + type, extends(mld_d_dec_aggregator_type) :: mld_d_hybrid_aggregator_type contains - procedure, pass(ag) :: bld_tprol => mld_d_hybrid_aggregator_build_tprol -!!$ procedure, pass(ag) :: mat_asb => mld_d_base_aggregator_mat_asb -!!$ procedure, pass(ag) :: update_level => mld_d_base_aggregator_update_level -!!$ procedure, pass(ag) :: clone => mld_d_base_aggregator_clone -!!$ procedure, pass(ag) :: free => mld_d_base_aggregator_free -!!$ procedure, pass(ag) :: default => mld_d_base_aggregator_default + procedure, pass(ag) :: bld_tprol => mld_d_hybrid_aggregator_build_tprol procedure, nopass :: fmt => mld_d_hybrid_aggregator_fmt end type mld_d_hybrid_aggregator_type diff --git a/mlprec/mld_d_symdec_aggregator_mod.f90 b/mlprec/mld_d_symdec_aggregator_mod.f90 index 893cfbf2..86fd4ba2 100644 --- a/mlprec/mld_d_symdec_aggregator_mod.f90 +++ b/mlprec/mld_d_symdec_aggregator_mod.f90 @@ -94,7 +94,7 @@ module mld_d_symdec_aggregator_mod type, extends(mld_d_dec_aggregator_type) :: mld_d_symdec_aggregator_type contains - procedure, pass(ag) :: tprol => mld_d_symdec_aggregator_build_tprol + procedure, pass(ag) :: bld_tprol => mld_d_symdec_aggregator_build_tprol procedure, nopass :: fmt => mld_d_symdec_aggregator_fmt end type mld_d_symdec_aggregator_type diff --git a/mlprec/mld_s_dec_aggregator_mod.f90 b/mlprec/mld_s_dec_aggregator_mod.f90 index 63cdd6ea..76604cbf 100644 --- a/mlprec/mld_s_dec_aggregator_mod.f90 +++ b/mlprec/mld_s_dec_aggregator_mod.f90 @@ -92,7 +92,7 @@ module mld_s_dec_aggregator_mod type, extends(mld_s_base_aggregator_type) :: mld_s_dec_aggregator_type contains - procedure, pass(ag) :: tprol => mld_s_dec_aggregator_build_tprol + procedure, pass(ag) :: bld_tprol => mld_s_dec_aggregator_build_tprol procedure, pass(ag) :: mat_asb => mld_s_dec_aggregator_mat_asb procedure, nopass :: fmt => mld_s_dec_aggregator_fmt end type mld_s_dec_aggregator_type diff --git a/mlprec/mld_s_hybrid_aggregator_mod.F90 b/mlprec/mld_s_hybrid_aggregator_mod.F90 index c7619e98..b8a1ce23 100644 --- a/mlprec/mld_s_hybrid_aggregator_mod.F90 +++ b/mlprec/mld_s_hybrid_aggregator_mod.F90 @@ -47,7 +47,7 @@ ! module mld_s_hybrid_aggregator_mod - use mld_s_base_aggregator_mod + use mld_s_dec_aggregator_mod ! ! sm - class(mld_T_base_smoother_type), allocatable ! The current level preconditioner (aka smoother). @@ -88,15 +88,10 @@ module mld_s_hybrid_aggregator_mod ! get_nzeros - Number of nonzeros ! ! - type, extends(mld_s_base_aggregator_type) :: mld_s_hybrid_aggregator_type + type, extends(mld_s_dec_aggregator_type) :: mld_s_hybrid_aggregator_type contains - procedure, pass(ag) :: bld_tprol => mld_s_hybrid_aggregator_build_tprol -!!$ procedure, pass(ag) :: mat_asb => mld_s_base_aggregator_mat_asb -!!$ procedure, pass(ag) :: update_level => mld_s_base_aggregator_update_level -!!$ procedure, pass(ag) :: clone => mld_s_base_aggregator_clone -!!$ procedure, pass(ag) :: free => mld_s_base_aggregator_free -!!$ procedure, pass(ag) :: default => mld_s_base_aggregator_default + procedure, pass(ag) :: bld_tprol => mld_s_hybrid_aggregator_build_tprol procedure, nopass :: fmt => mld_s_hybrid_aggregator_fmt end type mld_s_hybrid_aggregator_type diff --git a/mlprec/mld_s_symdec_aggregator_mod.f90 b/mlprec/mld_s_symdec_aggregator_mod.f90 index 0e980885..152ede99 100644 --- a/mlprec/mld_s_symdec_aggregator_mod.f90 +++ b/mlprec/mld_s_symdec_aggregator_mod.f90 @@ -94,7 +94,7 @@ module mld_s_symdec_aggregator_mod type, extends(mld_s_dec_aggregator_type) :: mld_s_symdec_aggregator_type contains - procedure, pass(ag) :: tprol => mld_s_symdec_aggregator_build_tprol + procedure, pass(ag) :: bld_tprol => mld_s_symdec_aggregator_build_tprol procedure, nopass :: fmt => mld_s_symdec_aggregator_fmt end type mld_s_symdec_aggregator_type diff --git a/mlprec/mld_z_dec_aggregator_mod.f90 b/mlprec/mld_z_dec_aggregator_mod.f90 index 61f9bcbd..391ec596 100644 --- a/mlprec/mld_z_dec_aggregator_mod.f90 +++ b/mlprec/mld_z_dec_aggregator_mod.f90 @@ -92,7 +92,7 @@ module mld_z_dec_aggregator_mod type, extends(mld_z_base_aggregator_type) :: mld_z_dec_aggregator_type contains - procedure, pass(ag) :: tprol => mld_z_dec_aggregator_build_tprol + procedure, pass(ag) :: bld_tprol => mld_z_dec_aggregator_build_tprol procedure, pass(ag) :: mat_asb => mld_z_dec_aggregator_mat_asb procedure, nopass :: fmt => mld_z_dec_aggregator_fmt end type mld_z_dec_aggregator_type diff --git a/mlprec/mld_z_hybrid_aggregator_mod.F90 b/mlprec/mld_z_hybrid_aggregator_mod.F90 index 4e74d5bb..75ff9719 100644 --- a/mlprec/mld_z_hybrid_aggregator_mod.F90 +++ b/mlprec/mld_z_hybrid_aggregator_mod.F90 @@ -47,7 +47,7 @@ ! module mld_z_hybrid_aggregator_mod - use mld_z_base_aggregator_mod + use mld_z_dec_aggregator_mod ! ! sm - class(mld_T_base_smoother_type), allocatable ! The current level preconditioner (aka smoother). @@ -88,15 +88,10 @@ module mld_z_hybrid_aggregator_mod ! get_nzeros - Number of nonzeros ! ! - type, extends(mld_z_base_aggregator_type) :: mld_z_hybrid_aggregator_type + type, extends(mld_z_dec_aggregator_type) :: mld_z_hybrid_aggregator_type contains - procedure, pass(ag) :: bld_tprol => mld_z_hybrid_aggregator_build_tprol -!!$ procedure, pass(ag) :: mat_asb => mld_z_base_aggregator_mat_asb -!!$ procedure, pass(ag) :: update_level => mld_z_base_aggregator_update_level -!!$ procedure, pass(ag) :: clone => mld_z_base_aggregator_clone -!!$ procedure, pass(ag) :: free => mld_z_base_aggregator_free -!!$ procedure, pass(ag) :: default => mld_z_base_aggregator_default + procedure, pass(ag) :: bld_tprol => mld_z_hybrid_aggregator_build_tprol procedure, nopass :: fmt => mld_z_hybrid_aggregator_fmt end type mld_z_hybrid_aggregator_type diff --git a/mlprec/mld_z_symdec_aggregator_mod.f90 b/mlprec/mld_z_symdec_aggregator_mod.f90 index ae7916b2..2044c273 100644 --- a/mlprec/mld_z_symdec_aggregator_mod.f90 +++ b/mlprec/mld_z_symdec_aggregator_mod.f90 @@ -94,7 +94,7 @@ module mld_z_symdec_aggregator_mod type, extends(mld_z_dec_aggregator_type) :: mld_z_symdec_aggregator_type contains - procedure, pass(ag) :: tprol => mld_z_symdec_aggregator_build_tprol + procedure, pass(ag) :: bld_tprol => mld_z_symdec_aggregator_build_tprol procedure, nopass :: fmt => mld_z_symdec_aggregator_fmt end type mld_z_symdec_aggregator_type From cce189c45070a281e0405e04534c9ebf6683513a Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 11 May 2018 08:57:37 +0100 Subject: [PATCH 22/33] Rename dec_map_bld into vmb_map_bld, following the split between PAR_AGGR_ALG and AGGR_TYPE. --- mlprec/impl/aggregator/Makefile | 8 ++++---- .../impl/aggregator/mld_c_dec_aggregator_tprol.f90 | 6 +++--- mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 | 13 ++++++------- .../aggregator/mld_c_symdec_aggregator_tprol.f90 | 6 +++--- ...mld_c_dec_map_bld.f90 => mld_c_vmb_map_bld.f90} | 14 +++++++------- .../impl/aggregator/mld_d_dec_aggregator_tprol.f90 | 6 +++--- mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 | 13 ++++++------- .../aggregator/mld_d_symdec_aggregator_tprol.f90 | 6 +++--- ...mld_d_dec_map_bld.f90 => mld_d_vmb_map_bld.f90} | 14 +++++++------- .../impl/aggregator/mld_s_dec_aggregator_tprol.f90 | 6 +++--- mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 | 13 ++++++------- .../aggregator/mld_s_symdec_aggregator_tprol.f90 | 6 +++--- ...mld_s_dec_map_bld.f90 => mld_s_vmb_map_bld.f90} | 14 +++++++------- .../impl/aggregator/mld_z_dec_aggregator_tprol.f90 | 6 +++--- mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 | 13 ++++++------- .../aggregator/mld_z_symdec_aggregator_tprol.f90 | 6 +++--- ...mld_z_dec_map_bld.f90 => mld_z_vmb_map_bld.f90} | 14 +++++++------- mlprec/mld_c_inner_mod.f90 | 8 ++++---- mlprec/mld_d_inner_mod.f90 | 8 ++++---- mlprec/mld_s_inner_mod.f90 | 8 ++++---- mlprec/mld_z_inner_mod.f90 | 8 ++++---- 21 files changed, 96 insertions(+), 100 deletions(-) rename mlprec/impl/aggregator/{mld_c_dec_map_bld.f90 => mld_c_vmb_map_bld.f90} (96%) rename mlprec/impl/aggregator/{mld_d_dec_map_bld.f90 => mld_d_vmb_map_bld.f90} (96%) rename mlprec/impl/aggregator/{mld_s_dec_map_bld.f90 => mld_s_vmb_map_bld.f90} (96%) rename mlprec/impl/aggregator/{mld_z_dec_map_bld.f90 => mld_z_vmb_map_bld.f90} (96%) diff --git a/mlprec/impl/aggregator/Makefile b/mlprec/impl/aggregator/Makefile index ba217c1c..56f21c72 100644 --- a/mlprec/impl/aggregator/Makefile +++ b/mlprec/impl/aggregator/Makefile @@ -13,28 +13,28 @@ mld_s_dec_aggregator_mat_asb.o \ mld_s_dec_aggregator_tprol.o \ mld_s_hybrid_aggregator_tprol.o \ mld_s_symdec_aggregator_tprol.o \ -mld_s_map_to_tprol.o mld_s_dec_map_bld.o mld_s_hyb_map_bld.o\ +mld_s_map_to_tprol.o mld_s_vmb_map_bld.o mld_s_hyb_map_bld.o\ mld_saggrmat_biz_asb.o mld_saggrmat_minnrg_asb.o\ mld_saggrmat_nosmth_asb.o mld_saggrmat_smth_asb.o \ mld_d_dec_aggregator_mat_asb.o \ mld_d_dec_aggregator_tprol.o \ mld_d_hybrid_aggregator_tprol.o \ mld_d_symdec_aggregator_tprol.o \ -mld_d_map_to_tprol.o mld_d_dec_map_bld.o mld_d_hyb_map_bld.o\ +mld_d_map_to_tprol.o mld_d_vmb_map_bld.o mld_d_hyb_map_bld.o\ mld_daggrmat_biz_asb.o mld_daggrmat_minnrg_asb.o\ mld_daggrmat_nosmth_asb.o mld_daggrmat_smth_asb.o \ mld_c_dec_aggregator_mat_asb.o \ mld_c_dec_aggregator_tprol.o \ mld_c_hybrid_aggregator_tprol.o \ mld_c_symdec_aggregator_tprol.o \ -mld_c_map_to_tprol.o mld_c_dec_map_bld.o mld_c_hyb_map_bld.o\ +mld_c_map_to_tprol.o mld_c_vmb_map_bld.o mld_c_hyb_map_bld.o\ mld_caggrmat_biz_asb.o mld_caggrmat_minnrg_asb.o\ mld_caggrmat_nosmth_asb.o mld_caggrmat_smth_asb.o \ mld_z_dec_aggregator_mat_asb.o \ mld_z_dec_aggregator_tprol.o \ mld_z_hybrid_aggregator_tprol.o \ mld_z_symdec_aggregator_tprol.o \ -mld_z_map_to_tprol.o mld_z_dec_map_bld.o mld_z_hyb_map_bld.o\ +mld_z_map_to_tprol.o mld_z_vmb_map_bld.o mld_z_hyb_map_bld.o\ mld_zaggrmat_biz_asb.o mld_zaggrmat_minnrg_asb.o\ mld_zaggrmat_nosmth_asb.o mld_zaggrmat_smth_asb.o diff --git a/mlprec/impl/aggregator/mld_c_dec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_c_dec_aggregator_tprol.f90 index cd978972..9d5eea9f 100644 --- a/mlprec/impl/aggregator/mld_c_dec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_c_dec_aggregator_tprol.f90 @@ -40,7 +40,7 @@ ! Subroutine: mld_c_dec_aggregator_tprol ! Version: complex ! -! This routine is mainly an interface to dec_map_bld where the real work is performed. +! This routine is mainly an interface to vmb_map_bld where the real work is performed. ! It takes care of some consistency checking, and calls map_to_tprol, which is ! refactored and shared among all the aggregation methods that produce a simple ! integer mapping. @@ -110,12 +110,12 @@ subroutine mld_c_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_ call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) - call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + call mld_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='dec_map_bld/map_to_tprol') + call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') goto 9999 endif diff --git a/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 index 33e50511..dc993846 100644 --- a/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 @@ -41,14 +41,13 @@ ! Subroutine: mld_c_hyb_map_bld ! Version: complex ! -! This routine builds the tentative prolongator based on the -! decoupled aggregation algorithm presented in +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. This variant is based on the hybrid method +! presented in ! -! M. Brezina and P. Vanek, A black-box iterative solver based on a -! two-level Schwarz method, Computing, 63 (1999), 233-263. -! P. D'Ambra, D. di Serafino and S. Filippone, On the development of -! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. -! 57 (2007), 1181-1196. +! S. Gratton, P. Henon, P. Jiranek and X. Vasseur: +! Reducing complexity of algebraic multigrid by aggregation +! Numerical Lin. Algebra with Applications, 2016, 23:501-518 ! ! Note: upon exit ! diff --git a/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 index 2486de43..53f2b04f 100644 --- a/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 @@ -41,7 +41,7 @@ ! Version: complex ! ! -! This routine is mainly an interface to dec_map_bld where the real work is performed. +! This routine is mainly an interface to vmb_map_bld where the real work is performed. ! It takes care of some consistency checking, and calls map_to_tprol, which is ! refactored and shared among all the aggregation methods that produce a simple ! integer mapping. @@ -127,13 +127,13 @@ subroutine mld_c_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, if (info == psb_success_) call atmp%cscnv(info,type='CSR') if (info == psb_success_) & - & call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) + & call mld_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) if (info == psb_success_) call atmp%free() if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='dec_map_bld/map_to_tprol') + call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') goto 9999 endif diff --git a/mlprec/impl/aggregator/mld_c_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_c_vmb_map_bld.f90 similarity index 96% rename from mlprec/impl/aggregator/mld_c_dec_map_bld.f90 rename to mlprec/impl/aggregator/mld_c_vmb_map_bld.f90 index cc40d5fd..1c300ae4 100644 --- a/mlprec/impl/aggregator/mld_c_dec_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_c_vmb_map_bld.f90 @@ -36,13 +36,13 @@ ! ! ! -! File: mld_c_dec_map__bld.f90 +! File: mld_c_vmb_map__bld.f90 ! -! Subroutine: mld_c_dec_map_bld +! Subroutine: mld_c_vmb_map_bld ! Version: complex ! ! This routine builds the tentative prolongator based on the -! decoupled aggregation algorithm presented in +! strength of connection aggregation algorithm presented in ! ! M. Brezina and P. Vanek, A black-box iterative solver based on a ! two-level Schwarz method, Computing, 63 (1999), 233-263. @@ -67,11 +67,11 @@ ! ! ! -subroutine mld_c_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) +subroutine mld_c_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_c_inner_mod, mld_protect_name => mld_c_dec_map_bld + use mld_c_inner_mod, mld_protect_name => mld_c_vmb_map_bld implicit none @@ -98,7 +98,7 @@ subroutine mld_c_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) if (psb_get_errstatus() /= 0) return info=psb_success_ - name = 'mld_dec_map_bld' + name = 'mld_vmb_map_bld' call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() debug_level = psb_get_debug_level() @@ -318,5 +318,5 @@ subroutine mld_c_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) return -end subroutine mld_c_dec_map_bld +end subroutine mld_c_vmb_map_bld diff --git a/mlprec/impl/aggregator/mld_d_dec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_d_dec_aggregator_tprol.f90 index a919f55b..3a02f8c9 100644 --- a/mlprec/impl/aggregator/mld_d_dec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_d_dec_aggregator_tprol.f90 @@ -40,7 +40,7 @@ ! Subroutine: mld_d_dec_aggregator_tprol ! Version: real ! -! This routine is mainly an interface to dec_map_bld where the real work is performed. +! This routine is mainly an interface to vmb_map_bld where the real work is performed. ! It takes care of some consistency checking, and calls map_to_tprol, which is ! refactored and shared among all the aggregation methods that produce a simple ! integer mapping. @@ -110,12 +110,12 @@ subroutine mld_d_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_ call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) - call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + call mld_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='dec_map_bld/map_to_tprol') + call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') goto 9999 endif diff --git a/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 index 5f3b5cbe..e7bc63dc 100644 --- a/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 @@ -41,14 +41,13 @@ ! Subroutine: mld_d_hyb_map_bld ! Version: real ! -! This routine builds the tentative prolongator based on the -! decoupled aggregation algorithm presented in +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. This variant is based on the hybrid method +! presented in ! -! M. Brezina and P. Vanek, A black-box iterative solver based on a -! two-level Schwarz method, Computing, 63 (1999), 233-263. -! P. D'Ambra, D. di Serafino and S. Filippone, On the development of -! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. -! 57 (2007), 1181-1196. +! S. Gratton, P. Henon, P. Jiranek and X. Vasseur: +! Reducing complexity of algebraic multigrid by aggregation +! Numerical Lin. Algebra with Applications, 2016, 23:501-518 ! ! Note: upon exit ! diff --git a/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 index 74bffe40..cd0ee7dc 100644 --- a/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 @@ -41,7 +41,7 @@ ! Version: real ! ! -! This routine is mainly an interface to dec_map_bld where the real work is performed. +! This routine is mainly an interface to vmb_map_bld where the real work is performed. ! It takes care of some consistency checking, and calls map_to_tprol, which is ! refactored and shared among all the aggregation methods that produce a simple ! integer mapping. @@ -127,13 +127,13 @@ subroutine mld_d_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, if (info == psb_success_) call atmp%cscnv(info,type='CSR') if (info == psb_success_) & - & call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) + & call mld_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) if (info == psb_success_) call atmp%free() if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='dec_map_bld/map_to_tprol') + call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') goto 9999 endif diff --git a/mlprec/impl/aggregator/mld_d_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_d_vmb_map_bld.f90 similarity index 96% rename from mlprec/impl/aggregator/mld_d_dec_map_bld.f90 rename to mlprec/impl/aggregator/mld_d_vmb_map_bld.f90 index 8d50c23e..2b523f7c 100644 --- a/mlprec/impl/aggregator/mld_d_dec_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_d_vmb_map_bld.f90 @@ -36,13 +36,13 @@ ! ! ! -! File: mld_d_dec_map__bld.f90 +! File: mld_d_vmb_map__bld.f90 ! -! Subroutine: mld_d_dec_map_bld +! Subroutine: mld_d_vmb_map_bld ! Version: real ! ! This routine builds the tentative prolongator based on the -! decoupled aggregation algorithm presented in +! strength of connection aggregation algorithm presented in ! ! M. Brezina and P. Vanek, A black-box iterative solver based on a ! two-level Schwarz method, Computing, 63 (1999), 233-263. @@ -67,11 +67,11 @@ ! ! ! -subroutine mld_d_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) +subroutine mld_d_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_d_inner_mod, mld_protect_name => mld_d_dec_map_bld + use mld_d_inner_mod, mld_protect_name => mld_d_vmb_map_bld implicit none @@ -98,7 +98,7 @@ subroutine mld_d_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) if (psb_get_errstatus() /= 0) return info=psb_success_ - name = 'mld_dec_map_bld' + name = 'mld_vmb_map_bld' call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() debug_level = psb_get_debug_level() @@ -318,5 +318,5 @@ subroutine mld_d_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) return -end subroutine mld_d_dec_map_bld +end subroutine mld_d_vmb_map_bld diff --git a/mlprec/impl/aggregator/mld_s_dec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_s_dec_aggregator_tprol.f90 index 78bce133..e749fe77 100644 --- a/mlprec/impl/aggregator/mld_s_dec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_s_dec_aggregator_tprol.f90 @@ -40,7 +40,7 @@ ! Subroutine: mld_s_dec_aggregator_tprol ! Version: real ! -! This routine is mainly an interface to dec_map_bld where the real work is performed. +! This routine is mainly an interface to vmb_map_bld where the real work is performed. ! It takes care of some consistency checking, and calls map_to_tprol, which is ! refactored and shared among all the aggregation methods that produce a simple ! integer mapping. @@ -110,12 +110,12 @@ subroutine mld_s_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_ call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) - call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + call mld_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='dec_map_bld/map_to_tprol') + call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') goto 9999 endif diff --git a/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 index 5f093685..96fe92d6 100644 --- a/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 @@ -41,14 +41,13 @@ ! Subroutine: mld_s_hyb_map_bld ! Version: real ! -! This routine builds the tentative prolongator based on the -! decoupled aggregation algorithm presented in +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. This variant is based on the hybrid method +! presented in ! -! M. Brezina and P. Vanek, A black-box iterative solver based on a -! two-level Schwarz method, Computing, 63 (1999), 233-263. -! P. D'Ambra, D. di Serafino and S. Filippone, On the development of -! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. -! 57 (2007), 1181-1196. +! S. Gratton, P. Henon, P. Jiranek and X. Vasseur: +! Reducing complexity of algebraic multigrid by aggregation +! Numerical Lin. Algebra with Applications, 2016, 23:501-518 ! ! Note: upon exit ! diff --git a/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 index ea815091..fc54ba9d 100644 --- a/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 @@ -41,7 +41,7 @@ ! Version: real ! ! -! This routine is mainly an interface to dec_map_bld where the real work is performed. +! This routine is mainly an interface to vmb_map_bld where the real work is performed. ! It takes care of some consistency checking, and calls map_to_tprol, which is ! refactored and shared among all the aggregation methods that produce a simple ! integer mapping. @@ -127,13 +127,13 @@ subroutine mld_s_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, if (info == psb_success_) call atmp%cscnv(info,type='CSR') if (info == psb_success_) & - & call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) + & call mld_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) if (info == psb_success_) call atmp%free() if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='dec_map_bld/map_to_tprol') + call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') goto 9999 endif diff --git a/mlprec/impl/aggregator/mld_s_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_s_vmb_map_bld.f90 similarity index 96% rename from mlprec/impl/aggregator/mld_s_dec_map_bld.f90 rename to mlprec/impl/aggregator/mld_s_vmb_map_bld.f90 index be2212ad..b0de5055 100644 --- a/mlprec/impl/aggregator/mld_s_dec_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_s_vmb_map_bld.f90 @@ -36,13 +36,13 @@ ! ! ! -! File: mld_s_dec_map__bld.f90 +! File: mld_s_vmb_map__bld.f90 ! -! Subroutine: mld_s_dec_map_bld +! Subroutine: mld_s_vmb_map_bld ! Version: real ! ! This routine builds the tentative prolongator based on the -! decoupled aggregation algorithm presented in +! strength of connection aggregation algorithm presented in ! ! M. Brezina and P. Vanek, A black-box iterative solver based on a ! two-level Schwarz method, Computing, 63 (1999), 233-263. @@ -67,11 +67,11 @@ ! ! ! -subroutine mld_s_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) +subroutine mld_s_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_s_inner_mod, mld_protect_name => mld_s_dec_map_bld + use mld_s_inner_mod, mld_protect_name => mld_s_vmb_map_bld implicit none @@ -98,7 +98,7 @@ subroutine mld_s_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) if (psb_get_errstatus() /= 0) return info=psb_success_ - name = 'mld_dec_map_bld' + name = 'mld_vmb_map_bld' call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() debug_level = psb_get_debug_level() @@ -318,5 +318,5 @@ subroutine mld_s_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) return -end subroutine mld_s_dec_map_bld +end subroutine mld_s_vmb_map_bld diff --git a/mlprec/impl/aggregator/mld_z_dec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_z_dec_aggregator_tprol.f90 index cc3f23cb..aa0e63ce 100644 --- a/mlprec/impl/aggregator/mld_z_dec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_z_dec_aggregator_tprol.f90 @@ -40,7 +40,7 @@ ! Subroutine: mld_z_dec_aggregator_tprol ! Version: complex ! -! This routine is mainly an interface to dec_map_bld where the real work is performed. +! This routine is mainly an interface to vmb_map_bld where the real work is performed. ! It takes care of some consistency checking, and calls map_to_tprol, which is ! refactored and shared among all the aggregation methods that produce a simple ! integer mapping. @@ -110,12 +110,12 @@ subroutine mld_z_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_ call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) - call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + call mld_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='dec_map_bld/map_to_tprol') + call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') goto 9999 endif diff --git a/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 index 57ae369c..4fc95dd3 100644 --- a/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 @@ -41,14 +41,13 @@ ! Subroutine: mld_z_hyb_map_bld ! Version: complex ! -! This routine builds the tentative prolongator based on the -! decoupled aggregation algorithm presented in +! The aggregator object hosts the aggregation method for building +! the multilevel hierarchy. This variant is based on the hybrid method +! presented in ! -! M. Brezina and P. Vanek, A black-box iterative solver based on a -! two-level Schwarz method, Computing, 63 (1999), 233-263. -! P. D'Ambra, D. di Serafino and S. Filippone, On the development of -! PSBLAS-based parallel two-level Schwarz preconditioners, Appl. Num. Math. -! 57 (2007), 1181-1196. +! S. Gratton, P. Henon, P. Jiranek and X. Vasseur: +! Reducing complexity of algebraic multigrid by aggregation +! Numerical Lin. Algebra with Applications, 2016, 23:501-518 ! ! Note: upon exit ! diff --git a/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 index a0de3a6a..3fab8e96 100644 --- a/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 @@ -41,7 +41,7 @@ ! Version: complex ! ! -! This routine is mainly an interface to dec_map_bld where the real work is performed. +! This routine is mainly an interface to vmb_map_bld where the real work is performed. ! It takes care of some consistency checking, and calls map_to_tprol, which is ! refactored and shared among all the aggregation methods that produce a simple ! integer mapping. @@ -127,13 +127,13 @@ subroutine mld_z_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, if (info == psb_success_) call atmp%cscnv(info,type='CSR') if (info == psb_success_) & - & call mld_dec_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) + & call mld_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) if (info == psb_success_) call atmp%free() if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='dec_map_bld/map_to_tprol') + call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') goto 9999 endif diff --git a/mlprec/impl/aggregator/mld_z_dec_map_bld.f90 b/mlprec/impl/aggregator/mld_z_vmb_map_bld.f90 similarity index 96% rename from mlprec/impl/aggregator/mld_z_dec_map_bld.f90 rename to mlprec/impl/aggregator/mld_z_vmb_map_bld.f90 index 80119809..ff131c33 100644 --- a/mlprec/impl/aggregator/mld_z_dec_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_z_vmb_map_bld.f90 @@ -36,13 +36,13 @@ ! ! ! -! File: mld_z_dec_map__bld.f90 +! File: mld_z_vmb_map__bld.f90 ! -! Subroutine: mld_z_dec_map_bld +! Subroutine: mld_z_vmb_map_bld ! Version: complex ! ! This routine builds the tentative prolongator based on the -! decoupled aggregation algorithm presented in +! strength of connection aggregation algorithm presented in ! ! M. Brezina and P. Vanek, A black-box iterative solver based on a ! two-level Schwarz method, Computing, 63 (1999), 233-263. @@ -67,11 +67,11 @@ ! ! ! -subroutine mld_z_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) +subroutine mld_z_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_z_inner_mod, mld_protect_name => mld_z_dec_map_bld + use mld_z_inner_mod, mld_protect_name => mld_z_vmb_map_bld implicit none @@ -98,7 +98,7 @@ subroutine mld_z_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) if (psb_get_errstatus() /= 0) return info=psb_success_ - name = 'mld_dec_map_bld' + name = 'mld_vmb_map_bld' call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() debug_level = psb_get_debug_level() @@ -318,5 +318,5 @@ subroutine mld_z_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) return -end subroutine mld_z_dec_map_bld +end subroutine mld_z_vmb_map_bld diff --git a/mlprec/mld_c_inner_mod.f90 b/mlprec/mld_c_inner_mod.f90 index 2b4c9fd7..44d7266d 100644 --- a/mlprec/mld_c_inner_mod.f90 +++ b/mlprec/mld_c_inner_mod.f90 @@ -124,8 +124,8 @@ module mld_c_inner_mod end interface mld_aggrmap_bld - interface mld_dec_map_bld - subroutine mld_c_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + interface mld_vmb_map_bld + subroutine mld_c_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) import :: psb_cspmat_type, psb_desc_type, psb_spk_, psb_ipk_ implicit none integer(psb_ipk_), intent(in) :: iorder @@ -134,8 +134,8 @@ module mld_c_inner_mod real(psb_spk_), intent(in) :: theta integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) integer(psb_ipk_), intent(out) :: info - end subroutine mld_c_dec_map_bld - end interface mld_dec_map_bld + end subroutine mld_c_vmb_map_bld + end interface mld_vmb_map_bld interface mld_hyb_map_bld subroutine mld_c_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) diff --git a/mlprec/mld_d_inner_mod.f90 b/mlprec/mld_d_inner_mod.f90 index 454d934a..fdae973d 100644 --- a/mlprec/mld_d_inner_mod.f90 +++ b/mlprec/mld_d_inner_mod.f90 @@ -124,8 +124,8 @@ module mld_d_inner_mod end interface mld_aggrmap_bld - interface mld_dec_map_bld - subroutine mld_d_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + interface mld_vmb_map_bld + subroutine mld_d_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) import :: psb_dspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ implicit none integer(psb_ipk_), intent(in) :: iorder @@ -134,8 +134,8 @@ module mld_d_inner_mod real(psb_dpk_), intent(in) :: theta integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) integer(psb_ipk_), intent(out) :: info - end subroutine mld_d_dec_map_bld - end interface mld_dec_map_bld + end subroutine mld_d_vmb_map_bld + end interface mld_vmb_map_bld interface mld_hyb_map_bld subroutine mld_d_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) diff --git a/mlprec/mld_s_inner_mod.f90 b/mlprec/mld_s_inner_mod.f90 index 512d60c7..32c22e1f 100644 --- a/mlprec/mld_s_inner_mod.f90 +++ b/mlprec/mld_s_inner_mod.f90 @@ -124,8 +124,8 @@ module mld_s_inner_mod end interface mld_aggrmap_bld - interface mld_dec_map_bld - subroutine mld_s_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + interface mld_vmb_map_bld + subroutine mld_s_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) import :: psb_sspmat_type, psb_desc_type, psb_spk_, psb_ipk_ implicit none integer(psb_ipk_), intent(in) :: iorder @@ -134,8 +134,8 @@ module mld_s_inner_mod real(psb_spk_), intent(in) :: theta integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) integer(psb_ipk_), intent(out) :: info - end subroutine mld_s_dec_map_bld - end interface mld_dec_map_bld + end subroutine mld_s_vmb_map_bld + end interface mld_vmb_map_bld interface mld_hyb_map_bld subroutine mld_s_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) diff --git a/mlprec/mld_z_inner_mod.f90 b/mlprec/mld_z_inner_mod.f90 index 2100d576..c27d01c4 100644 --- a/mlprec/mld_z_inner_mod.f90 +++ b/mlprec/mld_z_inner_mod.f90 @@ -124,8 +124,8 @@ module mld_z_inner_mod end interface mld_aggrmap_bld - interface mld_dec_map_bld - subroutine mld_z_dec_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + interface mld_vmb_map_bld + subroutine mld_z_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) import :: psb_zspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ implicit none integer(psb_ipk_), intent(in) :: iorder @@ -134,8 +134,8 @@ module mld_z_inner_mod real(psb_dpk_), intent(in) :: theta integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) integer(psb_ipk_), intent(out) :: info - end subroutine mld_z_dec_map_bld - end interface mld_dec_map_bld + end subroutine mld_z_vmb_map_bld + end interface mld_vmb_map_bld interface mld_hyb_map_bld subroutine mld_z_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) From 9f2c23b2a4cb05dd051163bec2c02706cafe5798 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 11 May 2018 12:55:50 +0100 Subject: [PATCH 23/33] Redefine map_bld interfaces. --- .../aggregator/mld_c_dec_aggregator_tprol.f90 | 2 +- .../mld_c_hybrid_aggregator_tprol.f90 | 2 +- .../mld_c_symdec_aggregator_tprol.f90 | 2 +- .../aggregator/mld_d_dec_aggregator_tprol.f90 | 2 +- .../mld_d_hybrid_aggregator_tprol.f90 | 2 +- .../mld_d_symdec_aggregator_tprol.f90 | 2 +- .../aggregator/mld_s_dec_aggregator_tprol.f90 | 2 +- .../mld_s_hybrid_aggregator_tprol.f90 | 2 +- .../mld_s_symdec_aggregator_tprol.f90 | 2 +- .../aggregator/mld_z_dec_aggregator_tprol.f90 | 2 +- .../mld_z_hybrid_aggregator_tprol.f90 | 2 +- .../mld_z_symdec_aggregator_tprol.f90 | 2 +- mlprec/impl/level/mld_c_base_onelev_descr.f90 | 11 +++- mlprec/impl/level/mld_d_base_onelev_descr.f90 | 11 +++- mlprec/impl/level/mld_s_base_onelev_descr.f90 | 11 +++- mlprec/impl/level/mld_z_base_onelev_descr.f90 | 11 +++- mlprec/mld_base_prec_type.F90 | 57 ++++++++++--------- mlprec/mld_c_inner_mod.f90 | 25 ++------ mlprec/mld_d_inner_mod.f90 | 25 ++------ mlprec/mld_s_inner_mod.f90 | 25 ++------ mlprec/mld_z_inner_mod.f90 | 25 ++------ 21 files changed, 105 insertions(+), 120 deletions(-) diff --git a/mlprec/impl/aggregator/mld_c_dec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_c_dec_aggregator_tprol.f90 index 9d5eea9f..b9e6ae1f 100644 --- a/mlprec/impl/aggregator/mld_c_dec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_c_dec_aggregator_tprol.f90 @@ -110,7 +110,7 @@ subroutine mld_c_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_ call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) - call mld_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + call mld_c_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then diff --git a/mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 index 997e0200..79da415e 100644 --- a/mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 @@ -112,7 +112,7 @@ subroutine mld_c_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) - call mld_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + call mld_c_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then diff --git a/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 index 53f2b04f..df43dc0a 100644 --- a/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 @@ -127,7 +127,7 @@ subroutine mld_c_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, if (info == psb_success_) call atmp%cscnv(info,type='CSR') if (info == psb_success_) & - & call mld_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) + & call mld_c_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) if (info == psb_success_) call atmp%free() if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) diff --git a/mlprec/impl/aggregator/mld_d_dec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_d_dec_aggregator_tprol.f90 index 3a02f8c9..b3f1d099 100644 --- a/mlprec/impl/aggregator/mld_d_dec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_d_dec_aggregator_tprol.f90 @@ -110,7 +110,7 @@ subroutine mld_d_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_ call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) - call mld_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + call mld_d_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then diff --git a/mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 index 557082e4..b822a956 100644 --- a/mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 @@ -112,7 +112,7 @@ subroutine mld_d_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) - call mld_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + call mld_d_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then diff --git a/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 index cd0ee7dc..6216c2fc 100644 --- a/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 @@ -127,7 +127,7 @@ subroutine mld_d_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, if (info == psb_success_) call atmp%cscnv(info,type='CSR') if (info == psb_success_) & - & call mld_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) + & call mld_d_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) if (info == psb_success_) call atmp%free() if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) diff --git a/mlprec/impl/aggregator/mld_s_dec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_s_dec_aggregator_tprol.f90 index e749fe77..a1a784e1 100644 --- a/mlprec/impl/aggregator/mld_s_dec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_s_dec_aggregator_tprol.f90 @@ -110,7 +110,7 @@ subroutine mld_s_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_ call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) - call mld_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + call mld_s_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then diff --git a/mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 index 765f556c..d2100775 100644 --- a/mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 @@ -112,7 +112,7 @@ subroutine mld_s_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) - call mld_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + call mld_s_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then diff --git a/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 index fc54ba9d..551ff721 100644 --- a/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 @@ -127,7 +127,7 @@ subroutine mld_s_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, if (info == psb_success_) call atmp%cscnv(info,type='CSR') if (info == psb_success_) & - & call mld_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) + & call mld_s_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) if (info == psb_success_) call atmp%free() if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) diff --git a/mlprec/impl/aggregator/mld_z_dec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_z_dec_aggregator_tprol.f90 index aa0e63ce..2cb8d57c 100644 --- a/mlprec/impl/aggregator/mld_z_dec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_z_dec_aggregator_tprol.f90 @@ -110,7 +110,7 @@ subroutine mld_z_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_ call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) - call mld_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + call mld_z_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then diff --git a/mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 index c31ed21c..bf739e8f 100644 --- a/mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 @@ -112,7 +112,7 @@ subroutine mld_z_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) - call mld_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + call mld_z_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then diff --git a/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 index 3fab8e96..5425f75c 100644 --- a/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 @@ -127,7 +127,7 @@ subroutine mld_z_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, if (info == psb_success_) call atmp%cscnv(info,type='CSR') if (info == psb_success_) & - & call mld_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) + & call mld_z_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) if (info == psb_success_) call atmp%free() if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) diff --git a/mlprec/impl/level/mld_c_base_onelev_descr.f90 b/mlprec/impl/level/mld_c_base_onelev_descr.f90 index c2698ddd..f271be0c 100644 --- a/mlprec/impl/level/mld_c_base_onelev_descr.f90 +++ b/mlprec/impl/level/mld_c_base_onelev_descr.f90 @@ -66,9 +66,18 @@ subroutine mld_c_base_onelev_descr(lv,il,nl,ilmin,info,iout) write(iout_,*) if (il == ilmin) then - call lv%parms%mldescr(iout_,info) + call lv%parms%mlcycledsc(iout_,info) + if (allocated(lv%aggr)) then + call lv%aggr%descr(lv%parms,iout_,info) + else + write(iout_,*) 'Internal error: unallocated aggregator object' + info = psb_err_internal_error_ + call psb_errpush(info,name) + goto 9999 + end if write(iout_,*) end if + if (il > 1) then if (coarse) then diff --git a/mlprec/impl/level/mld_d_base_onelev_descr.f90 b/mlprec/impl/level/mld_d_base_onelev_descr.f90 index fc602b40..6ca546df 100644 --- a/mlprec/impl/level/mld_d_base_onelev_descr.f90 +++ b/mlprec/impl/level/mld_d_base_onelev_descr.f90 @@ -66,9 +66,18 @@ subroutine mld_d_base_onelev_descr(lv,il,nl,ilmin,info,iout) write(iout_,*) if (il == ilmin) then - call lv%parms%mldescr(iout_,info) + call lv%parms%mlcycledsc(iout_,info) + if (allocated(lv%aggr)) then + call lv%aggr%descr(lv%parms,iout_,info) + else + write(iout_,*) 'Internal error: unallocated aggregator object' + info = psb_err_internal_error_ + call psb_errpush(info,name) + goto 9999 + end if write(iout_,*) end if + if (il > 1) then if (coarse) then diff --git a/mlprec/impl/level/mld_s_base_onelev_descr.f90 b/mlprec/impl/level/mld_s_base_onelev_descr.f90 index 254086cf..5c09e28b 100644 --- a/mlprec/impl/level/mld_s_base_onelev_descr.f90 +++ b/mlprec/impl/level/mld_s_base_onelev_descr.f90 @@ -66,9 +66,18 @@ subroutine mld_s_base_onelev_descr(lv,il,nl,ilmin,info,iout) write(iout_,*) if (il == ilmin) then - call lv%parms%mldescr(iout_,info) + call lv%parms%mlcycledsc(iout_,info) + if (allocated(lv%aggr)) then + call lv%aggr%descr(lv%parms,iout_,info) + else + write(iout_,*) 'Internal error: unallocated aggregator object' + info = psb_err_internal_error_ + call psb_errpush(info,name) + goto 9999 + end if write(iout_,*) end if + if (il > 1) then if (coarse) then diff --git a/mlprec/impl/level/mld_z_base_onelev_descr.f90 b/mlprec/impl/level/mld_z_base_onelev_descr.f90 index 795f8c4f..7ec9e91f 100644 --- a/mlprec/impl/level/mld_z_base_onelev_descr.f90 +++ b/mlprec/impl/level/mld_z_base_onelev_descr.f90 @@ -66,9 +66,18 @@ subroutine mld_z_base_onelev_descr(lv,il,nl,ilmin,info,iout) write(iout_,*) if (il == ilmin) then - call lv%parms%mldescr(iout_,info) + call lv%parms%mlcycledsc(iout_,info) + if (allocated(lv%aggr)) then + call lv%aggr%descr(lv%parms,iout_,info) + else + write(iout_,*) 'Internal error: unallocated aggregator object' + info = psb_err_internal_error_ + call psb_errpush(info,name) + goto 9999 + end if write(iout_,*) end if + if (il > 1) then if (coarse) then diff --git a/mlprec/mld_base_prec_type.F90 b/mlprec/mld_base_prec_type.F90 index 28cda2db..81b2f368 100644 --- a/mlprec/mld_base_prec_type.F90 +++ b/mlprec/mld_base_prec_type.F90 @@ -569,10 +569,10 @@ contains if ((pm%ml_cycle>=mld_no_ml_).and.(pm%ml_cycle<=mld_max_ml_cycle_)) then + write(iout,*) ' Parallel aggregation algorithm: ',& + & par_aggr_alg_names(pm%par_aggr_alg) write(iout,*) ' Aggregation type: ',& & aggr_type_names(pm%aggr_type) - write(iout,*) ' parallel algorithm: ',& - & par_aggr_alg_names(pm%par_aggr_alg) if (pm%par_aggr_alg /= mld_ext_aggr_) then if ( pm%aggr_ord /= mld_aggr_ord_nat_) & & write(iout,*) ' with initial ordering: ',& @@ -601,6 +601,33 @@ contains end subroutine ml_parms_mldescr + subroutine ml_parms_descr(pm,iout,info,coarse) + + Implicit None + + ! Arguments + class(mld_ml_parms), intent(in) :: pm + integer(psb_ipk_), intent(in) :: iout + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: coarse + logical :: coarse_ + + info = psb_success_ + if (present(coarse)) then + coarse_ = coarse + else + coarse_ = .false. + end if + + if (coarse_) then + call pm%coarsedescr(iout,info) + end if + + return + + end subroutine ml_parms_descr + + subroutine ml_parms_coarsedescr(pm,iout,info) @@ -632,32 +659,6 @@ contains end subroutine ml_parms_coarsedescr - subroutine ml_parms_descr(pm,iout,info,coarse) - - Implicit None - - ! Arguments - class(mld_ml_parms), intent(in) :: pm - integer(psb_ipk_), intent(in) :: iout - integer(psb_ipk_), intent(out) :: info - logical, intent(in), optional :: coarse - logical :: coarse_ - - info = psb_success_ - if (present(coarse)) then - coarse_ = coarse - else - coarse_ = .false. - end if - - if (coarse_) then - call pm%coarsedescr(iout,info) - end if - - return - - end subroutine ml_parms_descr - subroutine s_ml_parms_descr(pm,iout,info,coarse) Implicit None diff --git a/mlprec/mld_c_inner_mod.f90 b/mlprec/mld_c_inner_mod.f90 index 44d7266d..d84296d4 100644 --- a/mlprec/mld_c_inner_mod.f90 +++ b/mlprec/mld_c_inner_mod.f90 @@ -123,9 +123,8 @@ module mld_c_inner_mod end subroutine mld_caggrmap_bld end interface mld_aggrmap_bld - - interface mld_vmb_map_bld - subroutine mld_c_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + abstract interface + subroutine mld_c_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) import :: psb_cspmat_type, psb_desc_type, psb_spk_, psb_ipk_ implicit none integer(psb_ipk_), intent(in) :: iorder @@ -134,22 +133,11 @@ module mld_c_inner_mod real(psb_spk_), intent(in) :: theta integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) integer(psb_ipk_), intent(out) :: info - end subroutine mld_c_vmb_map_bld - end interface mld_vmb_map_bld - - interface mld_hyb_map_bld - subroutine mld_c_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) - use psb_base_mod, only : psb_cspmat_type, psb_desc_type, psb_spk_, psb_ipk_ - implicit none - integer(psb_ipk_), intent(in) :: iorder - type(psb_cspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - real(psb_spk_), intent(in) :: theta - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - integer(psb_ipk_), intent(out) :: info - end subroutine mld_c_hyb_map_bld - end interface mld_hyb_map_bld + end subroutine mld_c_map_bld + end interface + procedure(mld_c_map_bld) :: mld_c_vmb_map_bld, mld_c_hyb_map_bld + interface mld_map_to_tprol subroutine mld_c_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod, only : psb_cspmat_type, psb_desc_type, psb_spk_, psb_ipk_ @@ -162,7 +150,6 @@ module mld_c_inner_mod end subroutine mld_c_map_to_tprol end interface mld_map_to_tprol - interface mld_lev_mat_asb subroutine mld_c_lev_aggrmat_asb(p,a,desc_a,ilaggr,nlaggr,op_prol,info) import :: psb_cspmat_type, psb_desc_type, psb_spk_, psb_ipk_ diff --git a/mlprec/mld_d_inner_mod.f90 b/mlprec/mld_d_inner_mod.f90 index fdae973d..9b33e872 100644 --- a/mlprec/mld_d_inner_mod.f90 +++ b/mlprec/mld_d_inner_mod.f90 @@ -123,9 +123,8 @@ module mld_d_inner_mod end subroutine mld_daggrmap_bld end interface mld_aggrmap_bld - - interface mld_vmb_map_bld - subroutine mld_d_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + abstract interface + subroutine mld_d_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) import :: psb_dspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ implicit none integer(psb_ipk_), intent(in) :: iorder @@ -134,22 +133,11 @@ module mld_d_inner_mod real(psb_dpk_), intent(in) :: theta integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) integer(psb_ipk_), intent(out) :: info - end subroutine mld_d_vmb_map_bld - end interface mld_vmb_map_bld - - interface mld_hyb_map_bld - subroutine mld_d_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) - use psb_base_mod, only : psb_dspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ - implicit none - integer(psb_ipk_), intent(in) :: iorder - type(psb_dspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - real(psb_dpk_), intent(in) :: theta - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - integer(psb_ipk_), intent(out) :: info - end subroutine mld_d_hyb_map_bld - end interface mld_hyb_map_bld + end subroutine mld_d_map_bld + end interface + procedure(mld_d_map_bld) :: mld_d_vmb_map_bld, mld_d_hyb_map_bld + interface mld_map_to_tprol subroutine mld_d_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod, only : psb_dspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ @@ -162,7 +150,6 @@ module mld_d_inner_mod end subroutine mld_d_map_to_tprol end interface mld_map_to_tprol - interface mld_lev_mat_asb subroutine mld_d_lev_aggrmat_asb(p,a,desc_a,ilaggr,nlaggr,op_prol,info) import :: psb_dspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ diff --git a/mlprec/mld_s_inner_mod.f90 b/mlprec/mld_s_inner_mod.f90 index 32c22e1f..3793d055 100644 --- a/mlprec/mld_s_inner_mod.f90 +++ b/mlprec/mld_s_inner_mod.f90 @@ -123,9 +123,8 @@ module mld_s_inner_mod end subroutine mld_saggrmap_bld end interface mld_aggrmap_bld - - interface mld_vmb_map_bld - subroutine mld_s_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + abstract interface + subroutine mld_s_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) import :: psb_sspmat_type, psb_desc_type, psb_spk_, psb_ipk_ implicit none integer(psb_ipk_), intent(in) :: iorder @@ -134,22 +133,11 @@ module mld_s_inner_mod real(psb_spk_), intent(in) :: theta integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) integer(psb_ipk_), intent(out) :: info - end subroutine mld_s_vmb_map_bld - end interface mld_vmb_map_bld - - interface mld_hyb_map_bld - subroutine mld_s_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) - use psb_base_mod, only : psb_sspmat_type, psb_desc_type, psb_spk_, psb_ipk_ - implicit none - integer(psb_ipk_), intent(in) :: iorder - type(psb_sspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - real(psb_spk_), intent(in) :: theta - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - integer(psb_ipk_), intent(out) :: info - end subroutine mld_s_hyb_map_bld - end interface mld_hyb_map_bld + end subroutine mld_s_map_bld + end interface + procedure(mld_s_map_bld) :: mld_s_vmb_map_bld, mld_s_hyb_map_bld + interface mld_map_to_tprol subroutine mld_s_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod, only : psb_sspmat_type, psb_desc_type, psb_spk_, psb_ipk_ @@ -162,7 +150,6 @@ module mld_s_inner_mod end subroutine mld_s_map_to_tprol end interface mld_map_to_tprol - interface mld_lev_mat_asb subroutine mld_s_lev_aggrmat_asb(p,a,desc_a,ilaggr,nlaggr,op_prol,info) import :: psb_sspmat_type, psb_desc_type, psb_spk_, psb_ipk_ diff --git a/mlprec/mld_z_inner_mod.f90 b/mlprec/mld_z_inner_mod.f90 index c27d01c4..461de81d 100644 --- a/mlprec/mld_z_inner_mod.f90 +++ b/mlprec/mld_z_inner_mod.f90 @@ -123,9 +123,8 @@ module mld_z_inner_mod end subroutine mld_zaggrmap_bld end interface mld_aggrmap_bld - - interface mld_vmb_map_bld - subroutine mld_z_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + abstract interface + subroutine mld_z_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) import :: psb_zspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ implicit none integer(psb_ipk_), intent(in) :: iorder @@ -134,22 +133,11 @@ module mld_z_inner_mod real(psb_dpk_), intent(in) :: theta integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) integer(psb_ipk_), intent(out) :: info - end subroutine mld_z_vmb_map_bld - end interface mld_vmb_map_bld - - interface mld_hyb_map_bld - subroutine mld_z_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) - use psb_base_mod, only : psb_zspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ - implicit none - integer(psb_ipk_), intent(in) :: iorder - type(psb_zspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - real(psb_dpk_), intent(in) :: theta - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - integer(psb_ipk_), intent(out) :: info - end subroutine mld_z_hyb_map_bld - end interface mld_hyb_map_bld + end subroutine mld_z_map_bld + end interface + procedure(mld_z_map_bld) :: mld_z_vmb_map_bld, mld_z_hyb_map_bld + interface mld_map_to_tprol subroutine mld_z_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod, only : psb_zspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ @@ -162,7 +150,6 @@ module mld_z_inner_mod end subroutine mld_z_map_to_tprol end interface mld_map_to_tprol - interface mld_lev_mat_asb subroutine mld_z_lev_aggrmat_asb(p,a,desc_a,ilaggr,nlaggr,op_prol,info) import :: psb_zspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ From e1d9157136e808cc8394e78a4990a444241f3fde Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 11 May 2018 13:38:22 +0100 Subject: [PATCH 24/33] Unified vmb and hyb map_bld inside dec_aggregator. --- .../aggregator/mld_c_dec_aggregator_tprol.f90 | 3 +- mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 | 2 +- mlprec/impl/aggregator/mld_c_vmb_map_bld.f90 | 2 +- .../aggregator/mld_d_dec_aggregator_tprol.f90 | 3 +- mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 | 2 +- mlprec/impl/aggregator/mld_d_vmb_map_bld.f90 | 2 +- .../aggregator/mld_s_dec_aggregator_tprol.f90 | 3 +- mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 | 2 +- mlprec/impl/aggregator/mld_s_vmb_map_bld.f90 | 2 +- .../aggregator/mld_z_dec_aggregator_tprol.f90 | 3 +- mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 | 2 +- mlprec/impl/aggregator/mld_z_vmb_map_bld.f90 | 2 +- mlprec/impl/level/mld_c_base_onelev_cseti.F90 | 6 +- mlprec/impl/level/mld_c_base_onelev_seti.F90 | 5 +- mlprec/impl/level/mld_d_base_onelev_cseti.F90 | 6 +- mlprec/impl/level/mld_d_base_onelev_seti.F90 | 5 +- mlprec/impl/level/mld_s_base_onelev_cseti.F90 | 6 +- mlprec/impl/level/mld_s_base_onelev_seti.F90 | 5 +- mlprec/impl/level/mld_z_base_onelev_cseti.F90 | 6 +- mlprec/impl/level/mld_z_base_onelev_seti.F90 | 5 +- mlprec/mld_c_base_aggregator_mod.f90 | 12 ++++ mlprec/mld_c_dec_aggregator_mod.f90 | 56 ++++++++++++++++++- mlprec/mld_c_inner_mod.f90 | 15 ----- mlprec/mld_d_base_aggregator_mod.f90 | 12 ++++ mlprec/mld_d_dec_aggregator_mod.f90 | 56 ++++++++++++++++++- mlprec/mld_d_inner_mod.f90 | 15 ----- mlprec/mld_s_base_aggregator_mod.f90 | 12 ++++ mlprec/mld_s_dec_aggregator_mod.f90 | 56 ++++++++++++++++++- mlprec/mld_s_inner_mod.f90 | 15 ----- mlprec/mld_z_base_aggregator_mod.f90 | 12 ++++ mlprec/mld_z_dec_aggregator_mod.f90 | 56 ++++++++++++++++++- mlprec/mld_z_inner_mod.f90 | 15 ----- 32 files changed, 296 insertions(+), 108 deletions(-) diff --git a/mlprec/impl/aggregator/mld_c_dec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_c_dec_aggregator_tprol.f90 index b9e6ae1f..f6caf655 100644 --- a/mlprec/impl/aggregator/mld_c_dec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_c_dec_aggregator_tprol.f90 @@ -110,7 +110,8 @@ subroutine mld_c_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_ call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) - call mld_c_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) +!!$ call mld_c_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then diff --git a/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 index dc993846..e6d0d75c 100644 --- a/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 @@ -70,7 +70,7 @@ subroutine mld_c_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_c_inner_mod, mld_protect_name => mld_c_hyb_map_bld + use mld_c_inner_mod!, mld_protect_name => mld_c_hyb_map_bld implicit none diff --git a/mlprec/impl/aggregator/mld_c_vmb_map_bld.f90 b/mlprec/impl/aggregator/mld_c_vmb_map_bld.f90 index 1c300ae4..4c5cf944 100644 --- a/mlprec/impl/aggregator/mld_c_vmb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_c_vmb_map_bld.f90 @@ -71,7 +71,7 @@ subroutine mld_c_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_c_inner_mod, mld_protect_name => mld_c_vmb_map_bld + use mld_c_inner_mod!, mld_protect_name => mld_c_vmb_map_bld implicit none diff --git a/mlprec/impl/aggregator/mld_d_dec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_d_dec_aggregator_tprol.f90 index b3f1d099..cd5196bc 100644 --- a/mlprec/impl/aggregator/mld_d_dec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_d_dec_aggregator_tprol.f90 @@ -110,7 +110,8 @@ subroutine mld_d_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_ call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) - call mld_d_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) +!!$ call mld_d_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then diff --git a/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 index e7bc63dc..ad73ae50 100644 --- a/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 @@ -70,7 +70,7 @@ subroutine mld_d_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_d_inner_mod, mld_protect_name => mld_d_hyb_map_bld + use mld_d_inner_mod!, mld_protect_name => mld_d_hyb_map_bld implicit none diff --git a/mlprec/impl/aggregator/mld_d_vmb_map_bld.f90 b/mlprec/impl/aggregator/mld_d_vmb_map_bld.f90 index 2b523f7c..83d22fc4 100644 --- a/mlprec/impl/aggregator/mld_d_vmb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_d_vmb_map_bld.f90 @@ -71,7 +71,7 @@ subroutine mld_d_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_d_inner_mod, mld_protect_name => mld_d_vmb_map_bld + use mld_d_inner_mod!, mld_protect_name => mld_d_vmb_map_bld implicit none diff --git a/mlprec/impl/aggregator/mld_s_dec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_s_dec_aggregator_tprol.f90 index a1a784e1..f305e2e6 100644 --- a/mlprec/impl/aggregator/mld_s_dec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_s_dec_aggregator_tprol.f90 @@ -110,7 +110,8 @@ subroutine mld_s_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_ call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) - call mld_s_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) +!!$ call mld_s_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then diff --git a/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 index 96fe92d6..04bd60ff 100644 --- a/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 @@ -70,7 +70,7 @@ subroutine mld_s_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_s_inner_mod, mld_protect_name => mld_s_hyb_map_bld + use mld_s_inner_mod!, mld_protect_name => mld_s_hyb_map_bld implicit none diff --git a/mlprec/impl/aggregator/mld_s_vmb_map_bld.f90 b/mlprec/impl/aggregator/mld_s_vmb_map_bld.f90 index b0de5055..93293632 100644 --- a/mlprec/impl/aggregator/mld_s_vmb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_s_vmb_map_bld.f90 @@ -71,7 +71,7 @@ subroutine mld_s_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_s_inner_mod, mld_protect_name => mld_s_vmb_map_bld + use mld_s_inner_mod!, mld_protect_name => mld_s_vmb_map_bld implicit none diff --git a/mlprec/impl/aggregator/mld_z_dec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_z_dec_aggregator_tprol.f90 index 2cb8d57c..a2ff5ca9 100644 --- a/mlprec/impl/aggregator/mld_z_dec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_z_dec_aggregator_tprol.f90 @@ -110,7 +110,8 @@ subroutine mld_z_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_ call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) - call mld_z_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) + call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) +!!$ call mld_z_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then diff --git a/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 index 4fc95dd3..0648421f 100644 --- a/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 @@ -70,7 +70,7 @@ subroutine mld_z_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_z_inner_mod, mld_protect_name => mld_z_hyb_map_bld + use mld_z_inner_mod!, mld_protect_name => mld_z_hyb_map_bld implicit none diff --git a/mlprec/impl/aggregator/mld_z_vmb_map_bld.f90 b/mlprec/impl/aggregator/mld_z_vmb_map_bld.f90 index ff131c33..507877fc 100644 --- a/mlprec/impl/aggregator/mld_z_vmb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_z_vmb_map_bld.f90 @@ -71,7 +71,7 @@ subroutine mld_z_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_z_inner_mod, mld_protect_name => mld_z_vmb_map_bld + use mld_z_inner_mod!, mld_protect_name => mld_z_vmb_map_bld implicit none diff --git a/mlprec/impl/level/mld_c_base_onelev_cseti.F90 b/mlprec/impl/level/mld_c_base_onelev_cseti.F90 index a2cf8bfc..b51817b3 100644 --- a/mlprec/impl/level/mld_c_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_c_base_onelev_cseti.F90 @@ -200,17 +200,17 @@ subroutine mld_c_base_onelev_cseti(lv,what,val,info,pos) allocate(mld_c_dec_aggregator_type :: lv%aggr, stat=info) case(mld_sym_dec_aggr_) allocate(mld_c_symdec_aggregator_type :: lv%aggr, stat=info) -!!$ case(mld_hybrid_aggr_) -!!$ allocate(mld_c_hybrid_aggregator_type :: lv%aggr, stat=info) case default info = psb_err_internal_error_ end select - + if (info == psb_success_) call lv%aggr%default() + case ('AGGR_ORD') lv%parms%aggr_ord = val case ('AGGR_TYPE') lv%parms%aggr_type = val + if (allocated(lv%aggr)) call lv%aggr%set_aggr_type(lv%parms,info) case ('AGGR_PROL') lv%parms%aggr_prol = val diff --git a/mlprec/impl/level/mld_c_base_onelev_seti.F90 b/mlprec/impl/level/mld_c_base_onelev_seti.F90 index 583bf2f1..534915cc 100644 --- a/mlprec/impl/level/mld_c_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_c_base_onelev_seti.F90 @@ -42,7 +42,6 @@ subroutine mld_c_base_onelev_seti(lv,what,val,info,pos) use mld_c_base_aggregator_mod use mld_c_dec_aggregator_mod use mld_c_symdec_aggregator_mod - use mld_c_hybrid_aggregator_mod use mld_c_jac_smoother use mld_c_as_smoother use mld_c_diag_solver @@ -200,17 +199,17 @@ subroutine mld_c_base_onelev_seti(lv,what,val,info,pos) allocate(mld_c_dec_aggregator_type :: lv%aggr, stat=info) case(mld_sym_dec_aggr_) allocate(mld_c_symdec_aggregator_type :: lv%aggr, stat=info) -!!$ case(mld_hybrid_aggr_) -!!$ allocate(mld_c_hybrid_aggregator_type :: lv%aggr, stat=info) case default info = psb_err_internal_error_ end select + if (info == psb_success_) call lv%aggr%default() case (mld_aggr_ord_) lv%parms%aggr_ord = val case (mld_aggr_type_) lv%parms%aggr_type = val + if (allocated(lv%aggr)) call lv%aggr%set_aggr_type(lv%parms,info) case (mld_aggr_prol_) lv%parms%aggr_prol = val diff --git a/mlprec/impl/level/mld_d_base_onelev_cseti.F90 b/mlprec/impl/level/mld_d_base_onelev_cseti.F90 index ea44e7de..25b34802 100644 --- a/mlprec/impl/level/mld_d_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_d_base_onelev_cseti.F90 @@ -220,17 +220,17 @@ subroutine mld_d_base_onelev_cseti(lv,what,val,info,pos) allocate(mld_d_dec_aggregator_type :: lv%aggr, stat=info) case(mld_sym_dec_aggr_) allocate(mld_d_symdec_aggregator_type :: lv%aggr, stat=info) -!!$ case(mld_hybrid_aggr_) -!!$ allocate(mld_d_hybrid_aggregator_type :: lv%aggr, stat=info) case default info = psb_err_internal_error_ end select - + if (info == psb_success_) call lv%aggr%default() + case ('AGGR_ORD') lv%parms%aggr_ord = val case ('AGGR_TYPE') lv%parms%aggr_type = val + if (allocated(lv%aggr)) call lv%aggr%set_aggr_type(lv%parms,info) case ('AGGR_PROL') lv%parms%aggr_prol = val diff --git a/mlprec/impl/level/mld_d_base_onelev_seti.F90 b/mlprec/impl/level/mld_d_base_onelev_seti.F90 index 82234b51..d68f2ec6 100644 --- a/mlprec/impl/level/mld_d_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_d_base_onelev_seti.F90 @@ -42,7 +42,6 @@ subroutine mld_d_base_onelev_seti(lv,what,val,info,pos) use mld_d_base_aggregator_mod use mld_d_dec_aggregator_mod use mld_d_symdec_aggregator_mod - use mld_d_hybrid_aggregator_mod use mld_d_jac_smoother use mld_d_as_smoother use mld_d_diag_solver @@ -220,17 +219,17 @@ subroutine mld_d_base_onelev_seti(lv,what,val,info,pos) allocate(mld_d_dec_aggregator_type :: lv%aggr, stat=info) case(mld_sym_dec_aggr_) allocate(mld_d_symdec_aggregator_type :: lv%aggr, stat=info) -!!$ case(mld_hybrid_aggr_) -!!$ allocate(mld_d_hybrid_aggregator_type :: lv%aggr, stat=info) case default info = psb_err_internal_error_ end select + if (info == psb_success_) call lv%aggr%default() case (mld_aggr_ord_) lv%parms%aggr_ord = val case (mld_aggr_type_) lv%parms%aggr_type = val + if (allocated(lv%aggr)) call lv%aggr%set_aggr_type(lv%parms,info) case (mld_aggr_prol_) lv%parms%aggr_prol = val diff --git a/mlprec/impl/level/mld_s_base_onelev_cseti.F90 b/mlprec/impl/level/mld_s_base_onelev_cseti.F90 index fc95bc22..12fcc41b 100644 --- a/mlprec/impl/level/mld_s_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_s_base_onelev_cseti.F90 @@ -200,17 +200,17 @@ subroutine mld_s_base_onelev_cseti(lv,what,val,info,pos) allocate(mld_s_dec_aggregator_type :: lv%aggr, stat=info) case(mld_sym_dec_aggr_) allocate(mld_s_symdec_aggregator_type :: lv%aggr, stat=info) -!!$ case(mld_hybrid_aggr_) -!!$ allocate(mld_s_hybrid_aggregator_type :: lv%aggr, stat=info) case default info = psb_err_internal_error_ end select - + if (info == psb_success_) call lv%aggr%default() + case ('AGGR_ORD') lv%parms%aggr_ord = val case ('AGGR_TYPE') lv%parms%aggr_type = val + if (allocated(lv%aggr)) call lv%aggr%set_aggr_type(lv%parms,info) case ('AGGR_PROL') lv%parms%aggr_prol = val diff --git a/mlprec/impl/level/mld_s_base_onelev_seti.F90 b/mlprec/impl/level/mld_s_base_onelev_seti.F90 index ad241194..7d12cf9b 100644 --- a/mlprec/impl/level/mld_s_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_s_base_onelev_seti.F90 @@ -42,7 +42,6 @@ subroutine mld_s_base_onelev_seti(lv,what,val,info,pos) use mld_s_base_aggregator_mod use mld_s_dec_aggregator_mod use mld_s_symdec_aggregator_mod - use mld_s_hybrid_aggregator_mod use mld_s_jac_smoother use mld_s_as_smoother use mld_s_diag_solver @@ -200,17 +199,17 @@ subroutine mld_s_base_onelev_seti(lv,what,val,info,pos) allocate(mld_s_dec_aggregator_type :: lv%aggr, stat=info) case(mld_sym_dec_aggr_) allocate(mld_s_symdec_aggregator_type :: lv%aggr, stat=info) -!!$ case(mld_hybrid_aggr_) -!!$ allocate(mld_s_hybrid_aggregator_type :: lv%aggr, stat=info) case default info = psb_err_internal_error_ end select + if (info == psb_success_) call lv%aggr%default() case (mld_aggr_ord_) lv%parms%aggr_ord = val case (mld_aggr_type_) lv%parms%aggr_type = val + if (allocated(lv%aggr)) call lv%aggr%set_aggr_type(lv%parms,info) case (mld_aggr_prol_) lv%parms%aggr_prol = val diff --git a/mlprec/impl/level/mld_z_base_onelev_cseti.F90 b/mlprec/impl/level/mld_z_base_onelev_cseti.F90 index d519e8a6..0d0c2bc0 100644 --- a/mlprec/impl/level/mld_z_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_z_base_onelev_cseti.F90 @@ -220,17 +220,17 @@ subroutine mld_z_base_onelev_cseti(lv,what,val,info,pos) allocate(mld_z_dec_aggregator_type :: lv%aggr, stat=info) case(mld_sym_dec_aggr_) allocate(mld_z_symdec_aggregator_type :: lv%aggr, stat=info) -!!$ case(mld_hybrid_aggr_) -!!$ allocate(mld_z_hybrid_aggregator_type :: lv%aggr, stat=info) case default info = psb_err_internal_error_ end select - + if (info == psb_success_) call lv%aggr%default() + case ('AGGR_ORD') lv%parms%aggr_ord = val case ('AGGR_TYPE') lv%parms%aggr_type = val + if (allocated(lv%aggr)) call lv%aggr%set_aggr_type(lv%parms,info) case ('AGGR_PROL') lv%parms%aggr_prol = val diff --git a/mlprec/impl/level/mld_z_base_onelev_seti.F90 b/mlprec/impl/level/mld_z_base_onelev_seti.F90 index 1d1505f4..bfba8765 100644 --- a/mlprec/impl/level/mld_z_base_onelev_seti.F90 +++ b/mlprec/impl/level/mld_z_base_onelev_seti.F90 @@ -42,7 +42,6 @@ subroutine mld_z_base_onelev_seti(lv,what,val,info,pos) use mld_z_base_aggregator_mod use mld_z_dec_aggregator_mod use mld_z_symdec_aggregator_mod - use mld_z_hybrid_aggregator_mod use mld_z_jac_smoother use mld_z_as_smoother use mld_z_diag_solver @@ -220,17 +219,17 @@ subroutine mld_z_base_onelev_seti(lv,what,val,info,pos) allocate(mld_z_dec_aggregator_type :: lv%aggr, stat=info) case(mld_sym_dec_aggr_) allocate(mld_z_symdec_aggregator_type :: lv%aggr, stat=info) -!!$ case(mld_hybrid_aggr_) -!!$ allocate(mld_z_hybrid_aggregator_type :: lv%aggr, stat=info) case default info = psb_err_internal_error_ end select + if (info == psb_success_) call lv%aggr%default() case (mld_aggr_ord_) lv%parms%aggr_ord = val case (mld_aggr_type_) lv%parms%aggr_type = val + if (allocated(lv%aggr)) call lv%aggr%set_aggr_type(lv%parms,info) case (mld_aggr_prol_) lv%parms%aggr_prol = val diff --git a/mlprec/mld_c_base_aggregator_mod.f90 b/mlprec/mld_c_base_aggregator_mod.f90 index 85d16d4d..b62c9af1 100644 --- a/mlprec/mld_c_base_aggregator_mod.f90 +++ b/mlprec/mld_c_base_aggregator_mod.f90 @@ -103,6 +103,7 @@ module mld_c_base_aggregator_mod procedure, pass(ag) :: free => mld_c_base_aggregator_free procedure, pass(ag) :: default => mld_c_base_aggregator_default procedure, pass(ag) :: descr => mld_c_base_aggregator_descr + procedure, pass(ag) :: set_aggr_type => mld_c_base_aggregator_set_aggr_type procedure, nopass :: fmt => mld_c_base_aggregator_fmt end type mld_c_base_aggregator_type @@ -173,6 +174,17 @@ contains return end subroutine mld_c_base_aggregator_descr + subroutine mld_c_base_aggregator_set_aggr_type(ag,parms,info) + implicit none + class(mld_c_base_aggregator_type), intent(inout) :: ag + type(mld_sml_parms), intent(in) :: parms + integer(psb_ipk_), intent(out) :: info + + ! Do nothing + + return + end subroutine mld_c_base_aggregator_set_aggr_type + subroutine mld_c_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod implicit none diff --git a/mlprec/mld_c_dec_aggregator_mod.f90 b/mlprec/mld_c_dec_aggregator_mod.f90 index 4548b4b0..ecf6f43c 100644 --- a/mlprec/mld_c_dec_aggregator_mod.f90 +++ b/mlprec/mld_c_dec_aggregator_mod.f90 @@ -90,14 +90,32 @@ module mld_c_dec_aggregator_mod ! ! type, extends(mld_c_base_aggregator_type) :: mld_c_dec_aggregator_type + procedure(mld_c_map_bld), nopass, pointer :: map_bld => null() contains - procedure, pass(ag) :: bld_tprol => mld_c_dec_aggregator_build_tprol - procedure, pass(ag) :: mat_asb => mld_c_dec_aggregator_mat_asb - procedure, nopass :: fmt => mld_c_dec_aggregator_fmt + procedure, pass(ag) :: bld_tprol => mld_c_dec_aggregator_build_tprol + procedure, pass(ag) :: mat_asb => mld_c_dec_aggregator_mat_asb + procedure, pass(ag) :: default => mld_c_dec_aggregator_default + procedure, pass(ag) :: set_aggr_type => mld_c_dec_aggregator_set_aggr_type + procedure, nopass :: fmt => mld_c_dec_aggregator_fmt end type mld_c_dec_aggregator_type + abstract interface + subroutine mld_c_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + import :: psb_cspmat_type, psb_desc_type, psb_spk_, psb_ipk_ + implicit none + integer(psb_ipk_), intent(in) :: iorder + type(psb_cspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + real(psb_spk_), intent(in) :: theta + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + integer(psb_ipk_), intent(out) :: info + end subroutine mld_c_map_bld + end interface + + procedure(mld_c_map_bld) :: mld_c_vmb_map_bld, mld_c_hyb_map_bld + interface subroutine mld_c_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) import :: mld_c_dec_aggregator_type, psb_desc_type, psb_cspmat_type, psb_spk_, & @@ -133,6 +151,38 @@ module mld_c_dec_aggregator_mod contains + subroutine mld_c_dec_aggregator_set_aggr_type(ag,parms,info) + use mld_base_prec_type + implicit none + class(mld_c_dec_aggregator_type), intent(inout) :: ag + type(mld_sml_parms), intent(in) :: parms + integer(psb_ipk_), intent(out) :: info + + select case(parms%aggr_type) + case (mld_noalg_) + ag%map_bld => null() + case (mld_vmb_) + ag%map_bld => mld_c_vmb_map_bld + case (mld_hyb_) + ag%map_bld => mld_c_hyb_map_bld + case default + write(0,*) 'Unknown aggregation type, defaulting to VMB' + ag%map_bld => mld_c_vmb_map_bld + end select + + return + end subroutine mld_c_dec_aggregator_set_aggr_type + + + subroutine mld_c_dec_aggregator_default(ag) + implicit none + class(mld_c_dec_aggregator_type), intent(inout) :: ag + + ag%map_bld => mld_c_vmb_map_bld + + return + end subroutine mld_c_dec_aggregator_default + function mld_c_dec_aggregator_fmt() result(val) implicit none character(len=32) :: val diff --git a/mlprec/mld_c_inner_mod.f90 b/mlprec/mld_c_inner_mod.f90 index d84296d4..46b74f36 100644 --- a/mlprec/mld_c_inner_mod.f90 +++ b/mlprec/mld_c_inner_mod.f90 @@ -122,21 +122,6 @@ module mld_c_inner_mod integer(psb_ipk_), intent(out) :: info end subroutine mld_caggrmap_bld end interface mld_aggrmap_bld - - abstract interface - subroutine mld_c_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) - import :: psb_cspmat_type, psb_desc_type, psb_spk_, psb_ipk_ - implicit none - integer(psb_ipk_), intent(in) :: iorder - type(psb_cspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - real(psb_spk_), intent(in) :: theta - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - integer(psb_ipk_), intent(out) :: info - end subroutine mld_c_map_bld - end interface - - procedure(mld_c_map_bld) :: mld_c_vmb_map_bld, mld_c_hyb_map_bld interface mld_map_to_tprol subroutine mld_c_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) diff --git a/mlprec/mld_d_base_aggregator_mod.f90 b/mlprec/mld_d_base_aggregator_mod.f90 index f89b636a..515d64c7 100644 --- a/mlprec/mld_d_base_aggregator_mod.f90 +++ b/mlprec/mld_d_base_aggregator_mod.f90 @@ -103,6 +103,7 @@ module mld_d_base_aggregator_mod procedure, pass(ag) :: free => mld_d_base_aggregator_free procedure, pass(ag) :: default => mld_d_base_aggregator_default procedure, pass(ag) :: descr => mld_d_base_aggregator_descr + procedure, pass(ag) :: set_aggr_type => mld_d_base_aggregator_set_aggr_type procedure, nopass :: fmt => mld_d_base_aggregator_fmt end type mld_d_base_aggregator_type @@ -173,6 +174,17 @@ contains return end subroutine mld_d_base_aggregator_descr + subroutine mld_d_base_aggregator_set_aggr_type(ag,parms,info) + implicit none + class(mld_d_base_aggregator_type), intent(inout) :: ag + type(mld_dml_parms), intent(in) :: parms + integer(psb_ipk_), intent(out) :: info + + ! Do nothing + + return + end subroutine mld_d_base_aggregator_set_aggr_type + subroutine mld_d_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod implicit none diff --git a/mlprec/mld_d_dec_aggregator_mod.f90 b/mlprec/mld_d_dec_aggregator_mod.f90 index 4ddb8f5a..3a64e30f 100644 --- a/mlprec/mld_d_dec_aggregator_mod.f90 +++ b/mlprec/mld_d_dec_aggregator_mod.f90 @@ -90,14 +90,32 @@ module mld_d_dec_aggregator_mod ! ! type, extends(mld_d_base_aggregator_type) :: mld_d_dec_aggregator_type + procedure(mld_d_map_bld), nopass, pointer :: map_bld => null() contains - procedure, pass(ag) :: bld_tprol => mld_d_dec_aggregator_build_tprol - procedure, pass(ag) :: mat_asb => mld_d_dec_aggregator_mat_asb - procedure, nopass :: fmt => mld_d_dec_aggregator_fmt + procedure, pass(ag) :: bld_tprol => mld_d_dec_aggregator_build_tprol + procedure, pass(ag) :: mat_asb => mld_d_dec_aggregator_mat_asb + procedure, pass(ag) :: default => mld_d_dec_aggregator_default + procedure, pass(ag) :: set_aggr_type => mld_d_dec_aggregator_set_aggr_type + procedure, nopass :: fmt => mld_d_dec_aggregator_fmt end type mld_d_dec_aggregator_type + abstract interface + subroutine mld_d_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + import :: psb_dspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ + implicit none + integer(psb_ipk_), intent(in) :: iorder + type(psb_dspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + real(psb_dpk_), intent(in) :: theta + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + integer(psb_ipk_), intent(out) :: info + end subroutine mld_d_map_bld + end interface + + procedure(mld_d_map_bld) :: mld_d_vmb_map_bld, mld_d_hyb_map_bld + interface subroutine mld_d_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) import :: mld_d_dec_aggregator_type, psb_desc_type, psb_dspmat_type, psb_dpk_, & @@ -133,6 +151,38 @@ module mld_d_dec_aggregator_mod contains + subroutine mld_d_dec_aggregator_set_aggr_type(ag,parms,info) + use mld_base_prec_type + implicit none + class(mld_d_dec_aggregator_type), intent(inout) :: ag + type(mld_dml_parms), intent(in) :: parms + integer(psb_ipk_), intent(out) :: info + + select case(parms%aggr_type) + case (mld_noalg_) + ag%map_bld => null() + case (mld_vmb_) + ag%map_bld => mld_d_vmb_map_bld + case (mld_hyb_) + ag%map_bld => mld_d_hyb_map_bld + case default + write(0,*) 'Unknown aggregation type, defaulting to VMB' + ag%map_bld => mld_d_vmb_map_bld + end select + + return + end subroutine mld_d_dec_aggregator_set_aggr_type + + + subroutine mld_d_dec_aggregator_default(ag) + implicit none + class(mld_d_dec_aggregator_type), intent(inout) :: ag + + ag%map_bld => mld_d_vmb_map_bld + + return + end subroutine mld_d_dec_aggregator_default + function mld_d_dec_aggregator_fmt() result(val) implicit none character(len=32) :: val diff --git a/mlprec/mld_d_inner_mod.f90 b/mlprec/mld_d_inner_mod.f90 index 9b33e872..81cb1ee2 100644 --- a/mlprec/mld_d_inner_mod.f90 +++ b/mlprec/mld_d_inner_mod.f90 @@ -122,21 +122,6 @@ module mld_d_inner_mod integer(psb_ipk_), intent(out) :: info end subroutine mld_daggrmap_bld end interface mld_aggrmap_bld - - abstract interface - subroutine mld_d_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) - import :: psb_dspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ - implicit none - integer(psb_ipk_), intent(in) :: iorder - type(psb_dspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - real(psb_dpk_), intent(in) :: theta - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - integer(psb_ipk_), intent(out) :: info - end subroutine mld_d_map_bld - end interface - - procedure(mld_d_map_bld) :: mld_d_vmb_map_bld, mld_d_hyb_map_bld interface mld_map_to_tprol subroutine mld_d_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) diff --git a/mlprec/mld_s_base_aggregator_mod.f90 b/mlprec/mld_s_base_aggregator_mod.f90 index 6128df62..f668023a 100644 --- a/mlprec/mld_s_base_aggregator_mod.f90 +++ b/mlprec/mld_s_base_aggregator_mod.f90 @@ -103,6 +103,7 @@ module mld_s_base_aggregator_mod procedure, pass(ag) :: free => mld_s_base_aggregator_free procedure, pass(ag) :: default => mld_s_base_aggregator_default procedure, pass(ag) :: descr => mld_s_base_aggregator_descr + procedure, pass(ag) :: set_aggr_type => mld_s_base_aggregator_set_aggr_type procedure, nopass :: fmt => mld_s_base_aggregator_fmt end type mld_s_base_aggregator_type @@ -173,6 +174,17 @@ contains return end subroutine mld_s_base_aggregator_descr + subroutine mld_s_base_aggregator_set_aggr_type(ag,parms,info) + implicit none + class(mld_s_base_aggregator_type), intent(inout) :: ag + type(mld_sml_parms), intent(in) :: parms + integer(psb_ipk_), intent(out) :: info + + ! Do nothing + + return + end subroutine mld_s_base_aggregator_set_aggr_type + subroutine mld_s_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod implicit none diff --git a/mlprec/mld_s_dec_aggregator_mod.f90 b/mlprec/mld_s_dec_aggregator_mod.f90 index 76604cbf..67a2618a 100644 --- a/mlprec/mld_s_dec_aggregator_mod.f90 +++ b/mlprec/mld_s_dec_aggregator_mod.f90 @@ -90,14 +90,32 @@ module mld_s_dec_aggregator_mod ! ! type, extends(mld_s_base_aggregator_type) :: mld_s_dec_aggregator_type + procedure(mld_s_map_bld), nopass, pointer :: map_bld => null() contains - procedure, pass(ag) :: bld_tprol => mld_s_dec_aggregator_build_tprol - procedure, pass(ag) :: mat_asb => mld_s_dec_aggregator_mat_asb - procedure, nopass :: fmt => mld_s_dec_aggregator_fmt + procedure, pass(ag) :: bld_tprol => mld_s_dec_aggregator_build_tprol + procedure, pass(ag) :: mat_asb => mld_s_dec_aggregator_mat_asb + procedure, pass(ag) :: default => mld_s_dec_aggregator_default + procedure, pass(ag) :: set_aggr_type => mld_s_dec_aggregator_set_aggr_type + procedure, nopass :: fmt => mld_s_dec_aggregator_fmt end type mld_s_dec_aggregator_type + abstract interface + subroutine mld_s_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + import :: psb_sspmat_type, psb_desc_type, psb_spk_, psb_ipk_ + implicit none + integer(psb_ipk_), intent(in) :: iorder + type(psb_sspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + real(psb_spk_), intent(in) :: theta + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + integer(psb_ipk_), intent(out) :: info + end subroutine mld_s_map_bld + end interface + + procedure(mld_s_map_bld) :: mld_s_vmb_map_bld, mld_s_hyb_map_bld + interface subroutine mld_s_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) import :: mld_s_dec_aggregator_type, psb_desc_type, psb_sspmat_type, psb_spk_, & @@ -133,6 +151,38 @@ module mld_s_dec_aggregator_mod contains + subroutine mld_s_dec_aggregator_set_aggr_type(ag,parms,info) + use mld_base_prec_type + implicit none + class(mld_s_dec_aggregator_type), intent(inout) :: ag + type(mld_sml_parms), intent(in) :: parms + integer(psb_ipk_), intent(out) :: info + + select case(parms%aggr_type) + case (mld_noalg_) + ag%map_bld => null() + case (mld_vmb_) + ag%map_bld => mld_s_vmb_map_bld + case (mld_hyb_) + ag%map_bld => mld_s_hyb_map_bld + case default + write(0,*) 'Unknown aggregation type, defaulting to VMB' + ag%map_bld => mld_s_vmb_map_bld + end select + + return + end subroutine mld_s_dec_aggregator_set_aggr_type + + + subroutine mld_s_dec_aggregator_default(ag) + implicit none + class(mld_s_dec_aggregator_type), intent(inout) :: ag + + ag%map_bld => mld_s_vmb_map_bld + + return + end subroutine mld_s_dec_aggregator_default + function mld_s_dec_aggregator_fmt() result(val) implicit none character(len=32) :: val diff --git a/mlprec/mld_s_inner_mod.f90 b/mlprec/mld_s_inner_mod.f90 index 3793d055..55bd0ad0 100644 --- a/mlprec/mld_s_inner_mod.f90 +++ b/mlprec/mld_s_inner_mod.f90 @@ -122,21 +122,6 @@ module mld_s_inner_mod integer(psb_ipk_), intent(out) :: info end subroutine mld_saggrmap_bld end interface mld_aggrmap_bld - - abstract interface - subroutine mld_s_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) - import :: psb_sspmat_type, psb_desc_type, psb_spk_, psb_ipk_ - implicit none - integer(psb_ipk_), intent(in) :: iorder - type(psb_sspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - real(psb_spk_), intent(in) :: theta - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - integer(psb_ipk_), intent(out) :: info - end subroutine mld_s_map_bld - end interface - - procedure(mld_s_map_bld) :: mld_s_vmb_map_bld, mld_s_hyb_map_bld interface mld_map_to_tprol subroutine mld_s_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) diff --git a/mlprec/mld_z_base_aggregator_mod.f90 b/mlprec/mld_z_base_aggregator_mod.f90 index e76f4561..660bc415 100644 --- a/mlprec/mld_z_base_aggregator_mod.f90 +++ b/mlprec/mld_z_base_aggregator_mod.f90 @@ -103,6 +103,7 @@ module mld_z_base_aggregator_mod procedure, pass(ag) :: free => mld_z_base_aggregator_free procedure, pass(ag) :: default => mld_z_base_aggregator_default procedure, pass(ag) :: descr => mld_z_base_aggregator_descr + procedure, pass(ag) :: set_aggr_type => mld_z_base_aggregator_set_aggr_type procedure, nopass :: fmt => mld_z_base_aggregator_fmt end type mld_z_base_aggregator_type @@ -173,6 +174,17 @@ contains return end subroutine mld_z_base_aggregator_descr + subroutine mld_z_base_aggregator_set_aggr_type(ag,parms,info) + implicit none + class(mld_z_base_aggregator_type), intent(inout) :: ag + type(mld_dml_parms), intent(in) :: parms + integer(psb_ipk_), intent(out) :: info + + ! Do nothing + + return + end subroutine mld_z_base_aggregator_set_aggr_type + subroutine mld_z_base_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) use psb_base_mod implicit none diff --git a/mlprec/mld_z_dec_aggregator_mod.f90 b/mlprec/mld_z_dec_aggregator_mod.f90 index 391ec596..1ed1fa4f 100644 --- a/mlprec/mld_z_dec_aggregator_mod.f90 +++ b/mlprec/mld_z_dec_aggregator_mod.f90 @@ -90,14 +90,32 @@ module mld_z_dec_aggregator_mod ! ! type, extends(mld_z_base_aggregator_type) :: mld_z_dec_aggregator_type + procedure(mld_z_map_bld), nopass, pointer :: map_bld => null() contains - procedure, pass(ag) :: bld_tprol => mld_z_dec_aggregator_build_tprol - procedure, pass(ag) :: mat_asb => mld_z_dec_aggregator_mat_asb - procedure, nopass :: fmt => mld_z_dec_aggregator_fmt + procedure, pass(ag) :: bld_tprol => mld_z_dec_aggregator_build_tprol + procedure, pass(ag) :: mat_asb => mld_z_dec_aggregator_mat_asb + procedure, pass(ag) :: default => mld_z_dec_aggregator_default + procedure, pass(ag) :: set_aggr_type => mld_z_dec_aggregator_set_aggr_type + procedure, nopass :: fmt => mld_z_dec_aggregator_fmt end type mld_z_dec_aggregator_type + abstract interface + subroutine mld_z_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) + import :: psb_zspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ + implicit none + integer(psb_ipk_), intent(in) :: iorder + type(psb_zspmat_type), intent(in) :: a + type(psb_desc_type), intent(in) :: desc_a + real(psb_dpk_), intent(in) :: theta + integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) + integer(psb_ipk_), intent(out) :: info + end subroutine mld_z_map_bld + end interface + + procedure(mld_z_map_bld) :: mld_z_vmb_map_bld, mld_z_hyb_map_bld + interface subroutine mld_z_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) import :: mld_z_dec_aggregator_type, psb_desc_type, psb_zspmat_type, psb_dpk_, & @@ -133,6 +151,38 @@ module mld_z_dec_aggregator_mod contains + subroutine mld_z_dec_aggregator_set_aggr_type(ag,parms,info) + use mld_base_prec_type + implicit none + class(mld_z_dec_aggregator_type), intent(inout) :: ag + type(mld_dml_parms), intent(in) :: parms + integer(psb_ipk_), intent(out) :: info + + select case(parms%aggr_type) + case (mld_noalg_) + ag%map_bld => null() + case (mld_vmb_) + ag%map_bld => mld_z_vmb_map_bld + case (mld_hyb_) + ag%map_bld => mld_z_hyb_map_bld + case default + write(0,*) 'Unknown aggregation type, defaulting to VMB' + ag%map_bld => mld_z_vmb_map_bld + end select + + return + end subroutine mld_z_dec_aggregator_set_aggr_type + + + subroutine mld_z_dec_aggregator_default(ag) + implicit none + class(mld_z_dec_aggregator_type), intent(inout) :: ag + + ag%map_bld => mld_z_vmb_map_bld + + return + end subroutine mld_z_dec_aggregator_default + function mld_z_dec_aggregator_fmt() result(val) implicit none character(len=32) :: val diff --git a/mlprec/mld_z_inner_mod.f90 b/mlprec/mld_z_inner_mod.f90 index 461de81d..04c41c4f 100644 --- a/mlprec/mld_z_inner_mod.f90 +++ b/mlprec/mld_z_inner_mod.f90 @@ -122,21 +122,6 @@ module mld_z_inner_mod integer(psb_ipk_), intent(out) :: info end subroutine mld_zaggrmap_bld end interface mld_aggrmap_bld - - abstract interface - subroutine mld_z_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) - import :: psb_zspmat_type, psb_desc_type, psb_dpk_, psb_ipk_ - implicit none - integer(psb_ipk_), intent(in) :: iorder - type(psb_zspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - real(psb_dpk_), intent(in) :: theta - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - integer(psb_ipk_), intent(out) :: info - end subroutine mld_z_map_bld - end interface - - procedure(mld_z_map_bld) :: mld_z_vmb_map_bld, mld_z_hyb_map_bld interface mld_map_to_tprol subroutine mld_z_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) From a2a843ce0b16a8ce9d93bc5564a9c91397682115 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 11 May 2018 13:42:50 +0100 Subject: [PATCH 25/33] Take out hybrid_aggregator for the time being. --- mlprec/Makefile | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/mlprec/Makefile b/mlprec/Makefile index 134d26e7..2366ca15 100644 --- a/mlprec/Makefile +++ b/mlprec/Makefile @@ -100,19 +100,19 @@ mld_z_onelev_mod.o: mld_z_base_smoother_mod.o mld_z_dec_aggregator_mod.o mld_s_base_aggregator_mod.o: mld_base_prec_type.o mld_s_dec_aggregator_mod.o: mld_s_base_aggregator_mod.o -mld_s_hybrid_aggregator_mod.o mld_s_symdec_aggregator_mod.o: mld_s_dec_aggregator_mod.o +mld_s_symdec_aggregator_mod.o: mld_s_dec_aggregator_mod.o mld_d_base_aggregator_mod.o: mld_base_prec_type.o mld_d_dec_aggregator_mod.o: mld_d_base_aggregator_mod.o -mld_d_hybrid_aggregator_mod.o mld_d_symdec_aggregator_mod.o: mld_d_dec_aggregator_mod.o +mld_d_symdec_aggregator_mod.o: mld_d_dec_aggregator_mod.o mld_c_base_aggregator_mod.o: mld_base_prec_type.o mld_c_dec_aggregator_mod.o: mld_c_base_aggregator_mod.o -mld_c_hybrid_aggregator_mod.o mld_c_symdec_aggregator_mod.o: mld_c_dec_aggregator_mod.o +mld_c_symdec_aggregator_mod.o: mld_c_dec_aggregator_mod.o mld_z_base_aggregator_mod.o: mld_base_prec_type.o mld_z_dec_aggregator_mod.o: mld_z_base_aggregator_mod.o -mld_z_hybrid_aggregator_mod.o mld_z_symdec_aggregator_mod.o: mld_z_dec_aggregator_mod.o +mld_z_symdec_aggregator_mod.o: mld_z_dec_aggregator_mod.o mld_s_base_smoother_mod.o: mld_s_base_solver_mod.o mld_d_base_smoother_mod.o: mld_d_base_solver_mod.o From 0b371bf7e2c57deb4f8abe815e60c7672613893b Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 11 May 2018 13:45:04 +0100 Subject: [PATCH 26/33] Take out hybrid --- mlprec/Makefile | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) diff --git a/mlprec/Makefile b/mlprec/Makefile index 2366ca15..e9870075 100644 --- a/mlprec/Makefile +++ b/mlprec/Makefile @@ -12,7 +12,7 @@ DMODOBJS=mld_d_prec_type.o mld_d_ilu_fact_mod.o \ mld_d_umf_solver.o mld_d_slu_solver.o mld_d_sludist_solver.o mld_d_id_solver.o\ mld_d_base_solver_mod.o mld_d_base_smoother_mod.o mld_d_onelev_mod.o \ mld_d_gs_solver.o mld_d_mumps_solver.o \ - mld_d_base_aggregator_mod.o mld_d_hybrid_aggregator_mod.o \ + mld_d_base_aggregator_mod.o \ mld_d_dec_aggregator_mod.o mld_d_symdec_aggregator_mod.o #mld_d_bcmatch_aggregator_mod.o @@ -21,7 +21,7 @@ SMODOBJS=mld_s_prec_type.o mld_s_ilu_fact_mod.o \ mld_s_slu_solver.o mld_s_id_solver.o\ mld_s_base_solver_mod.o mld_s_base_smoother_mod.o mld_s_onelev_mod.o \ mld_s_gs_solver.o mld_s_mumps_solver.o \ - mld_s_base_aggregator_mod.o mld_s_hybrid_aggregator_mod.o \ + mld_s_base_aggregator_mod.o \ mld_s_dec_aggregator_mod.o mld_s_symdec_aggregator_mod.o ZMODOBJS=mld_z_prec_type.o mld_z_ilu_fact_mod.o \ @@ -29,7 +29,7 @@ ZMODOBJS=mld_z_prec_type.o mld_z_ilu_fact_mod.o \ mld_z_umf_solver.o mld_z_slu_solver.o mld_z_sludist_solver.o mld_z_id_solver.o\ mld_z_base_solver_mod.o mld_z_base_smoother_mod.o mld_z_onelev_mod.o \ mld_z_gs_solver.o mld_z_mumps_solver.o \ - mld_z_base_aggregator_mod.o mld_z_hybrid_aggregator_mod.o \ + mld_z_base_aggregator_mod.o \ mld_z_dec_aggregator_mod.o mld_z_symdec_aggregator_mod.o CMODOBJS=mld_c_prec_type.o mld_c_ilu_fact_mod.o \ @@ -37,7 +37,7 @@ CMODOBJS=mld_c_prec_type.o mld_c_ilu_fact_mod.o \ mld_c_slu_solver.o mld_c_id_solver.o\ mld_c_base_solver_mod.o mld_c_base_smoother_mod.o mld_c_onelev_mod.o \ mld_c_gs_solver.o mld_c_mumps_solver.o \ - mld_c_base_aggregator_mod.o mld_c_hybrid_aggregator_mod.o \ + mld_c_base_aggregator_mod.o \ mld_c_dec_aggregator_mod.o mld_c_symdec_aggregator_mod.o @@ -100,19 +100,19 @@ mld_z_onelev_mod.o: mld_z_base_smoother_mod.o mld_z_dec_aggregator_mod.o mld_s_base_aggregator_mod.o: mld_base_prec_type.o mld_s_dec_aggregator_mod.o: mld_s_base_aggregator_mod.o -mld_s_symdec_aggregator_mod.o: mld_s_dec_aggregator_mod.o +mld_s_hybrid_aggregator_mod.o mld_s_symdec_aggregator_mod.o: mld_s_dec_aggregator_mod.o mld_d_base_aggregator_mod.o: mld_base_prec_type.o mld_d_dec_aggregator_mod.o: mld_d_base_aggregator_mod.o -mld_d_symdec_aggregator_mod.o: mld_d_dec_aggregator_mod.o +mld_d_hybrid_aggregator_mod.o mld_d_symdec_aggregator_mod.o: mld_d_dec_aggregator_mod.o mld_c_base_aggregator_mod.o: mld_base_prec_type.o mld_c_dec_aggregator_mod.o: mld_c_base_aggregator_mod.o -mld_c_symdec_aggregator_mod.o: mld_c_dec_aggregator_mod.o +mld_c_hybrid_aggregator_mod.o mld_c_symdec_aggregator_mod.o: mld_c_dec_aggregator_mod.o mld_z_base_aggregator_mod.o: mld_base_prec_type.o mld_z_dec_aggregator_mod.o: mld_z_base_aggregator_mod.o -mld_z_symdec_aggregator_mod.o: mld_z_dec_aggregator_mod.o +mld_z_hybrid_aggregator_mod.o mld_z_symdec_aggregator_mod.o: mld_z_dec_aggregator_mod.o mld_s_base_smoother_mod.o: mld_s_base_solver_mod.o mld_d_base_smoother_mod.o: mld_d_base_solver_mod.o From e58eab504ea2c76d633d9476fa99908d2fbc42d0 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 11 May 2018 14:12:25 +0100 Subject: [PATCH 27/33] Take out hybrid from internal makefiles. --- mlprec/impl/aggregator/Makefile | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/mlprec/impl/aggregator/Makefile b/mlprec/impl/aggregator/Makefile index 56f21c72..9ff4f87b 100644 --- a/mlprec/impl/aggregator/Makefile +++ b/mlprec/impl/aggregator/Makefile @@ -11,33 +11,34 @@ FINCLUDES=$(FMFLAG)$(HERE) $(FMFLAG)$(MODDIR) $(FMFLAG)$(INCDIR) $(PSBLAS_INCLUD OBJS= \ mld_s_dec_aggregator_mat_asb.o \ mld_s_dec_aggregator_tprol.o \ -mld_s_hybrid_aggregator_tprol.o \ mld_s_symdec_aggregator_tprol.o \ mld_s_map_to_tprol.o mld_s_vmb_map_bld.o mld_s_hyb_map_bld.o\ mld_saggrmat_biz_asb.o mld_saggrmat_minnrg_asb.o\ mld_saggrmat_nosmth_asb.o mld_saggrmat_smth_asb.o \ mld_d_dec_aggregator_mat_asb.o \ mld_d_dec_aggregator_tprol.o \ -mld_d_hybrid_aggregator_tprol.o \ mld_d_symdec_aggregator_tprol.o \ mld_d_map_to_tprol.o mld_d_vmb_map_bld.o mld_d_hyb_map_bld.o\ mld_daggrmat_biz_asb.o mld_daggrmat_minnrg_asb.o\ mld_daggrmat_nosmth_asb.o mld_daggrmat_smth_asb.o \ mld_c_dec_aggregator_mat_asb.o \ mld_c_dec_aggregator_tprol.o \ -mld_c_hybrid_aggregator_tprol.o \ mld_c_symdec_aggregator_tprol.o \ mld_c_map_to_tprol.o mld_c_vmb_map_bld.o mld_c_hyb_map_bld.o\ mld_caggrmat_biz_asb.o mld_caggrmat_minnrg_asb.o\ mld_caggrmat_nosmth_asb.o mld_caggrmat_smth_asb.o \ mld_z_dec_aggregator_mat_asb.o \ mld_z_dec_aggregator_tprol.o \ -mld_z_hybrid_aggregator_tprol.o \ mld_z_symdec_aggregator_tprol.o \ mld_z_map_to_tprol.o mld_z_vmb_map_bld.o mld_z_hyb_map_bld.o\ mld_zaggrmat_biz_asb.o mld_zaggrmat_minnrg_asb.o\ mld_zaggrmat_nosmth_asb.o mld_zaggrmat_smth_asb.o +#mld_s_hybrid_aggregator_tprol.o \ +#mld_d_hybrid_aggregator_tprol.o \ +#mld_c_hybrid_aggregator_tprol.o \ +#mld_z_hybrid_aggregator_tprol.o \ + #bootCMatch_interface.o mld_d_bcmatch_aggregator_tprol.o\ #mld_d_bcmatch_map_to_tprol.o mld_d_bcmatch_aggregator_mat_asb.o \ From 13f0954caba44a5865a694e8a4c6c4e0fc9e51ad Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 11 May 2018 14:32:48 +0100 Subject: [PATCH 28/33] Fixed hybrid map bld. --- mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 | 21 +++++++++++--------- mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 | 21 +++++++++++--------- mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 | 21 +++++++++++--------- mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 | 21 +++++++++++--------- 4 files changed, 48 insertions(+), 36 deletions(-) diff --git a/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 index e6d0d75c..d7dbe2b8 100644 --- a/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 @@ -86,7 +86,7 @@ subroutine mld_c_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) integer(psb_ipk_), allocatable :: ils(:), neigh(:), irow(:), icol(:),& & ideg(:), idxs(:), tmpaggr(:) complex(psb_spk_), allocatable :: val(:), diag(:) - integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m, nz, ilg, ii, ip, ip1,nzcnt + integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr,nc,naggr,i,j,m, nz, ilg, ii, ip, ip1,nzcnt type(psb_c_csr_sparse_mat) :: acsr, muij, s_neigh type(psb_c_coo_sparse_mat) :: s_neigh_coo real(psb_spk_) :: cpling, tcl @@ -109,6 +109,7 @@ subroutine mld_c_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) ncol = desc_a%get_local_cols() nr = a%get_nrows() + nc = a%get_ncols() allocate(ilaggr(nr),neigh(nr),ideg(nr),idxs(nr),icol(nr),stat=info) if(info /= psb_success_) then info=psb_err_alloc_request_ @@ -131,7 +132,7 @@ subroutine mld_c_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) do i=1, nr do k=muij%irp(i),muij%irp(i+1)-1 j = muij%ja(k) - muij%val(k) = abs(muij%val(k))/sqrt(abs(diag(i)*diag(j))) + if (j<= nr) muij%val(k) = abs(muij%val(k))/sqrt(abs(diag(i)*diag(j))) end do end do !write(*,*) 'murows/cols ',maxval(mu_rows),maxval(mu_cols) @@ -143,13 +144,15 @@ subroutine mld_c_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) do i=1, nr do k=muij%irp(i),muij%irp(i+1)-1 j = muij%ja(k) - ip = ip + 1 - s_neigh_coo%ia(ip) = i - s_neigh_coo%ja(ip) = j - if (real(muij%val(k)) >= theta) then - s_neigh_coo%val(ip) = sone - else - s_neigh_coo%val(ip) = -sone + if (j<=nr) then + ip = ip + 1 + s_neigh_coo%ia(ip) = i + s_neigh_coo%ja(ip) = j + if (real(muij%val(k)) >= theta) then + s_neigh_coo%val(ip) = sone + else + s_neigh_coo%val(ip) = -sone + end if end if end do end do diff --git a/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 index ad73ae50..1af79aa1 100644 --- a/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 @@ -86,7 +86,7 @@ subroutine mld_d_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) integer(psb_ipk_), allocatable :: ils(:), neigh(:), irow(:), icol(:),& & ideg(:), idxs(:), tmpaggr(:) real(psb_dpk_), allocatable :: val(:), diag(:) - integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m, nz, ilg, ii, ip, ip1,nzcnt + integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr,nc,naggr,i,j,m, nz, ilg, ii, ip, ip1,nzcnt type(psb_d_csr_sparse_mat) :: acsr, muij, s_neigh type(psb_d_coo_sparse_mat) :: s_neigh_coo real(psb_dpk_) :: cpling, tcl @@ -109,6 +109,7 @@ subroutine mld_d_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) ncol = desc_a%get_local_cols() nr = a%get_nrows() + nc = a%get_ncols() allocate(ilaggr(nr),neigh(nr),ideg(nr),idxs(nr),icol(nr),stat=info) if(info /= psb_success_) then info=psb_err_alloc_request_ @@ -131,7 +132,7 @@ subroutine mld_d_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) do i=1, nr do k=muij%irp(i),muij%irp(i+1)-1 j = muij%ja(k) - muij%val(k) = abs(muij%val(k))/sqrt(abs(diag(i)*diag(j))) + if (j<= nr) muij%val(k) = abs(muij%val(k))/sqrt(abs(diag(i)*diag(j))) end do end do !write(*,*) 'murows/cols ',maxval(mu_rows),maxval(mu_cols) @@ -143,13 +144,15 @@ subroutine mld_d_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) do i=1, nr do k=muij%irp(i),muij%irp(i+1)-1 j = muij%ja(k) - ip = ip + 1 - s_neigh_coo%ia(ip) = i - s_neigh_coo%ja(ip) = j - if (real(muij%val(k)) >= theta) then - s_neigh_coo%val(ip) = done - else - s_neigh_coo%val(ip) = -done + if (j<=nr) then + ip = ip + 1 + s_neigh_coo%ia(ip) = i + s_neigh_coo%ja(ip) = j + if (real(muij%val(k)) >= theta) then + s_neigh_coo%val(ip) = done + else + s_neigh_coo%val(ip) = -done + end if end if end do end do diff --git a/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 index 04bd60ff..ec70c6ce 100644 --- a/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 @@ -86,7 +86,7 @@ subroutine mld_s_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) integer(psb_ipk_), allocatable :: ils(:), neigh(:), irow(:), icol(:),& & ideg(:), idxs(:), tmpaggr(:) real(psb_spk_), allocatable :: val(:), diag(:) - integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m, nz, ilg, ii, ip, ip1,nzcnt + integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr,nc,naggr,i,j,m, nz, ilg, ii, ip, ip1,nzcnt type(psb_s_csr_sparse_mat) :: acsr, muij, s_neigh type(psb_s_coo_sparse_mat) :: s_neigh_coo real(psb_spk_) :: cpling, tcl @@ -109,6 +109,7 @@ subroutine mld_s_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) ncol = desc_a%get_local_cols() nr = a%get_nrows() + nc = a%get_ncols() allocate(ilaggr(nr),neigh(nr),ideg(nr),idxs(nr),icol(nr),stat=info) if(info /= psb_success_) then info=psb_err_alloc_request_ @@ -131,7 +132,7 @@ subroutine mld_s_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) do i=1, nr do k=muij%irp(i),muij%irp(i+1)-1 j = muij%ja(k) - muij%val(k) = abs(muij%val(k))/sqrt(abs(diag(i)*diag(j))) + if (j<= nr) muij%val(k) = abs(muij%val(k))/sqrt(abs(diag(i)*diag(j))) end do end do !write(*,*) 'murows/cols ',maxval(mu_rows),maxval(mu_cols) @@ -143,13 +144,15 @@ subroutine mld_s_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) do i=1, nr do k=muij%irp(i),muij%irp(i+1)-1 j = muij%ja(k) - ip = ip + 1 - s_neigh_coo%ia(ip) = i - s_neigh_coo%ja(ip) = j - if (real(muij%val(k)) >= theta) then - s_neigh_coo%val(ip) = sone - else - s_neigh_coo%val(ip) = -sone + if (j<=nr) then + ip = ip + 1 + s_neigh_coo%ia(ip) = i + s_neigh_coo%ja(ip) = j + if (real(muij%val(k)) >= theta) then + s_neigh_coo%val(ip) = sone + else + s_neigh_coo%val(ip) = -sone + end if end if end do end do diff --git a/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 index 0648421f..4e245d29 100644 --- a/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 @@ -86,7 +86,7 @@ subroutine mld_z_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) integer(psb_ipk_), allocatable :: ils(:), neigh(:), irow(:), icol(:),& & ideg(:), idxs(:), tmpaggr(:) complex(psb_dpk_), allocatable :: val(:), diag(:) - integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr, naggr,i,j,m, nz, ilg, ii, ip, ip1,nzcnt + integer(psb_ipk_) :: icnt,nlp,k,n,ia,isz,nr,nc,naggr,i,j,m, nz, ilg, ii, ip, ip1,nzcnt type(psb_z_csr_sparse_mat) :: acsr, muij, s_neigh type(psb_z_coo_sparse_mat) :: s_neigh_coo real(psb_dpk_) :: cpling, tcl @@ -109,6 +109,7 @@ subroutine mld_z_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) ncol = desc_a%get_local_cols() nr = a%get_nrows() + nc = a%get_ncols() allocate(ilaggr(nr),neigh(nr),ideg(nr),idxs(nr),icol(nr),stat=info) if(info /= psb_success_) then info=psb_err_alloc_request_ @@ -131,7 +132,7 @@ subroutine mld_z_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) do i=1, nr do k=muij%irp(i),muij%irp(i+1)-1 j = muij%ja(k) - muij%val(k) = abs(muij%val(k))/sqrt(abs(diag(i)*diag(j))) + if (j<= nr) muij%val(k) = abs(muij%val(k))/sqrt(abs(diag(i)*diag(j))) end do end do !write(*,*) 'murows/cols ',maxval(mu_rows),maxval(mu_cols) @@ -143,13 +144,15 @@ subroutine mld_z_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) do i=1, nr do k=muij%irp(i),muij%irp(i+1)-1 j = muij%ja(k) - ip = ip + 1 - s_neigh_coo%ia(ip) = i - s_neigh_coo%ja(ip) = j - if (real(muij%val(k)) >= theta) then - s_neigh_coo%val(ip) = done - else - s_neigh_coo%val(ip) = -done + if (j<=nr) then + ip = ip + 1 + s_neigh_coo%ia(ip) = i + s_neigh_coo%ja(ip) = j + if (real(muij%val(k)) >= theta) then + s_neigh_coo%val(ip) = done + else + s_neigh_coo%val(ip) = -done + end if end if end do end do From 7732bb90d3f298b3ff0e9568904bea8b656d5b4a Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 11 May 2018 14:52:07 +0100 Subject: [PATCH 29/33] Take out hybrid, no longer needed. --- mlprec/impl/level/mld_c_base_onelev_cseti.F90 | 1 - mlprec/impl/level/mld_d_base_onelev_cseti.F90 | 1 - mlprec/impl/level/mld_s_base_onelev_cseti.F90 | 1 - mlprec/impl/level/mld_z_base_onelev_cseti.F90 | 1 - 4 files changed, 4 deletions(-) diff --git a/mlprec/impl/level/mld_c_base_onelev_cseti.F90 b/mlprec/impl/level/mld_c_base_onelev_cseti.F90 index b51817b3..f412093e 100644 --- a/mlprec/impl/level/mld_c_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_c_base_onelev_cseti.F90 @@ -42,7 +42,6 @@ subroutine mld_c_base_onelev_cseti(lv,what,val,info,pos) use mld_c_base_aggregator_mod use mld_c_dec_aggregator_mod use mld_c_symdec_aggregator_mod - use mld_c_hybrid_aggregator_mod use mld_c_jac_smoother use mld_c_as_smoother use mld_c_diag_solver diff --git a/mlprec/impl/level/mld_d_base_onelev_cseti.F90 b/mlprec/impl/level/mld_d_base_onelev_cseti.F90 index 25b34802..d76c5b59 100644 --- a/mlprec/impl/level/mld_d_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_d_base_onelev_cseti.F90 @@ -42,7 +42,6 @@ subroutine mld_d_base_onelev_cseti(lv,what,val,info,pos) use mld_d_base_aggregator_mod use mld_d_dec_aggregator_mod use mld_d_symdec_aggregator_mod - use mld_d_hybrid_aggregator_mod use mld_d_jac_smoother use mld_d_as_smoother use mld_d_diag_solver diff --git a/mlprec/impl/level/mld_s_base_onelev_cseti.F90 b/mlprec/impl/level/mld_s_base_onelev_cseti.F90 index 12fcc41b..8ca26b54 100644 --- a/mlprec/impl/level/mld_s_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_s_base_onelev_cseti.F90 @@ -42,7 +42,6 @@ subroutine mld_s_base_onelev_cseti(lv,what,val,info,pos) use mld_s_base_aggregator_mod use mld_s_dec_aggregator_mod use mld_s_symdec_aggregator_mod - use mld_s_hybrid_aggregator_mod use mld_s_jac_smoother use mld_s_as_smoother use mld_s_diag_solver diff --git a/mlprec/impl/level/mld_z_base_onelev_cseti.F90 b/mlprec/impl/level/mld_z_base_onelev_cseti.F90 index 0d0c2bc0..bee8ba2b 100644 --- a/mlprec/impl/level/mld_z_base_onelev_cseti.F90 +++ b/mlprec/impl/level/mld_z_base_onelev_cseti.F90 @@ -42,7 +42,6 @@ subroutine mld_z_base_onelev_cseti(lv,what,val,info,pos) use mld_z_base_aggregator_mod use mld_z_dec_aggregator_mod use mld_z_symdec_aggregator_mod - use mld_z_hybrid_aggregator_mod use mld_z_jac_smoother use mld_z_as_smoother use mld_z_diag_solver From d6e990b04cf89fafe9aa242a0f3a9e98d317cb17 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Mon, 14 May 2018 11:48:15 +0100 Subject: [PATCH 30/33] Renamed VMB and HYB into SOC1 and SOC2. --- mlprec/impl/aggregator/Makefile | 8 +- .../aggregator/mld_c_dec_aggregator_tprol.f90 | 5 +- .../mld_c_hybrid_aggregator_tprol.f90 | 130 ------------------ ...vmb_map_bld.f90 => mld_c_soc1_map_bld.f90} | 12 +- ...hyb_map_bld.f90 => mld_c_soc2_map_bld.f90} | 14 +- .../mld_c_symdec_aggregator_tprol.f90 | 6 +- .../aggregator/mld_d_dec_aggregator_tprol.f90 | 5 +- .../mld_d_hybrid_aggregator_tprol.f90 | 130 ------------------ ...vmb_map_bld.f90 => mld_d_soc1_map_bld.f90} | 12 +- ...hyb_map_bld.f90 => mld_d_soc2_map_bld.f90} | 14 +- .../mld_d_symdec_aggregator_tprol.f90 | 6 +- .../aggregator/mld_s_dec_aggregator_tprol.f90 | 5 +- .../mld_s_hybrid_aggregator_tprol.f90 | 130 ------------------ ...vmb_map_bld.f90 => mld_s_soc1_map_bld.f90} | 12 +- ...hyb_map_bld.f90 => mld_s_soc2_map_bld.f90} | 14 +- .../mld_s_symdec_aggregator_tprol.f90 | 6 +- .../aggregator/mld_z_dec_aggregator_tprol.f90 | 5 +- .../mld_z_hybrid_aggregator_tprol.f90 | 130 ------------------ ...vmb_map_bld.f90 => mld_z_soc1_map_bld.f90} | 12 +- ...hyb_map_bld.f90 => mld_z_soc2_map_bld.f90} | 14 +- .../mld_z_symdec_aggregator_tprol.f90 | 6 +- mlprec/mld_base_prec_type.F90 | 16 +-- mlprec/mld_c_dec_aggregator_mod.f90 | 16 +-- mlprec/mld_c_onelev_mod.f90 | 2 +- mlprec/mld_d_dec_aggregator_mod.f90 | 16 +-- mlprec/mld_d_onelev_mod.f90 | 2 +- mlprec/mld_s_dec_aggregator_mod.f90 | 16 +-- mlprec/mld_s_onelev_mod.f90 | 2 +- mlprec/mld_z_dec_aggregator_mod.f90 | 16 +-- mlprec/mld_z_onelev_mod.f90 | 2 +- 30 files changed, 120 insertions(+), 644 deletions(-) delete mode 100644 mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 rename mlprec/impl/aggregator/{mld_c_vmb_map_bld.f90 => mld_c_soc1_map_bld.f90} (97%) rename mlprec/impl/aggregator/{mld_c_hyb_map_bld.f90 => mld_c_soc2_map_bld.f90} (96%) delete mode 100644 mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 rename mlprec/impl/aggregator/{mld_d_vmb_map_bld.f90 => mld_d_soc1_map_bld.f90} (97%) rename mlprec/impl/aggregator/{mld_d_hyb_map_bld.f90 => mld_d_soc2_map_bld.f90} (96%) delete mode 100644 mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 rename mlprec/impl/aggregator/{mld_s_vmb_map_bld.f90 => mld_s_soc1_map_bld.f90} (97%) rename mlprec/impl/aggregator/{mld_s_hyb_map_bld.f90 => mld_s_soc2_map_bld.f90} (96%) delete mode 100644 mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 rename mlprec/impl/aggregator/{mld_z_vmb_map_bld.f90 => mld_z_soc1_map_bld.f90} (97%) rename mlprec/impl/aggregator/{mld_z_hyb_map_bld.f90 => mld_z_soc2_map_bld.f90} (96%) diff --git a/mlprec/impl/aggregator/Makefile b/mlprec/impl/aggregator/Makefile index 9ff4f87b..81a51e87 100644 --- a/mlprec/impl/aggregator/Makefile +++ b/mlprec/impl/aggregator/Makefile @@ -12,25 +12,25 @@ OBJS= \ mld_s_dec_aggregator_mat_asb.o \ mld_s_dec_aggregator_tprol.o \ mld_s_symdec_aggregator_tprol.o \ -mld_s_map_to_tprol.o mld_s_vmb_map_bld.o mld_s_hyb_map_bld.o\ +mld_s_map_to_tprol.o mld_s_soc1_map_bld.o mld_s_soc2_map_bld.o\ mld_saggrmat_biz_asb.o mld_saggrmat_minnrg_asb.o\ mld_saggrmat_nosmth_asb.o mld_saggrmat_smth_asb.o \ mld_d_dec_aggregator_mat_asb.o \ mld_d_dec_aggregator_tprol.o \ mld_d_symdec_aggregator_tprol.o \ -mld_d_map_to_tprol.o mld_d_vmb_map_bld.o mld_d_hyb_map_bld.o\ +mld_d_map_to_tprol.o mld_d_soc1_map_bld.o mld_d_soc2_map_bld.o\ mld_daggrmat_biz_asb.o mld_daggrmat_minnrg_asb.o\ mld_daggrmat_nosmth_asb.o mld_daggrmat_smth_asb.o \ mld_c_dec_aggregator_mat_asb.o \ mld_c_dec_aggregator_tprol.o \ mld_c_symdec_aggregator_tprol.o \ -mld_c_map_to_tprol.o mld_c_vmb_map_bld.o mld_c_hyb_map_bld.o\ +mld_c_map_to_tprol.o mld_c_soc1_map_bld.o mld_c_soc2_map_bld.o\ mld_caggrmat_biz_asb.o mld_caggrmat_minnrg_asb.o\ mld_caggrmat_nosmth_asb.o mld_caggrmat_smth_asb.o \ mld_z_dec_aggregator_mat_asb.o \ mld_z_dec_aggregator_tprol.o \ mld_z_symdec_aggregator_tprol.o \ -mld_z_map_to_tprol.o mld_z_vmb_map_bld.o mld_z_hyb_map_bld.o\ +mld_z_map_to_tprol.o mld_z_soc1_map_bld.o mld_z_soc2_map_bld.o\ mld_zaggrmat_biz_asb.o mld_zaggrmat_minnrg_asb.o\ mld_zaggrmat_nosmth_asb.o mld_zaggrmat_smth_asb.o diff --git a/mlprec/impl/aggregator/mld_c_dec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_c_dec_aggregator_tprol.f90 index f6caf655..efe66b9a 100644 --- a/mlprec/impl/aggregator/mld_c_dec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_c_dec_aggregator_tprol.f90 @@ -40,7 +40,7 @@ ! Subroutine: mld_c_dec_aggregator_tprol ! Version: complex ! -! This routine is mainly an interface to vmb_map_bld where the real work is performed. +! This routine is mainly an interface to map_bld where the real work is performed. ! It takes care of some consistency checking, and calls map_to_tprol, which is ! refactored and shared among all the aggregation methods that produce a simple ! integer mapping. @@ -111,12 +111,11 @@ subroutine mld_c_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_ call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) -!!$ call mld_c_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') + call psb_errpush(info,name,a_err='map_bld/map_to_tprol') goto 9999 endif diff --git a/mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 deleted file mode 100644 index 79da415e..00000000 --- a/mlprec/impl/aggregator/mld_c_hybrid_aggregator_tprol.f90 +++ /dev/null @@ -1,130 +0,0 @@ -! -! -! MLD2P4 version 2.2 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_c_hybrid_aggregator_tprol.f90 -! -! Subroutine: mld_c_hybrid_aggregator_tprol -! Version: complex -! -! -! This routine is mainly an interface to hyb_map_bld where the real work is performed. -! It takes care of some consistency checking, and calls map_to_tprol, which is -! refactored and shared among all the aggregation methods that produce a simple -! integer mapping. -! -! -! Arguments: -! p - type(mld_c_onelev_type), input/output. -! The 'one-level' data structure containing the control -! parameters and (eventually) coarse matrix and prolongator/restrictors. -! -! a - type(psb_cspmat_type). -! The sparse matrix structure containing the local part of the -! fine-level matrix. -! desc_a - type(psb_desc_type), input. -! The communication descriptor of a. -! ilaggr - integer, dimension(:), allocatable, output -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that on exit the indices -! will be shifted so as to make sure the ranges on the various processes do not -! overlap. -! nlaggr - integer, dimension(:), allocatable, output -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_cspmat_type), output -! The tentative prolongator, based on ilaggr. -! -! info - integer, output. -! Error code. -! -subroutine mld_c_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) - use psb_base_mod - use mld_c_prec_type - use mld_c_hybrid_aggregator_mod, mld_protect_name => mld_c_hybrid_aggregator_build_tprol - use mld_c_inner_mod - implicit none - class(mld_c_hybrid_aggregator_type), target, intent(inout) :: ag - type(mld_sml_parms), intent(inout) :: parms - type(psb_cspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - type(psb_cspmat_type), intent(out) :: op_prol - integer(psb_ipk_), intent(out) :: info - - ! Local variables - character(len=20) :: name - integer(psb_mpik_) :: ictxt, np, me - integer(psb_ipk_) :: err_act - integer(psb_ipk_) :: ntaggr - integer(psb_ipk_) :: debug_level, debug_unit - - name='mld_c_hybrid_aggregator_tprol' - if (psb_get_errstatus().ne.0) return - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - info = psb_success_ - ictxt = desc_a%get_context() - call psb_info(ictxt,me,np) - - call mld_check_def(parms%ml_cycle,'Multilevel cycle',& - & mld_mult_ml_,is_legal_ml_cycle) - call mld_check_def(parms%par_aggr_alg,'Aggregation',& - & mld_dec_aggr_,is_legal_ml_par_aggr_alg) - call mld_check_def(parms%aggr_ord,'Ordering',& - & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) - call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) - - - call mld_c_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) - - if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) - if (info /= psb_success_) then - info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='hyb_map_bld/map_to_tprol') - goto 9999 - endif - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - return - -end subroutine mld_c_hybrid_aggregator_build_tprol diff --git a/mlprec/impl/aggregator/mld_c_vmb_map_bld.f90 b/mlprec/impl/aggregator/mld_c_soc1_map_bld.f90 similarity index 97% rename from mlprec/impl/aggregator/mld_c_vmb_map_bld.f90 rename to mlprec/impl/aggregator/mld_c_soc1_map_bld.f90 index 4c5cf944..1ec3aa18 100644 --- a/mlprec/impl/aggregator/mld_c_vmb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_c_soc1_map_bld.f90 @@ -36,9 +36,9 @@ ! ! ! -! File: mld_c_vmb_map__bld.f90 +! File: mld_c_soc1_map__bld.f90 ! -! Subroutine: mld_c_vmb_map_bld +! Subroutine: mld_c_soc1_map_bld ! Version: complex ! ! This routine builds the tentative prolongator based on the @@ -67,11 +67,11 @@ ! ! ! -subroutine mld_c_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) +subroutine mld_c_soc1_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_c_inner_mod!, mld_protect_name => mld_c_vmb_map_bld + use mld_c_inner_mod!, mld_protect_name => mld_c_soc1_map_bld implicit none @@ -98,7 +98,7 @@ subroutine mld_c_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) if (psb_get_errstatus() /= 0) return info=psb_success_ - name = 'mld_vmb_map_bld' + name = 'mld_soc1_map_bld' call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() debug_level = psb_get_debug_level() @@ -318,5 +318,5 @@ subroutine mld_c_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) return -end subroutine mld_c_vmb_map_bld +end subroutine mld_c_soc1_map_bld diff --git a/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_c_soc2_map_bld.f90 similarity index 96% rename from mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 rename to mlprec/impl/aggregator/mld_c_soc2_map_bld.f90 index d7dbe2b8..7ceb36fc 100644 --- a/mlprec/impl/aggregator/mld_c_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_c_soc2_map_bld.f90 @@ -36,13 +36,13 @@ ! ! ! -! File: mld_c_hyb_map__bld.f90 +! File: mld_c_soc2_map__bld.f90 ! -! Subroutine: mld_c_hyb_map_bld +! Subroutine: mld_c_soc2_map_bld ! Version: complex ! ! The aggregator object hosts the aggregation method for building -! the multilevel hierarchy. This variant is based on the hybrid method +! the multilevel hierarchy. This variant is based on the method ! presented in ! ! S. Gratton, P. Henon, P. Jiranek and X. Vasseur: @@ -66,11 +66,11 @@ ! ! ! -subroutine mld_c_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) +subroutine mld_c_soc2_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_c_inner_mod!, mld_protect_name => mld_c_hyb_map_bld + use mld_c_inner_mod!, mld_protect_name => mld_c_soc2_map_bld implicit none @@ -98,7 +98,7 @@ subroutine mld_c_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) if (psb_get_errstatus() /= 0) return info=psb_success_ - name = 'mld_hyb_map_bld' + name = 'mld_soc2_map_bld' call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() debug_level = psb_get_debug_level() @@ -326,5 +326,5 @@ subroutine mld_c_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) return -end subroutine mld_c_hyb_map_bld +end subroutine mld_c_soc2_map_bld diff --git a/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 index df43dc0a..594831f4 100644 --- a/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_c_symdec_aggregator_tprol.f90 @@ -41,7 +41,7 @@ ! Version: complex ! ! -! This routine is mainly an interface to vmb_map_bld where the real work is performed. +! This routine is mainly an interface to map_bld where the real work is performed. ! It takes care of some consistency checking, and calls map_to_tprol, which is ! refactored and shared among all the aggregation methods that produce a simple ! integer mapping. @@ -127,13 +127,13 @@ subroutine mld_c_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, if (info == psb_success_) call atmp%cscnv(info,type='CSR') if (info == psb_success_) & - & call mld_c_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) + & call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) if (info == psb_success_) call atmp%free() if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') + call psb_errpush(info,name,a_err='map_bld/map_to_tprol') goto 9999 endif diff --git a/mlprec/impl/aggregator/mld_d_dec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_d_dec_aggregator_tprol.f90 index cd5196bc..15a5c2c7 100644 --- a/mlprec/impl/aggregator/mld_d_dec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_d_dec_aggregator_tprol.f90 @@ -40,7 +40,7 @@ ! Subroutine: mld_d_dec_aggregator_tprol ! Version: real ! -! This routine is mainly an interface to vmb_map_bld where the real work is performed. +! This routine is mainly an interface to map_bld where the real work is performed. ! It takes care of some consistency checking, and calls map_to_tprol, which is ! refactored and shared among all the aggregation methods that produce a simple ! integer mapping. @@ -111,12 +111,11 @@ subroutine mld_d_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_ call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) -!!$ call mld_d_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') + call psb_errpush(info,name,a_err='map_bld/map_to_tprol') goto 9999 endif diff --git a/mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 deleted file mode 100644 index b822a956..00000000 --- a/mlprec/impl/aggregator/mld_d_hybrid_aggregator_tprol.f90 +++ /dev/null @@ -1,130 +0,0 @@ -! -! -! MLD2P4 version 2.2 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_d_hybrid_aggregator_tprol.f90 -! -! Subroutine: mld_d_hybrid_aggregator_tprol -! Version: real -! -! -! This routine is mainly an interface to hyb_map_bld where the real work is performed. -! It takes care of some consistency checking, and calls map_to_tprol, which is -! refactored and shared among all the aggregation methods that produce a simple -! integer mapping. -! -! -! Arguments: -! p - type(mld_d_onelev_type), input/output. -! The 'one-level' data structure containing the control -! parameters and (eventually) coarse matrix and prolongator/restrictors. -! -! a - type(psb_dspmat_type). -! The sparse matrix structure containing the local part of the -! fine-level matrix. -! desc_a - type(psb_desc_type), input. -! The communication descriptor of a. -! ilaggr - integer, dimension(:), allocatable, output -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that on exit the indices -! will be shifted so as to make sure the ranges on the various processes do not -! overlap. -! nlaggr - integer, dimension(:), allocatable, output -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_dspmat_type), output -! The tentative prolongator, based on ilaggr. -! -! info - integer, output. -! Error code. -! -subroutine mld_d_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) - use psb_base_mod - use mld_d_prec_type - use mld_d_hybrid_aggregator_mod, mld_protect_name => mld_d_hybrid_aggregator_build_tprol - use mld_d_inner_mod - implicit none - class(mld_d_hybrid_aggregator_type), target, intent(inout) :: ag - type(mld_dml_parms), intent(inout) :: parms - type(psb_dspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - type(psb_dspmat_type), intent(out) :: op_prol - integer(psb_ipk_), intent(out) :: info - - ! Local variables - character(len=20) :: name - integer(psb_mpik_) :: ictxt, np, me - integer(psb_ipk_) :: err_act - integer(psb_ipk_) :: ntaggr - integer(psb_ipk_) :: debug_level, debug_unit - - name='mld_d_hybrid_aggregator_tprol' - if (psb_get_errstatus().ne.0) return - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - info = psb_success_ - ictxt = desc_a%get_context() - call psb_info(ictxt,me,np) - - call mld_check_def(parms%ml_cycle,'Multilevel cycle',& - & mld_mult_ml_,is_legal_ml_cycle) - call mld_check_def(parms%par_aggr_alg,'Aggregation',& - & mld_dec_aggr_,is_legal_ml_par_aggr_alg) - call mld_check_def(parms%aggr_ord,'Ordering',& - & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) - call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) - - - call mld_d_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) - - if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) - if (info /= psb_success_) then - info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='hyb_map_bld/map_to_tprol') - goto 9999 - endif - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - return - -end subroutine mld_d_hybrid_aggregator_build_tprol diff --git a/mlprec/impl/aggregator/mld_d_vmb_map_bld.f90 b/mlprec/impl/aggregator/mld_d_soc1_map_bld.f90 similarity index 97% rename from mlprec/impl/aggregator/mld_d_vmb_map_bld.f90 rename to mlprec/impl/aggregator/mld_d_soc1_map_bld.f90 index 83d22fc4..4c9e935f 100644 --- a/mlprec/impl/aggregator/mld_d_vmb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_d_soc1_map_bld.f90 @@ -36,9 +36,9 @@ ! ! ! -! File: mld_d_vmb_map__bld.f90 +! File: mld_d_soc1_map__bld.f90 ! -! Subroutine: mld_d_vmb_map_bld +! Subroutine: mld_d_soc1_map_bld ! Version: real ! ! This routine builds the tentative prolongator based on the @@ -67,11 +67,11 @@ ! ! ! -subroutine mld_d_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) +subroutine mld_d_soc1_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_d_inner_mod!, mld_protect_name => mld_d_vmb_map_bld + use mld_d_inner_mod!, mld_protect_name => mld_d_soc1_map_bld implicit none @@ -98,7 +98,7 @@ subroutine mld_d_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) if (psb_get_errstatus() /= 0) return info=psb_success_ - name = 'mld_vmb_map_bld' + name = 'mld_soc1_map_bld' call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() debug_level = psb_get_debug_level() @@ -318,5 +318,5 @@ subroutine mld_d_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) return -end subroutine mld_d_vmb_map_bld +end subroutine mld_d_soc1_map_bld diff --git a/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_d_soc2_map_bld.f90 similarity index 96% rename from mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 rename to mlprec/impl/aggregator/mld_d_soc2_map_bld.f90 index 1af79aa1..2f57abb9 100644 --- a/mlprec/impl/aggregator/mld_d_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_d_soc2_map_bld.f90 @@ -36,13 +36,13 @@ ! ! ! -! File: mld_d_hyb_map__bld.f90 +! File: mld_d_soc2_map__bld.f90 ! -! Subroutine: mld_d_hyb_map_bld +! Subroutine: mld_d_soc2_map_bld ! Version: real ! ! The aggregator object hosts the aggregation method for building -! the multilevel hierarchy. This variant is based on the hybrid method +! the multilevel hierarchy. This variant is based on the method ! presented in ! ! S. Gratton, P. Henon, P. Jiranek and X. Vasseur: @@ -66,11 +66,11 @@ ! ! ! -subroutine mld_d_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) +subroutine mld_d_soc2_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_d_inner_mod!, mld_protect_name => mld_d_hyb_map_bld + use mld_d_inner_mod!, mld_protect_name => mld_d_soc2_map_bld implicit none @@ -98,7 +98,7 @@ subroutine mld_d_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) if (psb_get_errstatus() /= 0) return info=psb_success_ - name = 'mld_hyb_map_bld' + name = 'mld_soc2_map_bld' call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() debug_level = psb_get_debug_level() @@ -326,5 +326,5 @@ subroutine mld_d_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) return -end subroutine mld_d_hyb_map_bld +end subroutine mld_d_soc2_map_bld diff --git a/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 index 6216c2fc..b3079bdf 100644 --- a/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_d_symdec_aggregator_tprol.f90 @@ -41,7 +41,7 @@ ! Version: real ! ! -! This routine is mainly an interface to vmb_map_bld where the real work is performed. +! This routine is mainly an interface to map_bld where the real work is performed. ! It takes care of some consistency checking, and calls map_to_tprol, which is ! refactored and shared among all the aggregation methods that produce a simple ! integer mapping. @@ -127,13 +127,13 @@ subroutine mld_d_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, if (info == psb_success_) call atmp%cscnv(info,type='CSR') if (info == psb_success_) & - & call mld_d_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) + & call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) if (info == psb_success_) call atmp%free() if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') + call psb_errpush(info,name,a_err='map_bld/map_to_tprol') goto 9999 endif diff --git a/mlprec/impl/aggregator/mld_s_dec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_s_dec_aggregator_tprol.f90 index f305e2e6..02552a10 100644 --- a/mlprec/impl/aggregator/mld_s_dec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_s_dec_aggregator_tprol.f90 @@ -40,7 +40,7 @@ ! Subroutine: mld_s_dec_aggregator_tprol ! Version: real ! -! This routine is mainly an interface to vmb_map_bld where the real work is performed. +! This routine is mainly an interface to map_bld where the real work is performed. ! It takes care of some consistency checking, and calls map_to_tprol, which is ! refactored and shared among all the aggregation methods that produce a simple ! integer mapping. @@ -111,12 +111,11 @@ subroutine mld_s_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_ call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) -!!$ call mld_s_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') + call psb_errpush(info,name,a_err='map_bld/map_to_tprol') goto 9999 endif diff --git a/mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 deleted file mode 100644 index d2100775..00000000 --- a/mlprec/impl/aggregator/mld_s_hybrid_aggregator_tprol.f90 +++ /dev/null @@ -1,130 +0,0 @@ -! -! -! MLD2P4 version 2.2 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_s_hybrid_aggregator_tprol.f90 -! -! Subroutine: mld_s_hybrid_aggregator_tprol -! Version: real -! -! -! This routine is mainly an interface to hyb_map_bld where the real work is performed. -! It takes care of some consistency checking, and calls map_to_tprol, which is -! refactored and shared among all the aggregation methods that produce a simple -! integer mapping. -! -! -! Arguments: -! p - type(mld_s_onelev_type), input/output. -! The 'one-level' data structure containing the control -! parameters and (eventually) coarse matrix and prolongator/restrictors. -! -! a - type(psb_sspmat_type). -! The sparse matrix structure containing the local part of the -! fine-level matrix. -! desc_a - type(psb_desc_type), input. -! The communication descriptor of a. -! ilaggr - integer, dimension(:), allocatable, output -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that on exit the indices -! will be shifted so as to make sure the ranges on the various processes do not -! overlap. -! nlaggr - integer, dimension(:), allocatable, output -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_sspmat_type), output -! The tentative prolongator, based on ilaggr. -! -! info - integer, output. -! Error code. -! -subroutine mld_s_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) - use psb_base_mod - use mld_s_prec_type - use mld_s_hybrid_aggregator_mod, mld_protect_name => mld_s_hybrid_aggregator_build_tprol - use mld_s_inner_mod - implicit none - class(mld_s_hybrid_aggregator_type), target, intent(inout) :: ag - type(mld_sml_parms), intent(inout) :: parms - type(psb_sspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - type(psb_sspmat_type), intent(out) :: op_prol - integer(psb_ipk_), intent(out) :: info - - ! Local variables - character(len=20) :: name - integer(psb_mpik_) :: ictxt, np, me - integer(psb_ipk_) :: err_act - integer(psb_ipk_) :: ntaggr - integer(psb_ipk_) :: debug_level, debug_unit - - name='mld_s_hybrid_aggregator_tprol' - if (psb_get_errstatus().ne.0) return - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - info = psb_success_ - ictxt = desc_a%get_context() - call psb_info(ictxt,me,np) - - call mld_check_def(parms%ml_cycle,'Multilevel cycle',& - & mld_mult_ml_,is_legal_ml_cycle) - call mld_check_def(parms%par_aggr_alg,'Aggregation',& - & mld_dec_aggr_,is_legal_ml_par_aggr_alg) - call mld_check_def(parms%aggr_ord,'Ordering',& - & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) - call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',szero,is_legal_s_aggr_thrs) - - - call mld_s_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) - - if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) - if (info /= psb_success_) then - info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='hyb_map_bld/map_to_tprol') - goto 9999 - endif - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - return - -end subroutine mld_s_hybrid_aggregator_build_tprol diff --git a/mlprec/impl/aggregator/mld_s_vmb_map_bld.f90 b/mlprec/impl/aggregator/mld_s_soc1_map_bld.f90 similarity index 97% rename from mlprec/impl/aggregator/mld_s_vmb_map_bld.f90 rename to mlprec/impl/aggregator/mld_s_soc1_map_bld.f90 index 93293632..4729964d 100644 --- a/mlprec/impl/aggregator/mld_s_vmb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_s_soc1_map_bld.f90 @@ -36,9 +36,9 @@ ! ! ! -! File: mld_s_vmb_map__bld.f90 +! File: mld_s_soc1_map__bld.f90 ! -! Subroutine: mld_s_vmb_map_bld +! Subroutine: mld_s_soc1_map_bld ! Version: real ! ! This routine builds the tentative prolongator based on the @@ -67,11 +67,11 @@ ! ! ! -subroutine mld_s_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) +subroutine mld_s_soc1_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_s_inner_mod!, mld_protect_name => mld_s_vmb_map_bld + use mld_s_inner_mod!, mld_protect_name => mld_s_soc1_map_bld implicit none @@ -98,7 +98,7 @@ subroutine mld_s_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) if (psb_get_errstatus() /= 0) return info=psb_success_ - name = 'mld_vmb_map_bld' + name = 'mld_soc1_map_bld' call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() debug_level = psb_get_debug_level() @@ -318,5 +318,5 @@ subroutine mld_s_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) return -end subroutine mld_s_vmb_map_bld +end subroutine mld_s_soc1_map_bld diff --git a/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_s_soc2_map_bld.f90 similarity index 96% rename from mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 rename to mlprec/impl/aggregator/mld_s_soc2_map_bld.f90 index ec70c6ce..9e0a95cd 100644 --- a/mlprec/impl/aggregator/mld_s_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_s_soc2_map_bld.f90 @@ -36,13 +36,13 @@ ! ! ! -! File: mld_s_hyb_map__bld.f90 +! File: mld_s_soc2_map__bld.f90 ! -! Subroutine: mld_s_hyb_map_bld +! Subroutine: mld_s_soc2_map_bld ! Version: real ! ! The aggregator object hosts the aggregation method for building -! the multilevel hierarchy. This variant is based on the hybrid method +! the multilevel hierarchy. This variant is based on the method ! presented in ! ! S. Gratton, P. Henon, P. Jiranek and X. Vasseur: @@ -66,11 +66,11 @@ ! ! ! -subroutine mld_s_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) +subroutine mld_s_soc2_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_s_inner_mod!, mld_protect_name => mld_s_hyb_map_bld + use mld_s_inner_mod!, mld_protect_name => mld_s_soc2_map_bld implicit none @@ -98,7 +98,7 @@ subroutine mld_s_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) if (psb_get_errstatus() /= 0) return info=psb_success_ - name = 'mld_hyb_map_bld' + name = 'mld_soc2_map_bld' call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() debug_level = psb_get_debug_level() @@ -326,5 +326,5 @@ subroutine mld_s_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) return -end subroutine mld_s_hyb_map_bld +end subroutine mld_s_soc2_map_bld diff --git a/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 index 551ff721..a19f5344 100644 --- a/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_s_symdec_aggregator_tprol.f90 @@ -41,7 +41,7 @@ ! Version: real ! ! -! This routine is mainly an interface to vmb_map_bld where the real work is performed. +! This routine is mainly an interface to map_bld where the real work is performed. ! It takes care of some consistency checking, and calls map_to_tprol, which is ! refactored and shared among all the aggregation methods that produce a simple ! integer mapping. @@ -127,13 +127,13 @@ subroutine mld_s_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, if (info == psb_success_) call atmp%cscnv(info,type='CSR') if (info == psb_success_) & - & call mld_s_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) + & call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) if (info == psb_success_) call atmp%free() if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') + call psb_errpush(info,name,a_err='map_bld/map_to_tprol') goto 9999 endif diff --git a/mlprec/impl/aggregator/mld_z_dec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_z_dec_aggregator_tprol.f90 index a2ff5ca9..aeac2317 100644 --- a/mlprec/impl/aggregator/mld_z_dec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_z_dec_aggregator_tprol.f90 @@ -40,7 +40,7 @@ ! Subroutine: mld_z_dec_aggregator_tprol ! Version: complex ! -! This routine is mainly an interface to vmb_map_bld where the real work is performed. +! This routine is mainly an interface to map_bld where the real work is performed. ! It takes care of some consistency checking, and calls map_to_tprol, which is ! refactored and shared among all the aggregation methods that produce a simple ! integer mapping. @@ -111,12 +111,11 @@ subroutine mld_z_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_ call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) -!!$ call mld_z_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') + call psb_errpush(info,name,a_err='map_bld/map_to_tprol') goto 9999 endif diff --git a/mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 deleted file mode 100644 index bf739e8f..00000000 --- a/mlprec/impl/aggregator/mld_z_hybrid_aggregator_tprol.f90 +++ /dev/null @@ -1,130 +0,0 @@ -! -! -! MLD2P4 version 2.2 -! MultiLevel Domain Decomposition Parallel Preconditioners Package -! based on PSBLAS (Parallel Sparse BLAS version 3.5) -! -! (C) Copyright 2008-2018 -! -! Salvatore Filippone -! Pasqua D'Ambra -! Daniela di Serafino -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the MLD2P4 group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -! File: mld_z_hybrid_aggregator_tprol.f90 -! -! Subroutine: mld_z_hybrid_aggregator_tprol -! Version: complex -! -! -! This routine is mainly an interface to hyb_map_bld where the real work is performed. -! It takes care of some consistency checking, and calls map_to_tprol, which is -! refactored and shared among all the aggregation methods that produce a simple -! integer mapping. -! -! -! Arguments: -! p - type(mld_z_onelev_type), input/output. -! The 'one-level' data structure containing the control -! parameters and (eventually) coarse matrix and prolongator/restrictors. -! -! a - type(psb_zspmat_type). -! The sparse matrix structure containing the local part of the -! fine-level matrix. -! desc_a - type(psb_desc_type), input. -! The communication descriptor of a. -! ilaggr - integer, dimension(:), allocatable, output -! The mapping between the row indices of the coarse-level -! matrix and the row indices of the fine-level matrix. -! ilaggr(i)=j means that node i in the adjacency graph -! of the fine-level matrix is mapped onto node j in the -! adjacency graph of the coarse-level matrix. Note that on exit the indices -! will be shifted so as to make sure the ranges on the various processes do not -! overlap. -! nlaggr - integer, dimension(:), allocatable, output -! nlaggr(i) contains the aggregates held by process i. -! op_prol - type(psb_zspmat_type), output -! The tentative prolongator, based on ilaggr. -! -! info - integer, output. -! Error code. -! -subroutine mld_z_hybrid_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) - use psb_base_mod - use mld_z_prec_type - use mld_z_hybrid_aggregator_mod, mld_protect_name => mld_z_hybrid_aggregator_build_tprol - use mld_z_inner_mod - implicit none - class(mld_z_hybrid_aggregator_type), target, intent(inout) :: ag - type(mld_dml_parms), intent(inout) :: parms - type(psb_zspmat_type), intent(in) :: a - type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), allocatable, intent(out) :: ilaggr(:),nlaggr(:) - type(psb_zspmat_type), intent(out) :: op_prol - integer(psb_ipk_), intent(out) :: info - - ! Local variables - character(len=20) :: name - integer(psb_mpik_) :: ictxt, np, me - integer(psb_ipk_) :: err_act - integer(psb_ipk_) :: ntaggr - integer(psb_ipk_) :: debug_level, debug_unit - - name='mld_z_hybrid_aggregator_tprol' - if (psb_get_errstatus().ne.0) return - call psb_erractionsave(err_act) - debug_unit = psb_get_debug_unit() - debug_level = psb_get_debug_level() - info = psb_success_ - ictxt = desc_a%get_context() - call psb_info(ictxt,me,np) - - call mld_check_def(parms%ml_cycle,'Multilevel cycle',& - & mld_mult_ml_,is_legal_ml_cycle) - call mld_check_def(parms%par_aggr_alg,'Aggregation',& - & mld_dec_aggr_,is_legal_ml_par_aggr_alg) - call mld_check_def(parms%aggr_ord,'Ordering',& - & mld_aggr_ord_nat_,is_legal_ml_aggr_ord) - call mld_check_def(parms%aggr_thresh,'Aggr_Thresh',dzero,is_legal_d_aggr_thrs) - - - call mld_z_hyb_map_bld(parms%aggr_ord,parms%aggr_thresh,a,desc_a,nlaggr,ilaggr,info) - - if (info==psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) - if (info /= psb_success_) then - info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='hyb_map_bld/map_to_tprol') - goto 9999 - endif - - call psb_erractionrestore(err_act) - return - -9999 call psb_error_handler(err_act) - return - -end subroutine mld_z_hybrid_aggregator_build_tprol diff --git a/mlprec/impl/aggregator/mld_z_vmb_map_bld.f90 b/mlprec/impl/aggregator/mld_z_soc1_map_bld.f90 similarity index 97% rename from mlprec/impl/aggregator/mld_z_vmb_map_bld.f90 rename to mlprec/impl/aggregator/mld_z_soc1_map_bld.f90 index 507877fc..9a4bc47b 100644 --- a/mlprec/impl/aggregator/mld_z_vmb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_z_soc1_map_bld.f90 @@ -36,9 +36,9 @@ ! ! ! -! File: mld_z_vmb_map__bld.f90 +! File: mld_z_soc1_map__bld.f90 ! -! Subroutine: mld_z_vmb_map_bld +! Subroutine: mld_z_soc1_map_bld ! Version: complex ! ! This routine builds the tentative prolongator based on the @@ -67,11 +67,11 @@ ! ! ! -subroutine mld_z_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) +subroutine mld_z_soc1_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_z_inner_mod!, mld_protect_name => mld_z_vmb_map_bld + use mld_z_inner_mod!, mld_protect_name => mld_z_soc1_map_bld implicit none @@ -98,7 +98,7 @@ subroutine mld_z_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) if (psb_get_errstatus() /= 0) return info=psb_success_ - name = 'mld_vmb_map_bld' + name = 'mld_soc1_map_bld' call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() debug_level = psb_get_debug_level() @@ -318,5 +318,5 @@ subroutine mld_z_vmb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) return -end subroutine mld_z_vmb_map_bld +end subroutine mld_z_soc1_map_bld diff --git a/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 b/mlprec/impl/aggregator/mld_z_soc2_map_bld.f90 similarity index 96% rename from mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 rename to mlprec/impl/aggregator/mld_z_soc2_map_bld.f90 index 4e245d29..590c3d37 100644 --- a/mlprec/impl/aggregator/mld_z_hyb_map_bld.f90 +++ b/mlprec/impl/aggregator/mld_z_soc2_map_bld.f90 @@ -36,13 +36,13 @@ ! ! ! -! File: mld_z_hyb_map__bld.f90 +! File: mld_z_soc2_map__bld.f90 ! -! Subroutine: mld_z_hyb_map_bld +! Subroutine: mld_z_soc2_map_bld ! Version: complex ! ! The aggregator object hosts the aggregation method for building -! the multilevel hierarchy. This variant is based on the hybrid method +! the multilevel hierarchy. This variant is based on the method ! presented in ! ! S. Gratton, P. Henon, P. Jiranek and X. Vasseur: @@ -66,11 +66,11 @@ ! ! ! -subroutine mld_z_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) +subroutine mld_z_soc2_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) use psb_base_mod use mld_base_prec_type - use mld_z_inner_mod!, mld_protect_name => mld_z_hyb_map_bld + use mld_z_inner_mod!, mld_protect_name => mld_z_soc2_map_bld implicit none @@ -98,7 +98,7 @@ subroutine mld_z_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) if (psb_get_errstatus() /= 0) return info=psb_success_ - name = 'mld_hyb_map_bld' + name = 'mld_soc2_map_bld' call psb_erractionsave(err_act) debug_unit = psb_get_debug_unit() debug_level = psb_get_debug_level() @@ -326,5 +326,5 @@ subroutine mld_z_hyb_map_bld(iorder,theta,a,desc_a,nlaggr,ilaggr,info) return -end subroutine mld_z_hyb_map_bld +end subroutine mld_z_soc2_map_bld diff --git a/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 b/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 index 5425f75c..eb619419 100644 --- a/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 +++ b/mlprec/impl/aggregator/mld_z_symdec_aggregator_tprol.f90 @@ -41,7 +41,7 @@ ! Version: complex ! ! -! This routine is mainly an interface to vmb_map_bld where the real work is performed. +! This routine is mainly an interface to map_bld where the real work is performed. ! It takes care of some consistency checking, and calls map_to_tprol, which is ! refactored and shared among all the aggregation methods that produce a simple ! integer mapping. @@ -127,13 +127,13 @@ subroutine mld_z_symdec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr, if (info == psb_success_) call atmp%cscnv(info,type='CSR') if (info == psb_success_) & - & call mld_z_vmb_map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) + & call ag%map_bld(parms%aggr_ord,parms%aggr_thresh,atmp,desc_a,nlaggr,ilaggr,info) if (info == psb_success_) call atmp%free() if (info == psb_success_) call mld_map_to_tprol(desc_a,ilaggr,nlaggr,op_prol,info) if (info /= psb_success_) then info=psb_err_from_subroutine_ - call psb_errpush(info,name,a_err='vmb_map_bld/map_to_tprol') + call psb_errpush(info,name,a_err='map_bld/map_to_tprol') goto 9999 endif diff --git a/mlprec/mld_base_prec_type.F90 b/mlprec/mld_base_prec_type.F90 index 81b2f368..b7661e99 100644 --- a/mlprec/mld_base_prec_type.F90 +++ b/mlprec/mld_base_prec_type.F90 @@ -234,8 +234,8 @@ module mld_base_prec_type ! Legal values for entry: mld_aggr_type_ ! integer(psb_ipk_), parameter :: mld_noalg_ = 0 - integer(psb_ipk_), parameter :: mld_vmb_ = 1 - integer(psb_ipk_), parameter :: mld_hyb_ = 2 + integer(psb_ipk_), parameter :: mld_soc1_ = 1 + integer(psb_ipk_), parameter :: mld_soc2_ = 2 ! ! Legal values for entry: mld_aggr_prol_ ! @@ -323,7 +323,7 @@ module mld_base_prec_type & matrix_names(0:1)=(/'distributed ','replicated '/) character(len=18), parameter, private :: & & aggr_type_names(0:2)=(/'None ',& - & 'VMB aggregation ', 'Hybrid aggregation'/) + & 'SOC measure 1 ', 'SOC Measure 2 '/) character(len=18), parameter, private :: & & par_aggr_alg_names(0:2)=(/& & 'decoupled aggr. ', 'sym. dec. aggr. ',& @@ -438,10 +438,10 @@ contains val = mld_kcycle_ml_ case('KCYCLESYM') val = mld_kcyclesym_ml_ - case('HYB') - val = mld_hyb_ - case('VMB') - val = mld_vmb_ + case('SOC2') + val = mld_soc2_ + case('SOC1') + val = mld_soc1_ case('DEC') val = mld_dec_aggr_ case('SYMDEC') @@ -774,7 +774,7 @@ contains integer(psb_ipk_), intent(in) :: ip logical :: is_legal_ml_aggr_type - is_legal_ml_aggr_type = (ip >= mld_vmb_) .and. (ip <= mld_hyb_) + is_legal_ml_aggr_type = (ip >= mld_soc1_) .and. (ip <= mld_soc2_) return end function is_legal_ml_aggr_type function is_legal_ml_aggr_ord(ip) diff --git a/mlprec/mld_c_dec_aggregator_mod.f90 b/mlprec/mld_c_dec_aggregator_mod.f90 index ecf6f43c..53a5f2c9 100644 --- a/mlprec/mld_c_dec_aggregator_mod.f90 +++ b/mlprec/mld_c_dec_aggregator_mod.f90 @@ -114,7 +114,7 @@ module mld_c_dec_aggregator_mod end subroutine mld_c_map_bld end interface - procedure(mld_c_map_bld) :: mld_c_vmb_map_bld, mld_c_hyb_map_bld + procedure(mld_c_map_bld) :: mld_c_soc1_map_bld, mld_c_soc2_map_bld interface subroutine mld_c_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) @@ -161,13 +161,13 @@ contains select case(parms%aggr_type) case (mld_noalg_) ag%map_bld => null() - case (mld_vmb_) - ag%map_bld => mld_c_vmb_map_bld - case (mld_hyb_) - ag%map_bld => mld_c_hyb_map_bld + case (mld_soc1_) + ag%map_bld => mld_c_soc1_map_bld + case (mld_soc2_) + ag%map_bld => mld_c_soc2_map_bld case default - write(0,*) 'Unknown aggregation type, defaulting to VMB' - ag%map_bld => mld_c_vmb_map_bld + write(0,*) 'Unknown aggregation type, defaulting to SOC1' + ag%map_bld => mld_c_soc1_map_bld end select return @@ -178,7 +178,7 @@ contains implicit none class(mld_c_dec_aggregator_type), intent(inout) :: ag - ag%map_bld => mld_c_vmb_map_bld + ag%map_bld => mld_c_soc1_map_bld return end subroutine mld_c_dec_aggregator_default diff --git a/mlprec/mld_c_onelev_mod.f90 b/mlprec/mld_c_onelev_mod.f90 index 8ddbed4e..1ca988ed 100644 --- a/mlprec/mld_c_onelev_mod.f90 +++ b/mlprec/mld_c_onelev_mod.f90 @@ -489,7 +489,7 @@ contains lv%parms%sweeps_pre = 1 lv%parms%sweeps_post = 1 lv%parms%ml_cycle = mld_vcycle_ml_ - lv%parms%aggr_type = mld_vmb_ + lv%parms%aggr_type = mld_soc1_ lv%parms%par_aggr_alg = mld_dec_aggr_ lv%parms%aggr_ord = mld_aggr_ord_nat_ lv%parms%aggr_prol = mld_smooth_prol_ diff --git a/mlprec/mld_d_dec_aggregator_mod.f90 b/mlprec/mld_d_dec_aggregator_mod.f90 index 3a64e30f..4b5acff3 100644 --- a/mlprec/mld_d_dec_aggregator_mod.f90 +++ b/mlprec/mld_d_dec_aggregator_mod.f90 @@ -114,7 +114,7 @@ module mld_d_dec_aggregator_mod end subroutine mld_d_map_bld end interface - procedure(mld_d_map_bld) :: mld_d_vmb_map_bld, mld_d_hyb_map_bld + procedure(mld_d_map_bld) :: mld_d_soc1_map_bld, mld_d_soc2_map_bld interface subroutine mld_d_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) @@ -161,13 +161,13 @@ contains select case(parms%aggr_type) case (mld_noalg_) ag%map_bld => null() - case (mld_vmb_) - ag%map_bld => mld_d_vmb_map_bld - case (mld_hyb_) - ag%map_bld => mld_d_hyb_map_bld + case (mld_soc1_) + ag%map_bld => mld_d_soc1_map_bld + case (mld_soc2_) + ag%map_bld => mld_d_soc2_map_bld case default - write(0,*) 'Unknown aggregation type, defaulting to VMB' - ag%map_bld => mld_d_vmb_map_bld + write(0,*) 'Unknown aggregation type, defaulting to SOC1' + ag%map_bld => mld_d_soc1_map_bld end select return @@ -178,7 +178,7 @@ contains implicit none class(mld_d_dec_aggregator_type), intent(inout) :: ag - ag%map_bld => mld_d_vmb_map_bld + ag%map_bld => mld_d_soc1_map_bld return end subroutine mld_d_dec_aggregator_default diff --git a/mlprec/mld_d_onelev_mod.f90 b/mlprec/mld_d_onelev_mod.f90 index a109e6eb..25caa9d7 100644 --- a/mlprec/mld_d_onelev_mod.f90 +++ b/mlprec/mld_d_onelev_mod.f90 @@ -489,7 +489,7 @@ contains lv%parms%sweeps_pre = 1 lv%parms%sweeps_post = 1 lv%parms%ml_cycle = mld_vcycle_ml_ - lv%parms%aggr_type = mld_vmb_ + lv%parms%aggr_type = mld_soc1_ lv%parms%par_aggr_alg = mld_dec_aggr_ lv%parms%aggr_ord = mld_aggr_ord_nat_ lv%parms%aggr_prol = mld_smooth_prol_ diff --git a/mlprec/mld_s_dec_aggregator_mod.f90 b/mlprec/mld_s_dec_aggregator_mod.f90 index 67a2618a..f1c80053 100644 --- a/mlprec/mld_s_dec_aggregator_mod.f90 +++ b/mlprec/mld_s_dec_aggregator_mod.f90 @@ -114,7 +114,7 @@ module mld_s_dec_aggregator_mod end subroutine mld_s_map_bld end interface - procedure(mld_s_map_bld) :: mld_s_vmb_map_bld, mld_s_hyb_map_bld + procedure(mld_s_map_bld) :: mld_s_soc1_map_bld, mld_s_soc2_map_bld interface subroutine mld_s_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) @@ -161,13 +161,13 @@ contains select case(parms%aggr_type) case (mld_noalg_) ag%map_bld => null() - case (mld_vmb_) - ag%map_bld => mld_s_vmb_map_bld - case (mld_hyb_) - ag%map_bld => mld_s_hyb_map_bld + case (mld_soc1_) + ag%map_bld => mld_s_soc1_map_bld + case (mld_soc2_) + ag%map_bld => mld_s_soc2_map_bld case default - write(0,*) 'Unknown aggregation type, defaulting to VMB' - ag%map_bld => mld_s_vmb_map_bld + write(0,*) 'Unknown aggregation type, defaulting to SOC1' + ag%map_bld => mld_s_soc1_map_bld end select return @@ -178,7 +178,7 @@ contains implicit none class(mld_s_dec_aggregator_type), intent(inout) :: ag - ag%map_bld => mld_s_vmb_map_bld + ag%map_bld => mld_s_soc1_map_bld return end subroutine mld_s_dec_aggregator_default diff --git a/mlprec/mld_s_onelev_mod.f90 b/mlprec/mld_s_onelev_mod.f90 index e1c7bd01..ce5cd89e 100644 --- a/mlprec/mld_s_onelev_mod.f90 +++ b/mlprec/mld_s_onelev_mod.f90 @@ -489,7 +489,7 @@ contains lv%parms%sweeps_pre = 1 lv%parms%sweeps_post = 1 lv%parms%ml_cycle = mld_vcycle_ml_ - lv%parms%aggr_type = mld_vmb_ + lv%parms%aggr_type = mld_soc1_ lv%parms%par_aggr_alg = mld_dec_aggr_ lv%parms%aggr_ord = mld_aggr_ord_nat_ lv%parms%aggr_prol = mld_smooth_prol_ diff --git a/mlprec/mld_z_dec_aggregator_mod.f90 b/mlprec/mld_z_dec_aggregator_mod.f90 index 1ed1fa4f..6930230b 100644 --- a/mlprec/mld_z_dec_aggregator_mod.f90 +++ b/mlprec/mld_z_dec_aggregator_mod.f90 @@ -114,7 +114,7 @@ module mld_z_dec_aggregator_mod end subroutine mld_z_map_bld end interface - procedure(mld_z_map_bld) :: mld_z_vmb_map_bld, mld_z_hyb_map_bld + procedure(mld_z_map_bld) :: mld_z_soc1_map_bld, mld_z_soc2_map_bld interface subroutine mld_z_dec_aggregator_build_tprol(ag,parms,a,desc_a,ilaggr,nlaggr,op_prol,info) @@ -161,13 +161,13 @@ contains select case(parms%aggr_type) case (mld_noalg_) ag%map_bld => null() - case (mld_vmb_) - ag%map_bld => mld_z_vmb_map_bld - case (mld_hyb_) - ag%map_bld => mld_z_hyb_map_bld + case (mld_soc1_) + ag%map_bld => mld_z_soc1_map_bld + case (mld_soc2_) + ag%map_bld => mld_z_soc2_map_bld case default - write(0,*) 'Unknown aggregation type, defaulting to VMB' - ag%map_bld => mld_z_vmb_map_bld + write(0,*) 'Unknown aggregation type, defaulting to SOC1' + ag%map_bld => mld_z_soc1_map_bld end select return @@ -178,7 +178,7 @@ contains implicit none class(mld_z_dec_aggregator_type), intent(inout) :: ag - ag%map_bld => mld_z_vmb_map_bld + ag%map_bld => mld_z_soc1_map_bld return end subroutine mld_z_dec_aggregator_default diff --git a/mlprec/mld_z_onelev_mod.f90 b/mlprec/mld_z_onelev_mod.f90 index bfc59dde..3f68c9e1 100644 --- a/mlprec/mld_z_onelev_mod.f90 +++ b/mlprec/mld_z_onelev_mod.f90 @@ -489,7 +489,7 @@ contains lv%parms%sweeps_pre = 1 lv%parms%sweeps_post = 1 lv%parms%ml_cycle = mld_vcycle_ml_ - lv%parms%aggr_type = mld_vmb_ + lv%parms%aggr_type = mld_soc1_ lv%parms%par_aggr_alg = mld_dec_aggr_ lv%parms%aggr_ord = mld_aggr_ord_nat_ lv%parms%aggr_prol = mld_smooth_prol_ From 8ee76a1a8297860e920682b1402d528818905c89 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Mon, 14 May 2018 12:11:41 +0100 Subject: [PATCH 31/33] Made test program generate symmetric matrices. --- tests/pdegen/mld_d_pde2d.f90 | 16 +++++++++++++--- tests/pdegen/mld_d_pde3d.f90 | 16 +++++++++++++--- tests/pdegen/mld_s_pde2d.f90 | 16 +++++++++++++--- tests/pdegen/mld_s_pde3d.f90 | 16 +++++++++++++--- 4 files changed, 52 insertions(+), 12 deletions(-) diff --git a/tests/pdegen/mld_d_pde2d.f90 b/tests/pdegen/mld_d_pde2d.f90 index 1c35cb52..e1b1bde9 100644 --- a/tests/pdegen/mld_d_pde2d.f90 +++ b/tests/pdegen/mld_d_pde2d.f90 @@ -92,20 +92,30 @@ contains ! ! functions parametrizing the differential equation - ! + ! + + ! + ! Note: b1 and b2 are the coefficients of the first + ! derivative of the unknown function. The default + ! we apply here is to have them zero, so that the resulting + ! matrix is symmetric/hermitian and suitable for + ! testing with CG and FCG. + ! When testing methods for non-hermitian matrices you can + ! change the B1/B2 functions to e.g. done/sqrt((2*done)) + ! function b1(x,y) use psb_base_mod, only : psb_dpk_, done, dzero implicit none real(psb_dpk_) :: b1 real(psb_dpk_), intent(in) :: x,y - b1=done/sqrt((2*done)) + b1=dzero end function b1 function b2(x,y) use psb_base_mod, only : psb_dpk_, done, dzero implicit none real(psb_dpk_) :: b2 real(psb_dpk_), intent(in) :: x,y - b2=done/sqrt((2*done)) + b2=dzero end function b2 function c(x,y) use psb_base_mod, only : psb_dpk_, done, dzero diff --git a/tests/pdegen/mld_d_pde3d.f90 b/tests/pdegen/mld_d_pde3d.f90 index 50c77756..e8a85631 100644 --- a/tests/pdegen/mld_d_pde3d.f90 +++ b/tests/pdegen/mld_d_pde3d.f90 @@ -95,26 +95,36 @@ contains ! ! functions parametrizing the differential equation ! + + ! + ! Note: b1, b2 and b3 are the coefficients of the first + ! derivative of the unknown function. The default + ! we apply here is to have them zero, so that the resulting + ! matrix is symmetric/hermitian and suitable for + ! testing with CG and FCG. + ! When testing methods for non-hermitian matrices you can + ! change the B1/B2/B3 functions to e.g. done/sqrt((3*done)) + ! function b1(x,y,z) use psb_base_mod, only : psb_dpk_, done, dzero implicit none real(psb_dpk_) :: b1 real(psb_dpk_), intent(in) :: x,y,z - b1=done/sqrt((3*done)) + b1=dzero end function b1 function b2(x,y,z) use psb_base_mod, only : psb_dpk_, done, dzero implicit none real(psb_dpk_) :: b2 real(psb_dpk_), intent(in) :: x,y,z - b2=done/sqrt((3*done)) + b2=dzero end function b2 function b3(x,y,z) use psb_base_mod, only : psb_dpk_, done, dzero implicit none real(psb_dpk_) :: b3 real(psb_dpk_), intent(in) :: x,y,z - b3=done/sqrt((3*done)) + b3=dzero end function b3 function c(x,y,z) use psb_base_mod, only : psb_dpk_, done, dzero diff --git a/tests/pdegen/mld_s_pde2d.f90 b/tests/pdegen/mld_s_pde2d.f90 index cf30ffdb..6d8abb14 100644 --- a/tests/pdegen/mld_s_pde2d.f90 +++ b/tests/pdegen/mld_s_pde2d.f90 @@ -92,20 +92,30 @@ contains ! ! functions parametrizing the differential equation - ! + ! + + ! + ! Note: b1 and b2 are the coefficients of the first + ! derivative of the unknown function. The default + ! we apply here is to have them zero, so that the resulting + ! matrix is symmetric/hermitian and suitable for + ! testing with CG and FCG. + ! When testing methods for non-hermitian matrices you can + ! change the B1/B2 functions to e.g. sone/sqrt((2*sone)) + ! function b1(x,y) use psb_base_mod, only : psb_spk_, sone, szero implicit none real(psb_spk_) :: b1 real(psb_spk_), intent(in) :: x,y - b1=sone/sqrt((2*sone)) + b1=szero end function b1 function b2(x,y) use psb_base_mod, only : psb_spk_, sone, szero implicit none real(psb_spk_) :: b2 real(psb_spk_), intent(in) :: x,y - b2=sone/sqrt((2*sone)) + b2=szero end function b2 function c(x,y) use psb_base_mod, only : psb_spk_, sone, szero diff --git a/tests/pdegen/mld_s_pde3d.f90 b/tests/pdegen/mld_s_pde3d.f90 index 540ea723..26d318a7 100644 --- a/tests/pdegen/mld_s_pde3d.f90 +++ b/tests/pdegen/mld_s_pde3d.f90 @@ -95,26 +95,36 @@ contains ! ! functions parametrizing the differential equation ! + + ! + ! Note: b1, b2 and b3 are the coefficients of the first + ! derivative of the unknown function. The default + ! we apply here is to have them zero, so that the resulting + ! matrix is symmetric/hermitian and suitable for + ! testing with CG and FCG. + ! When testing methods for non-hermitian matrices you can + ! change the B1/B2/B3 functions to e.g. sone/sqrt((3*sone)) + ! function b1(x,y,z) use psb_base_mod, only : psb_spk_, sone, szero implicit none real(psb_spk_) :: b1 real(psb_spk_), intent(in) :: x,y,z - b1=sone/sqrt((3*sone)) + b1=szero end function b1 function b2(x,y,z) use psb_base_mod, only : psb_spk_, sone, szero implicit none real(psb_spk_) :: b2 real(psb_spk_), intent(in) :: x,y,z - b2=sone/sqrt((3*sone)) + b2=szero end function b2 function b3(x,y,z) use psb_base_mod, only : psb_spk_, sone, szero implicit none real(psb_spk_) :: b3 real(psb_spk_), intent(in) :: x,y,z - b3=sone/sqrt((3*sone)) + b3=szero end function b3 function c(x,y,z) use psb_base_mod, only : psb_spk_, sone, szero From 4b431646689245281f4f9d48de6de911ecba19b1 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Mon, 14 May 2018 14:32:48 +0100 Subject: [PATCH 32/33] Fixup the documentation. --- docs/html/img1.png | Bin 2481 -> 2455 bytes docs/html/img10.png | Bin 233 -> 234 bytes docs/html/img11.png | Bin 408 -> 404 bytes docs/html/img12.png | Bin 191 -> 196 bytes docs/html/img13.png | Bin 242 -> 233 bytes docs/html/img14.png | Bin 766 -> 781 bytes docs/html/img15.png | Bin 280 -> 278 bytes docs/html/img16.png | Bin 532 -> 531 bytes docs/html/img17.png | Bin 509 -> 510 bytes docs/html/img18.png | Bin 280 -> 278 bytes docs/html/img19.png | Bin 268 -> 265 bytes docs/html/img2.png | Bin 351 -> 350 bytes docs/html/img20.png | Bin 172 -> 173 bytes docs/html/img21.png | Bin 217 -> 216 bytes docs/html/img22.png | Bin 5826 -> 5817 bytes docs/html/img23.png | Bin 373 -> 365 bytes docs/html/img24.png | Bin 218 -> 217 bytes docs/html/img25.png | Bin 236 -> 240 bytes docs/html/img26.png | Bin 296 -> 292 bytes docs/html/img27.png | Bin 403 -> 405 bytes docs/html/img28.png | Bin 303 -> 295 bytes docs/html/img29.png | Bin 355 -> 347 bytes docs/html/img3.png | Bin 204 -> 203 bytes docs/html/img30.png | Bin 185 -> 179 bytes docs/html/img31.png | Bin 1776 -> 1745 bytes docs/html/img32.png | Bin 403 -> 390 bytes docs/html/img33.png | Bin 511 -> 511 bytes docs/html/img34.png | Bin 1582 -> 1542 bytes docs/html/img35.png | Bin 243 -> 246 bytes docs/html/img36.png | Bin 476 -> 475 bytes docs/html/img37.png | Bin 482 -> 483 bytes docs/html/img38.png | Bin 250 -> 248 bytes docs/html/img39.png | Bin 761 -> 760 bytes docs/html/img4.png | Bin 705 -> 689 bytes docs/html/img40.png | Bin 259 -> 257 bytes docs/html/img41.png | Bin 245 -> 242 bytes docs/html/img42.png | Bin 559 -> 538 bytes docs/html/img43.png | Bin 2488 -> 2405 bytes docs/html/img44.png | Bin 233 -> 230 bytes docs/html/img45.png | Bin 473 -> 480 bytes docs/html/img46.png | Bin 235 -> 235 bytes docs/html/img47.png | Bin 506 -> 502 bytes docs/html/img48.png | Bin 377 -> 378 bytes docs/html/img49.png | Bin 294 -> 289 bytes docs/html/img5.png | Bin 629 -> 643 bytes docs/html/img50.png | Bin 257 -> 256 bytes docs/html/img51.png | Bin 283 -> 292 bytes docs/html/img52.png | Bin 276 -> 269 bytes docs/html/img53.png | Bin 550 -> 573 bytes docs/html/img54.png | Bin 228 -> 227 bytes docs/html/img55.png | Bin 257 -> 255 bytes docs/html/img56.png | Bin 540 -> 527 bytes docs/html/img57.png | Bin 542 -> 533 bytes docs/html/img58.png | Bin 378 -> 374 bytes docs/html/img59.png | Bin 1189 -> 1167 bytes docs/html/img6.png | Bin 525 -> 537 bytes docs/html/img60.png | Bin 274 -> 273 bytes docs/html/img61.png | Bin 389 -> 389 bytes docs/html/img62.png | Bin 286 -> 283 bytes docs/html/img63.png | Bin 283 -> 282 bytes docs/html/img64.png | Bin 271 -> 266 bytes docs/html/img65.png | Bin 550 -> 547 bytes docs/html/img66.png | Bin 413 -> 415 bytes docs/html/img67.png | Bin 242 -> 239 bytes docs/html/img68.png | Bin 290 -> 299 bytes docs/html/img69.png | Bin 448 -> 458 bytes docs/html/img7.png | Bin 1071 -> 1059 bytes docs/html/img70.png | Bin 587 -> 605 bytes docs/html/img71.png | Bin 619 -> 622 bytes docs/html/img72.png | Bin 185 -> 180 bytes docs/html/img73.png | Bin 211 -> 203 bytes docs/html/img74.png | Bin 202 -> 201 bytes docs/html/img75.png | Bin 250 -> 249 bytes docs/html/img76.png | Bin 447 -> 442 bytes docs/html/img77.png | Bin 200 -> 192 bytes docs/html/img78.png | Bin 197 -> 199 bytes docs/html/img79.png | Bin 316 -> 309 bytes docs/html/img8.png | Bin 259 -> 272 bytes docs/html/img80.png | Bin 329 -> 321 bytes docs/html/img81.png | Bin 207 -> 209 bytes docs/html/img82.png | Bin 206 -> 206 bytes docs/html/img83.png | Bin 270 -> 272 bytes docs/html/img84.png | Bin 255 -> 254 bytes docs/html/img85.png | Bin 176 -> 166 bytes docs/html/img86.png | Bin 582 -> 574 bytes docs/html/img87.png | Bin 224 -> 248 bytes docs/html/img88.png | Bin 195 -> 188 bytes docs/html/img89.png | Bin 211 -> 209 bytes docs/html/img9.png | Bin 258 -> 253 bytes docs/html/img90.png | Bin 518 -> 506 bytes docs/html/img91.png | Bin 549 -> 547 bytes docs/html/img92.png | Bin 306 -> 300 bytes docs/html/img93.png | Bin 546 -> 558 bytes docs/html/index.html | 12 +- docs/html/node1.html | 4 +- docs/html/node10.html | 4 +- docs/html/node11.html | 4 +- docs/html/node12.html | 12 +- docs/html/node13.html | 63 +- docs/html/node14.html | 107 +- docs/html/node15.html | 32 +- docs/html/node16.html | 4 +- docs/html/node17.html | 4 +- docs/html/node18.html | 10 +- docs/html/node19.html | 4 +- docs/html/node2.html | 8 +- docs/html/node20.html | 78 +- docs/html/node21.html | 4 +- docs/html/node22.html | 4 +- docs/html/node23.html | 4 +- docs/html/node24.html | 20 +- docs/html/node25.html | 4 +- docs/html/node26.html | 4 +- docs/html/node27.html | 4 +- docs/html/node28.html | 4 +- docs/html/node29.html | 4 +- docs/html/node3.html | 17 +- docs/html/node30.html | 4 +- docs/html/node31.html | 4 +- docs/html/node32.html | 4 +- docs/html/node33.html | 4 +- docs/html/node34.html | 4 +- docs/html/node35.html | 4 +- docs/html/node36.html | 31 +- docs/html/node37.html | 8 +- docs/html/node4.html | 6 +- docs/html/node5.html | 4 +- docs/html/node6.html | 4 +- docs/html/node7.html | 10 +- docs/html/node8.html | 6 +- docs/html/node9.html | 4 +- docs/html/userhtml.html | 12 +- ...2p4-2.1-guide.pdf => mld2p4-2.2-guide.pdf} | 2079 +++++++++-------- docs/src/Makefile | 2 +- docs/src/bibliography.tex | 6 + docs/src/userguide.tex | 6 +- docs/src/userhtml.tex | 6 +- docs/src/userinterface.tex | 12 +- 138 files changed, 1368 insertions(+), 1267 deletions(-) rename docs/{mld2p4-2.1-guide.pdf => mld2p4-2.2-guide.pdf} (94%) diff --git a/docs/html/img1.png b/docs/html/img1.png index fdd84f66725d25c158959b1f708936c1ddbef3fc..82537736e6ffc08f71c0011830d9113d1c584bd5 100644 GIT binary patch literal 2455 zcmbuB`9Bj51IOoBj(wSstDMEx5lv`B%sJ<1Ae^T z!dBqvpW?(J5!V2}U7sj40RVgsR%XVI_-7la`6soP1(hBk;zcdvd7INjr-jZ?40VCX zt?^EM;JPo29}z!6HUryIpFhWr9*9Ls7+5gR+5Dsa^vA)|+mYyXb|VLLeh*E1PKLhI znm>vf*B}2Mvaap*Pu9lK2wcHU8^m{CQE?Jm(5$Z^c1t<$H(EF2c%#)=3lBdcy~^^2 z-q6EPb;|^4|91>fb%MoN`v7aSHso>2C?6N9eS~Q*{_rx6#2E)LP~25+uKLjfo1u3% zjo8=??OA`zVk}FtOjuf<3;ECrk^xfiiCPB|QTK6c+b*E;$n{dp%X=+JwpHnl1H=(7 zUH?QQ5P!hU#L~%aRk7X-Z8t{wixb)?-8tQuU|XI=9cUS4U^#i$E?5%LP6F5m7-D|r zXez+9uAj}>vkr`Egde5E^xosddvVTf-vTd22POvkR_8k#Q2HAp>Oy~hdd4IeniwLW zL`j1Wq5h5M2LhvV+8ArkXFE^MFN(wWG% zQ`arJKEdR#iPrN(0I0Tdm%$-IqOy9^iXW<8UIl##ypCOG?VSvZdA1!aUFX&EinbMM zH{P2<9r~pc0n=FW=_ja{`p6vNZ_!qA%unRK9O+mHyFy)H?~h6V$gsaz-Z&g}?Z7&a zxzmf~#5XyWBt!Yjrzp-w+R-6XQ;o|e+_ghCbO&wV!o_CiBILI$8~kKr^RqkX02_}f zF?{POIVaJI%HnnVH55m=_iBIjixNzv*V+9~mi4M{kG#-28o%1n3{nHIG1UfA*V#4M zZ0=fi6P+OgDUQjaQRj<;eJh&7&lgR`#K&*p~ZJ#@imM zGz)hrA|u(OLX#eUn~a5@+u*uS(1zjpB(z;IABi6fH^4$3tYEa9(X)J4K@|mI6^*?X zkf57SwfSVmsctGN6wbPBb2-Ey*~+ttr)zS)sajICtos=K2TUGHRmc z`;Aps6R;+8yOeA}{~d46)I5y?EFRdiAIXoy62p+;57j|q-$}%3D0F#Nm+>Ohb80fX)YKClPo|0{1c(=Kfs#E=6Lw>> z$QbsEsOJT0vxh|^^vT;vqG}tu(UMAcb5`R&D-fOKCF;10`6S&FS1!BxL$>`QcQ0V4 z=~FBoSPV(mis(SPL-B|7Qr+}rkbN18s={Km)oq$uHmw@GmaNe1^7~5mN-5p)f~iAj z3glfeC+&t+ZYoc;&x_;8U&#gyk|N(l&TBdhqHPZ|o7OFKkQG_JKP+(Uo3@hT2akFZ zUJoHEa(2Upxq>fa0UUD$Q=HY7Oi`e=E_S$b1s&_9p zi`%BWkE4=F8(e@X%Sq-{_5F3HK4svQ_n42;)}mUX8#uX$z?^K*&s1zs#EnVSzM-co zp`TrS6hpBwf3<4p3GyG8@L+8P6qK35Pu*)oNlTYk(2VOSp$bMsY(eQ_y%rkYwI!o? z$r@VBwWw1h*?aJwOd5WOojD$E1J{h>@l|cpPI_m0&d`=CIIBLZml@grxGjrKfi6GQ z@QqPs6pCj5yVwy=wW;(4=}fGf1P)XX>q8E+U@V_1!=YGevOb~OgQM4)r}GPP)yw2AH_E@gls~1@-RUG(P1NA`@d5c~h9=(Z$@jbkmvF*8aeS@! zaWX7MTYyodnj2IWe%qSyuQV)V<3x%d`rHx}G-~e_#rV0{RD5&;C+qkvq6=A> zu9l3?T)D4ARjS7hiiN6lw0ov}651Tyly+%=y*ZU5P~WyX{z#K0`dY-#Sw^=1z`=W~ z{o?w?q+@rW$aZBrCi2VEf0z{p&dg{w)T0`Syzh9@h6+bmw$@ z;eQ9r+q?s*IGdr`VrjP2mo!+sbc^6-I+<*+NZ`+N>1 z$bPXUm6S2_4oYd&xD}6=N;e@PfI@@bb*{ZgW}6_e_vQvYtb%*p-e< zA$lM(Qi1?o1y3T`*@Ot1w3pYZLQB2+IES1sx}^i@;C*q}C(@0@;*>lifyRe)%;`Z7 zrhUonVTz%uJ7TNT7=O4A>YO_U(=v}Gz80~2H_5RD$btN(JbDP!USv&;Z{PF?v@&o2 zioLYm_i7@Rz1*-9eRM4SAwQptU>!4pcjkj^Ru;a1_e_u4my3SOUPpIOe@+ZhWq(}> zRv{%G%#E0qyxsbh^J9Uuus4cZ*|giVz03aef8uYBvfx;QrAF0?e;=2XIl`>Y1e5Sz Dq$ literal 2481 zcma);_dgVlAII;|$#KZY*+p^4`dB%cNpaC3dmNE<%FGBKo5+aHIwM)x`)so5iaVXl zC?n&H=yXc9ukRo5eLTLuyk4(gUaueCkM|GH1fYc7P0893^m1mAT(%i0>ZsPdhdsU<-b4 zlA#x}Z8jqJ>GSA*GU)ipdRnuUjH1(BbcIcgYAZ?Z;%<9hBfa!mD61LKZACui*GmwbV?yGQ7QzyzDd79}yV+u3M0|pk^ zgipC#`wWZ78?mrnyE!J@@Sr)I;nqLj5!XbM2Z)L)DpAWWG+Afp&pR=pRp`6Aks-GO40HN{f?%CM2g(wV7+3?CnNe!{~xCOU$~@XU7+0&cKU2>ke;zr~JG* zXYZbjnh#ix9N2Hc(vtJZ;{W83ly5lqR8csQT+r|@{QQD_g3C5hl(F1 z_rECSx0rIh;KD?DvYa%>ZZV{6M^t!s;`<$tdn-q)2+{m6q|PDR-VlganHV@^@%Y%w zHdFFIVfgD^OKp~P8qZ$aEG~ilE1aWMNDIVwrHg?DD=qgEi{NQxyeK;dM$9Y)wLg9( zB9gYGliIo1n{kx>c-!*IaVSHSeq}N|?({}jGIOYj=EsF$3XvF89=kTT^Hr{aUd3+> zxKi{K1-UiEQ5nZyceso~{di4D0VmXyRCAeAD1Uw8P@%7_Y+559q zcAGZ#Dmz=!qA{ckYcUIVjnvA(~4K^F#oTZ3aNxKt}%c7racSu)a2P&8XI z)JxbY_OcbQVd8c-euKlr8l|+sR6^i*XxTNFBYY#dcO6 zzWbq);REj{9YauF4ZoPvX^uX;+c37>*+df*QltL3`BPwF@T`mSx zPIHceZJoSoJLYB~qa^_Ou@5WSqOlgUb@Ab&3KjC>8hsq}rN=}5;k9NKm1*D%MN=s8 zAoZ%4?etWDWX>hPbW)ZLXh!#@34;r)_E5k1G|fUHycBqJ=>|4EXP5Xw#dftwT7UO% z-WV~RISqn}`yfaT>1{7JtC}HqD%dlt4;$LuW>%wI&wP*AZxvc*4eh4)q+VeBtaEF& zYgonDnTe8zInueC>mLnCC6Kz!gYWj>J>G_UPSBNH@fa*<02s2V>0?Uuw37b=Ig&E zFWwSkWZkW74xcD_tx(xW2&#Z_&xxPEy}&m#zXs&B+H)$9K&mA7UGeZ2T;XF8r;*_C zOp>f>G#sNp)%a1V|FY^8`{JCpp2GXBvF+Y6xo@og8a)#Tpkie-B%7IV+W)}2ujFKG*H8F@9zc}&mPqt{?P1c_X?mSwv#H{aZy z_~jO@f!6Tvr~bcZ({XqnpYTXVHlS^S`C3k{5#-7G;q^<>?49Ev+X z^9=l3dDqJlYr~%{nLmmfET*_BoE2*PoF2vt9?a6uhRE>6Q6?x#-ZLi2WBUncgaE4R zi>cCu;AEm4g?^Q=8Zr^%i; z?!lbc5ynPAF5Y7qHnbo2sg#4ryua&x+0fTKotP1WH{)l+%w`7uuMA_5SJNEAGi#3v zX~l(AqALpmLp4FouRtjOI@gSvMpE{88)l4nEVSsk>Sz!zoZ*-D;xH8wt3E=8w#PMU z-uPkblRQWeKe_vOlOkByEzXp!mY_b{1=2Q58Qaf!sR?tzhK~Iy`kEYB8Pbwd@{s2V zkAn5*PYPNYuADa$DEViwuEdGqYOAJB$7^GBL*~wOl81^;pLn8TD-m1tsK7yt4`XJ8 zb9YREiIHfT8y;iF{w=*CJt1A{S)zMhKvyu9hjB*tqLNssxLxq5JKk^DOB?7uOm&QH zuqjR|rI6UF@F~Si@21Z1Vs27Np^c)L+1WTIL4BixCl8Yu@BFf<<3tsD40~t<0C{%G zSE&&{!VH3|DROI2`y>sz&7;vwEuH$iLueeqeWWaCQ0bZ_Sl7xgjI=%QP0~9da}(?2 z$SO~uR}Pj3X2$BYI*nguFik46*jh~Ufay1BC2%{%0A@%@K0OZA^=v!fVk@?Eh9ij_ z^jGZa2D71rBPJ`7{A{?DZl082Ckt;ztfl#lW`0QGX zgk68z|F=A5*ZCy!jiId(&YzS@z)wm1Hl19}dT(^JOR1sFc_xo6d=KR6(RY>Hptc<@ zg$+ND)#N!XP+ptTK3b-{B~*p{Yw&$-yM3cfxY!#9JjWPNY!#$!qf7;6`=r-UrCa-d rLd`dS5kBGMZm&Nq&80psPI7Iyigm%J0 diff --git a/docs/html/img10.png b/docs/html/img10.png index 764b81139c6bffcb1e8e58e9bcf15870d4cd78bc..1b225d49a5381f028c451c32efaf5d02c7223a5e 100644 GIT binary patch delta 201 zcmV;)05<>W0qOyeDS!X}{{R30?(Xj0-QCR0%)7h0s;a7)nVEKWc8G|GWo2blR8&Jl zLozZlAt50?Hi?)30004WQchCrPKFq_Y7hsg zx^ogkPXR<30|N^K!^sXLs|9@65zg44Q%rr&Q4;_Fc-Rs-%6cB>00000NkvXXu0mjf D0wzpY delta 200 zcmV;(05|{Y0qFsdDSyDgz_YWnCMG6;fPhR)Os1x$85tRKb8|mGKbe`CW@csp001*H zGmVXnSy@^6@AJt30004WQchCDxHGu|%z4Ma zw@Tnm0Yq5<1H%M{Q}2*$-f)K<&gN~9DW$HzXbJ#vI2gj}-L?Aw0000KBu^BopJ=8XlY0$td&G8&-rk0Y24a8?|eCSf?MwtoSa@vINnra@RWV0W;# zu+Ib=&r+GdJd?o#EXA>5${rBS)C+N|THGX#2_WOU7@9eF9TLHUJTnYZKx(=JAm$a- zDR4BfK49Q{z|d4|sK5*H$5Aj<4^_ipu!4cNfMWpz|B0Cn2HgxC5Pw)408#A66`-n~ zF&G-~6fih~bbnoEV2Aoclnt!v1Vk0H5W^f+MH2-_5J!k185&FiArNow00$uZ1%~6C zft(Ed1`H_-0t^MvU^+Gd8W_7ksyG@LIw$F7GO)E~Ixwt=gcxtYzzPd8W>8=<149TL k_N+j8W(S5*FbaqU0DAp3#vMF0hX4Qo07*qoM6N<$f&_P!D*ylh delta 395 zcmV;60d)S91DFGl7k?rI0{{R3|EJl-0000mP)t-sz`($>v$G~9CV+r|OiWCsrluJg z8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001bW%=J06^y0W&i*I7D+@w zR5*=eU>KBuI}M8+-R*AYxkIO`djrlW8cyMI0|jXSD(AZie|_DSn5Yy z|G<~Pz@5PGu{1`23F41?5WChvtq<^LU@G8uVBosHdqThu27ZV?;xB;d+Cr$RWQLdk z-U5a>4}ffS27h*_Kh7~jRDA?ftOptP^2tOB%mHx@GMGYx>A*{f5ih=i?Nwm7&i#g) zfh&N)lHmYD0W_E{Z-83#!WHD(4-CII3RyES|FfRJ;Qv|x;!p-Yc$me5tOE!91Ym#x pJUBxb93V;&0Kuhu`1Y-J82|tP07*qoL2y?fQFRWoPKEGsMP z=;%mIO$`YNadviAR8;)vc3>t@9b-w5UoeBivm0qZj<=_aV+hC0=yGx`&YX)8CTWv3cLJn5*BznTdg63olTC7 ZjUmaDkM*x8YXi_c22WQ%mvv4FO#lEBJMI7g diff --git a/docs/html/img13.png b/docs/html/img13.png index c0e0675d65e796fe21d988042dd3dca5b4710d92..55a924725436f92aa03ccca2ba9e370b09305911 100644 GIT binary patch delta 218 zcmeyw_>ysgc)bD(GXn#|?2L9#Af+DQ6XN>+|9>F!?%lg*&Yao3d-tkUt7gueSyooo z(b18bni>)k;_U3KsHphS?Z8Z+I>wS9zhDN3XE)M-oB~f5#}JK)$q5TIA6PW22{0_w z3S@~~#iG!Y8_>wK!XhMsW3|C)#%p0Zhu(0{3Qrb%7MvH(aZKsV4px_8)JXDQntz?>^mMHklbVguIuj`EJbq#D{iR)|=R#kn!c6YbA zVoU$8yaQ=ZQ`<~^B3iZ^>R2?oR&X9(#_4fLXZ!Sc#*2JBHX3P*ndRObTHK(sflK>< bA`gSv6U*mO?;1;iPGInK^>bP0l+XkK4jEPK diff --git a/docs/html/img14.png b/docs/html/img14.png index 7f5706eab9b758aa2ee1ca0994846172ab006ef1..1d415cf2f69513dd2a1be0c3a261a70e500f5e2e 100644 GIT binary patch literal 781 zcmV+o1M>WdP)KmCtL_U>L`rrD^jfjazSmr{E9Ju4uQz$gw>Prl)u) z7Q9q1L);+@Wd}V}hc(VBQSiq>aD-`xr=XXD9)dVFv>-zSz4;FaJBlaY{CMA_&5v$v z!Arl8=KVg&^Ld~5&65;htg*%#%T-GI-;hxhFcf4f;aUdZ_|Ood8Zf1(cy3M!Pkec? zXrDQiF{nvW5`<_4@=^pV{b|t*m+rgXo-(SD% z6k+xkx6ac&KJU%3P*H^Ew}S>-aXMr&Ul^VN% zaJyrOXeC1I0uVm(Qp<_KbjsU;M*!m9MP}P+i=_t1MOhGwg=?87H$af!H8s%%yabpq z6CtDk1B99#gDV%jKKKAIqk0_tXvprJ%{wEs#rV@;!)Q(Iakzl@xCYYLk&u(x&OHeQ zA5l}0;FLZ118Lek(?D|B&3Dd76z2UL$3*VH-%8c!1Mzl%%Gyxi7TziLh}Muu@F~fi z{PEo#W%=uVj$?2ETt|g2v4<;b{UCVqo59z_e5Sw&eCBh3;Db)5V>!jka_=IEP(+O1 zgF|{BNIiy^wF2f2DPBa?@JG#6Dhgu4B%L4z689aQ3RZTG=7RY)CLt1{!wlsd5K<1V zR8VQ|LP1K*TMDiSe+JIiYXd>#-BvKNS+ak*&ktA8{cnl6mvnzD@7{$ot2A%`Na#7U zO{ahMBfZ-)l|dkJjkXV^N`vQ8W%~ZZ$BQ4q{6j&Gj-r5(K!(#lR8+<>4YYE~00000 LNkvXXu0mjf_*ZOC literal 766 zcmV zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001 zbW%=J06^y0W&i*Jd`Uz>R7i>Kl+SAuK@`W|xJi>VZf4a`R0y6tSv8`fpq2y=p%+c> zg)ROC5h~V$vK|Uvv;mI>Z-5}Fy@Oe#F_mk1KsuYYk2xLJwLN_Pc11^b-%wGZzbd6-*> zWMbcF{uX#bgxn`VAyZl63nq0)X&<`|UQ33}S&%ZJG*n5N%mGhGlb!c8 z8iAD3LdY4o3^H(^gGE&;0%_?uy(o(BaF3Y~#_bw76?@bC z9stqWhQ~))hz!Rowlg_iuh)A^S5@~GnM99l{0Z#Qw}JRP&e1B5vB8!u}<89u2I2QRlHb-G;+kY+!JRwCWxy_gZHV>CO~2hkzsoE#_6Y wIK0==+2O5t1m)dlxD)LgL3tG1;(tMZ0DIi<>&n`+djJ3c07*qoM6N<$g0E9tYXATM diff --git a/docs/html/img15.png b/docs/html/img15.png index d22a82cca0c5cbb0d57a261c6a06dbad7db67fd0..b13cea97be4262373ff79727726d8c17860fb992 100644 GIT binary patch delta 264 zcmV+j0r&ox0+s@h7k?830{{R3`&#KU0000mP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001bW%=J06^y0W&i*Hlu1NE zR2Y?GV4wqF?trn_P{hH)1q=-A6A@wo3=Bs>bOR7G!bMpH7=IW9%mUDbc?B3)kECxv z7oIN4z;PUCYsZO>0)#NrR8a<=84c)Wb0~{3FtQvdKobsUkYI>rI&J_KW^ZhV3O4|S zVJrk--_h|K$}~U{)?i>b!+;5z7#Q|qin0P-(1;<*vhWCl#lu!qK>#(w9R-=*CIJ8d O002ovPDHLkU;%<8YGQ%_ delta 266 zcmV+l0rmct0+<4j7k?520{{R3Fa|o70000mP)t-sz`($>v$G~9CV+r|OiWCsrluJg z8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001bW%=J06^y0W&i*HmPtfG zR2Y?GV4x;o{SRX?qlklr3m6#K_aMX`FfiN$(I0@A2QJEYfPaDEK=1=}VWtBNd^gP- z(1o|3W8l9IwDte}{{;wP#(n1)c=vxmH=AGdFarn+)+e|4;=1!|X02^M2gg Q00000NkvXXt^-0~f@tn&!vFvP diff --git a/docs/html/img16.png b/docs/html/img16.png index 7903ab111ebe820c03c2a863695a2441c567dd83..e2714415104e9ab3534ee5b11aa0cf99d8cfd1fb 100644 GIT binary patch delta 518 zcmV+h0{Q)v1d{}i7k?ZC0{{R3u!9l90000mP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001bW%=J06^y0W&i*Ikx4{B zR5*=eU>F6XfTqBr0me$eFO9@x?m$t)0hTCWV5k(pW&}qAHh(6n5j+7P5+sY&2#7Q~ z^C*fMM&?v}MnI&|nF3~T<5(FOV%)0n83B<-QVHf9N#6id5XivLQveK|juRaP=ti*i z?C4kul15U=zz}h|qq~9QI6~P)28NU1puy$}{s|0@2`4+yRQ_aOI?Xeq0j7wvFn~e8 zhaHCzjt&ew2Y(>a2$d`%3=EBoEC-;DW6%r?VBMfo3^AfYq5##1`M?m|3Xw*r#M15LqD$$fxv$G~9CV+r|OiWCsrluJg z8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001bW%=J06^y0W&i*Il1W5C zR5*?8l08eqP#A?zglIp~q_ZOU13J`65ET3aT5v7&FJuu43V&vFQ42bDaBy?5vj}Do zii5UWt3}PGLz`a3FT@gWlIHU!MR4sI!h3U`d+wVz7Z_`-c$J7#x{(pK9WEaNjKD9Cim>f)sjjbmA^Bp5Zo`7p-F5Jncw=}4|shEgr z1(~L8dt~wo_z}eBusO_hHBp(}up_n`axmhIPH@k*Ju*!Xx_jnYg(37(bgmNts~wuc zkclSvx^G~z;A}0p?{rhv@>uV$Fl36L=j&F2z?|+yB!BDrTb3cKYsS0}FB{)V#0LzO zKEgzeAlsP+kEsBI8PXqK5_0;$-=(XsQe27fm zxc*WBhu0PUqoKtmlyaY#ez%6HrpqINi||z<(fM7J#C`ih+T(XGg~l z29ONX0tRLVeg`I~+)oA;G1epL8&EWC0%HCN3_2UYGMPZ0KiqN=28J^n$5CCxx&TNx zIxuhufMs|U7#L>5Odek9NZ3xHm9xer9AjP=Ks~ zA4Ke7U@$BI%YT3@`~sI-8rr20&2-!V$PNX8U?9U5B=duT^*94qhWP?RheQHYgJWsL zBA8~lh8U3Nq&nIZpb`Q|w$Eo^xXFMHKpHraR3U5F&A{*is|M}^*fsoQV3vTf_nZNO zV?c%v$a4*FHB286>VeU~D#3@`XNW}MZ6d6J%>jwS?tnuTGC+1UGZE@X!6+DP008^1 VP`^8#Sv~*&002ovPDHLkV1l^E$2R}~ delta 478 zcmV<40U`eW1N{S#DSyDgz_YWnCMG6;fPhR)Os1x$85tRKb8|mGKbe`C3=9lrW@Z2Y z05dZ)jg5_2Sy_pPb2I<|00DGTPE!Ct=GbNc00DbRL_t(IjqQ>#OT$1M#b0bg)26-V z3n=b7xH&jjCpRhDO~H>~K7pj0Af=h5LKg?=(2k;l1s&>?fPX`Es02iCu`SwF<6Uf$ zyVz1!r4R17|NY+Me|HJ+k0iU3$i>s=s>AJ%4Gf9gSB=;bxBVEgC3TL(H6)-k$aja{ zy*qHw+;W6K0U#e`w+u$49Au3{RiKr*>I;E5JK!adsd^+!Z*=H0#ejN}CbrH8Qfw*#JGw_$!_$Cm zbO+jt)Xvj&m+6@ULWOwK*grY;A3 zr!+S1o!+=`Im4>*OT}z$52Sf`)U6jV@v2MA=sF@H!BTT$A=6!+oE#^fHPR(r2WzIa z$gzp{adW)36lId+s+cHq^q|0sbqi)R=p2YRG+{-907vqJ_yZTZpB&%MdWTE!|Ez^E Z42?^qkDFTF`2}z%h2bc-5%V69DfaQ8o>(t-288y#bgH8i%rcVcvD*xz{YfLp^u*2iBNHXKO# z$2~{bPBC)-#Gee-&32Oxu1q=-C5Me%J1CUTGU|^UG;Rgl) zi9`bih6V_~k%57kp^pL1KLax96axcG0Rzl>3x*SLPL_Plj5Rm}q^IiZFOb!eT(_|rho)17mrhtKAD}?{% z0g$i>U|{$F;s0S^U}gBm0O#KYnRJDLfwO=CW_>)veYo*J>seJ9elRfX1anzGo&VpZ lz##k2WCDsW=7DTs005o`B%*z>U%mhU002ovPDHLkV1kfyUAzDQ diff --git a/docs/html/img2.png b/docs/html/img2.png index ee136a211a75bcd99179444db703ba63a40d3cce..3c901a59eb9797cea6fa249019f9517beaeddde7 100644 GIT binary patch literal 350 zcmV-k0iphhP)SU>F5-1FU#u1F>khr~qSL#G<1X#^5Xrz?AKPF*F0Q z$UcKHnhX;dSZ1nCN0ww3oe8m+wScjK!JX}Dq5%U#Cq01e?SK#^5c;QRnKSb>520+4F}3b8$B zfZ!OA5zoNg0Fn&{DiC1%P{n-~%&z<9w??(OZ3jEwATFE#=48B2ovf*Bm1-2h46 z^>lFz(U_Q=Ai-L~TvL&HKjGp6WrpNe2^Rxdk_)ce9GLR8-EhhMgo(awhIYp!3<}~E zNB`HewK3GOi)7#AvG8xoIL6Pj$H939S3pWC%MS4dUa^D+0SraV4vNPL#aVbHB;pJU zY8X!1v1?fz*t4MRq3otO!!~!OGvSiU=FC0t>+PS%r=!pCPDtHpZf;~SzwM)wq}rl3 vHw_QYGzG;*k3E~@KX@8(J(!%Dz`*d%$X2gyzT`!qM;Sa_{an^LB{Ts57P*1g diff --git a/docs/html/img20.png b/docs/html/img20.png index 39e252e2193e4ffc8e872c88c5af254bbbf573e8..de2c1495b93ae8cbf51affb85e1ca46d255f4531 100644 GIT binary patch literal 173 zcmeAS@N?(olHy`uVBq!ia0vp^0zk~q!VDzkV}oRXlyrbki0l9V|AEZAckk}ry}PWe zEF>hv+1c61$VfmyV3vWpGEk1OB*-tA!Qt7BG$6;p)5S4_V`g%~0rnYpon#br+%(Q6 zWH6*!91>Z2P(sNd_D}#@Hv@AsQ^&z+2M#=7Fl{@@nAKzD;kER_(XDeE85tP1u>QW2 S_~a$fECx?kKbLh*2~7au);5j+ literal 172 zcmeAS@N?(olHy`uVBq!ia0vp^fL5}GT-CJS|FdXB*-tA!Qt7BG$6;`)5S4_V`g%K0*lrp>x45L63w?G>GiU$+ diff --git a/docs/html/img21.png b/docs/html/img21.png index 2add4701371024993ade7b2fce7b9b1353303b58..5f0acfca5eac6675d93d9c28977bd34db3953fe0 100644 GIT binary patch delta 183 zcmV;o07(DY0oVbMDS!X}{{R30?(Xj0-QCR0%)7h0s;a7)nVEKWc8G|GWo2blR8&Jl zLozZlAt50?Hi?)30004WQchCSmg518#k+uk!5z#}EMQ=m3}z)7FfcTLS$zyJ)-Wjs29^Ra>jX?ILpKA% l6bMVFHOm2Nv1g m!%7HC=B>#DsKs+HfJgu~;1dva1^A!<00005&{jq+1xek%GqWX|8!##yo3}Npk|E8`vt#Zp0|tbPHA{ zyQb>IE8pRru@zj#o5N6bIWGz}lx_oEFcw){TZ9I`#(J^5W+p?#!$O=OWoHc_3s+a8 z0P||k^~hNR0RLff-~q;0@ddgwe(9{3-%X@%cu<>vn|8|)IM0-oZZP54BVlzI zc0Ot*R zSzZh-A_H(ZIZP_&fr!ufnx`!=Erc(TZ`fNtlUe`^JQEx`VbEx}BVTr_%kiOkgdZlk>jzhlF}2$sq6~P~!Tmo%~{m0{0n1ks6D9#YJH| zL+wudGaGLq9=??Qwzwb8&NK9#w7hIDz~)YFaCw*clb8GiXGRPmeSEBHFWVpLm8uqZ zRaY#8$3&@n-%H+cS{;lyz}CA)ROG*Y=?`U^?gYqnFckUdhCkbcl6<)*Up!oRBt9@> zr@#iVz)JLX61?9Z?UrEfvjSC07*$}3-oyiM?M7{}mW|~{Vj`5I17^r!oFee|NuGK- zhwdfzG zTM_t&G(FUU8R!e5wadW=8pqS8eo~r?$cl@ubM@7aCXxjsggsAO1CnyB zTKACdHR)jIFG=7TYMj!fbFfJ$uwayJL|o5>jE2b&~VCjL@)Wu-QTSHMLrC zkRR~roE?LqVW&%Owt3$rc-7yTT3~%gTK;xPb)q(NhWpq`mJVqm6WJ7nXvEV<#x3qh7<@B|CP+Z)$kTNSk|n$)I@yiUmV{j9fGra2m==wDIO47vkGxiFL+E zsysJ`OTM<95&6_Dza zPpr$;?ro7P+r)wIlky+aTQUm!TUOJ~3etQdHuoCzRrJ#RsfLcj(!(N|#U}@UD|YX^ zliAJy9ZBA<0pMy?4OJ?Z;;!{OWRwOKCyCkxCk3;1?PBR!>aU675QIu!uZ+EU79=ZL zCZ;yZX#3sVXPi$8SM{AOISc#0){G!QVz~J8IQcHJLd?l0V@eLwweyhmj1N{D0 zY?SsVHXg+m$FZ4%y@^e4f2$D?9DPXj3P-2Yk4{II(^gIC399eF>1@0)80KFPm2ZJiN1s-v4-L9ffk|e6v1-mNl?C=JBW5c%bg4aucrHMflbGIfCvyp!_iFbhNi?_Z8Q{qs0_)Za@cU3z)f z7%aP@+l3pZo(fdG(p2}{ZhVbz|6SW9%`3|Y)JX_-Z3dp(b-^vW4F3eb=DA0zJp5lQcj?z)g+~@tB=qbVVjUWYbFQ-M35;E zesAA0(RBLhf}wKRTVaG}h~nLAMY7I~ftZ^y@P6oAu*_&IoTc;)yL3{C7>fd8)cpF7 zJLJFpiHnf-IA}hU0%4#tZ>#U@eRjk(n>@81? zF;aW3@m7-`A|Z=aPtPTmy0Fd$H z7^h|dmU0hdJO9{rN787Qp#72XKL%g>BVP0jJ*59j%@XR~AU!6=(=f>TzHk-u{taCB z&GUjFY1~DWw@Npwlj#oZjWIFiAO{$*L#>y|D=9GgTTfsSUVffRNvxz%-Bb}|9LiB0 ziL{uB&aRJ&vn|(ImJ(wWDdw_)gG-#Pz*$f>KjYk=BYrlRgEV&{1nw;XFbkI0+*PCF z{*y6#;fha3Z+&tm#5Cd4)7bdaX<*5 zYR$};{-tm#1P6=WXvemeEqd5%v#P~^<<+el*qTAU@|DA$-Sp4-jMLA^ksId^yen+? zx8?ghSvg61YQzqbMvd?hvu1=&s-1x>@WjYYjXToKg4+=yc26J&;T-{wFE&ex) zSKvxYEJ1c4bTpjQF0V<|l`t)yPL$WX5C+-*>lkC=L7xxt)&LfRVxv0KPq;C2s78{rV?X#h6NL%vh zkf&BP>~(CFCgL6K-^Zu|>8+kGe#P#)FTuC7ESTkQ&)owoRuVH?7!aELPM;F;I@BR% z3ZrDkbx3Tca!ZP;Y96*go~juGYj^{U#Q`d2qiWuWTlG+ba=FK(`RPv=UJysfpC^;O z+$_u(&7MwabS~=ufL>kL%#TXgqHcf21@^vocRQJ=;3c0WkhzHvevdL*zQBAZ-qzgv zZM%__7XU1uYC??4ySaaP^257^`=}Qy30{?s2|32cqQXkrtcotbk?PcuI;01G4F2cC z9wDTnzbVE8#g*4AH0BPbVfv;pjRvtsHW0K&LvbK-%MMs5FCuoDx zk{3vhlG|uupD~qpJ;8Z5goRoiyQ4go!a2O>Jk;uG*1MPsSWsQh#p5Z9@F*W0hom*p2Jfb-!J>i1(bRa@yan-{ZjEgkbZU zVZ4^n(WbE#fd?tz7BtEURF|a3sI5;2Mk;=Dw^`fv-W5 zdcAo~6I5doxY_iJWN1P3-%cn0_|Ui&9b*vtD3+Ssi}yB{O1*Rv55{UQz?XTQxr^2O zO>?*U>3t)AJN-JI!zdz4%JFrONxai>Tba)-A<-G8IRe?le;BpksV|iZeI5aEwTf!r$GdnIRyb$ zvt1^D?=Wi7Q(G!E;Dvbc`TA!o8B-6OJ5GuB&d?)PvSJ48!RFbv#>m-sw8W{%n@8f0 z@8kFk62#Z=9AYebs{bL1xXSUqVrr%j(IndPBCCiT7x&oH`?#Lp$T*G*-8@_j=4u%C z*K!r_3ag!R2xiCiX$qf}CDWJ{WsSdoN5QYa|CJBr1F`YDN^s^3Gt@G23sCHO?&p6N zH21pA3Faaj_ZNGdGmKr!NJg}E7*=<>iR0sk1s@~aI>Z5g1dOjgfJlIHhFRwVN&d@k zh#HuhMW2Xy?PT z*;RZWa3kA#PJf3!;XKI{y3!H!V%XAATSH;QPUTP%JYez9>Jp!$@~&*S&+QfyHT^F zyu}p)cvFy4TLle2M-m;eNBV~1X*VYL$X09nasaA4QOK?xcRs=3xwb97NanQ2?l=tF z3Ok?R_S{~$tcOj=XUlc;)QQrVdN1k!F(GckH0JBdzg5jzhwJz4eA3y`SYCLUhQe1r z@@w*j1uvORiuvy}cK%e%}dP6caIO zz)k^{&Y$~zoxl%oLjk!Vp-QN5F-agR%d|;%VHF`-{#e#osoPI|i&=ik%b;T`hcRyY zy_Y{a4mLl+R%*;F<61w^zmkw%$5{#l8#Xif%Q8 z0dKDk{&t*ewdoxd?^n4%HvG{jB?*?9h1VWLzB5|0$^uYfm*nYgdUOVO=P0JP6o`+g ztRLN_VtoxZWt;YB5$(riz5lUO^3P@Ue;XHkwWJ0B&%{zA6pZ?E10&X61)AMC?#|Hi75AH-6EPFq;|-vRmvi XEDS}nK+s(;8beuLL#|TBD)fHorN9lf{cHDc63FiJ!TqPHj`#)wYTkZ93c5Q9kc8VrIUdLN?3=yjA3 zuioVwdDpkT`>uQM_s6r&*}wDKd!Of=v-aA1ztz)GCnaVi#=^oP)znbc$HKza#(a8& z7yyfP+|v>>;CSil7+|5^W)*2*VbKO?sy;M)nYC-Fdr-zc<$%p_!p+pTS(eifVmN}p z<^dgO^69^<{GKylB4QYI5ztuB_bEF7@}5O@=^qXw7a|JogavXLDlMfwXpz@G8FUM zz#?8eVZRx_1f_f6K}oo3U3<|bN|O&I7cSRf%^)nG+Q(DG*8W^@PVo5CXGjASbl~$VWRJU*dLG=Q zeR{?^kGt$5nAYDk(0WR8SM?LuHk{?jTr>5({N3J!4{;CP8Y{NChPB=YKh)~wH_+HO z3NlzEGdu33t(IY?XV5yeQg@fEgOb^>iQjt;v~+p_mkic%`5k`;o2`uNy9p#r8&F9g zFnRC6^0d*evRYSRV}#mq?Y@2I8Fpzf3aBqH3+g6^E)jiNj5la1=}7YgM=V8fPB@I8 zv#vpt^}kVA;UsxFNm2B^)#(#yaszYs73KixJaL(hyj72qCLPD-u~7M4Ezq}`G}%aS zzqA1V`Imk=#MXKS{K9WKbis2tU<-P`+kERD#phah3ejKe!wYsf1V?!Jg~;I1tvi~% zLsyiR7e6pY@=q#|4pc&ef-tqBO+vdldsjw**{!o_a+!21oc%}Uz;n;s{XWSN0#Y{; z>Qa*Wg!NE5a|LKn95Ow?;es?^n%p8b$S}@y-x`#u1au+W+dnuzAt)$wx;mWF<@dyx zn9a%OqZj>pI14L`lXBCY3SVfW&V{nD)#2Qx~xqIVZX-^;qUoJu{baz*@{RVe`w@`mbL!7FBroWRr3V-ahP~FH7 z5Bq{|JWlAj3=B;uKWwb!&%Xg?+crp$S6)XxXfZPlD4ioa$%V}h{~lXUUN736@ns4u zX1?k1Cmc*tQ1xtB8YQ{>M(?`xMvDU1q-&Bf+e=nw6>ksu)!-Gu=PPtNU4R>Xn|(H` zl}SJcowwV<6>*b}PiK!it+mUQ_y+SFpPhoRMHq}s7}c!&IIwuy>gfSmF%Ic^AxQ9J zFbZ(Te+Yf1dL|46r<;7T$n(B@|kvUR*J)?8%*xC)p#UE(u5j8U}wn zQZi}c$+bi+Yhzt>drc=FFsWZH8h9qPrw#(d!(N<~#hT-Zv{f@O)(}rJj ze;mU@G(rsc#Y@RJh2b~-zwLo>9#YAbE%3tg-rthMKuz+^dWLVzME8$AeGt&wQp4sz zQ-8#k zD{jL|56!FCgS6>(h*+Djk6y~YLHq2p5vcoB0H7pTMc<65^LO3wUbXWs%W9!pI+GUV zw$7b@dv($ska`1y>H-6c+*yOk`#;@E8It9vr4XOXr`ZLCmYBF`4C{uV2E*bi$pk2i zQ@0s7r4U7+i*PaY{bWIwZ3H)YP2;cSS}86Qb`#h@DHQ29@CQz)#=wRdN#jnZ28zlVP5<3BycrND8AAaeG)YR~Y^d&up|Sb;z_IF|3yeqTxXf&oxK^ zjQnN#t2%9zIeO7~RN3(~xHB4=Yq1|^X1gqpZ?2VHvu8NOvonEL)tL5#!xphu8-$z= z+VoIBFm+eCPCS}dfLkNdlI5nuvNI1P1UOU{X_yG?-Di+oekFGn7d zY?OR9)#|tO<>)IZ5#zFKURUJ4HsA0 z8&K8l-gyi+I%wEtqWN)GS~qk`zd!RNH%t3F#)w@X@m`N2`J`Wn)3{Drwd({i`v!k8 zi(>{yzhw}>4Jv@#EFwMn7_nj=Yc0m6tHfQMmp}bgdV~HAbZ{)zyxTM?nAoUD@qTk}i zKmefYn}0;KYZy*x%rCvIx)u6^c+q90#jIJUG)5D1eFFf1@$L*(LCcEK^lOX>O^gWwxSH3p7QY9o_N)CGY1&D&dG+1W=2hqD9McobSXm9ecDMT7yyr>e{ z!#ZYBeCHch#OEMk?1kO-7(Q}zs@jPLt+6cgKSB*rTVjooAJ)o*RNsVnE)B|w^g#+Y zaY7hs1MLx7Xd!8X%D=aJ;3uK(g>927dX2};>ZLK9g`RpN`1eotj$dMrhQD6gqI4{v zFFuG*>AH_y*?7_##TgOuXWoyF!$2Yf=%D`_DhJRmx4Z!~=pVVRdl(YunB)$bQTF`I zRcuTUTqQ`NAowBv?1JZ`PA(_&?UW!>66}5sAYhx$kXc+&5_x1OISVg8Pp2W#AggYy z2sVAqUmZET&;k&zPqx8iX|xV%RA=8GcHty*!FVP_DRO*H zd0Lbi!M*MQ>2SsL^&`^k-vxl6r^rW(4`!0r97si%jT$+z`ze86CPm#S54U1s!EseQ zMH5j4;!nVd@W#nd6H;W_#D*P#&PvTu!~Ht&t?3tK)=GC(KeQrE#tEHkwiCJ|+%mO` zaQB}|3I>fo*Gf)zP+*=9;KJ@FtB4$b!aX4>X7!oIeBcUpcu8lrce@bs`^iWXf|@A{A}6i3Kn{3Pq!I_bDxUL|%jscN+>UytPWAXZ|6Wl(Pxn%RV%oYpyWi zTF(`tL)5j%^#vw^yU%^WlaFhvQd!?MH&Kr4d^i2uzGUKGb4 zsv&wmo`vKIJL`LUz*uNGhp{;)n}yEx79Skd$|{(mb_nz;w6s><~AZ~$mOIi?^|=THxk0x z1gK&jfwvPnocN?JIjx0mu}@kR`02%pswk_#7bgy_CQ2TZK#7ow8>Kd7B@Z@W(j*(9 z39-hnPBe?&zZQt0701$Pl*6+QhIAX}q=~hxCJb+y%c5gHLmxj1$v;$t!Y?dcBhClN;`-CwEPht=+R4Ywv!O>9e%Psf`(2XYdM6{N&?*p?o{42*suyVCrBR92i;%I}Ic z@loJ;^-J^GuTg$k%?}az@!enVaL~FvtbU2`R!4th;vHCxRZs3tvUf#6L&Ve@Mw0a5 z8&1$4J;DTp*a6n8yN*)2^K+1_i>kN}TN87rFJ`x-6_MY4SnZ1Zg?YP=LqzoC(--e} zHHJ;Sf&QfA$Tn6DZ&4nT_@w^&w;ip8K9wb0l!1r}p z*utIv+_zBWfyX2Y&`@|>La6l%a8yq;Mh1`5^Dx!R12`}?dSFt#(zw^c{#`VoCeV`p zow%{?q(?lRX#uBlG?G7d;Oz6$fSaM1a(zmUZZx%8c(ILSLLrUSE#C=P6#J<2#IIHV z3GWRge>$t9m?AHaLRUfEs3a<}nWRxnpo`c;v6K1MSh6-i4IF9saW5WW1+=LLQTk)lwmj6m!H(9g@9;HnrQQy zpLpN8KDNGhubzLz@jd1FX!5scWG$S`JQ+eFqsysAdWWdWbm!{Oj@edXs}LZ~uwO;7 zq*?o1vmX2%>=uTh>a2=GSnd@nhwzS0P&o&ux=?!2Fh9eP$1fF|UL_Ul?P#tM*ovdo zQM3<@+bMx5FJxPPCQ9-j5WDzM1*NGe__qB4NBo98dB9d5g>^aYf>WRU@Dxr($e>8> z&3gq_BuilEq(6CqXmti35S@w)Jf%f1s(>x|>)vMiR6d{l>2^-DxT1jb4;sB8NIjdr zSgKtLr{}N9$Pci?yqJ#}NSI=Nf4>F}4;VdH2E#$Ce`$;Vs#ni8*2QD5&n-1QB&pcM z>{IoAH}ZkEO<%soi>mj|!Co?{i1%!7O20^|-0C?O^+_l;vHBb#ujmag6l!esYqvC0 z?Sj3)f5NNE%t=4$fLqok_(&_O>7;en-Yc1RRMh>KPS4bwZ`$ot1a7XQ=IBRtO~t!c zQz6HYjn>3)htQ=dqkcK6-?|EXLR=I6kx2e6wArLAx;Ji6@7N)NO1+P)6hlu*0}N$J zeNK=%)lMshpv&bn=OjlPUbz3D`cYv7aU>V4iBW)g3q(osyVgM5KKH!qx?7_fH0 zb?e-%N=dXI&ty9eBVx)erPSYydJCa*`Fge(P7Oz}={x#By6pl#sysF2l#2Q7piwPz z$w9;=wC!~=z!UWVZlKl)DFX<=+4W%;!5W!JE7xRW;6v^`_CtbWxBQ#tz5E*x9fR&3$zk5U+;{CdddIxVzGwe`LjZwl&K~XO z$XbvRgl9CsZ>PiP`B)vYkEzJ9x}jNyY-VMCcmZN*_ZCY;u6%erKfJj{p%3%8po}GE z`V}n|rmw)GUx0o7I5LPos$=b%!`0EtgRsA~Ut<>VtHV+zhVR%~tFSYNTGj60rr`s| z1vhFFp#BFyMs62ms(VL$VUy!hgMnAN<*>!V-PY)0$itu*E!(OHZUWlQ0n|K4K#=L#*nrzel| zZF4K?DG-s^%kvoq`G|>H8QNuASTK2kv8ZXUOtQXPN+MEo9DC-aVLnBTjFYSqQ$jSg zEpX$gAWj`j%mGg+w6h)mvR|yh(L^Gn-CI8Y7e-q@YP$ATd(~LD89q$gGR49>SU>MvWfmnr=0z{ihC6%n*J33Y<5M?I+1O}c9>>V8) z&4g4sIxuj+RNz-RpMin<0ftKEnG9?S5vVG6GceRUK$sO01wa)ZASNfT1EWJD$RD8~ zU;q;P6!!*@R%H!92oEdW{^Aple;lJmVg*l00000 LNkvXXu0mjfqaumC literal 373 zcmeAS@N?(olHy`uVBq!ia0vp^AS}wl3?$X#m(&0$g8-ip*8>L*Y~H+CO--$#p~1(; zXW6o4l9H0e#l`ma_A_VBjO=VLHUaV(OM?7@862M707-uK zba4#Pn3$X(!EwN6jng+LAL)J@{j90(K^6>oOerOXm!zP&V zJ=-xRk*Tr{Q`H4ymNBtyu<2(w&r&vFb=7;OgQ*h)3@m1f2xwKZ%wSeHD4=|xKS@Qy zVy~LQ%9I55%YXj=`(5i2cH-B|KmYfiP}2Et<|Hx6p+nxKsl)gP)1y!(hPe+rZ=S5; RI}G$bgQu&X%Q~loCIDb|jp_gZ diff --git a/docs/html/img24.png b/docs/html/img24.png index 9d61d84488dbc6bd6c6811c2c49dffd7620192aa..a561fcc08bb42e93d3c9490c48ff671be6d7de76 100644 GIT binary patch delta 184 zcmV;p07w7Y0oehNDS!X}{{R30?(Xj0-QCR0%)7h0s;a7)nVEKWc8G|GWo2blR8&Jl zLozZlAt50U5D;SNC%OOt00DGTPE!Ct=GbNc0037>L_t&tnPXre0z~ZY=xTzpe=;zf zg|Jve7#JEMOwJDs4ErEV?hOp=Um#5WrQs_SAWTOGhPVU>b1^;x1IH%_b2pGF0ymcT m0^Hd34j>kDuS7==$X);nv=b58}M@MREYDh?kv$M02k&%FaK#vULcA#p;k|4ie28U-i(tw;oPZ!4!iK)p63j_?x z7Ze0mx+{ugpYQ9F<>6sUV@%My&%!pBca8fc^M=a4C_Ww;CYj?4t<;PRKG-~%d6D7a z+r$I|orDz20ETCK6B2CC37jpt!*C>V;;W3{hUg=j4LQ2s8B^rqnT^gHGIS;v7Fy2X ZW#CK~`%=l7It6GugQu&X%Q~loCIFAfQ-c5i delta 221 zcmV<303!eJ0qg;g7k?520{{R3w>Q&}0000jP)t-sz`($>v$G~9CV+r|OiWCsrlxaq zb3Z>nnVFdk3=C#wW&i*HGcz-djg47ZS&54D3hfDJ%7NkA@~A>JBxwwIPVFw0x*YT2UY{aYrbPpm0TMb7*6u6 zdjR3FA7EhJ#?5;m0nFokz;GwwI^(ebFt6M1ogu=e)hPDXpz!7)b2#=QJO0s@1Q;6t X(=#5Q#s!R|N(Jo&XRFBnK5{T7MNMHu8=4I z3l};tFzkam749dXiyIi2zCzgs2w~<24D1Uq0)yG1g@H>U0YiLgCIeS!1BUQH2?j>N c08}vmgMT7krw^CyrT_o{07*qoM6N<$g5!l|wg3PC delta 282 zcmV+#0pv$G~9CV+r|OiWCsrluJg z8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001bW%=J06^y0W&i*Hrb$FW zR2Y?GV4x;o{SRX?qlklr3m6#K_rOHv2>^+EAl3&U=79(@x_`W@HDF*k5c~i|Sm*-- z=W+(Vo8}ED!ahJF{siz}2ip4o{{I4)@L3>!^MQB&2UN2m!aRHz3Q&Z#fOwC=3&!gK zU}5$@-@(E)6BroUpicdO@CWY)2F7(zb^wyM6ByW$RKY|i{A6GeFu)M^vu0pIJ2xdX;x!=nnUh#iO~VwYzL0uo0-EDj)MgqfXy ztVU~T_%Q|s0kZ&9MO+(@)G*y(VDK+sJ(9iwRS^`ph6aFi2mvL9IgT?hSakGsw4*7? zX#*=_Jix%fD#0_O0o6^c)4)Di0O3ItF|r&eKv9&!=Kv(Np$77PU|`@Bi)K1*09M4_ z*bWw+zz9+_4XTJ;gn@zk0ffzgaEwAci0nOc=F9;Q;{*ePegHIVkeu8NB3fZQI|ha- z225}gM0i0tCL9h7i?BqP2#DY+fN;3NCNM0Gz)-{b0ZgrM08>1I4Ge;!7>YO`vBJ^= zaX3~mnXdq+9NaR|Sp?NEFq8!lp=cD00-^u_XEZP$xto~h00000NkvXXu0mjfqfV8B literal 403 zcmV;E0c`$>P) zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001 zbW%=J06^y0W&i*I5lKWrR5*=eU>G_e{sW9`#cXXFf2TIftp}2ZWjr xaX41M9gvPw4i4VDb|9>X-Hx!DQ7{Uq2ms`eMoE}P!|eb7002ovPDHLkV1if|oAv+z diff --git a/docs/html/img28.png b/docs/html/img28.png index 0d58d893d6f730fcc0566a703d29acf59330afd0..d111c43d9f56b2b2b97c6b69290337174f51e3d2 100644 GIT binary patch delta 262 zcmV+h0r~!~0;d9yDS!X}{{R30?(Xj0-QCR0%)7h0s;a7)nVEKWc8G|GWo2blR8&Jl zLozZlAt50U5D;SNC%OOt00DGTPE!Ct=GbNc005;)L_t(2kz-(>DzIok=5fGzt_lnc zJOL0k)2hO`UtR4`Asfq~^aLyTKBn70t9uF;^U0HRU`h<^hcPIe&k1bo=Ry!${r zF?EAZF_>5Az`(E%ZZA&*1JhSHkNE)u`vL|AHU%)pp@o45U~D7;lg?I1c1an z2%FL6U9ABF!-3!jAfC_%2F~RSd^gP-Ks+Cyx<3K@*C8s;0)O$F54`(7An|zkE);-x zT0p$V;05FL01&Tc0s})E+*;lb42z#;&&z7;IzXU)L!?gLEa zo%0MlXC5#-o`B>9zIPXpc%1AXka!F%2FN@%0c2hfN=Vcru~`$ZB1@GAFbo|40P4Ff V8xAy-u>b%700>D%PDHLkV1n3VYfu0H diff --git a/docs/html/img29.png b/docs/html/img29.png index 665df9d72d84e50b81241cd296618d05fe211f3b..7910f1d22bfff91efcfb21748fa3e92ca99af4e6 100644 GIT binary patch delta 315 zcmV-B0mS~}0^0(RDS!X}{{R30?(Xj0-QCR0%)7h0s;a7)nVEKWc8G|GWo2blR8&Jl zLozZlAt50U5D;SNC%OOt00DGTPE!Ct=GbNc007xZL_t(IjbmUK#DKX2w;XmUR|Oz( z6skJ`NrGurXbq4rU={%4aa}-?(rsX1`Od(4Bz*(2L7^ap3x9#eH5zanN46rT4J;)C z#DNVwGaA5F%>(A z2eZVW8$|Y=IdkR!kmhM%VEPJoz%vlh3gs|AfLqJJ!1@8?WiP0VLkk0!0xS$T8bA)^ zDuD2oW-@SvHZ(w`*p`D_$gl!TG8~j(U=$31nP>ziS$e?E7zHB?003xXF1%8oC4v9| N002ovPDHLkV1g{Vcu@cV delta 323 zcmV-J0lfa(0^a2q%(% z0)rznOzJ;Bh&*(Ma9AF1VDNhnlQO9Ui~R(1c+Y%bICBmr#VP=%=0lt@3Pu4G0004Y VHQJoS7%Kn(002ovPDHLkV1npqfEfS) diff --git a/docs/html/img3.png b/docs/html/img3.png index 6210a8a54f439887f4f735153f6f666a191d85f7..ee03beefe22d484496294dd80701b14b511684cd 100644 GIT binary patch delta 170 zcmV;b09F6Y0m}i9DS!X}{{R30?(Xj0-QCR0%)7h0s;a7)nVEKWc8G|GWo2blR8&Jl zLozZlAt50U5D;SNC%OOt00DGTPE!Ct=GbNc002ozL_t&tnPXtU2?AgYRsk4`7tWe4 z3S}@&g|Rr4#h|Qk1_>yu0mfqA(eWF?(qLdX17S5WFzkg`P$R&=&c(9q!HgTe~DWM4fj&wqL diff --git a/docs/html/img30.png b/docs/html/img30.png index 20700d366f034e01744a4b21a44103fb3912e6ab..cf23a26fade08d82eb1a237269d6254b42d4994f 100644 GIT binary patch literal 179 zcmeAS@N?(olHy`uVBq!ia0vp^AhrMtGmyL+__-KJ=?3_Oxc>kDAIN<7?%mzHch8(T zvwQdMRjXFboH?_stgNG>BQ-TOBqYSh$VgF9Q9wXoVgJu%K-G*TL4Lsu4$p3+0XZg~ zE{-7_Gm{ezu$?*ZM5-k5G^fI*ha3|U%*B`{osp4tP};+(VARL!QdZD#VvUf%$u$QU Z7#=TUi`0-{+6&ar;OXk;vd$@?2>?Z|K0W{d literal 185 zcmeAS@N?(olHy`uVBq!ia0vp^+(0bE!VDzqqb=Qllx~1ei0gp^2R3istfr>c(9q!H z>5`2{mLJi7ssvGR0r z4B?oWoN$1#NpXs>*vc2Y39lN}I#T#;ITl6ylseFq!rCarR|CS_ef|Gfc2x eW@29;!f?t=VDXyC`mceeFnGH9xvXslF;=b(g8j z9I2wCfT*`u4}UA!Frd_fKB9V#f|3|jJuI`_SgEF?_>eQTaugr(!df|s54o#Wj^aZu z-LfNf=KvLtI5&fQJ=}l}xM*eERN7Vpc`(XgmqETBt~>?9mZ_*VtBk_Q$kOpnre$E8 zGRW7%MLUp^c2jPf`TA{83fhx+tDhW-RkiT{Td7WMM}LhD{9C3KGK@xUwt{eCXXPcK zZB~+jrZjTWd7cs`Cmffi)A77=>=?&H*#$=H`Iw(?m-70D`65el_2uIU#ADj%ZTf+PR@I;4kDjZ8I25bQA!480< z09ktxtbeG0!bAtOKfn*iLlY%I3Jla$5>?b@B)s2z6xar?Qf&DDfIpa+c>XX(X5Mso zwmF~YJ-PWZ0Jg^&?9K$T*#&KowL%nb^XHn$@Ez3Il5^qQs6`3Os4ffxB~gnm1!^-w z=l#YgXro*tLsIY_P=^(XF?CvrOjo@mDRhknK!30Gb969UK)C{Iz>w%djDBAREt%n1 z2JJ{VkAf&+8SP_n9wJZ@z2H(fBWJPbH#&J-tboE|nFXup@Bxy_PQJYap^czul+X_>d((O^m z;(vfijTV{vy!f0~EmfT1r=ix#{5ep+!Av60gvFqoW4HE;!yTXHkNAJBATnE8$g$}( zO7cVj)c2^T2^1a|)?AO;j8dZCh=TcTfWi_C@2p2b#{r%07n!{-gG8aJL$`Sv2W;K; zJiZ*%2Pmv&9`p(QDa&Wsi8h}~ka67c3xAN6!-`V?bvNTcpz5!fS|8G5Dba8I2)n=F zr*Ihbhj0o%AlKj1JpD9FZ+9sekS(G5ctN2xmmI+$!f&`t^!M8P`rxcU|Px&b5SETXX%*XfK zt!O=X7>_3hl0tvB>v$F@e@+qUIm}yQ4iua=knUqbaW}D!oMibeRl5sJs}Q7654$v( z;g7}J00byxi;(R0^pZ}}@mmmuR)1R>)82&qmSD(DLdBfd4Lu8B9x0h}%;vV@WbA?j z+2@54U&oO6erhM3OiBh%nO!>B}_gZB~>(8ppFjhA6=4}Z(0Z7`n4 z5L2PA49St;oj?zB%g@F@U4xuvYiw$}mzV9_I=4rk*k0lkHoeZP36yP+8F2MrKK>}R z_PaK`_}0c(%+%@myKO;Xv$G~9CV+r|OiWCsrluJg z8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001bW%=J06^y0W&i*NZb?Kz zRA_jg5@Yvxk{GD=hl%(oA&ns^uto_QEv$ir*LGPH0#%@%`n3eCwkgUHfdO_VghK@YY4~`vIw7W)*f@79PO85VU zgm|qS1;>20R*r&W9=d5q%5a&E=SSFo%QIh3SJnYXcBIbg=Bk_rV^k7K(2XoX6K))- zF45IVI9jrGVlkd8KV}5x>*-265HK>Ll|qCq>oWEB#mrozUAhmK`AZ}Fx)lJZik-Q|d9rFaQP%WxA}0&rQ-JOJ>1+Bo8m zC656c0Do8U3xLf4k<1C0SA~QLMbJJ5HysO&w|FHGQidL%RHx*UKz2Wc#)h9q*n>dE z^M}zF|CX<(&O(9B!kR7s%%NW}BXv}B0R|!B%OrijyVgkuK7}?{ESt`bnzxXOV$%>( z+sGr;DG>?UL7T}C5}XIrV~2jIUeA*0hWUR834cTT0MKjipbByhq@6GqjI>vRk#bdV zBpG;sP!|QABZ0S&iuN`?Oi)q^CFzsul<2m-stO6Gq$7k^P1+$9R}u+&``xd?c!0VT zT&3TJ8)Uh_xh;E4*GMLT)7{A(pIvS778E(Cb|=2#pQgf3kBiajXkjX7Q?Q~J2uKXlRB~%vHNNN?c|U%>O7O~+9Ca)g z8-#c^)ym^J>Y9*J#7tqwq_#*afs3XRm90@8WbS%XyJ+^{qq9d*Hmo+AA z{j~!AIOz3Am`x^0os_CGT_ZQ(n0E!qWPj%PHHe6`;>%gNOf)dk5BLPQ?9>!Y6CCXP z_j$rCp#{{XxPahqeT{2(b`vn3c1$)fp0E+KD4_c93%z9tG4ndR>90|NuZMZ5^o zE{|CjUWU6Y#$>;dq^E(CDlcGZtz$b-D56BYJ2brFD*LR*^c%zxZ&0Yr;=Fp}cLK_%ofVldsCQ0W;Axr3X?$Gf5V z92}=cvdCHMJTAr|&}qG%T$gYe_>PnE6uhnBWj?Zb9>@jpHO!|kA*EM(aS}4k+?wMO z)}05&Oa38>B-yV{W=A{PpkZ}7`cNZYOu|aqyayBTd!`+R4ZfVwN4&oX{eK7b0wZr? z;?)BfMMD>yZYH%@28=f_#5&*a+bBs`aTsf1BY!;v_5C^CHaA1(?yot+=TA4Q6B@Hj z!p6^7Hzft5i~Z_kb}02E7(JVY&DHk};>ET$_QtF`cJgwDOPIBuOL$lWrSSyTuF_Sh z{Y1(ZSSzR?wAzBtxaE~V_kVrSh9iAn5=RykOEIk#N&~Q5Q0-lB3uW2QW}4ZZZq~Qu zU@0tuMJaN5&PaNJdCRjcp1oAVo;Z3;c*rC){SbsAfXUK`Bl!Oiz z>}+agw=OQ}J~op+qExAx@%7%2gqd)-jD!tl)@8RH-eZY|X-hJ85F;U9FQ?5k`uCW!V`wizX+2gdA0 ztn}$?ERe65#bbllD{UO3M|5{!)NUBND%*@2t;qn%Z8ViUf`$kY!iT>B4>%~u+c_Q* P00000NkvXXu0mjff>}OZ diff --git a/docs/html/img32.png b/docs/html/img32.png index 9c811f3a857fd4cef7002cd5ca6bd2907ee3f490..8232f6b1fcb3a676c265b82a8b9278faa5fc1c57 100644 GIT binary patch delta 376 zcmV-;0f+vR1BL^T7k?rI0{{R3`%($`0000mP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001bW%=J06^y0W&i*I1W80e zR5*=eU>JnJ37Nxx9GS;)2109PIUtGhFfeGQLD>mlE(ly82|vn WVlS~IijUj?0000v$G~9CV+r|OiWCsrluJg z8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001bW%=J06^y0W&i*I5lKWr zR5*=eU>Jm8A~J{TIx>&{E`$~_nSdn9%fKLQ3}qXDxgem)=YN2rhE0dKLX;d_eA<9vxt j%_tbu;0!@r1OEe%DK!88{{R30?(Xj0-QCR0%)7h0s;a7)nVEKWc8G|GWo2blR8&Jl zLozZlAt50U5D;SNC%Tbc8h-_(0G80uUKKwS0$rbTcL3gDl>ptFJXNcsjOu?QZ9wj~TjH(58ZGy%Eg zS_%jb5HP_^adcqd5a2it<++9iK=fL0Fc>{xU%+qxoO2o47WLw|MyRP{s#2A&T* zGa%fYHke)xZU(jmTnS7Yj2IZSmNOtYK)oC=y?YoK3=0@p4itcVwgB#CPb~(H0zFQ) zsnrZji?|Bl92C7j7+8-pL^B-+`9T}*UzQb{8F&nIN;r-(F>om`EQ4{FI(j-L!Su37 zb+jqK!e|;yFW-%;5PudAmn$L&!5k!eIR%iyxA)AMGY7!-T3A3txH(G^(qIlyZw)kL zxep-eZH2p;BLXSDQ2+;m$=`q^?giJ&uwfGpz03%vBeMBi1#rC{Itn;6!-2)c<;dI> z4j_{KR9`bk_hmwQ(Ev*iIIKp&C>RB!fEEA%NE%$qQyr1OEe%DKx;qz_YWnCMG6;fPhR)Os1x$85tRKb8|mGKbe`C3=9lrW@Z2Y z05dZ)jg5_2Sy_pPb2O1%8h?Rc-n(}JtpCZ^%Rr`HFt~?L(tv?+0#=FlH~#t1HjyJ1`z=`2L-HVV7$S1)4Tymi0{J%ev=7>+I$TR^92|f*b5yQ z;2aPTg{tE`$-wZ3|2mX6@7)84Ue*sE0u$IB75jU=?6sbSYqfbAWo`Azu zhoswD|NMaeO<2+(KEU}G99E-X6pVsVFxUV9h^>dZ4+>iw01E&B07*qoM6N<$f=zbN AAOHXW diff --git a/docs/html/img34.png b/docs/html/img34.png index a9566abd3af7c0b575e7a189a72d721306d2b9d0..7fb3b0b64f3e0d156e4e5f20c12caf99819e1190 100644 GIT binary patch literal 1542 zcmV+h2Ko7kP)?#bU1h?Q8+yX7o0xhTp{_Zy|&;l*c0xi%27a{z{9z1b! zoUGYvWhS;I9@|0^Vp#m(1ngfA;Mw@lbBYf=r})rwiVrh@qR0Q7d>te z{zp6Hc6;Z+^!QGGu>~7iq}(LNqBm=X9!wACyIZDB)2aN)byp_t4;6!y)@q)gTkeb& ztH;l!$1}aYVL>#GRxqTccU}~FEP{HxIHlV*qPtIQ~u+bL0QqwcNcK1tqtcZc@ zb*%i0^hB5CCSiz!EB}VI=Z!;0--^|p_n)LEuISO;voUn54GWqPaiTwIXhtQkKEp-v zOG>xV<0DKq0|O_FH+UXP=yrWA8X{+IaoJs*?>qD~D&0m;3h|T8z_v}F&1UjQW|K&6 z>DlMir?@D7Md?0zY&YeTZta=9i-4<3h9a@u#cVs==ha)dW$0Uo%ccyztq;U~^dxJY z>{YGd zF8tE49V}h*sz+pn_r2dT(+LXv}?mq8{*WSdG`EpY1=)t02?Up-tJnORzJ_bbPK11ZDfg@UWSqKPnrX=u~?_@!_kr zus5)u0Mg@_Oo3~g5yjfT$#-dQ(DM1#7oWx5Bb_=urf*xQ_hMh##u=&hjTh0Aq7S~? z9%7&sP^dj?XVxi7mDe#t@t^j~DSr-pXWBR;Q4ModjFE59=&MX}DEYD^o98r-Iz{Qc z%ue;YABCL)Hbw)?yUE^PPLcZ(|u{r7r-tKgbc)_uh83Q z^D8dNCYhGmTWDPAkkY7gjKliyPl9K?$S)D-t^n)1WEY%tg6HM!rVTA*DG% zJ%nLfo`W*)1baKQ_*PdP_SJHj&aEUjf;9P@C``#_v6};WiVi8c*9V~cJy*)g^|f$M zuRXL(Qm|U6xLhsdvAB`kJ&l%<&9Yhb^;I+J6ean}5O(xr8*kgMjVQ06Ws;#f?9236 zmA1~~$OTn5DA_EBN_FFzb&68|s{XN~Ctt(st^SNq0>S$gyXlEhMlpchqkC~J29&?gcK?mq$%65mISiIg zHylveY81QSq@tQ^-l6k8J#;Xk_)L$<71i{>lcPpU^!YNo#E}Vw6zW;*j)R<9vU!Kj zo*tZZ3q7<+O7asuf!M{9K|m*19;6MRmJnTz5}1~C9Y;eO#eUN{7hOX`vIvD9i!9)K z$Q5I@;I`1ChX}5ZvzrN8_QUcO{2qE@K8u2e#K+`G>5eFgGd(67Uf9KE&M2!_D8>np1^J6 z31Sf1W-=vc6Rl*@TEQSW;fv0XAR*Hb4P1U;{Kj12jMb%>7LRG(ZEC_7cDk1QpME zR?p0RX4YLXA@CSNfCcwIjsQRf9woMex-IT!QJw4{K1iMM}?N;Edc*1Rplx7ePo-B-=DK4_6|()N`||Xva}0 zLBexIv=lUd4s8}6fB}&gC`O@8l>+k8YeN%15w^ZA*`WB!^SMV%#LGh?<{d;%Z%j}CIPFmr=WKkX*`4qg1_AnR2%T6_SXj4zlk z9>N%yW^gWZK>?9D+8@=lLM_KWz(w&ZI=As-9Gks{4J2YJAfYX`D>K7YO);daF!U~V z_y_zn>fFYUpXudndRwOnjx(=gm8|%wN$2+NAi-? z*Gzmk8DTY@152RKg>HqO;@~*xrDo!+$uCY#OttN$B)^DJM$=0P z;DrXa!Uc0R$6h1mo04fOxZa4X!w6K@*@fxknaKUN#>1zZV?Tf?I{*&D&*-PGA~mWtJO(gfBsxFY24py}y{A(( z<7D49R_{e+yBpjbep(Ru@fkb5-QHJcB^D%ZkLoFO%3O5?PQD$SeI{*5>D=I^@Y958 z0vrU!D~VABZ&TU{hq@b`GFM$A?&y6Lq81dvrSMY&B{O6!(UBjE+iiS1!PxG|d|jt* z1})u}{(J(s*b)d=>A!66)fB$vly*kvk`*Vd=*&vH*xfV!D!{M-#&%z(F_WZBQS7Sr z`OutphHbiaa-Jd6S>>vGkgz4%aw(e|x`G&F*w;arkJb-HNK%t2fVCDDFpZ%jMW%GK1z%~og1Rd-SF6PBB8 zYquHc9l*Jytv9scBYkU-7N~8q_mHMpK#C47yc{QG#$VdrQGOc z4XKR}9;tH_BSK6&(;kAYcYCW-%T;r1`HAb*wpE$pf?1p}fQ21H@NoeP{Gi4lsn}?} zfM850pBej7_Fq^tOQFKBk7CaKh}mL(ijm~vUkOhCno;tDR|YM0kGMe5%Z3_o8$1t5 z;0(9rInLV5`>^mIJE(Bxp;_FL0debKmZ zAL3%zBl9Xac*P>-?l|A6rkyt^mHc3@TlnEH$ z2@q!LzVBV+A&njUErSc%#jh;*xuVw-KN!M&ia(3FKgG|8J?&f8Lbwukc-(-I2s;lh zay8%$U-${M{4oUnxn zX)hROx^P4o&O8{E3Ks}T4A)9nUxA7L1bHXa_78U72YYdR_QQX7X^vD!1I7-MgxSmhk?PcfRW`u0hsrKf%P~;G}Cbduys-$Z3=LUI0cZcxy`W*+~*=Xx+wqxSue-Ou?Y%vjzopr0Bwa=S^xk5 diff --git a/docs/html/img36.png b/docs/html/img36.png index 42a164f1e12411bc1426bb7664b4f5dde557e644..1c3f280842fba814352e7c2eb61b09a15bd16b9f 100644 GIT binary patch delta 444 zcmV;t0Ym=W1KR_TDS!X}{{R30?(Xj0-QCR0%)7h0s;a7)nVEKWc8G|GWo2blR8&Jl zLozZlAt50U5D;SNC%OOt00DGTPE!Ct=GbNc00CJ^L_t(IjbmUK1u($eL53z$^)Lr9 zDICS8Ac29&0Zq&Dh-w7^vj8Nad3XNoX=Y$cN;d#=%Nev3;C~!2&{bgQWj&I<0Z9*Q z!vT&ghoYOT8yGwk7#P@#7BRp%V6dElA%f#Ll;av20MWzT&|vg{eE|axNOX<@1A+qr z&lwoPcxE(!**R@6Jq!&S*cNalFlaL?FfgquV1RSL;B5i}10&0U0w5D;6wGZblNN9k z=y5V+hHn7+W`8*YoC5}lg4-CPnT~^esEzQCSGNI=fldiSPk;i$A_lGmI0q7LJ%X?> zn+DhOwihaPUp9#E727Z!Ne_(U%D}(_)6jAub2U~tfT@}lFAO^N8erD|1O}$T m2o6gRI1EO?C>RAp8~_0E)MI||+7z+?00003aA{)WiCa zQGoXW9t8#rj1$nbxWBIu;9<2x656J_w)ZOogRyWam|M;uB7XqqfPs(z!zYHflPi$) z@O`+zZ!&>hXu}JJ`2q|K?1hdDa1I!_Gcdeo_*($saK3v7(Zl-T1FINA2?H-kbguvd zf&&8S3=EGMZvO|fneW>{^)P&BU@&2DW{_YNU|@6snh4{7L6QNGIPjJo#4drmjdP;| z!*|An4c5;afPcOLx&_7o1Di9=415i;ARjU|!1YY|5x{Vj@%n_n4+Iz-8CVS997wqR zJp&79ZUdN}q)$+>3!X4ZR8ABuLiu&?-n|RfbM-4!tl>M79vEjH0|PHy&jYyI{{3UX z4fZiGFu{!Cbb#yO;1Ix}0SNj*!3YEHa6OzKFXGm7`!?TuMEYd;38rfO^8@}j1>n>Z n5cd>`Hy<1ZqhJ(_f)NM+67qUCZe(@O00000NkvXXu0mjf;kUeF diff --git a/docs/html/img37.png b/docs/html/img37.png index 6410868e2b72b3d2198d1dce94bbe9e42e16ae4f..6795fb99b55527f35c5e3061f83983e16e475936 100644 GIT binary patch literal 483 zcmV<90UZ8`P)F4h379*uiCQ#ZV}bxy*TCEC&iulrIMw z%OK#x&cMJT!obi7VS>O!U|tOqL^T-% z-X_3U+y@w##Ss!e7+B%{3o!D zv53M2a|{?PE-uHW{A6nc#8&2BDR{6XPQa!V1Pn}rv54YSjukLFkffZGB-IQ`q$y`$ Z005hHPj1@+bnpNG002ovPDHLkV1i(#x!(W) literal 482 zcmV<80UiE{P) zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001 zbW%=J06^y0W&i*IU`a$lR5*=eU>F4h0pdSk5oG<3jR^$&*il+1hgE`R|=HSYs# zs_!9G-$NGXVYS1e`atjlEKCN5x05T-9sQ6|?xuMIl*b2U^8M}q-_P*309~>B`wIE% zAlCaE|9^bozYZ1W+Q1;&aQi=+Y9RrJPrUoVeqYVNcmv90V3;$3f&ajPx9q5@-GPSk z@Ld2}$$652;SYof1bcuXvaUh46jgOP1H?xxP}RN2;#^4SiQ_H^fc&?Qfr04(%wI@g&I4>__cJh)p$)=x)Z0m6J5n@SJ}hOV diff --git a/docs/html/img38.png b/docs/html/img38.png index 18edc7a812e76a368e511efdb3aa03a5b1a5ae0b..76e1f9c1839c928bc73fd043e79655442e44023e 100644 GIT binary patch literal 248 zcmeAS@N?(olHy`uVBq!ia0vp^5(8WIxX?Cfl0WTdF5C?Ft^^iq8nPy=I0kY6x^!?PP{ zKu(#bi(`ny)Z_#Od4qC=&ktmtDX6tBHu(0bBa4-BGlPM9c;mw9Up;=Y8Khe>JF^@w zT(Rjn4^N_vv6RA`?VLP3Jv!`M2j;jO%;mZ0bDURU*;fuWg_{}o8IpGz8GJZk87wJL t@$gicfkDba(>Xc44Xcw340zi%G5okCey3uke>~6y44$rjF6*2UngAcMTKWJ0 literal 250 zcmeAS@N?(olHy`uVBq!ia0vp^l0YoX!VDy*$Lux(QU(D&A+84w9N4^hvznS(Lqmg) zkI%AY%OoWwi;Iix?d@mIoXNw(la`hSRBLQ(+}qn585!BxUTgy7GnNGT1v5B2y8)7{ z@N{tuk(ipCpdfjq-r?ED!q2e76&wI&# zVh*9pj16qkcKnq;zP90000mP)t-s|Ns90 z008dp?%mzp%*@QYySu8Ys+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001 zbW%=J06^y0W&i*Jc1c7*R7i>Kls#w^K^TU={kz@GZEz1fxmYb&XrXYRk;BGVs7;FX z|4@-AikRxaLM0ZP=;07@uogiZ@hl{wO$Z_Z5e^cGAy-5#Y-435q!APwznT4Eb|;%n z8moI@hk0+_edhaiXAhvKo_fkt&CAayWD{G+NEurI1If1fn1A*33DH9JT#9dMup%Os7d2o+mTJ%A#u@ee@DVfI$C;(j|wG0k8JU=Qo5zRLnw zQacT}h!b@uB0OgModozvIY=@6064GB?!TSt+ZMo=#NKfAw(a4grhuN z4pK}%M+5}zyTiLdydJU{GNFiXr!Ux8YbUDNvx{?AOYfqoc8-c|D0%!H5Aga;C(0@g zJAB-D4PqbbLgLLRQ>EzOao|(@kyYp}cUXcpa%>1U4ogiuF)#JXk0z=MG){;6T@?0h zI&ufj#^C3)Pgex%^W-o7?R+9{s5_2rZ2(^3jR~3uehhw(R~JO^KK8S=21V+o@#sWt z7iopv5jq{fx-eTH|w6rZB_Vhyil6^{41Eg1*KIXucKAdk3;H zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001 zbW%=J06^y0W&i*JcS%G+R7i>KR555%K^Xp$_DEuq_hLZ=wHRGo96E?atdc>fgXjZY zbTGxm#UYDODAK5lof2_y5$Pzn#7S_d4|Gr|NkpWU5`ChggEeU=xR^ZuyZ4gZd)L=A zi-Yuo9{1h*?z`{5`%_>W+xTygZS>bLdlNbqpwhQs3_F<4m;tJ!wFTpkn@}@Am0&0P z8=L2?Kx%HV%sz)wtM{h+`fAJLdEmZGhf_Xd%T)>A$@+AvmGhaj3Ko3Om$*6u)IZqk zYl4P|&DyqYxW=04s02n*Xkx|pFi5DcnS4%bQJ(QJ&`b$>+?zOTIx2xliU4yp;&u6{ z1V%!u=J1s!vDakL5H#Gm3&;3r*-;5x1-@wc(d%B9KZ-AYgq94PrAd6A?jS^`e-PC!%>^*omlRWSze2g~TQnZ+E8JFAi~F#j}By_K2%v zX&QEv=)$MOmsncXefMl*twl>Q*2?mREd519(OQ*;2NXWxMm1$!!-ZHeG^C5_zrq+ARF%&%R^I$a<)LN zVrlJLSgI#_G zng2e}tH6bp6I~k4?PfS(V5MDGZ=!zqw@fEqjl6MBngeTA>{Ffp0P$XBu`|oaUTb6D zx%afA1mp5IHLwrNz+HDb00000NkvXXu0mjfnYm+p diff --git a/docs/html/img4.png b/docs/html/img4.png index 0dbad0b84489412cbbd523d5bc488dccbcc94e3c..01cf60ff2c6bd9c12796fa13d9e99903873ad69b 100644 GIT binary patch literal 689 zcmV;i0#5yjP)Kl0Rq@Q5?s=xy!p0bJaXWQZ>|@{I~Q(km7W8ii3C= zgbs?1oyrB5BB&Rr<|S&3qS!H=>z{Th6$hg@6wFXTs7REmOK?)#VicvmdoLt4=3)iA zNWQ~y@B96IKfL>KKt~;Q)Y1PW#ti=KAN3vBW3&hO+ka7V33G-nVK*~_%o(|XL3R^yW&(RNhL*1Hirc|#g_-emC}Vi} z&>3byWk;rEo_h6TLU6TjxvJ#ebIwgG0`??bCseC%Zs7=)oZ30@@&Gn zR{ZXpl;h=RSJ)zsvDm}f2Fxu1!R^bdJ<{sKMsvd?u7YgGVco$4K)1o22_)=pxl>__ zJtPW2!^_E5%wvYPYFtDl_f&nq;nPPExOMzG$YwzMo;Cz`lZ^o+pu1v5*ph2Nztk7^idr7k1`#8l^GG^=zbKMv_uT zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001 zbW%=J06^y0W&i*JKS@MER7i>Kluu~WU>L@qtgGF0X@Yv12YV2wpt#dclMWAKj0pu5 zFTy4$UIwc$J&b{aUB)&rXB~8iL!4vHO+2*>oZ`N^4FqKv8pKnrwg{%yR$sq-=^w0V z2jW4Y&moZadEOsio`e8RHPuv8|F?)#ejU!&4IEY*1Kj;s(X_p>x@&38ZF+GRA00Lp z$;LtmnQJ6_fYZe8;-?CkM62nWM$9GDe%oSSF;CUzdD?(QhFUvZ$EN z^iv)pWc%aGw1hj9m~kFI^t3}@J9Y1-m`IDbiUBAAr2E<-hcO4pCR(TXFm1MkMd&r! zbf*M6Wc&V?=)!G$F13odgH2Vsoo)|c|jNxjI}PDs=+R(lG80Z_k_S* zQ>^i4O^LOZEN)h@bMP;6KUg|)1-qQB!OGhQoo>;_`{~t{5wRh!!V+tqRsW+ZcE{v? zN}Z{}Quza8#`^ro3S)6;{`rY5G4gHjN=FmgBx7O7v+OvA7z<$Hg)XyaEFm&)R@O8q zY#SnE`)}DK+Ztl)S(mRkM&vgBMf-@Tj^)1$Zlw1=b_!8*9Kk77+#p-Ug22P{o`d z7#KJ%@XTm{aJhksxC9tk4itd7{1X@$cpgME9X9}T9UT}L7#F}ToDal_0dVeaAU=a| s4$xZ8OK={GD99CXpY%#}tSW$V0DPAk+s*P$egFUf07*qoM6N<$f~LM(1^@s6 delta 244 zcmZo;_sH8eE%`1mYawoFn|vbea| z-rj!Z%$YnqJZWiZK()rk#=X70k&%&|?ZqZQK4VFcUoeBivl}4EMo$;V5Q(YD2@2dB z{<%M0T=?Gc<#+Rc^*>J>C{Xyp*s_0CM6nz|lM05)wZ| zE56q^6j(NNMeu$25UasZywl9U;Dg$pggtT$&(6&RI`1*V_5yK%+cpiw)(t=O4p};6 s?-YG#bFNq+{6Ouemw)P~Gik6hG#pbpvZ=&22Iv|FPgg&ebxsLQ0JxB2l>h($ diff --git a/docs/html/img41.png b/docs/html/img41.png index becee53d11000bd80ea6f4877b54f6bb19371c0c..f8327c9642e7e6688df1c9fdd87e5895b5766c16 100644 GIT binary patch literal 242 zcmeAS@N?(olHy`uVBq!ia0vp^l0YoX!VDy*$Lux(QU(D&A+G=b{|7SPy?b}}?%gwI z&g|a3d)2B{GiS~$D=X{h=txaX4G9Txc6K&0GE!7j6c7+dda1q(sDZI0$S;_|;n|He zAg937#W6%;YI4E?fd~_Y&lUnUVQg&k7%cQBG&WAO6g{^4!~ucFVZ2WZ#MlhJh#XjA z!ptn;S9YMnw~dpB$?i>nFt>zsg!u~*=e0=*E}M4kT3pXO=kS#S2Z|XUs&7g+RfnU>gTe~DWM4fr^-~} literal 245 zcmeAS@N?(olHy`uVBq!ia0vp^Qa~)k!VDz0n_r#)qznRlLR=3VIIwy1W;HdnhK2?o zAD?B*mPtxV78e)W+uP5aIg^KnCoL@vsMgrnxVN`AGBUEWz1RfEXDkWw3ubV5b^|0? z?CIhd!Z9;BK|ylEKlg`9ALR@T?lc$w;4?6g;izMHYABoVV0Y#{hNrpq#}CxYE}Kwz z-;(X#U-<<#br%ow*wlz~DeQU9^IS5{AdbJ`gB?Rsg!B&mSldKluB^feS4K o92eHu8}KbZ@7wlcPJMzILxGBXReWw7E6{odPgg&ebxsLQ0JbDo@Bjb+ diff --git a/docs/html/img42.png b/docs/html/img42.png index e19cd72f6d01da7ceefab9ebc8b1580aed12fdb3..14f3d892ac5b671e16fe91641ddf79318dac8a97 100644 GIT binary patch literal 538 zcmV+#0_FXQP)P)S-i$t9B8$?k-+(Ny%L))=~6>XpRI1o<8cw%zF& c{nszo7sPi|y5vjAg8%>k07*qoM6N<$g1{H^OaK4? literal 559 zcmV+~0?_@5P) zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001 zbW%=J06^y0W&i*Itw}^dR5*?8lRrqqKorKmG(D4On{?4GEp~J5)FOfuTpR?0ifeUp z(4m4AH>*xg7IYOH9lN<{Ko^(VMM{xs7g3Ow7P|Q-Uj8&BS0k>XA0&78-j93l%Uyt9 zETa2mvhDtuFRZX|1Gw*_q?|c~X%fMR6P7hVn{P1if;EK5B*0~ya6p4xOBWb;2U4r` zi00uIT}(LPvoe$_+l8F5;CHi|K(7z(yo~S#>mz8lb!S>va&}l5zC=i_3AS-fS)n9kA7+anpd5YN+K{(J)S$7t^ zikQm4qd=XW>VrPb!16Ux)P53t#DP1&F2FBAqzkcbC`o6>##wbG@NI}HxD%^O+SVKW zBpE24okJiRw-W7nsTgl*riSd=2elF<9#|~mHLZ8(x01(!p^`fno4xfK6iOf}iO5Hd z7WEod-MJLlBQy(x3`C0C&aJZ5h04J8-Pr)9j9cZ_7+CQ|bJ)*e8A8#W$zC=3Xsgs- xk|aR-l714t_zV5C7-!vlw{iaG?7#k~J^{);a}`s`-gp22002ovPDHLkV1hTK`S}0< diff --git a/docs/html/img43.png b/docs/html/img43.png index 948803310a63cf022fbd87bf03e17bd4e480beef..3e1916f810131b8d601d700d2187c26416fd9918 100644 GIT binary patch literal 2405 zcmV-r37YnaP)g00002bW%=J0RLN& zBDDYj2_8vAK~#90?OeN+C!!Cx~f`l_`D0e$AxON+;}&juWrDNPsh#q`{CyN{qRiAB_U5N z?Q=?gM_l8amMQo+W^T@(h%20nVUooMBY&(hMJPr-sN{FW13cK>}43kL%>H@5mlzIH*lZ#{ge9C4fz0Ag z(vq<;QJo$^%nS;$Ti=Zmp29hwsnS7rTGU9(8NJzHbAqCUfX^YE(=0BNrN{OaOxKd_ zAPgL6z4)gSm?piON|=;-d=t30rig+R6^(|9ch^D>NjO&D2J=K82PHqYvkyZo8gCWellp2fhaFy6}PJj8O7ianhsW z^7&wuvCFP;&SAQ;-n7!rS60fUx18(h))k#(83MF~YHCST>=HQFKQPWa@HJ@Hg%2zz zl!Z;w7562NRT;aiP2kKqU(DtSn70)amD!y0agEhtJDQEyraElHIa}K;R?by#D^cC@ z)o9m+4=h!OGKy(YfOxD*l)OKbPM4f>X&9jDAfV@*qY$fc@}KqeHeJ_gej3hw0VwRz zVCJ*27Fa~JQJa1~BI35Wt;Lcflxdt^YEF7`rOMF7h=o1rG-=qTHZn6xh^C2~c5${P zYO&iiseeqN={%mHIAWKg(N1jD8xtONcQR&#&i;4v457WE#!0_^WGZjGQ-FsLh`5bz zYqBJ$(iNGs?^2bai^vLKT<%M!aWPrYkyqIS5RVAjTsuCm2?Y{ruv|FYbox?WQd1kQ@MXWh0mS;`Leg@$Z;a#&EgalVVu z+I}pZ8j!yB#Hnd`=eW#4uN8CiYMO|2Je`kr{8#2Eu7#q(rGdHyZA?L;VjYrf!Adr&QlU>6_*U~tqWNq`%xMwVdacQA zXB@0Udd_Bdw#uR<58K`mz^t#1;_Ia6kAPc~HsqOy`|mY(xSI^C1eJVduY(CBeS@L33Z z#&laKQy=$^gHxPGUNdfE^~G)L;2l#7k*)2fC)+CPL{%*V=Zlw4x0u2yPZ-9cdS&9( zAXd(U$_rik?T@%idJQn|&WX5HujM}5ac~i8$kq%oo+_ti>AQ%6bh;y>#lXMJiS;^j z6Gb7FwBQiJ-pc^L)>YgMBEgx{R4S~S8mm21gQ2kVM0u4vMAa;P7tt!6w#sNMJ2q7_ zJKmBf;6uwwDjvMxI60@J;T)&UXV`A|%$BXH;${efvvyk|6;@4+)xPNx&I=Qmo+MT7 z5>>JET|}#N+A5=E+N&H?;c`p%6+2BmcEOT?;B;bjB|4+)-F2Rmln=dYY40X{I^wkae4K2L!qML z?g8A^Hsp=fzA4QlVB6euB-k<<^v=X`?PBEnMj0*R+o0wAM<m`wHVvNVIiV-xfJ|LQQQxQq2oJ%m+%o4J>feIo#A|cx57+4w6i=f zfpdFJT_+ZfbA@!)(TkOHJ;!yf&sVb>kK+lPW8knq7?CDDnTQGO^Ab3>QscaGzDzxQ zA5Hki5qPZk)XuC~9KBJ;6F65RKfYwICd$p=z=X1eV}v=M5YZXiMEI=pdHum;tqeon zVJd>VvSeZ$R48ZGE{@));>zC~$iH328)lz!Lq%qCeL9Ae`{zF?_vc8Q+0FUGxR4tS zjgs4k;DR{%OCelXF*(iNU5v}Pz&Wq}agk5Jcc13r9)$Vc$>9ZyE4Z=;V%?Wrd3&GC z{qUUqIxg*dW$}>r#>0s2L6`vgF~q-t*757W-foZ}IsWwnj+>4ySX{%+`3oVs2VuXH z)pTBZ8aL-J1#`OrzIE}h{&D8|(HY#FzZ76z>$Uyw-(h`ky^C=cH|MVee-DDV9b4O7 zjI+2oen+a7-eaS0RVu&lldyw zNdauOcgPN?q@H(f9l+|Lcug{e& z18uTl4_<~^zR&|e7lGJL3to_D;zga!_Jf~{KQUu;rdrRPCt^JsJ%-cbakmkHY~ubP zf8LL13G{VR$}DLXs5NnF;!I(YPGJK8T+dd|aq~I&xhldW@c#)l%p#v#0X4^h*HWNv zxVDCY3el^WebiG4t;J-+m?ynHJp=hInv`f^4@EQ1k`I*XA5!!+d^i||h=h&~qkI!! zZ%OJuHL1`1w2XIxJSE`Wj z*@pHk(V&8BfkF5QTWlTHYb=oIxCZ zcBRRE=d=!gMV=iM35r(zQb@wH%UKjnMbTXNS_q<(85eJUVHDi~fMp7sELMQZhB-as zNqiM~iuCSn;Cu|u_ytkCkNCA~%J=sINda0T!~L{XM+BH2ZL0QBIpC_L!SAknth{&k z!j81X%t2G>j6WLN8=Zt;_~Dmf1xs4vl2j*wLP@^T3g}6tEL+u}Dm#j<*8<`V6*&KF$cS zs<0>3Rqsi3yj~Zv zf@BI|-?s?Ngv8TWRJO#V?gPmMEBKw7^GD6RnA8jQVs7%iHh%o-M7y%S6iofeN5tJ^ z%kwi0H*uLl^4?O#flTYTDb96!)f|_iUwl4PN&uPmN%pRm)v6^dNcX}HWCwXe{e-(} z>I0Mc5Q6yhOQ9^eW?u}e@o)}A&64&io|ZSf>=Q737AQ~k+T4Tb`$;ES;x00-5^B57 zm=h-+zgpz@=Ek`1g=Tb7+Wt?Rc6Y|=fl;Om#2~un z5mZ9RwROw|({-_2&Fk-00hNLs?J_CN&!s=rQ%s~2bVuK}*}2lQH|Qn@fCFcC9_)_%Kt)*OU%sFmKwIi z@FYGZ_uN{2k2*PSlXyLmf)QAA;X%r}e~*|=fNS992!ByRFsfv3!UNnEH8awH5!!F7 zz24p1&<^ZVJXSDPnb=#s?k3=D~@!@Wc|>W*_fZXbcdh|KgGKKGAT1BlJ++$S!Dp@$mq{aL6LF zGduq!gu!$Oz9Q!sXbGBx)oB*z{&U~qzI%@Qu0X)heUNNT!?DgwE#cfd)zzKGS(N2W zEaGpN%OfRh4!*)*{{TULE)KB7QKi!&m zQ_(Kp{gha&JZ=*(z*BUl&0bqJyP<~WU_Y6nUpQO-y(>xhD_C)T&es!A1A*E|Cb9P5 zYNzI76OtEV^5Bp|SUB_a?koetB6HGofY8#jAOFZ7^9_x4$qo<2hr4r~6>*t}%TZW& zVqW0%<v{*ysa6jylCMUyx+t5_z9YjUnL`65arJaL3L-njYKyqpDi76lu?8g*$apmRxNK~ zm^2p0_SZjHg!o$54N*w3^K1&iPWaS}ZhiMVssy2X`dys7Za`LrUVEXIa1PQkD|JNbD_?An8Q#UJ?}GM#U95q2yX%lkoMJ74hwwS0Skj&y*pgHNaysgc)c(SGXn!d#k>m~KuRmXC&cx@fdiX2Z&p)NYiMX#wrp8(ak0I<{mhv& zd3boz($avcjE#+ZdwU}zBfs3ZBo5>=mIV0)GdMiE0g}x1ba4#fn3qM z$L1jx)`GXVGxMGMn7IRg((KwV0YA7^g{9H418FbX#{=n7W$ci`Nu*88typ2S&&pI> z$asmm^Q0y5u+wBW;x~#HU>&z7rnKaARi0@O-&6b;8lgp?C((vGX_~ z_hY_YEx?R!L%oGW~6-+7Lz?g9llt!@@(Onhv|lL zIeJmkg*%d$3n6D$wy7fsHD+SY{Ve8K0k^&MG)R^XzvXlg44xrW>#rG|Ep+Bk~Bhq^$w5z+k|q)DK{o z%=2t|R;RK-ysB|Z@dC8qnzlASRL;2Ol?N$ZScVhYdceIaS0 zcA$K4Lw2|2FZnpS4kcxIOZFZ;rH1d`hP)7d1Ubt$MKeC+T_yf~%mk)khFqU_&ePez k+zc@~Qt+iL{_C&TCl@?e$F+H8cK`qY07*qoM6N<$f)jqnl>h($ diff --git a/docs/html/img46.png b/docs/html/img46.png index c1a8232d18ad2866171e0162aae6130ba96a8117..bbfec924ad1d8a92ad80f69ac9b7e58a8b229727 100644 GIT binary patch delta 202 zcmV;*05$*X0qX&fDS!X}{{R30?(Xj0-QCR0%)7h0s;a7)nVEKWc8G|GWo2blR8&Jl zLozZlAt50?Hi?)30004WQchCyh*gFgC|=gc6<^4G;!XMFJzsfdVkwN8xBR({Tf^@FRvUxI?}L40~W~-U5afFt(xs zt1yh6$iPzoV|Pzo4!7qzE1by$SIoe`_5g`pz%YaX0HJpjSL4+kMgRZ+07*qoM6N<$ Ef|BG?c>n+a delta 202 zcmV;*05$*X0qX&fDSyDgz_YWnCMG6;fPhR)Os1x$85tRKb8|mGKbe`CW@csp001*H zGmVXnSy@^6@AJt30004WQchCkPPg4-|mea|F)bU_2fG7EWY%0z=p5z|aF@GZir8!PwFQ zyjx*xYX+VI82iOqcep+3yl^HXTrmR!a{>~(fMJ*b0FFWy9v8OIh5!Hn07*qoM6N<$ Ef<5C-#Q*>R diff --git a/docs/html/img47.png b/docs/html/img47.png index ccf736bf32a66c071f76ebfd1808279d1328ecc1..d9ff9c2349a5602a286d725f6df1142773b5b9e8 100644 GIT binary patch delta 471 zcmV;|0Vw|Z1NH-uDS!X}{{R30?(Xj0-QCR0%)7h0s;a7)nVEKWc8G|GWo2blR8&Jl zLozZlAt50U5D;SNC%OOt00DGTPE!Ct=GbNc00DGKL_t(IjqQ=WO9Md=#b53&m`hH) z!bq?RSZJ9_f>o?+uTvC6K@hu?Nf!lS2?WxJcAkYG+K5;PB7X#oM9?DG*v9`Lt=Kp_ z_rYE^rIqBt-0l44F}php{C}B3&34A)P%5jtWAIwMdI7S{@WS?)KRZMsHZ*h>cPP<^t+N7{%2{tl4Su3I@geZm9(>xfnE-CCGkm);T z4f<8puEt3ojDJ}}c?jAe>!z$u6=`3!W)|kam~Yjm&rBO|23tn26y&5@LDtt%0As#l zhd!$nAmt~96sSSgSZqC~*!6Vl)PwjLu|86~L$@w5F29N!nOV|GW3@kmsxefo^ej)* zZGc?V#mdVUP4gU&nB&izb6Q5^_oyRqEeFn%Xw$ zpa>#pC;tN-bco>KAQ;rW{R14jI{9OAGdL?a3NGCQ6%FX((tmc5+Cj}A=pxoqa4DYe za!Gq>x{J^+JaX@o@4dTwcfdcD%H&KLjD5*0c{Kp1O2O!vVlhZE;^PV|v;llRvi29? zth*QuTXjcZpgf}} zn9klbDgTzM#(%CW5SVL(LZcNDPDZcM314NaF?I`qxz@OyHkd8G$Lbbv=r^mw%fF!t zfw?{?j%=!8hMFYQBx_IHdO@+^My<&McG_p%r+7ltI_2TQ3tRTmV|Z;%=l$Okl9jGy zk6uF&T2Lib;Wr?y;!CHKcc={}3@_JgwN+(H-G^}5byTKS8Ypc3AYK|*#n#IR=>h$k zTn$()#8oq5okeh6^C7O~BGxwiD}Z9ld@JI_OmAq(-0C-?aOXy+4>i;u=obSqW5Hzf RDt-U}002ovPDHLkV1j=m+bIA5 diff --git a/docs/html/img48.png b/docs/html/img48.png index 4c213639fdc9c65b53bd4fe120a1493e77b09ae9..7c9c1ba825d0c415cdac3932193d98abfc26991d 100644 GIT binary patch delta 346 zcmV-g0j2)=0{Q}wDS!X}{{R30?(Xj0-QCR0%)7h0s;a7)nVEKWc8G|GWo2blR8&Jl zLozZlAt50U5D;SNC%OOt00DGTPE!Ct=GbNc008(&L_t(IjbmUKLV&r0fC8-Y+zg>$ zI)H)UD44N$BW#F07 zfK#4BS&V^^<%z_mW4+cEFQKp@D!*sgXPT_ zxNa~oOh67l5K~}WaTwyhUy zxRL!20*pug22z0C#}~lB27{t-#`5joH{;MxBkiGAKF3*H5 remEHfp)A%vejsWBqX5Gw7#RQn_`qcM8}e5?00000NkvXXu0mjf}+IYq^PJUARv(RQhgUt17k^$UoeBivm0qZ z&U{Z7#}JK)$q5VWHe@(FEK(?pl$5Ao61d~Q#^&}c#NxXWvvW_hY0vRUi31mc8Kz(1 z;YqN#$@tt%Qq6$l$A-gabQ5wC?k))C**vLH@Fwq7*}u{PHp|%9<}ve}v6YQYaO7iU zd&kYgQwY?TXA$7i(73R>F_CG)bJfQO?x+hMD44VI0K-X#m2xR^ubKHo{_7>UJ^Li4 h@Og&xbR!;bpht^kxp}|W8Uvlm;OXk;vd$@?2>@A`XF31? literal 294 zcmeAS@N?(olHy`uVBq!ia0vp^vOuiP!VDxCW8%I8DT4r?5Z40-4s71MSxrr?p`pRY z$7k8HWs;JT#l^+;_VzPp&g9|YNlQxusx>w??(OZ3jEwATFE#-gQ4-`A%;50s21s&= zr;B5V#>C`=1wsjb`_&o_)gL%ez~6bgyrJ=-!v|)I`7arm@B4mcv#9@V$@cFx$J3tQ z=L|o*`_J(FbGKaDgNM5V7#`cFTb%#U^s$Pe=Re~KccwRg|A#Alekv*P&dA`%{r~S7 zAJ(TNWF#dd_$54Ou;9yhC%-_IkLQnq-tzOlZ9nGJ^Z2knT61FAi68NT7k?!L0{{R3gw)q>0000mP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001bW%=J06^y0W&i*J0ZBwb zR7iF5M1O%XRSqhLii*V>+V_;B05nvTSRbYk8(L&~MzJEP``h)>Pnp!afdjZoT z2DYSh1DG5ynkk!5?3{qii{N2sTf(k8A)0}qTuXtW=qBq1nACJpRHrRK;a&ohETN%L zQ!F@`^%$yv?mEQ4VDx|;rkH6eswrHk!PE|R(TP-;DIDAkSq#g7UR@3pUci+ARmPz# zhN6uh*b|oKTr?1_=-q3If4EhAj}UV0y*C z1hggz!e!b3H-%-zW`@H|#~rv7fDYm@&?$k+G@zLh!@$7)fZ;j=TLS~bW(EdEpb#g_ z-4T2@t}^nMsqX+;^;hVrD4C8`K;ka|=%o&JVEPpJpnxetLa0cC!KnJ!5K%X*% zIY3Q;1$YDxM??U+2_VqKz_1rY?*UqO<`|IS12lz!V}Ywz0Bh(01_phg5X%C%DGVDn zVKIainA{stM1YnXGUyc*^C_^fH-MeSz_1))iieH@h9N8qk1$v~Y(*C0c3|L`R?(pV zj9pM_m~aUa<7xp*v7hQ|=IFkR%}eNj9hl~g8H^aV6fp1stvw7D^f+?{zb*`L077j` z0Hqb?1tjW*fk-&30_Z;lGEHG~fY8j3fW9fgs}vuAl^Nv*2=*u#1*2dH00067YGM|R R_!R&E002ovPDHLkV1g*~0+0Xz delta 617 zcmV-v0+#)Q1@#1w7k?%M0{{R30zjp~0000mP)t-sz`($>v$G~9CV+r|OiWCsrluJg z8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001bW%=J06^y0W&i*I^GQTO zR7iF572M-%7-9xM36b$Nq@I)+z()2HZ%`lC}$86 z05hO~3C)y7WDfHNWZrvThR>c1h1z@#4D5xD5C#-%KZjxnp92b45kk#-_W)u_JU>HV z0y|L6UI8cr3>f#Jn!@q`h5H>$+J1(a!q36L?7#vH6_)}C0|NL(52I+~0=Z|qD2)3A zM8K>Bnlf92fq%b1j2jp#?hpn9JZCr$qTYePQy?Pb= zAi5W5-QCMT#$2E&4EzrBraa(#2ee-bBsm3c3PVF97DM=e$^8$C2+;Bv2C>3YHUUod z4`8POW4{1y%6wS?3`015ZZgE@{6iMvn83ilx&FUE2~aaIns$Q){lR&L{mQqm{6AE& zc?lh`17g#BC_^AaX8{8n(AujI+x~(>mjnP+-fRF$I;;+)X@&!9IIAA$Kg>`d4lqN@ z4c0`UZz}Pt#RFhvMtJ~&Jqkv_C>RRh3>Clu>X-rm=;8AL03IxO00000NkvXXu0mjf D6+`mC diff --git a/docs/html/img50.png b/docs/html/img50.png index 49cb9d92e30f4fb20581430e6298beda521bf4e2..dcc78c667d350c71459255c0ce91799f4ee303fa 100644 GIT binary patch delta 223 zcmV<503iQ?0)PULDS!X}{{R30?(Xj0-QCR0%)7h0s;a7)nVEKWc8G|GWo2blR8&Jl zLozZlAt50?Hi?)30004WQchC5HJe> zacdbk7BGmIvmQy`0OEEq@Dwl{o4|1#qS%0enSp_YfoDbovTGPw4iq49qnVByP}#rq Z0RRK>7_eoeR#5-|002ovPDHLkV1h1tTR#8* delta 224 zcmV<603ZK=0)YaMDSyDgz_YWnCMG6;fPhR)Os1x$85tRKb8|mGKbe`CW@csp001*H zGmVXnSy@^6@AJt30004WQchCDzIok=5fGyEI~km zCji3HS{i!NA~Oz!2kB4dQVL0W}FT^b~*B6YyaN z@pwNlFmQ^oZqO+P@z_Ne7`Pw6?LEQ3pdSF|*)cFw0WC@Zb4)lK7#6WHut8kL6*hrk zX#`9mk6;6XpeRE)vKLsr0+4vjd5X65#=JCUM^8^?e zcppI6j4tnL4H$S>?Z7;t4-A~k8QxB=0P}o+>iz`$Er6&z3v)L9Hn_dK9~c@*3r?CnwlCC65{OaY-D7lsHkXX);R;Hnz1CvFPOpM*^M+Hr_a;H zF+^ixa)N}3!l8vlOh)rHzbl#k^78 zlW|i4;~@n``LeczymE{ArOkeZhxOi>gxD7>sy-zWtH2PO5WvV#V?A+84w9N4^hvznS(Lqmg) zkI%AY%OoWwi;Iix?d@mIoSBxE22^NlY~0)18yOk-^ZnVhh!y8eSh@ZR0&CE+Mh5nYBxzf=lefJd^x{2Xl)URX+4J=1*m~UpS#Khe@H4 zfvt^`$L6)ev#AO^kDl2E6ii*XnL)3h`D29xyYptoF8Li7Y(=~E3K;Vxc&r#0?i^KI T7=7s?$lnZ}u6{1-oD!Ma*ZrFnYkg zfZ+g$9}INEAqHkWhAIY#01(V)U|`&EvIF9a6R9wL9NY|S3%C-PHURBn0ynBs}Sz=)MDT$(BovA3iN>40S2Z;Tm=m6Ob;f21wi0eXv8Ac z4LTqnGi`wDV_C78fyY3ngySd^1B3Af1}+7lU5A;DJAeg1J`xY@QhFpP0stw+VH@KykwX9g002ovPDHLkV1iYc+uQ&E delta 520 zcmV+j0{8vB1f~R#DSyDgz_YWnCMG6;fPhR)Os1x$85tRKb8|mGKbe`C3=9lrW@Z2Y z05dZ)jg5_2Sy_pPb2I<|00DGTPE!Ct=GbNc00E>)L_t(YiDO_GA%OKinHtH}caM+) z0|v$kC<5MB(ZI}YkR*kFdLc&z=g^gL+I$V1A3^*;1_t&*M+Srd5OAJkV7SYF9m<>c?g2y}>xU143G5CG7eJyd;#P7Xg;V0e@Ggv_0JFZ-xPpH9~j6z zc9`Jbj~J6pRA00RTi}f865nlA8bk002ov KPDHLkU;%=5HQtZ_ diff --git a/docs/html/img54.png b/docs/html/img54.png index 8ee9efc171844fbedbdaf685955cae00ef4d70fb..ff4ebe8b0f04a115590e1d0aca738e258c194aa5 100644 GIT binary patch delta 212 zcmV;_04x9G0pkIX7k?B40{{R3l#shU0000mP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001bW%=J06^y0W&i*HVM#OyOkjK94p(l#u>eUkFS1FB2COh9+lNAiP&ntu9Dq{vGC<_3T=Mnl;az=Up O0000;_sH8eE%`1mYawoFn|vbea| z-rj!Z%$YnqJZWiZK()rk#=X70k&%&|?ZqZQK4VFcUoeBivl}4EBu^K|5RRG22@0G? z>Kz_^P%f^JS17EAcq=ex`($l_Ir~{XPUZb?zc9ydck6aznTpeV&wSFaZSKsTpvzip zW}xoVuFe0T+~LxhmYhjG4DvlE_bh08C_AUPvU?|EOsK|T7Y%L(Attezap8W2K%l-I3U73_}M1 Y01hY?7_{`6W&i*H07*qoM6N<$f?3j8djJ3c delta 224 zcmV<603ZMV0f7RLDSyDgz_YWnCMG6;fPhR)Os1x$85tRKb8|mGKbe`C3=9lrW@Z2Y z05dZ)jg5_2Sy_pPb2I<|00DGTPE!Ct=GbNc004hUL_t&-m1AHa55#{!u=$bLyblm; z9#%Uz`|ackIQwq_Le1^}V2X3M@OFj+Z`ncY>CAdIaSgJiAX)YX=7i}mr2+g72z^XI zGZ+mZY?%N)24=7um>1MAyo0J>zP!cUfZ;iW6Us1=fo}@JZLDkp2(wC%{MCu%wq^r{ aAqfDLvK(QBk~L5O00005 zl!{X)SK}h$lujM3Xr!n^5Yf72b&H4?{D8PA4hEs%7{o!*A%BC~p@RA^_!o3=P$w_f zq$byjt6*QaAD7>APwp-O{&RTiH*!3`T`foYKMDciP08)kBkg;3T`5BP3rIq?MU^%x z4QtOtZlWAp&pQzJudEt;!a3lPRk?tDfNO|%Yi>-C3qaOJQKw{`bf!Zj3<8^}I&-20 zGKwnF9wix~pMQi%$^lR5BQq|Lv)~j+xRj&};JUrJ2R@$=JR>GF$+#hoLW$@AZz0N> zSTYv5x1Y9eEI z5pMl5+C`9E4446m3h#cY2J$1x1DOaO{SD)03vtcw^=ZOTw98Hqj-m?|%O$phl?Y0z m9l~mdz()|@L3`=t@8=6oNnRAMg#%Fl0000uT% zSS#sm6bli-#21JQ+F6KC;5LFFNbD350u}+WNMj)>l2TMKpnsq?CS9TuSN>NRWOtIhK*%X(X3sa@%$c*mAjMj<46=urF;d zUV+gFyzu3zxu;Rlznch>1$QNJgS0dhmNh930)I-fSQb(RwWBSU;ENbUzM)UENzAj4 zV;jj2zz=>^cYj6i7O95IY&F94a~lN;z%yQSw~*i@1KfwMSv$h)xP$iPC6GH5YF?L+ z;UtN`X^@swQ1+rT8~K~4sWdsh$=0;aLt$@@a+0XGA|Fy&fgFWiw3~Xeq)*#&Tc9OQ zb{dNoC^#;^LXR+n3t+N`aL9+TUcw%*VIilG<3r49Kz5Y}D^})07Nlq*Dbv|6KlUn# zAIW|LEqXc^nnAv9S&ykI3j2%{RVlY>pg>;0p9xXeHm3>AKp{oI%DO0oTxdna-nf|Y zlocn~<^SCzT5#@2qqd*&CgRt6;g=3o;%0oa?tfzg|LUSB^WDldZ~NRz6H5vlR&RQ8vV11EjWrdvm0FIf~10Wu$rqR z*Ti~?1cMHWcE|crAvm1}5zF*m;TkMR-?;0*mhSV0h+lC^hTgJo sd>DP1Q!@0f#9eN3N(I6 zto{Ky6dc_Am|Ub392JVYUL!S2pnnd!GzEuRq>@F{p>5QT z)|l5OCNFuTn?2KgC%?nH_r3uCOoGO>(<%pWu>53HE^VYogI=u>eCtax*`H)G!M5JAb5s&#>Spk5Un}-4BPl zMjXjKVBK*0KyUae-B-e7-hmxpwpV8xy6$OJgdiJkA9&~uPnYU7H%s(AeYu*|pOeU5 zCy-a{$YLGowQs_{iSQwdp3*XP4S>4o$pz3&GkQz9uEm(bbIFmyoKvfAhVKf)G3M-> z<0ZN727B}$^O9V5-|?GHag#iEH^DIn8fc(D*AMXgpGN@!rMdtB002ovPDHLkV1n$F BxsDS!X}{{R30?(Xj0-QCR0%)7h0s;a7)nVEKWc8G|GWo2blR8&Jl zLozZlAt50U5D;SNC%OOt00DGTPE!Ct=GbNc008t!L_t(2kz-&OD8Sr-RT#VIQDjcU z9w5PXqJcrcEC5M(qX7ehwh#mBk@O7+L6$_Il8Orq9LJGO;D6LBU|_XvVBne2fF#Pn z)4-svn83iua-aZ7lw$)!LZSjgG}Cbdgs2DpbTI26j2n zK{KXLfQT}PJFp3XSZ5d*JQ%pZUSUmO_{G3+0mx#{Wnfs!zyT6u?!V5kiM9U)(0VsV z28J~OOlTHNU{5q)&=zb!7353}1RBZq3{_N}fv13-fuRk}00!;`ZU%-;D1y<48EUUv oPmORu_YVVu0&4)K;3z-=0F&Y_{~yzHtN;K207*qoM6N<$f?L9nH~;_u delta 346 zcmV-g0j2)-0{Q}wDSyDgz_YWnCMG6;fPhR)Os1x$85tRKb8|mGKbe`C3=9lrW@Z2Y z05dZ)jg5_2Sy_pPb2I<|00DGTPE!Ct=GbNc008(&L_t(2kz-(>Jz)KhRT#VIJ!H=N zULe7I{{zE;;0H*;Jpl|15(gRhZkjhB1UYShO6nCD_^%_Iz<(`Pz`z&ufq{4b2P9E` z-VY4oG6oDhd>0CkMEM&S3~U4#UNBw{K!{G}zrZ=+6S^}uG9O@P&_@^jz<02a@i5rs zKnLyLz5yc2aC`#uK_G+iE(61S1{Sba_zW19Fz_n?S?op(41Ns!AVJn&>I{v1zw&|B zPoBfT;QN3P%~OI6JOK<6XFi|`a@)ND8p)iDDk{#vTfol1@EOej296IL3=EAZf-kNz s6sbq-dp`l)KMV{4d=D@MM*$H40FFUEO1fCEVgLXD07*qoM6N<$f@b@N+yDRo diff --git a/docs/html/img59.png b/docs/html/img59.png index 5a6adcc861aba0dde16c19449846687868505aea..12303b80e72984a6e20c48ae4e3d83c9dfcf537c 100644 GIT binary patch literal 1167 zcmV;A1aSL_P)_&M-t69Po_dSQeQ>+;`|W(cZ~p#f4(Owg|27VfzqRvNR$}^O`c^rv_Gq4sMcD{Qmv1F71Vl{ z%Z*qA)@6ntEXyjVu%ecm?Do;+I$n&JdCTK(rFx^8#*!_Go}l(!mnW)*^P@q*xShs| zSjD(ot4SYs`uk|mPEmW}Ve#d7jJ1asE8I$=2ce$Fe9Z*i8% zyE9buV?^n9p^XKh32lcqOM5wY1%-275N1e>MOc@!Cwflj~ zLFhp$l;2SU+2vtCYX_5P)THV%)ZcGP)`vi0gR_>Hshl14V?^lr4dB5b^e~HE@UZ<6 z7YCK~U>mU>Gt8BwHN-KyRWj&&KUw3f4c^8_$NU%(y4gbhk0A6eR?BF?owcPf>J?dm z%rN*3F)T^{4#>Jx{{Tt}^x>tMQzG^&^tan+YtHFN7a}7lt0`Ci4E@^H`bj?yX|ty% z)FSlhx2vCuGE@7A6m|TRt`@<*hr(h$ti{#z)%xEF^pAm`Wi^kC98<=aRizC+x7gTB zEgx=hm`p=)h1z3u?E&L)wXcC&fg8^=H9X+tMwmrw?`6wW*^mWHo{L@I&^jYI?9oS# zJv65F9`G%2gtb7X--TN8-88M!hPn6)2Af#@P0+P$h(OQRr|rQq{saz|_@cu!YEQ0oo@QF?Hj8rYY0a z)1{hn=V|87ZGkSwZ48t#!A_Mz87UZSMs4yO?_iju_p^N-r*Erpcb?wXI?nuSFHmak zH=e3fun@D=`)u|K@9JfiYr5&&{S@$0$F&`W8qMt|{ZyR@{hCk_o_F|@h#}IONTPE$ zt&?*?R|BSJvbws{RXxByF-C^)T<~+ttAT0KgD!#2+=@*L;TRuW!@Jj?JzI4;4Ua?p zRg{)R;VakwBElX<5}mmdV3W zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001 zbW%=J06^y0W&i*LBS}O-R9J=WS6yfvRTw>!+0D)**_qWUg<`eZhk_Q|A{eEqUBSl^ zr~bT%nEKS0K1{6zi=eB%C|VP&Skx$1R0IQV@j=i~SDH4qtm(c;TBYeiE47ep#?YFm ziQ{)??wz@_yOTaN4pR1mx%Zws-*?XazcWDF+IBsdx~cc^-dtjGyYDjAncb@EH1mZd<=XcD zvjL~EMvcPCk7t>UR4T`Uy0j~ML{S*tOii1(u`V+j#iOVE{MJ9l!pew11WDmd)MVLO zV@*#KY8Bz}S9mQVb8Exk=Y;1?c@kyAzv@lvJ~RF)sD37VRZT7(Pg#{gr2 zo$y;+%pBln;Y~4enEpYO82#*Ncfm2v^cFoDA}Yf}k#J*a(CrVXU!q5&iC5mpVM+8< zE#XDib*&~jvr>}b7f?={lY#~vWq2qW-c`bIo>LnIN)AlW=*$7X1oM1*Oz*JqgamW~ zi`nlSPJ^!};Gt;v@DQ?9PMxYza(E~3>)kZ&Ga2qTA1C+3ap}{cyA1r?V^nRQMmaJ8 z4@JYjp}fecyIA6!gR=W5jN;n8-0y;)WftcVHMLR*fmTI&{5NIN@@dSQkHSOI@K;Ik zDNg-}C$|7q{a$8$O9n=rndO7U@$f~LgBgELJerF*)hhgx`fRXNXXw%MOL*5@C%Z%j zF(P;4$)VuI@Wbw=kOod5Cx`3f^~=EoFu(3xAMB3Ewr`rVFnT0xS9oYJn#`d4d5iGw zkI+$){Y*@+&fSt{{UFWv|9*ZsIgB0(iu+lzO3>T}oaIms*NW(LpyWO9fhX6q4}Gk| zYpc*5^aE>T0nIy?^Blbw4(69E*(zx0<#5_|PdZSYpxfusRlpoWd)Bcf?eMv1 zY0CPbs80k%qA_UEEOID^)3%#-ytZz!pbcT*V_VD3es+c8?=K@Y1?uOwv2x)&r02$L zUxfx>NZ)n_1H1n5p%gx_aUN@~lrB=SuOuI}G^;p9hZ$R5KgG&D)POJbvoxUbVMDl5 zH{PyMPEPXo_g8f`Joo02F2t#sjo<6m(_U7UVRLx8lZGr!v%XnsgpEl$>CHT}*q@wd z#2da1k@2ZF%dkcGv#hD~sNq8E1_n`N&imrj^iM@eY*X!^mkAmVwg`WX=JW=+nK1TS znLGBrUjI|7YqWPn<5J?T((dtdOM)%JU&%MuktwLhNwK#ZMAPm};-516rgwavzr1Vg z>dx10+bY6NT;2KFtsYn{3Awhdq^;t)x~$iV*;YSm{CD`TZJFDC1b&HoNF6+fF%fB#H)okof(TDwARw_W2iFBpMeA$l--el z$Bb?;$#jE(!M^}Sf>nTlAz~whovE}|0k;u>V3JFSfq_F9!w9G>!y*R720}(K9suf* zz-0upGy~58%8X!`!oaryo8}0I$_X$r@8f5gziz@Q%h=AD4EVE#CP@FviO3$Pi%47BDtkU9mj zlEIFFp$b*rwgAb9N^B-DFz_WX3q#$@V8Y?Run3fnxX*w<0+7Y_0AU1M0Yd{eBMcQd z4+Jncg4tYQ6Bw38ph&}FBnRk9kI?W5Y=?nH9ft5>xR!yZU;@-09>E3%K~W4NEDr84 zNSwgH^ifc-fK3u;#1{sJdY)^0+!4!;B3I(_lr)(6A bf{_gXSm{p9H3k3700000NkvXXu0mjf+vn4E literal 525 zcmV+o0`mQdP) zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001 zbW%=J06^y0W&i*Ii%CR5R7iF4`V4eV)0H^;1qBJspf#_s(c~@(IDisv~l!mh7 zKjSfjzX41MePG~RjwD9fR6bSfNlgB0|AQw<9UKcoCT@> zfXj%O28O#78o@n*Ap@J{_YUxX;yu9dk8&2FtDQr z1*WNZrzup$QDf(@|XymOv`=gb3iBjWG$2QZ&zV30a<<~WFE zUWvdqK)?NG;NL9(GXe{Md4d~_h5?`vK!;3VAi{`9G#Uz6;rST15p$rq9~MHWA%zsa z%n7)R;BN&}j8Kyp(aIA+ILi!oxgr;UQwkYyJ|IfjC>RAJ9GsyTP{9ZQrRCuzI*72V P00000NkvXXu0mjfte4D< diff --git a/docs/html/img60.png b/docs/html/img60.png index a936486bc8f114d0b6aea1b9da96effd0a461522..fa89897d1759ef00946a0f8d73b81f5b1bf489b2 100644 GIT binary patch delta 240 zcmVDq!wF;Ue(@7#NPi zIjjN<3<72WP#&)U1M89W4N%^6Q3j6VFojH0MHzTzG(dSA%4uQ@j4THVAiQt}35IB< z;|3631CR#?>^nMsBX}AN3}+Y^)S$d328O*13>i>|0L^NIsbg7qgu&urD{BF=7ebaI q^9&v#^Vk<4^SIqncxep70{{S_&luNebfgRb00005U~D7;Ue)KFfiPM zbNCK0FdPVe0Oc_qVBouH-T>uoKgYm-9j1_R-#G@}{U4w_ernOf3_N@n3Lw1a4CfhM zFkTOU@IC-}aKPUGe+7ak&%kh(fk7C``^do1#K2$=bqLU`KQMKiJ~tWSbN=xaAba7Z rA2Kf>5t+yCfXw5Vj>0o$7>)n{%?cw^fB?ib00000NkvXXu0mjfLnmTR diff --git a/docs/html/img61.png b/docs/html/img61.png index 373ca564e9186c84e21f21967c863deb26fe4a82..22890c94fd3b155a97cbb50aa07c33e0c1895e0b 100644 GIT binary patch delta 335 zcmV-V0kHms1BC;SDK!88{{R30?(Xj0-QCR0%)7h0s;a7)nVEKWc8G|GWo2blR8&Jl zLozZlAt50U5D;SNC%Tbc8h`A7xdWM(fG&+JTPXl#xP!?628N>y3|tB@X{apo0uadx zf<6HPV>OimYN;5ZIarNB_p(a~W5lU)iTn5K#{@XTmn zVBjb~)%yWNa43s0FtQvdU|?NWt002ovPDHLkV1i-4et7@@ delta 335 zcmV-V0kHms1BC;SDKx;qz_YWnCMG6;fPhR)Os1x$85tRKb8|mGKbe`C3=9lrW@Z2Y z05dZ)jg5_2Sy_pPb2O1%8h->J{sR(+8C{kiNtS&Nl)+g5A|Eg?@B**I|dPS*+vk-1eAR{xq^Xt1F9^a1Bl#yj)CDX$O=UU_W%F?e}&1i0BvJn+y|7s z{U6Bsj;fan>|D{q3=9X}vNJF|L6r>x5ziUUGw?OYmNGC*g8JwW#D9>tAmRg17S*j# z0Fq_z|GxsatULq5U7*tpFlFZg@ka)RCScHlLQ)D<7O0pH=+Qq&Mj-)?37kGR8RB#P z0UZtmyHRD?VPVHN=NPG+ApHqXcA+0GcfG1Sq2u=(tJ-bPxcg hn+*``Q7|k30MtS}Vh~)7lkETi002ovPDHLkV1i$@gbn}z diff --git a/docs/html/img62.png b/docs/html/img62.png index 66fe4003ba79c27adf9a72b8f9fa8ebf99c01db4..48b9615955cbe58d76503bdfd78aa0d86ec4720c 100644 GIT binary patch delta 250 zcmVDzIok=5fGzt_lnc zJOL0k)2hO`UtR4`Asfq~^aLyTKBn70t9uF;^U0HRU`h;suQPIe&k1bo=Ry!${r zF?EAZF_>5Az`(E%ZZA&*1JhSHkNE)u`vL~01PI5Wg@H>Ufeq@irI`#|p>S6olwe>K z3yN#qV1Rka^n@7={M`0FFQ%<$8_ZuK)l507*qoM6N<$f?w%n Ak^lez delta 253 zcmV5U~D7;lg?I1c1an z2%FL6U9ABF!-3!jAfC_%2F~RSd^gP-Ks+Cyx<3K@*C8s;0(SA654`(7An|zkE);-x zT0p$V;05FL01&Tc0s})E+*;lb42npS{pJPo)s?mP{E{Nl6}6fZz)gDnUw;1|5@0Mw@7Ty;y8b?vGKWs zKV!)08aB3Lyz15q_S|(~WM-5v<9HvQaYX4Fuhr26zV3>Q=}dRj&hhi?5q@Cvj+du~ zm&b>*;5Co5#0{wj*I3O|4#?DRoa?y1(#hh`NuPyl;ut;R5}pM+JTeSf_@maF(I`Kf d>F@^z2HQ&tCN<|7Rs!9~;OXk;vd$@?2>>U=X-EJ7 literal 283 zcmeAS@N?(olHy`uVBq!ia0vp^Qb4TE!VDxIH@NlzDT4r?5Z40-4s71MSxrr?p`pRY z$7k8HWs;JT#l^+;_VzPp&g9|YNlQxusx>w??(OZ3jEwATFE#=48B2ovf*Bm1-2h3> z^mK6y(U_Q=us~qLKlg`=KD~2%`Q7|qedU1yg&&M9yJt0iHn{Kmna!a6vkLR!*nh7B zrrzO}knsEP?mxrBLKA}m{ihFi2QWM<{JHnH(ubyxRSYxCm%rPqd}vuL56>-*ICf@d zJLYBs<}+5;KJ)N=<1u*sDq!wF;iB@6Lg|Rp z9o-EK0%ida?oS4$)2v6*H-I@TA`A?T9LJ$5IRzLP&hyM@fMW2t4=^x`GqM~g0Q2}8 z7-9;dnT{KPd5$YOk`OjcM6q`dh){#^et?J!D2GK9+3~$nK%-d;koATvMdleiLgukA jK<06~qwvxgh6w-wfj%0``Br`F00000NkvXXu0mjf*|uRo delta 238 zcmV6vTf(=JBKOcppIM z_c#9k_`tx!Y6s!2W?;O*@OE+qn8SIJf#DCs-vWpf_W=fmTW1Wn|3i2j7Z_NNGaPu! z4(4%vV0c@=*C1O8=FRc{Z-}sI4~m<5L4+`jw;n{;Lphx1kkqk$Is&wpuK-!^OFv{@ oKq4}a-2s`$F&%|x%rGng0N7b1EXBzP#sB~S07*qoM6N<$f@j%eX#fBK diff --git a/docs/html/img65.png b/docs/html/img65.png index 96c2af83e9c08ba41bde6ff76bc7a7d81872afa0..85a75169da2034ebbd4d9d6e3857bb96caa682af 100644 GIT binary patch delta 516 zcmV+f0{i`@1fv9yDS!X}{{R30?(Xj0-QCR0%)7h0s;a7)nVEKWc8G|GWo2blR8&Jl zLozZlAt50U5D;SNC%OOt00DGTPE!Ct=GbNc00E&%L_t(IjbmUK1yEqoK%4|~2ZGIk zOAopPk{+G_9D2|tjv|#TfR4G4L;7=moLLE--Kf03F51V5qp_#oq#Mg@}L6Koe607`Toy zC@^reu3Xv#lUHIe!t@U!Fc^e^X-ERdQUOBZz_d_cB4Wr(AW}I907L3HLjeN^DS9{= z7)L_t(IjqQ@ZO9EjW#-Ga$70`U5%xp&>};5)K?%ikAKWgPeq-oZ^bE&y@8^BK-|ze00e@0-XGpN7TYgZ+4LDooeo)2*!m8y<%c_HEIr8v5 z=x)H!NyD;t^BHHsJrRg19?;BhnPXO6BLx$r{7%dRJ|%0+qV8m&NeS$d?g6#_ot*Ll z!&W2*1!q8dR0ckC(0^uyx)7JUa1}{Ft>Zh%L0hnXmia2y|9SQI}n(k)p-30^+D4 zVzv<=^lh$AbkobAEc+Bj+Z&`-{s34|De|*w?;3Apc$#--Y$`A!qSvGWB~$Vb`)mp&pH=d+t`E2S zTM>jM^5x$~$rKRK13-3!NaGfp@s$g0$dg#&S#{LNzy9^>^aXK(fuP8b=c)hz002ov KPDHLkU;%;#AMFJI diff --git a/docs/html/img66.png b/docs/html/img66.png index 299747ec8311b576e4c501b96560686865f25c34..28dcbacb1780dcab266015dd9a18938b478ef2b6 100644 GIT binary patch delta 383 zcmV-_0f7FU1D^wsDS!X}{{R30?(Xj0-QCR0%)7h0s;a7)nVEKWc8G|GWo2blR8&Jl zLozZlAt50U5D;SNC%OOt00DGTPE!Ct=GbNc00A9IL_t(IjbmUKK7hG{ICVrSJ4&1~ z0kZ%Ehx6_E(P*t%WN#B6Pjo@KuTf$IulXU}26MwQYj^j{v@yuud(>ZN0WgOfLYzw#&m^K)JB`hZ}B(XLyvK%M?a)7#FmU?P2a1`iq zvQ4c9i%ht}Ai^OK&2${(T5Y)7SXOLi;4#oC;W)|!5@0tLV*LPjz%-aLz8hDeuHkY8 zQOq10I5sdeKzOBl&zw1P0Bo9t1w@3KvlLA87Vu19Du60$gUA-%!@?5|UO%^cmAQH)aoLO5XQIdgzv d6pVsl1OOcrKnu~0`QHEl002ovPDHLkV1nNcoQMDb delta 381 zcmV-@0fPRY1DykqDSyDgz_YWnCMG6;fPhR)Os1x$85tRKb8|mGKbe`C3=9lrW@Z2Y z05dZ)jg5_2Sy_pPb2I<|00DGTPE!Ct=GbNc00A3GL_t(IjbmUK0)X{Daq5Uvc8@q^ z2ZA3U@wVx%?fuHYY-k>Us*3NXc>^-{!v%hm35D8x4V)j5m4ESHhcf29djL_!`r$)h z0=oml1!QHs`#*qb+s`m%3?CYp9asz)8v?-+(Hj^H`9ARQT_^x@fVyFpa&C0sFA(Eq z-d6z@*`UdAlK;R9#_J&0N+8@e!0-Vo{dVc@-MbgS%C3Heh;i`OfoY}!-VKZeP-XuRmi~jWA%I7KX9BwblrsgP zjDte}MHxek06&bwQh@O3$BW3y`2YR)Lxi;d1Tac^fe;Qj|K3Fj_E9hj bMhE}^RcBsPMA6~e00000NkvXXu0mjfnxv+( diff --git a/docs/html/img67.png b/docs/html/img67.png index 83860d2413c5d1e1e8923fcc8553d17050e00d63..5de398fbb70f6748bd04dc2c7c284393ffed742a 100644 GIT binary patch delta 224 zcmV<603ZMI0q+5j7k?B40{{R3idl<}0000jP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBOYl5R4oFw*UYD0d!JMQvg8b*k%9#0B}h}K~xx( zV_={VSTrE>I8b;z0mwW?=2RqJj9WDlucrW6<;e~(#XOUNO<5s=LBNL{#N*_3V036? z-Jnwp;uRYz#4+%|G#GRifK apiBVUQV~%rIw36p0000v$G~9CV+r|OiWCsrlxaq zb3Z>nnVFdk3=C#wW&i*HGcz-djg47ZS&54Dc0 dSON$k000S_8YlZ#(`f(z002ovPDHLkV1iI;SY-eJ diff --git a/docs/html/img68.png b/docs/html/img68.png index 5c05b81b1f2e00af9ac36b231553bca808835c10..29cc1f3e6b76a6f13c24411ef7fd279220597fbd 100644 GIT binary patch delta 285 zcmV+&0pk9m0;>X$7k?830{{R3|F1a?0000mP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001bW%=J06^y0W&i*HsYygZ zR2Y?GV4xguzCC~XgaJdES}}@n1P?>o5_a7Q(F`n2Aifby)PI75S&yNLf#Cp%9}E-a z;AY5TSjND#0jQ4204D0G#n8_5U;^9JY6b?g15i`~0{{R3i@W>o0000jP)t-sz`(#JCMJM@fJ{tGrlzJD85whP zb3Z>nnVFdk3=C#wX0x-iGcz-djg47ZS?vxMKmY&$0d!JMQvg8b*k%9#0HaAnK~xx( zV_={ha0Q+`e$Ih`Nn6bUS@<3g!y^lZY$@IXj@KZ*H%!!zkAJ~CfX#s60EmADCd$Xo zz+}Lzz+C`T$L#B?KgVO=1D2H7M1CPU=48F763=A#>5K&e+S%|$n z%)KlOd>T--etr;9cD`Kp1?+dBqI~x*z}=~UaBo31Ops{6k7G#i4@1pn_TaF$TNo5^*rt4jHS9Md+SEM1OGUpp=4(le>R`vy+!X z0(ZUJ1^XReK9}TP0{p)kA#bWg0-$j@A^|YkT>d5il5#{jwf7ti0du|01qT}!^m7+t zG=25;B;kTyz~^1GP2#i^(o_h8dt!sunoeU%V;loI5QI1pJZx#U!Tbn*#pibNR7=&ztur`UMS` VQ5CLt84Lgb002ovPDHLkV1fb!$5{XX delta 417 zcmV;S0bc&f1Hc22DSyDgz_YWnCMG6;fPhR)Os1x$85tRKb8|mGKbe`C3=9lrW@Z2Y z05dZ)jg5_2Sy_pPb2I<|00DGTPE!Ct=GbNc00BNpL_t(IjbmUK27vWH0Z}vsSd}A- zqAIwDRrx(!3JwH6K;gf?@&C&MWKk3ad^gP-Pz_$qzAP1#lnf3$TfDOvj6rXFhi6UhcD}00000 LNkvXXu0mjfV4J7H diff --git a/docs/html/img7.png b/docs/html/img7.png index 57b209d47a1bdb1b5ff9193597ea880c7fa01583..006d8d2a400be76e8e068b128e14a2b5162c10ec 100644 GIT binary patch delta 1033 zcmV+k1or!{2%`v)DS!X}{{R30?(Xj0-QCR0%)7h0s;a7)nVEKWc8G|GWo2blR8&Jl zLozZlAt50U5D;SNC%OOt00DGTPE!Ct=GbNc00W^(L_t(oh3!_&OB7)o{_V`p&g_Sx zm7?HbFt7}@HH<>221)`6TCHuhJZv7c524j0%sh;u>8aKrJb!dqgU#yXp}?SGORKV2ui)_LU=@j?$oYji23iuMIQhEJqJ?IMV4jZdY_|w-=i+bIx+q zZz4xu-Axz;_J5Wbfd^DUfgJX|JiYxvJ^@F1xtLc}7Xs^ zgfeWfl~+!diswv{4r-3v3E;}?dZFr}44)_sHup^izkhT1CS*PXoQ;t=8f9?*rZK0P z!Z9?fyIOgGS zxYNM6qXL?<;c!?qnP*wea+=A^O}3>#nqi`();k!YNooj2m*Oc%4RAHRixLBa#e)`#r6L!sc1hG0_~= zW`5i<9VJ*{Z>7y@TD9Z{I-e%`D;l%9DJPQ*Mt>KzMVFPmt|VNt^zVJzp|2)i2=JDd6rb% znYq8HFUVb2IhJ3V`D4ABUPYe{qb3r)@eNP!MH7SIr}pq$S{lH}5J=gv`_Un_UQVsH z2!9ehCcivcX%c*5RNqRF3`Q%pN2`^k5rPQ*H9HnPA>UXpr&fIz;*iwu*)Rrv`6jP| zFDz?pLy%+;m}UGs5CjjJc$ST9o~4EX>B;*_4jEQ^I4dIyXvRoxu3`p8wY zK$1YY4CNJMj(1hyD%URYeJemPc!$R%{C{^t0?$uSMvl$1)NtAGN^h@`*n3qWB8SEz zp?iJ>j((d`cCcDCM}3r$U(MyHh5{H%rx!$$v2(Ji`DSyDgz_YWnCMG6;fPhR)Os1x$85tRKb8|mGKbe`C3=9lrW@Z2Y z05dZ)jg5_2Sy_pPb2I<|00DGTPE!Ct=GbNc00XT_L_t(oh3%J3h|@q6$6vP1re)it zev2Y{R>8^&iXTu>5K(FbSy>TX58gafSV7Un#e*QCTW~=X6n}3jh}4q`A{FrpalM72Bj>9x6hlE)A1{0Bdj(T`E zQ~X%DCYSjRv44+dAtAOF&!CR(Ime(MVDDwoY}0G{{$pazg{cb}B&R8e-Z zGc%6cTm^8oK-S?*#QMu@WtS0&_W9zF01v z?ZMemJ9s;YKS8_DGqMhc!U0_$^N?g#0WbAR)OFozcqjUpQhy44_qP|nK~gd1Q0Duu zSao1(sekK~2A3dcT_K-RnBUcZ1!ae60sm&CYG|6OaJuRneVdv+elY2heU+Esr9>TH zhs;8-XTlg2-d^7UO81Fmp4vZ!$FD$|`pKZS7Efs6ol1>e2KJ@ZB_}?WP<9yp>gzGq zg*ws*Nv~x{(xjx4uiZM>eXyj=dum@LaFg{cL4RR#Kj(+p<7=wp2AV_)`>1TNd@{46 z-|=ZVIv#Of5E@YBQn`@gi~}oLdXC1Vk56k%A9K>v_;d=rjhqec29m+7!=(!F>R?8H z09d5i*L7!I`KZ-nA8ArjW*un*guB7rK!Y+geai`O*OiAJpZ+}To)Q4l;er zhJO(20~ zl7YmsnMKDxmLUJ#{-R@zlXQtnk|y1xx(AjpiqH8C5ZC<^5*zh=ks!eJd z8>p1B6XqOFJKktFd%9vk#o4x-b$IE5cYi<-m##0m2QFj4{Cr=9R7LZ*^uoPP?tBLa zkNhF(uqieUzbuMBs+t`ZyKNn~jg2LLG$T7(1NHhg`iFu^rF#9%(ZEFXt4Smy85Z!5 zBy#qa)%$NoB1{bUe;GM@%i``|!A2rXX*GMR5`tb``9?BqR*TvHd;JBK9bM>V&kjAf P00000NkvXXu0mjfQqc2z diff --git a/docs/html/img70.png b/docs/html/img70.png index 3485c81064f9c764ddbcf9eeee4e151c021a1726..838139b8bd15d89f8fbd7cab4914c0e0bc58fbf7 100644 GIT binary patch delta 575 zcmV-F0>J&t1lojG5EP2zTkO^)nv( zYgO#?{_kOiVSl(o%z}~? zzw2KNKiQ(fyS8EdhES%6c?iR(<4ZTI)F&LdZC>gF^OwjJU6iyT1aYDUwGqBC1LePR!zk`FDgK-iEv40>^q$n8_MOs_Ie~1!u zmnOZtw6lYKhL^kN$?xucFTlT*>~u<&8thJQYj=bP*{@cuw)U;S#0^qaAYlV@fgQla zZn+EW4p^kM3Mldnl3|$GzSQffJO^*kItkSFa)=y+U}6U&l=-gJSyBhqZ2XY^#}RcL z=Z%4>?T>KGJ%1{C=@27T8x``DAEBEo{tF*!x}ug07Vf9@C9T7%MS;5(EFU4F)jgZE z>}(s4QaR-=pNa0>#XRlZP#S7}Gz;uD+4T!!pvP3qZ_joW$B2J$0N3cLP@2Oit)8-J z?Fot2K7IgE6wWzc`4F7?#HV{~pnX8n!HK|91BsHCFn=&6P{B|D#C7NqufLreSC{Uh zNV?V#8v{*-8TbTe$e;z?oSUV*ja*CNKoSX9dg-w$q zCUWYpb?We8!! vWRjH-%O(Mvx|pVzB=j@d0bO;~)nDrueH)OwwoIti00000NkvXXu0mjf{%8Dz diff --git a/docs/html/img71.png b/docs/html/img71.png index 687f8f112e9657faa0554d486adccb3e3e373b23..c553eec29631ee5c11dd105725abbf9319486888 100644 GIT binary patch delta 592 zcmV-W08Jv%yfFfa(11z>23ajQmg!a@fS$+7{cy`A9^gElk73H%cnbT+Ua zN#B5>siy$do4S|4R54KdWwuQPnc)yEjt&eQ0vyM&Xgb+}Y53XBJcRZIyGE*ps8J^&)sV4BpRN`KuTvLFSZ^mhiLWeHSc1DIl; z2qO8xoD7(z45$N+D=o%!00)}07(s+1JnbTD(qI?F;)e<-9gbvx#l_`7lC=P;i503% ziNOd{KMN$~6|;H;cK|^F#06jwvJ|Qb%)kY76u`zDVCGXm@&XtbJVIw+16x1@Q~d;n zDh5!}P)R^CfPDcv0}J4I1B#A|f(8s*iqXBm?T*gC0w75;G?am1TLQ$k#&);?Y3Phm eFbYP&pa1~S#eGJt&1|^<0000!O$sRnQ1Nvix#xzUz=J*0~`0qB_h5r0<|^#=;Hgf32!BF3BBYQ36=_3i%>#CNt=v!eQr(bmU3VtTHsJmQI^|~NOT#+I15?BXIuBkI~rmF!Uhh=)FH0Q z;gVh!0xuL(BNI?m3U1A|nw5COK-MI}@yffL#Wg-O&400iP=>nznWKK(ZgMF^Yu*4* z*SP%wkI^uF0(EKRqWhzEyJ9!>6r#1c?mYIwh>WDU9pK$hOc_Yf2e#e3MA9Fa0P%Ix zdNx_55UB}@sJH`Wa7_D@)?u2afp>uP)IuP6N^^5m!Xe(Mm_fr60iiB3_^EN^L04F? z1U(>IUq<7W36L7-sONVc-t6Z%+S`H=HTejh#H){}To&mWOM_wZ!h;9Y?Fmv7t)-Mw bO8-OO&G55HzX3FP00000NkvXXu0mjflHwPo diff --git a/docs/html/img72.png b/docs/html/img72.png index bc6b7ac6042735c07c6239b26ff8c03bb45207bb..b114a9115baf4fef10bd872f1494b98ebdf84205 100644 GIT binary patch delta 165 zcmdnVxP@_oc)b7%GXn#|m0iJ{KuSHpC&cyt|NlVdyLa#I-o1O~%$eQ0cduHtYUa$D zWo2a@9UZBusUaaDMn*FVdQ&MBb@0OQC!!TqqHj3q&S!3+-1Zh&MQJY5_^IA$g%C`h{aJ+NR{#GhfH z&k&TekXuru!9?4ikvU?HW}_mbOEISbdqXCh*#>31X_ti+*<2K6Z{uQ0Fk$Gc7QDMC SbK5nbVGN$GelF{r5}E*bOEvNU diff --git a/docs/html/img73.png b/docs/html/img73.png index a6d5d19b79fc0a82b0a9bf6d798f24571d339624..a848d51605e6f069d3ace08b7d962b9a8a34b3c9 100644 GIT binary patch delta 188 zcmcc2c$#s7c)b7%GXnzylYD0mkkSqC332`Z|38rV?%lh)ckiA#b7uGM-K$ounmKc3 zSy@>}M@MREYDh?kv$M02k&%FaK#vULcA#p;k|4ie28U-i(tsQvPZ!4!j+w~`3-}V| zojkBifHA4?la+y$NmInpHm*V*8-;0(=FaBK>=6%3P1`2(yh@lR(9Gd1I79V-&XEfY nX{9b_y8;+C&yblR(;&idSCUKnWQB(w&|n5nS3j3^P6YXL delta 196 zcmX@jc$sm6c)bt{GXn#I|8;_sH8eE%`1mYawye0g*xufL z=FFKqJUnS>X+VX>#>Tz9y^)cTon2p^0{M(3L4Lsu4$p3YBttx1978x}CMPW5aM4XL zcv8!dqVz;ZJHryV90c+lXVaD#zi-ZcJ_vX)uTfi^IBy85}Sb4q9e0P^=k^8f$< literal 202 zcmeAS@N?(olHy`uVBq!ia0vp^@*vE@3?$z+aDyZi1AIbU4;(nKdGls9HMNF@hGol^ z6&DxV+uH*rjg5_adwU}zBeQ;R*#P;BB|(0{3=Yq3qyahMo-U3d8WWQf7VsE2uh_sD z@NZ2C$Jrfc7_^LJy^Pm!IEW@Bba1!`Cv-$Ks0p-a9gq-g$aUuT44$rjF6*2UngFprJxBlm diff --git a/docs/html/img75.png b/docs/html/img75.png index 107e05d7b9e15fadf05cba87a841501479b66665..c5cd61b3477c3cc74dcc8ae3452e11e8de84ff9e 100644 GIT binary patch literal 249 zcmeAS@N?(olHy`uVBq!ia0vp^@*vE@3?$z+aDyZa0(?ST|Ns9FWWIa%?(W^YXU?42 zy?ghnRjX#soLN>@*3r?CnwlCC65{OaY-D7lsHi9)AdvJ@eHTyzV@Z%-FoVOh8)-mJ zxu=U`h{nX^gavvRe4L*e$0x-zEE8S86vN7M+|lH;9&-mnGJ~`EjDwrFl!RU!xWImO zj}?Q?fddyfjMrH+gf=v0@_INhDhh0sP!TwAf%~bud9%kqhBiHp{ku3H^|7@rPjEY{ svcl2bQp&-kn(>UvwS+}`ZDSZ1SZYKc`rQ8a5aW9@sO4%G_^PJD^a+s8JxGc;LAZgGxi2mc!4#j0#z@%=?*VoWG~fuLH1Q4j>++zlv_ssRiP<)|_TfS9F#foWO-nCHX5aDRybAp@m&8yIXAszAI6 zHVkYHmk00000NkvXXu0mjf4=J5S delta 434 zcmV;j0Zsn81HS{17k?%M0{{R3fv8@;0000mP)t-sz`($>v$G~9CV+r|OiWCsrluJg z8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001bW%=J06^y0W&i*IJxN4C zR5*?8(7#HBfZA@2Rws9msGtr39wm^w#4ySnb1FDZ-d{a& z$Qc|x0p~!)F*+*nSbvpXgEWB^7-HO{^XG2Y&4GDF6)Ql}>WU2k(?AxFxg*#AGq&me cp72lb4S3m|$v@8k6951J07*qoM6N<$f=sBt(EtDd diff --git a/docs/html/img77.png b/docs/html/img77.png index 4e67821f8da22dc11601799b1b37d7d2b77a662f..c8b6481cf5e82e52ffe547a9410683f6e5a8326d 100644 GIT binary patch literal 192 zcmeAS@N?(olHy`uVBq!ia0vp^d_XL~!VDy@>gTe~DWM4f9L7SD literal 200 zcmeAS@N?(olHy`uVBq!ia0vp^{6H+k!VDzKHq5jEQd$8%A+84w9N4^hvznS(Lqmg) zkI%AY%OoWwi;IhA&YYQ+mIhR1Y;4@y+Z!1f`MK9G4#;OL3GxeOaCmkDBf|YR2`C_rV?w#&f*v4n0b2@0d1h t+s(7bnAM?&fvt@#r8wO20FwnX!4?m1n0-@IV~653MM*mJl!kd+i)=3a27-J)i4uAw(hkVOgvHS0jv?>k_$LCyfbjP ucxaz94>0 zgM}Zzr#NM}?>OPd5t`Pdb|4@JNIaO+3nV53357ijp$)fhFuFEaA7^ys&hBIATDV4g kLCyTB0#g_AEN0+iIQ@)&Pxzz`PoTLBp00i_>zopr0G*dZ<^TWy diff --git a/docs/html/img79.png b/docs/html/img79.png index 26284a8377b65a1473bce5c7f3cfe8f3cc826aaa..226f53362d9da72bc2f98cd900fce36b112f54ff 100644 GIT binary patch literal 309 zcmeAS@N?(olHy`uVBq!ia0vp^c0jDo!VDyrnmtniQU(D&A+G=b{|7SPy?b}}?%gwI z&g|a3d)2B{GiS~$D=X{h=txaX4G9Txc6K&0GE!7j6c7+dda1q(sDZI0$S;_|;n|He zAZN3ui(`mIZ*qdfs)ph$w+L;yO76CsJedJz+PhQ&7BnQPJ9A8t?$F~GF-Z7vXaU31 zIG5?{oEvHytd|-v_!KYTD9CFlG-bZ{;e1NL`hvmJ L)z4*}Q$iB}57T%_ diff --git a/docs/html/img8.png b/docs/html/img8.png index fd5994ec6b8e634759f8d6abd1928555ce6984c7..f2dfeb5d19c046d891c38b3fc7ba07cb5fce7d40 100644 GIT binary patch delta 257 zcmV+c0sj7j0+0fb7k?830{{R3?09+l0000mP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001bW%=J06^y0W&i*Hj!8s8 zR2Y?GU?307yYpvHGXq1KS}{z7wc!9qmIJ%)glGm21(*nPLwW`~0{{R3m~6Wm0000jP)t-sz`(#JCMJM@fJ{tGrlzJD85whP zb3Z>nnVFdk3=C#wX0x-iGcz-djg47ZS?vxMKmY&$0d!JMQvg8b*k%9#0E9_IK~xx( zV_+Z;a0Q+`e$IhGX;TVZ=pGNlBMY{T3$8P8yoQVT@v&@WNNr|dH~<&nV`oriFk;{? z@P>(WZDx4J9k76DZ8}th!>)wk2=}oDzO&pA5mq@_h<+aCUZ@&BKZpoBUoKRH@7@Iz uCjw0_s74p*+p_^lfbHJ{17k?rI0{{R3_~i%C0000mP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001bW%=J06^y0W&i*Hzez+v zR49>SU>H!qe;k>|aRx<_hk-#e4a!acb5SIjFR?EGu~@qW5Py=cp#fk?t^x*#(X0r` zoHnQ=V*o=pnk2+15HHYyp$|<`8*XPH14AR4sW3=nP=!MU(V` zOY#RWbfHNCeFv4~YG8QEkYj-2&lL_(Nv5M54Gf7B7?^vcn_-eHJx~WRum%I^3Gkps z30p8=cEBUa$t-|Pk~bJkDM9UuL6Kw)M&_}EFpL5k0syC?BI&e5b`Agl002ovPDHLk FV1gEhcW?jz delta 315 zcmV-B0mS~n0?7i97k?xK0{{R3F1+N;0000mP)t-sz`($>v$G~9CV+r|OiWCsrluJg z8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001bW%=J06^y0W&i*H$4Nv% zR5*=eU>H!qbsd?M-aPL3Qbr$BlG z%pha{<*`n{BQ(j+fK8I=DVP$3+VvJilJ6-pkMkwND4-=cg9qT11ON!aXX~95=b!)p N002ovPDHLkV1m&5eBS^7 diff --git a/docs/html/img81.png b/docs/html/img81.png index e6ddac599bd9e73d7d635a22e200af2bd25bcc92..50e53c27794a7fbf0a6b26c125ef3959a320fcb8 100644 GIT binary patch delta 194 zcmX@lc#&~}c)bVED7=pW^j0RBMrz2@^oL zzDo u9b?42g|az3?x~DNq|^;GIoOz9m@ueR@;==yE~WxBp25@A&t;ucLK6U0??xy9 delta 192 zcmcb}c%E^Bc)b7%GXn#IeeVk{Af+4N6XJT{z=6%1H>;_sH8eE%`1mYawoFn|vbeZ- z=FFKqJUnS>X+VX>#>Tz9y^)cT%{;uPfPBW1AirP+hi5lHk^!DBjv*W~lM@awNhwb0 z@MNBG?LjF+U=80Mc84t~%%52V_VzULpSixXnp4Me|ND1unG}xho_a8f!6iSTAd%s6 r&&q^kvk#&TFQ1=QJXYKg!pKlEQ=ma{{kP{p!x=nX{an^LB{Ts5>pVuv diff --git a/docs/html/img82.png b/docs/html/img82.png index 9485b3d590ba76989d66e5aea51ea3ffe246caf1..9e70e6eb114eabcc114cfbfb9c7760b5d8eb75dc 100644 GIT binary patch delta 173 zcmV;e08;-favbltziAvSth^~lQ6_M3sDGd8md6K b+i(H^%Ipn`m?F`&00000NkvXXu0mjfC0s?2 delta 173 zcmX@dc#d&`X8nN!2R3istfr>c(9q!Hp<28x{Fg&W9Y>CF$bLUZC2LkB8&4Fc)$#P2M}q{#lY79Vrck7jJVEVm;j<@gLzEC z4D-N@olF5BlLeTbGUNaa`^u>RsW`2h3N2);`z>;{N#8$H06V=&0>r`_v^t8i9Bsh{t#oL`K4#7Jm*z net>b~-U$Ge2#_8Cg9QKpm`EKn#-zAP00000NkvXXu0mjfV@O~r diff --git a/docs/html/img84.png b/docs/html/img84.png index 429992b049765841aa5bd48bcd8b3c427f29acdb..0e63e6c211161df4d76fa07fee3f098bdfec4f69 100644 GIT binary patch literal 254 zcmeAS@N?(olHy`uVBq!ia0vp^3P3E+!VDx!DlY8@QU(D&A+G=b{|7SPy?b}}?%gwI z&g|a3d)2B{GiS~$D=X{h=txaX4G9Txc6K&0GE!7j6c7+dda1q(sDZI0$S;_|;n|He zAg9LD#W6%jE0A?YmP6YHu7fNyst&eoV&dJ)kYrHqEc06nhZ%>% z3_cv3A+SLBLgTZU0n7%eQd}%2vJ6?;co`T}Z;Sg0&$1Q+x`V;f)z4*}Q$iB}AL>_> literal 255 zcmeAS@N?(olHy`uVBq!ia0vp^@*vE@3?$z+aDyZa0(?ST4;(nKdGls9HMNF@1|J`v zWy_XHN=gL5}va`L|1juJB3GxeOaCmkDBw6d} z;uxYaF*#uYhe4hh!(~za1x$`issf$z0-SASZ1Zea9ILkJUFUtZ{G_b>O)sAJD!g`9V2@G)M6aduHh# vPR33A{}xw1i)EP6Rn5+FBFm7aO`m~bbE5hctGi!79%Jxy^>bP0l+XkK?f6p= diff --git a/docs/html/img85.png b/docs/html/img85.png index f93f9c2c5cd41cf462108a5091b7f74997c32d1d..e0aa874c12cf6be93fa4138e36697d74390f99c8 100644 GIT binary patch literal 166 zcmeAS@N?(olHy`uVBq!ia0vp^AhrMtGmyL+__-KJ$p!d?xc>kD|J}QHXU?42y?gh} znKR4E$~rnaLPA0m6%_>p1Xh-AF9E7#ED7=pW^j0RBMrzg^K@|x;h346aDX#{*Fj}D zQ^yq+!DXU~3afZ@tT|l_d>JO@uqsTlb(C0gM?r9jDeD^ViH(d5+g7oLCr_St4QK*` Mr>mdKI;Vst0LWf6@c;k- literal 176 zcmeAS@N?(olHy`uVBq!ia0vp^+(0bE!VDzqqb=QllwyESi0gp^2R3isEGa2jTwH8# zZ$ES9OdcMdw6rv!d~a`WWMrh?=4GKk4r57>UoeBivl}28TTd6q5RRG22?rR%oK}Pw zoSem=WH~)UvLRy{(*}iTh8bMV8aj;u?|OtCLezFMbVTKGUDRtZ*v`x%wLpa7a1GB2 T0htg3pg|0tu6{1-oD!MS->P)L4|ja-fF6Ny*rj>=_ZU|2+)M&<14P>l+L9<%=v+VVIRUyhIV8H zmJ=9UP;{72XJBhlpTh6~|c;{g55DwZ8}(>;R?fXAQcJ%!9WK4BF+ZQxCy+* z7l0i8rQs_SAR5^lffm{V8SZRX6AeHD#zG9j$U5^BSOtpn7*q02fLIzz7e61jz^BEX8KB4I};8+0R@D{*WV8AL03YO~(hN&Q( zyMa1I&~yTIKsgFLAl9BUKyVDGQ-FcDfk~KQ9t%h(FgkfJAnDWx5sC(^P-6@YkmQ(z z7-|*R1el&O2tcB9y#tbL3@|l(C}ao)bGW9hL-r;^MMM(=$ByU#hAj-ty%HTgO~{fn zfjW=PN>70BjJr^DG6aBp0<@@-0TUbssb_G4xb7#@V+;j~AoufNY6N8hguf2yIAADf z1lr5MikZB@nE(#lCSe*K8U&(JFeFMaoq-iFV~7}FQ8fxi!6?8B02mBgwNfkKjQ{`u M07*qoM6N<$f{c0IvH$=8 literal 582 zcmV-M0=fN(P) zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001 zbW%=J06^y0W&i*I#7RU!R7iKHwnM{4`dx%y#9hJ+&z~D%fK2`??hW8!+zkEb! z6d_6@hX9aR&A@O8p^okUr;nMJ^(te5NJ&`117i%QqM3EtZp@9Du%oa$nm_G`atO(Zox&_ z2^jK!fVN^w(HsIuoXHz84Sx3!L|I};RAM>;8(_r{3BaOi6pVsVfCkQx3CPw60Cug= U>{lvzp8x;=07*qoM6N<$f`4w|kpKVy diff --git a/docs/html/img87.png b/docs/html/img87.png index d3b680ce2e05c856bd0ff55ee835c76dca880e22..1ab611d8958a18f1f0e2f6ba4eb12318246f619d 100644 GIT binary patch delta 232 zcmVU|($j delta 208 zcmV;>05AXe0pJ0U7=H)=0000j=h-X(0007XQchC<*@>K|NB{r;nMp)JR49?%kU4*d>w6$Kji zQ0Y&qdq6nEiU8FYZ6yFB^;S~dWzq2>=>xnE#giIk6y%o08A{c)U diff --git a/docs/html/img88.png b/docs/html/img88.png index 80e1ebdf4e2685c18f27a89839019ee7dfbd653f..ba389bdeb19414339a48634fad6af8be3ca8d309 100644 GIT binary patch literal 188 zcmeAS@N?(olHy`uVBq!ia0vp^d_XL~!VDy@>?A+G=b{|7SPy?b}}?%gwI z&g|a3d)2B{GiS~$D=X{h=txaXb#`_(GBQ$BR1^>pn7v^e4^TB@NswPKgTu2MX+Vyx zr;B3<$IRpe1?dfELT2+Vx_h%vO^V?qXO8$C#~S87RsmKUR)MIC4Wb^KY&B9iSTEjA jTdLmB(knSfLV}@JmuvDo^WLdIgBUzr{an^LB{Ts5hu}WS literal 195 zcmeAS@N?(olHy`uVBq!ia0vp^{6H+k!VDzKHq5jEQn~>?A+84w9N4^hvznS(Lqmg) zkI%AY%OoWwi;IhA&Ya1^!;_Yl22^NlY~0)18yOkd%)@&M$Y(4G@(X5gcyEh|) z7{W0#IYB|VV2w~5U)mPq*HP>Z65KO{Zyi)(tl#>g&2;5X#r+oFugMC0mJ}{1t}m(e}W!J8-tG05wI{z erUJ!o!wmpGZwtDbX~Yr$0000c(9q!HSpO94cZs<6($v$CTq>ur(w;gV^gX8 dGfzp1fg!(?Z`-2?d1IjI44$rjF6*2Ung9^^JbC~C diff --git a/docs/html/img9.png b/docs/html/img9.png index 043b345d9b4647e2154b9f3ed39013489c25de82..2e5452b92f974975d13b2a3be764f55b0ca9f06d 100644 GIT binary patch delta 238 zcmV|ow~AfA}IL8lnZD|BFB*ax?lr-6a#E1bvtfPsAhoa4~Kz@?A? o<1Wo);0lGi@}L9*qaehU0QK@2A}n3HVE_OC07*qoM6N<$f-xsyjsO4v delta 243 zcmVv$G~9CV+r|OiWCsrluJg z8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001bW%=J06^y0W&i*HfJsC_ zR0x@4U?3T={zu`$dGiE-#61X`(dAvO0RzK<;0GX{&<6(2kw{AU||0M=S=v? tz#?D(;1RKH*=`6gY(-F%2qJ%6(8?lby;ZTGk!2mt^)Tqw!r_J2O3?{2ci5x&UqyYXAM zmVJ2N-C*OfBg0HsfZ`M+*^`a;v)*?%*gNJ6xx_`Rw{PyD+Z6+MUaXSz6b;5H8D4cc z!h{IFYBBe0>{q<+PK%y`dRrmPOh z*`&uU$EAYd+JBrSB>{KrfjfG`Zi)TnA*67H%FYFYrPWj2Av18ZNW~n;DHoRM%1#BN zMm4wY0ej$1>~O`wJ4X4Ely`Hm)A{tA-J7687oG3b~n(o|+bvyZd z?$<^wDhayN$Q>aH5JEG802J|Lix6&svoH>}>rAYY?PkF?cIOSIQ9|X;uc$`DGHbKr zn5NFX63cx&^pV>RJ|>UZ78sTre6(@#;Yai*o904&mTtAzN$Nq&GxkLfD*2|^UH0E= jvL}18CwsCd`>nnKP8#b{&}v5p00000NkvXXu0mjfZN2NS delta 505 zcmVv$G~9CV+r|OiWCsrluJg z8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001bW%=J06^y0W&i*Igh@m} zR7iK%=nIdWSJtRs`N9FP`FgW7T&x6Kibzoq4-|_#;M}LI82$~W!X%xUA03=p3 zFkC{&GjBjsgDQ;zo&YiDNd|^L4E6v2{|^AmE21hvmqrGDK+L^>fuRk_`0uDn(4|2j zd^-d4Pw|}$3qT%dU|?T~B>x1>e`wM`!0yQXLHgMSrcebShs*D|zW`MH576pKAl5q& zc*=l98VJk;_!mHcY)wC z0~Top2F8O7MFPwR81onoK;qSF0+Q@o6tx)AKv4hwBXR?O|BD9&j0`W5m|CK zG6z!{Wc>r6iwc2eRx@CNt60P^flL69;KdXN^$*YmnE3;miwJ9f_Yg!`Vn|dH vqZ@7thDZP@+DE}C7zMNjXD9&&DAW!B)gIq%86K6B00000NkvXXu0mjft;N!) diff --git a/docs/html/img91.png b/docs/html/img91.png index efb2a515cb3409d7d2b37ea5d1f6e4469603f845..4a631dd625fa84ac25f8e8d6fd51b1d9f8629d14 100644 GIT binary patch literal 547 zcmV+;0^I$HP)Kkv&MmKp2K!lcs5!)&~5cV~V?UQA$CG&VubwL2#&B z-7?xP{!s{YFpHo#*wL{R1jVJJf`dPUE<$k--8yt~G8e18+|^JAo$^BNxbL|qU+w|~ z`KuIt>EUv6g<0Hn8lG{86)ONprgt-zLpZ8|5 zY@)PKHWFlU0c;w5-~A>kH1781ihdyMzu|t4EZz&1onCz-X+k82l?o(j23yIZJBOc< zmuK6!T6GqoaY!$8L(SuJ*vY7k{8XflSK=!jU{7cKemLwTpL1>{ZiG6L23wc8 lif_2Xioeo>1PSuL`2a@}WBQ+CYB2x+002ovPDHLkV1gJN_<;Zb literal 549 zcmV+=0^0qFP)i9}qX@q$@!8U1H~&aExg56jAWbr4SbBN zbO_X1y_=Tf4!vU0Rer}Ua-HyM5W%Cy2yVU9!bo`y<89o@@=2zTyIK=rj?{!^P z*mwXQhmhoUHrY;p#T`rE#LtvZbegCdzusSM(A*(4w<<}?aU5z6WWajVal$1#YMCew z_8d>`>Q~&`b&7+$hc$RjBhO2^;7YNEnFxr{^|Ed1~g~vF=ed6`69k=T3MpI626Vu;D8|?wVnK zZs+6HEh=d`Q`en22n2C^f&x;@6R)DfffTV*OvjeHN!Q!n1$SxQsmn<8d7{|srdgBg zk7-Hl&X>}!aWA=D=biHtyaPeyqWdygr0%?NYj|!MTR2nSFGYA^%w_yR7pnSV;hXrk n=)phu2mjz7{DXfN{$J}87VK($>PSja00000NkvXXu0mjfY(E4= diff --git a/docs/html/img92.png b/docs/html/img92.png index b69a09644240db5470c281581ad316ec4f120229..ed89fe01e72248263b00f4fff6d1778eb7934a68 100644 GIT binary patch literal 300 zcmV+{0n`48P)SV4wj=z$#iPfL%3EcoCEtvAd(I2_dWnQ}UC6;VeR! zZ32YJBErDX$WYPI(P01*X1D|q=KR3Gun(b{p&i2H-oU{A1xYvx!sK5XzCr=QtdJ;R zV6cU-9UU0rkiEeOq2@C%aD2iP-VGEM!4w8MoA&~eus+<`>m87UV?YFRuS7>r6Ot&y yOa`prFji6K1z3f-6|f4IU^m(TyYMI=2><{eh8{?-?2L2(0000!VDzaa<_j3QU(D&A+84w9N4^hvznS(Lqmg) zkI%AY%OoWwi;Iix?d@mIoXNw(la`hSRBLQ(+}qn585!BxUTgy7GnNGT1v5B2y8)8i z;OXKRqA@W!VF6>pF|AYk*mq~iv9Y;pe6BtIUteDEkdlGwYDoz_#g>`o4m0McOG^AR zxbpx1e|rX%GYdEbpT!+GaG@>W><8IHPcjk`;yYFTupD~wsrsEhL+Jzg1(!SpzRls} zInNUy%gMA`LgI&b5?47xtA7#~^W3vb8dP*x%eP%;QF*vsq3P@8pa1Lal{$^yq#fW| zmn526dO+)pVngT-q1_i5Z?w8IWzopr05NTG AOaK4? diff --git a/docs/html/img93.png b/docs/html/img93.png index c0282ff038fb7fea8f74c8dd7f8c954b1f5edd42..925d3460e3ae6499bd11ee88319f287cd989a708 100644 GIT binary patch delta 546 zcmV+-0^R+h1g->-7k?)N0{{R3JB;Ck0000mP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001bW%=J06^y0W&i*ItVu*c zR7i>Kl08VnKp2K!lg9Md2K>P>#l=awD5W4o!AX&J=pZ=Mt$%J=1lz?w3V{v=QE;=P zqZ9F16(DQbQNPp)cH#yXSlF`@XvXef^d4{&>QM$ISGl+p9Yl5g>~97X^^VChs6ytG90au5w{WTR7L7v7m~VI z9u^ByXtFs2L4QrPENjp4$Aku4tPm=5EKI980U}K|e^9s*7gN95uB2$9Fkdv{ba4r6 z8Lr={i4lWefdl8Gq#sL1A9$Fhi?3X1_a}C9+=NV~Qg@cs zVEYT%Y^VpfbCB^EAP3nZ0isFoUKdHu&s_I{bWe7qM(Mob1-0J%(>a~YgNC@TdUkx} kX;$tQ)f-n|ef<-C1Il4!QfX%VEdT%j07*qoM6N<$f{}Im(EtDd delta 534 zcmV+x0_pv(1fm3x7k?-S000009iI`t00002bW%=J0NIJ0r$_(*0ozGLK~z|U?Um7S zg&+_`DZmD3fCemp25ev(pn+|G1}K2ZKMl|TrG-U6V*rhB=4CSR{wTVaBkZ!W@T+1E z{?Fm{OHdC0%EDbds#~@qJ6oDWjPMpmGpx47-=cFz7e89PTYu8UfRu5k7C3-bn_tGD zwtI&Bc7T_~F{xw`Equ^w%x}3JbKmAU%9M3kMtKSl;}BN4olT6lzvVXB>jwD6TazmmD^HP999X5@Vg`*WAf&(nnIPKsp$D!>`GUrE3TNu1?(=>rz5F2 zwZ;5;J-0!Kra3mAQloON()I0`d&PU^sRjF> - + userhtml @@ -9,7 +9,7 @@ - + @@ -69,17 +69,15 @@ based on PSBLAS


-Software version: 2.1 +Software version: 2.2
-July 31, 2017 +July 31, 2018

- - - +



diff --git a/docs/html/node1.html b/docs/html/node1.html index 202c3887..fc552ff5 100644 --- a/docs/html/node1.html +++ b/docs/html/node1.html @@ -1,6 +1,6 @@ - + Abstract @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node10.html b/docs/html/node10.html index a880f838..37ec11f4 100644 --- a/docs/html/node10.html +++ b/docs/html/node10.html @@ -1,6 +1,6 @@ - + Bug reporting @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node11.html b/docs/html/node11.html index 7b4e7b1b..13e572cb 100644 --- a/docs/html/node11.html +++ b/docs/html/node11.html @@ -1,6 +1,6 @@ - + Example and test programs @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node12.html b/docs/html/node12.html index b2da8f7e..0a40de2f 100644 --- a/docs/html/node12.html +++ b/docs/html/node12.html @@ -1,6 +1,6 @@ - + Multigrid Background @@ -9,7 +9,7 @@ - + @@ -88,19 +88,19 @@ are considered. The second approach performs a fully automatic coarsening and en interplay between fine and coarse level by suitably choosing the coarse space and the coarse-to-fine interpolation (see, e.g., [3,23,21] for details.) + HREF="node36.html#Stuben_01">24,22] for details.)

MLD2P4 uses a pure algebraic approach, based on the smoothed aggregation algorithm [2,25], + HREF="node36.html#VANEK_MANDEL_BREZINA">26], for building the sequence of coarse matrices and transfer operators, starting from the original one. A decoupled version of this algorithm is implemented, where the smoothed aggregation is applied locally to each submatrix [24]. + HREF="node36.html#TUMINARO_TONG">25]. A brief description of the AMG preconditioners implemented in MLD2P4 is given in Sections 4.1-4.3. For further details the reader is referred to [ - + AMG preconditioners @@ -9,7 +9,7 @@ - + @@ -67,7 +67,7 @@ Ax=b,
\begin{displaymath}
 Ax=b,
@@ -80,7 +80,7 @@ where <!-- MATH
  $A=(a_{ij}) \in \mathbb{R}^{n \times n}$
  -->
 <SPAN CLASS=$A=(a_{ij}) \in \mathbb{R}^{n \times n}$ is a nonsingular sparse matrix; for ease of presentation we assume $\Omega = \{1, 2, \ldots, n\}$. Any algebraic multilevel preconditioners implemented in MLD2P4 generates @@ -116,7 +116,8 @@ a hierarchy of index spaces and a corresponding hierarchy of matrices, \begin{displaymath}\Omega^1 \equiv \Omega \supset \Omega^2 \supset \ldots \supset \Omega^{nlev},
\quad A^1 \equiv A, A^2, \ldots, A^{nlev}, \end{displaymath} + ALT="\begin{displaymath}\Omega^1 \equiv \Omega \supset \Omega^2 \supset \ldots \supset \Omega^{nlev}, +\quad A^1 \equiv A, A^2, \ldots, A^{nlev}, \end{displaymath}">

@@ -132,28 +133,28 @@ A vector space $\mathbb{R}^{n_{k}}$ is associated with $\Omega^k$, where $n_k$ is the size of $\Omega^k$. For all $k < nlev$, a restriction operator and a prolongation one are built, which connect two levels $k$ and $k+1$: @@ -167,14 +168,17 @@ P^k \in \mathbb{R}^{n_k \times n_{k+1}}, \quad --> \begin{displaymath}
 P^k \in \mathbb{R}^{n_k \times n_{k+1}}, \quad 
 R^k \in \mathbb{R}^{n_{k+1}\times n_k};
\end{displaymath} + ALT="\begin{displaymath} +P^k \in \mathbb{R}^{n_k \times n_{k+1}}, \quad +R^k \in \mathbb{R}^{n_{k+1}\times n_k}; +\end{displaymath}">

the matrix $A^{k+1}$ is computed by using the previous operators according to the Galerkin approach, i.e., @@ -188,9 +192,11 @@ A^{k+1}=R^kA^kP^k. --> \begin{displaymath}
 A^{k+1}=R^kA^kP^k.
\end{displaymath} + ALT="\begin{displaymath} +A^{k+1}=R^kA^kP^k. +\end{displaymath}">

@@ -199,10 +205,10 @@ In the current implementation of MLD2P4 we have $R^k=(P^k)^T$ A smoother with iteration matrix $M^k$ is set up at each level $k < nlev$, and a solver is set up at the coarsest level, so that they are ready for application @@ -211,7 +217,7 @@ is set up at the coarsest level, so that they are ready for application SRC="img19.png" ALT="$LU$">
factorization means computing and storing the $L$ and \framebox{
\begin{minipage}{.85\textwidth}
\begin{tabbing}
\quad \=\quad \=\quad...
-...mm]
\>endif  [1mm]
\>return $u^k$  [1mm]
end
\end{tabbing}
\end{minipage}
} + ALT="\framebox{ +\begin{minipage}{.85\textwidth} +\begin{tabbing} +\quad \=\quad \=\quad... +...[1mm] +\>endif [1mm] +\>return $u^k$ [1mm] +end +\end{tabbing}\end{minipage}}">
@@ -263,14 +276,14 @@ end to obtain different multilevel preconditioners; this is done in the application phase, i.e., in the computation of a vector of type $w=B^{-1}v$, where $B$ denotes the preconditioner, usually within an iteration of a Krylov solver [20]. An example of such a combination, known as + HREF="node36.html#Saad_book">21]. An example of such a combination, known as V-cycle, is given in Figure 1. In this case, a single iteration of the same smoother is used before and after the the recursive call to the V-cycle (i.e., in the pre-smoothing and post-smoothing phases); however, different choices can be @@ -278,7 +291,7 @@ performed. Other cycles can be defined; in MLD2P4, we implemented the standard V and W-cycle [3], and a version of the K-cycle described in [19]. + HREF="node36.html#Notay2008">20].

diff --git a/docs/html/node14.html b/docs/html/node14.html index a4d6105f..4a6e3560 100644 --- a/docs/html/node14.html +++ b/docs/html/node14.html @@ -1,6 +1,6 @@ - + Smoothed Aggregation @@ -9,7 +9,7 @@ - + @@ -54,27 +54,27 @@ Smoothed Aggregation

In order to define the prolongator $P^k$, used to compute the coarse-level matrix $A^{k+1}$, MLD2P4 uses the smoothed aggregation algorithm described in [2,25]. + HREF="node36.html#VANEK_MANDEL_BREZINA">26]. The basic idea of this algorithm is to build a coarse set of indices $\Omega^{k+1}$ by suitably grouping the indices of $\Omega^k$ into disjoint subsets (aggregates), and to define the coarse-to-fine space transfer operator $P^k$ by applying a suitable smoother to a simple piecewise constant prolongation operator, with the aim of improving the quality of the coarse-space correction. @@ -84,26 +84,26 @@ prolongation operator, with the aim of improving the quality of the coarse-space

  1. aggregation of the indices of $\Omega^k$ to obtain $\Omega^{k+1}$;
  2. construction of the prolongator $P^k$;
  3. application of $P^k$ and $R^k=(P^k)^T$ to build $A^{k+1}$.
  4. @@ -111,18 +111,18 @@ prolongation operator, with the aim of improving the quality of the coarse-space

    In order to perform the coarsening step, the smoothed aggregation algorithm described in [25] is used. In this algorithm, + HREF="node36.html#VANEK_MANDEL_BREZINA">26] is used. In this algorithm, each index $j \in \Omega^{k+1}$ corresponds to an aggregate $\Omega^k_j$ of $\Omega^k$, consisting of a suitably chosen index $\theta \in [0,1]$ (see [25] for the details). + HREF="node36.html#VANEK_MANDEL_BREZINA">26] for the details). Since this algorithm has a sequential nature, a decoupled version of it is applied, where each processor independently executes the algorithm on the set of indices assigned to it in the initial data @@ -180,11 +182,11 @@ MLD2P4, since it has been shown to produce good results in practice [5,7,24]. + HREF="node36.html#TUMINARO_TONG">25].

    The prolongator $P^k$ is built starting from a tentative prolongator $j \in \Omega^{k+1}$. $P^k$ is obtained by applying to $\bar{P}^k$ a smoother \begin{displaymath}
P^k = S^k \bar{P}^k,
\end{displaymath} + ALT="\begin{displaymath} +P^k = S^k \bar{P}^k, +\end{displaymath}">

    @@ -267,9 +275,9 @@ in order to remove nonsmooth components from the range of the prolongator, and hence to improve the convergence properties of the multilevel method [2,23]. + HREF="node36.html#Stuben_01">24]. A simple choice for $S^k$ is the damped Jacobi smoother: @@ -282,24 +290,26 @@ S^k = I - \omega^k (D^k)^{-1} A^k_F , --> \begin{displaymath}
S^k = I - \omega^k (D^k)^{-1} A^k_F , 
\end{displaymath} + ALT="\begin{displaymath} +S^k = I - \omega^k (D^k)^{-1} A^k_F , +\end{displaymath}">

    where $D^k$ is the diagonal matrix with the same diagonal entries as $A^k$, $A^k_F = (\bar{a}_{ij}^k)$ is the filtered matrix defined as @@ -321,17 +331,20 @@ where +\bar{a}_{ij}^k = +\left \{ \begin{array}{ll} +a_{ij}^k & \m... +...ii}^k = a_{ii}^k - \sum_{j \ne i} (a_{ij}^k - \bar{a}_{ij}^k), +\end{displaymath}">
    \begin{displaymath}
-\bar{a}_{ij}^k =
 \left \{ \begin{array}{ll}
 a_{ij}^k & ...
-...ii}^k = a_{ii}^k - \sum_{j \ne i} (a_{ij}^k - \bar{a}_{ij}^k),
\end{displaymath} (5)

    and $\omega^k$ is an approximation of $\rho^k$. Note that for systems coming from uniformly elliptic problems, filtering the matrix $A^k$ has little or no effect, and $A^k$ can be used instead of $A^k_F$. The latter choice is the default in MLD2P4. diff --git a/docs/html/node15.html b/docs/html/node15.html index bc801420..db064fff 100644 --- a/docs/html/node15.html +++ b/docs/html/node15.html @@ -1,6 +1,6 @@ - + Smoothers and coarsest-level solvers @@ -9,7 +9,7 @@ - + @@ -55,8 +55,8 @@ Smoothers and coarsest-level solvers The smoothers implemented in MLD2P4 include the Jacobi and block-Jacobi methods, a hybrid version of the forward and backward Gauss-Seidel methods, and the additive Schwarz (AS) ones (see, e.g., [20,21]). + HREF="node36.html#Saad_book">21,22]).

    The hybrid Gauss-Seidel @@ -68,7 +68,7 @@ the beginning of the current iteration.

    In the AS methods, the index space $\Omega^k$ is divided into $\Omega^k_i$ of size $n_{k,i}$, possibly overlapping. For each $i$ we consider the restriction operator \begin{displaymath}
 ( M^k_{AS} )^{-1} = \sum_{i=1}^{m_k} P_i^k (A_i^k)^{-1} R_i^{k},
\end{displaymath} + ALT="\begin{displaymath} +( M^k_{AS} )^{-1} = \sum_{i=1}^{m_k} P_i^k (A_i^k)^{-1} R_i^{k}, +\end{displaymath}">

    @@ -170,7 +172,7 @@ involves SRC="img62.png" ALT="$\Omega_i^k$">
    and of the corresponding operators $R_i^k$ (and
    • the restriction of $w^k$ to the subspaces $\mathbb{R}^{n_{k,i}}$, i.e. + Getting Started @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node17.html b/docs/html/node17.html index 830f4f6c..bb8015ed 100644 --- a/docs/html/node17.html +++ b/docs/html/node17.html @@ -1,6 +1,6 @@ - + Examples @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node18.html b/docs/html/node18.html index fc22110c..614a5f09 100644 --- a/docs/html/node18.html +++ b/docs/html/node18.html @@ -1,6 +1,6 @@ - + User Interface @@ -9,7 +9,7 @@ - + @@ -83,14 +83,14 @@ i.e., matrix data structure;
    • the arrays containing the vectors $v$ and $w$ involved in the preconditioner application $w=B^{-1}v$ must be of type psb_xvect_type with x = diff --git a/docs/html/node19.html b/docs/html/node19.html index 1ea569b5..70549f3d 100644 --- a/docs/html/node19.html +++ b/docs/html/node19.html @@ -1,6 +1,6 @@ - + Method init @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node2.html b/docs/html/node2.html index 27a15212..18abc9b0 100644 --- a/docs/html/node2.html +++ b/docs/html/node2.html @@ -1,6 +1,6 @@ - + Contents @@ -9,7 +9,7 @@ - + @@ -122,9 +122,7 @@ Contents

      - - - +



      diff --git a/docs/html/node20.html b/docs/html/node20.html index 6d8135bf..c688ab59 100644 --- a/docs/html/node20.html +++ b/docs/html/node20.html @@ -1,6 +1,6 @@ - + Method set @@ -9,7 +9,7 @@ - + @@ -247,7 +247,7 @@ solver is changed to the default sequential solver.


      -
      +
      @@ -300,7 +300,7 @@ number

      -
      +
      Table 2: Parameters defining the multilevel cycle and the number of cycles to @@ -285,7 +285,7 @@ Note that hybrid Multiplicative Schwarz is equivalent to V-cycle and
      Any integer

      number $\ge 1$

      1
      @@ -344,7 +344,7 @@ Parameters defining the aggregation algorithm. @@ -358,7 +358,7 @@ Parameters defining the aggregation algorithm. @@ -376,18 +376,22 @@ Currently, only the SYMDEC option applies decoupled aggregation to the sparsity pattern of $A+A^T$. - - - + + + @@ -415,7 +419,7 @@ of levels.


      -
      +
      Table 3: Parameters defining the aggregation algorithm. @@ -319,17 +319,17 @@ Parameters defining the aggregation algorithm.
      Any number

      $> 0$

      $\lfloor 40 \sqrt[3]{n} \rfloor$, where $n$ is the dimension of the matrix at the finest levelAny number

      $> 1$

      1.5Any integer

      number $> 1$

      20
      'AGGR_TYPE' character(len=*)'VMB''VMB'Type of aggregation algorithm: currently, the scalar aggregation - algorithm by Vanek, Mandel and Brezina is implemented - [25].'SOC1''SOC1', + 'SOC2'Type of aggregation algorithm: currently, + we implement to measures of strength of + connection, the one by Vanek, Mandel + and Brezina [26], + and the one by Gratton et al [16].
      'AGGR_PROL' character(len=*)
      +


      -
      +
      Table 4: Parameters defining the aggregation algorithm (continued). @@ -440,18 +444,17 @@ Parameters defining the aggregation algorithm (continued). descending degrees of the nodes in the matrix graph. -
      -'AGGR_THRESH'
      'AGGR_THRESH' real(kind_parameter) Any real

      number $\in [0, 1]$

      0.01 The threshold $\theta$ in the aggregation algorithm, see (3) in Section 4.2. @@ -468,7 +471,7 @@ number 
      Note. Different thresholds at different levels, such as those used in [25, Section 5.1], can be easily set by + HREF="node36.html#VANEK_MANDEL_BREZINA">26, Section 5.1], can be easily set by invoking the rou-
      tine set with @@ -483,7 +486,7 @@ the parameter ilev.
      Table 5: Parameters defining the coarse-space correction at the coarsest @@ -590,7 +593,7 @@ Note that UMF and SLU require the coarsest


      -
      +
      @@ -621,7 +624,7 @@ number Any integer

      number $\ge 0$

      @@ -635,12 +638,12 @@ number Any real

      number $\ge 0$

      @@ -376,7 +376,7 @@ Currently, only the SYMDEC option applies decoupled aggregation to the sparsity pattern of $A+A^T$. @@ -449,12 +449,12 @@ Parameters defining the aggregation algorithm (continued). diff --git a/docs/html/node3.html b/docs/html/node3.html index 02b8228b..b7f7bd1d 100644 --- a/docs/html/node3.html +++ b/docs/html/node3.html @@ -82,7 +82,7 @@ Ax=b,
      Table 6: Parameters defining the coarse-space correction at the coarsest @@ -609,7 +612,7 @@ level (continued).
      Any integer

      number $> 0$

      1000 Drop tolerance $t$ in the ILU(

      -
      +
      @@ -767,7 +770,7 @@ Parameters defining the smoother or the details of the one-level preconditioner. @@ -783,7 +786,7 @@ Parameters defining the smoother or the details of the one-level preconditioner.


      -
      +
      Table 7: Parameters defining the smoother or the details of the one-level preconditioner. @@ -748,7 +751,7 @@ Parameters defining the smoother or the details of the one-level preconditioner.
      Any integer

      number $\ge 0$

      Any integer

      number $\ge 0$

      @@ -856,22 +859,21 @@ Parameters defining the smoother or the details of the one-level preconditioner - + diff --git a/docs/html/node21.html b/docs/html/node21.html index 8a1d324e..be357628 100644 --- a/docs/html/node21.html +++ b/docs/html/node21.html @@ -1,6 +1,6 @@ - +Method hierarchy_build @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node22.html b/docs/html/node22.html index 0bb9ab16..d9fa00f9 100644 --- a/docs/html/node22.html +++ b/docs/html/node22.html @@ -1,6 +1,6 @@ - +Method smoothers_build @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node23.html b/docs/html/node23.html index 445ce6f3..54375c9a 100644 --- a/docs/html/node23.html +++ b/docs/html/node23.html @@ -1,6 +1,6 @@ - +Method build @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node24.html b/docs/html/node24.html index be5f014a..357893fa 100644 --- a/docs/html/node24.html +++ b/docs/html/node24.html @@ -1,6 +1,6 @@ - +Method apply @@ -9,7 +9,7 @@ - + @@ -62,9 +62,9 @@ This method computes $y = op(B^{-1})  x$, where $y = op(B^{-1})\, x$, where $B$ is a previously built @@ -91,7 +91,7 @@ and hence it is completely transparent to the user. diff --git a/docs/html/node25.html b/docs/html/node25.html index da626cdc..23211355 100644 --- a/docs/html/node25.html +++ b/docs/html/node25.html @@ -1,6 +1,6 @@ - +Method free @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node26.html b/docs/html/node26.html index 494e7369..f07bcf9f 100644 --- a/docs/html/node26.html +++ b/docs/html/node26.html @@ -1,6 +1,6 @@ - +Method descr @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node27.html b/docs/html/node27.html index b4165d36..64b9a5db 100644 --- a/docs/html/node27.html +++ b/docs/html/node27.html @@ -1,6 +1,6 @@ - +Auxiliary Methods @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node28.html b/docs/html/node28.html index ffbacc9b..813e8e25 100644 --- a/docs/html/node28.html +++ b/docs/html/node28.html @@ -1,6 +1,6 @@ - +Method: dump @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node29.html b/docs/html/node29.html index 888861cf..da717d1c 100644 --- a/docs/html/node29.html +++ b/docs/html/node29.html @@ -1,6 +1,6 @@ - +Method: clone @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node3.html b/docs/html/node3.html index a5e870ba..02b8228b 100644 --- a/docs/html/node3.html +++ b/docs/html/node3.html @@ -1,6 +1,6 @@ - +General Overview @@ -9,7 +9,7 @@ - + @@ -57,8 +57,8 @@ General Overview PSBLAS (MLD2P4) provides parallel Algebraic MultiGrid (AMG) and Domain Decomposition preconditioners (see, e.g., [3,23,21]), + HREF="node36.html#Stuben_01">24,22]), to be used in the iterative solution of linear systems,
      @@ -72,7 +72,7 @@ Ax=b,
      Table 8: Parameters defining the smoother or the details of the one-level preconditioner @@ -840,7 +843,7 @@ Parameters defining the smoother or the details of the one-level preconditioner
      Any integer

      number $\ge 0$

      real(kind_parameter) Any real number $\ge 0$ 0 Drop tolerance $t$ in the ILU($p,t$) factorization.
      -
      The local part of the vector $x$. Note that type and kind_parameter must be chosen according @@ -137,28 +137,28 @@ and hence it is completely transparent to the user. $op(B^{-1}) = B^{-1}$ --> $op(B^{-1}) = B^{-1}$; if trans = 'T','t' then $op(B^{-1}) = B^{-T}$ (transpose of $B^{-1})$; if trans = 'C','c' then $op(B^{-1}) = B^{-C}$ (conjugate transpose of $B^{-1})$.
      \begin{displaymath}
 Ax=b,
@@ -95,7 +95,7 @@ multilevel cycles and smoothers widely used in multigrid methods.
 AMG cycles with smoothers and coarsest-level solvers. The V-, W-, and
 K-cycles [<A
  HREF=3,19] are available, which allow to define + HREF="node36.html#Notay2008">20] are available, which allow to define almost all the preconditioners in the package, including the multilevel hybrid Schwarz ones; a specific cycle is implemented to obtain multilevel additive Schwarz preconditioners. The Jacobi, hybrid @@ -105,7 +105,7 @@ coarse-level matrices and operators, without explicitly using any information on geometry of the original problem, e.g., the discretization of a PDE. To this end, the smoothed aggregation technique [2,25] + HREF="node36.html#VANEK_MANDEL_BREZINA">26] is applied. Either exact or approximate solvers can be used on the coarsest-level system. Specifically, different sparse LU factorizations from external packages, and native incomplete LU factorizations and Jacobi, hybrid Gauss-Seidel, @@ -116,8 +116,7 @@ preconditioners. MLD2P4 is written in Fortran 2003, following an object-oriented design through the exploitation of features such as abstract data type creation, type extension, functional overloading, and -dynamic memory management. -The parallel implementation is based on a Single Program Multiple Data +dynamic memory management. The parallel implementation is based on a Single Program Multiple Data (SPMD) paradigm. Single and double precision implementations of MLD2P4 are available for both the real and the complex case, which can be used through a single diff --git a/docs/html/node30.html b/docs/html/node30.html index e5cfa8fa..873b2304 100644 --- a/docs/html/node30.html +++ b/docs/html/node30.html @@ -1,6 +1,6 @@ - + Method: sizeof @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node31.html b/docs/html/node31.html index a2044f73..1243f28c 100644 --- a/docs/html/node31.html +++ b/docs/html/node31.html @@ -1,6 +1,6 @@ - + Method: allocate_wrk @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node32.html b/docs/html/node32.html index 66687d38..5805fd18 100644 --- a/docs/html/node32.html +++ b/docs/html/node32.html @@ -1,6 +1,6 @@ - + Method: free_wrk @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node33.html b/docs/html/node33.html index a9e120a5..463a9879 100644 --- a/docs/html/node33.html +++ b/docs/html/node33.html @@ -1,6 +1,6 @@ - + Adding new smoother and solver objects to MLD2P4 @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node34.html b/docs/html/node34.html index 150cb8e1..a32c73cd 100644 --- a/docs/html/node34.html +++ b/docs/html/node34.html @@ -1,6 +1,6 @@ - + Error Handling @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node35.html b/docs/html/node35.html index 5a7991e0..369bfe3a 100644 --- a/docs/html/node35.html +++ b/docs/html/node35.html @@ -1,6 +1,6 @@ - + License @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node36.html b/docs/html/node36.html index bf1feef1..0504c1f0 100644 --- a/docs/html/node36.html +++ b/docs/html/node36.html @@ -1,6 +1,6 @@ - + Bibliography @@ -9,7 +9,7 @@ - + @@ -138,53 +138,60 @@ S. Filippone, M. Colajanni, PSBLAS: A Library for Parallel Linear Algebra Computation on Sparse Matrices, ACM Transactions on Mathematical Software, 26 (4), 2000, 527-550. -

      16 +

      16 +
      +S. Gratton, P. Henon, P. Jiranek and X. Vasseur, + Reducing complexity of algebraic multigrid by aggregation, +Numerical Lin. Algebra with Applications, 2016, 23:501-518 + +

      +

      17
      W. Gropp, S. Huss-Lederman, A. Lumsdaine, E. Lusk, B. Nitzberg, W. Saphir, M. Snir, MPI: The Complete Reference. Volume 2 - The MPI-2 Extensions, MIT Press, 1998. -

      17 +

      18
      C. L. Lawson, R. J. Hanson, D. Kincaid, F. T. Krogh, Basic Linear Algebra Subprograms for FORTRAN usage, ACM Transactions on Mathematical Software, 5 (3), 1979, 308-323. -

      18 +

      19
      X. S. Li, J. W. Demmel, SuperLU_DIST: A Scalable Distributed-memory Sparse Direct Solver for Unsymmetric Linear Systems, ACM Transactions on Mathematical Software, 29 (2), 2003, 110-140. -

      19 +

      20
      Y. Notay, P. S. Vassilevski, Recursive Krylov-based multigrid cycles, Numerical Linear Algebra with Applications, 15 (5), 2008, 473-487. -

      20 +

      21
      Y. Saad, Iterative methods for sparse linear systems, 2nd edition, SIAM, 2003. -

      21 +

      22
      B. Smith, P. Bjorstad, W. Gropp, Domain Decomposition: Parallel Multilevel Methods for Elliptic Partial Differential Equations, Cambridge University Press, 1996. -

      22 +

      23
      M. Snir, S. Otto, S. Huss-Lederman, D. Walker, J. Dongarra, MPI: The Complete Reference. Volume 1 - The MPI Core, second edition, MIT Press, 1998. -

      23 +

      24
      K. Stüben, An Introduction to Algebraic Multigrid, in A. Schüller, U. Trottenberg, C. Oosterlee, Multigrid, Academic Press, 2001. -

      24 +

      25
      R. S. Tuminaro, C. Tong, Parallel Smoothed Aggregation Multigrid: Aggregation Strategies on Massively Parallel Machines, in J. Donnelley, editor, Proceedings of SuperComputing 2000, Dallas, 2000. -

      25 +

      26
      P. Vanek, J. Mandel, M. Brezina, Algebraic Multigrid by Smoothed Aggregation for Second and Fourth Order Elliptic Problems, diff --git a/docs/html/node37.html b/docs/html/node37.html index 0eb0b5e6..657869fa 100644 --- a/docs/html/node37.html +++ b/docs/html/node37.html @@ -1,6 +1,6 @@ - + About this document ... @@ -9,7 +9,7 @@ - + @@ -47,7 +47,7 @@ About this document ...

      This document was generated using the -LaTeX2HTML translator Version 2017.2 (Released Jan 23, 2017) +LaTeX2HTML translator Version 2018 (Released Feb 1, 2018)

      Copyright © 1993, 1994, 1995, 1996, Nikos Drakos, @@ -60,7 +60,7 @@ Mathematics Department, Macquarie University, Sydney. The command line arguments were:
      latex2html -local_icons -noaddress -dir ../../html userhtml.tex

      -The translation was initiated on 2018-01-27 +The translation was initiated on 2018-05-14


      diff --git a/docs/html/node4.html b/docs/html/node4.html index 7b2ac12c..c478e331 100644 --- a/docs/html/node4.html +++ b/docs/html/node4.html @@ -1,6 +1,6 @@ - + Code Distribution @@ -9,7 +9,7 @@ - + @@ -80,7 +80,7 @@ constant --> \begin{displaymath}\verb\vert mld_version_string_\vert\end{displaymath} diff --git a/docs/html/node5.html b/docs/html/node5.html index 3e5ba8d6..a15ea834 100644 --- a/docs/html/node5.html +++ b/docs/html/node5.html @@ -1,6 +1,6 @@ - + Contributors @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node6.html b/docs/html/node6.html index 8c177d8c..54be0f4b 100644 --- a/docs/html/node6.html +++ b/docs/html/node6.html @@ -1,6 +1,6 @@ - + Configuring and Building MLD2P4 @@ -9,7 +9,7 @@ - + diff --git a/docs/html/node7.html b/docs/html/node7.html index 13445741..7eed7f21 100644 --- a/docs/html/node7.html +++ b/docs/html/node7.html @@ -1,6 +1,6 @@ - + Prerequisites @@ -9,7 +9,7 @@ - + @@ -59,7 +59,7 @@ Prerequisites
      [11,12,17] Many vendors provide optimized versions + HREF="node36.html#blas1">18] Many vendors provide optimized versions of BLAS; if no vendor version is available for a given platform, the ATLAS software (
      MPI
      [16,22] A version of MPI is available on most + HREF="node36.html#MPI2">17,23] A version of MPI is available on most high-performance computing systems.
      diff --git a/docs/html/node8.html b/docs/html/node8.html index f1b81928..b008d3ae 100644 --- a/docs/html/node8.html +++ b/docs/html/node8.html @@ -1,6 +1,6 @@ - + Optional third party libraries @@ -9,7 +9,7 @@ - + @@ -92,7 +92,7 @@ for multilevel preconditioners may change to reflect their presence.
      SuperLU_Dist
      [18] + HREF="node36.html#SUPERLUDIST">19] A sparse LU factorization package available from the same site as SuperLU; it provides parallel factorization and triangular system solution for double precision real and complex data. diff --git a/docs/html/node9.html b/docs/html/node9.html index df5e4663..212118d8 100644 --- a/docs/html/node9.html +++ b/docs/html/node9.html @@ -1,6 +1,6 @@ - + Configuration options @@ -9,7 +9,7 @@ - + diff --git a/docs/html/userhtml.html b/docs/html/userhtml.html index f026ce9d..1f0d2ee7 100644 --- a/docs/html/userhtml.html +++ b/docs/html/userhtml.html @@ -1,6 +1,6 @@ - + userhtml @@ -9,7 +9,7 @@ - + @@ -69,17 +69,15 @@ based on PSBLAS


      -Software version: 2.1 +Software version: 2.2
      -July 31, 2017 +July 31, 2018

      - - - +



      diff --git a/docs/mld2p4-2.1-guide.pdf b/docs/mld2p4-2.2-guide.pdf similarity index 94% rename from docs/mld2p4-2.1-guide.pdf rename to docs/mld2p4-2.2-guide.pdf index 859ae4c5..664a13a8 100644 --- a/docs/mld2p4-2.1-guide.pdf +++ b/docs/mld2p4-2.2-guide.pdf @@ -24,7 +24,7 @@ BT /F17 11.9552 Tf 218.644 -79.389 Td [(P)31(asqua)-375(D'Am)31(bra)]TJ/F37 11.9552 Tf -22.655 -13.947 Td [(IA)27(C-CNR,)-326(Naples,)-326(Italy)]TJ/F17 11.9552 Tf 11.494 -29.39 Td [(Daniela)-375(di)-375(Sera\014no)]TJ/F37 11.9552 Tf -181.63 -13.948 Td [(Univ)27(ersit)27(y)-326(of)-326(Campania)-326(\134Luigi)-327(V)82(an)27(vitelli",)-326(Caserta,)-326(Italy)]TJ/F17 11.9552 Tf 179.561 -29.39 Td [(Salv)62(atore)-375(Filipp)-31(one)]TJ/F37 11.9552 Tf -134.787 -13.947 Td [(Cran\014eld)-326(Univ)27(ersit)27(y)82(,)-326(Cran\014eld,)-327(United)-326(Kingdom)]TJ 0 g 0 G 0 g 0 G - 141.76 -78.924 Td [(Soft)27(w)28(are)-327(v)27(ersion)1(:)-436(2.1)]TJ 38.924 -13.948 Td [(July)-326(31,)-327(2017)]TJ + 141.76 -78.924 Td [(Soft)27(w)28(are)-327(v)27(ersion)1(:)-436(2.2)]TJ 38.924 -13.948 Td [(July)-326(31,)-327(2018)]TJ 0 g 0 G 0 g 0 G ET @@ -722,11 +722,11 @@ BT 0 g 0 G [(,)]TJ 1 0 0 rg 1 0 0 RG - [-269(23)]TJ + [-269(24)]TJ 0 g 0 G [(,)]TJ 1 0 0 rg 1 0 0 RG - [-268(21)]TJ + [-268(22)]TJ 0 g 0 G [(]\051,)-281(to)-269(b)-27(e)-269(used)-268(in)-268(the)-269(iterativ)28(e)]TJ 0 -13.549 Td [(solution)-333(of)-334(lin)1(e)-1(ar)-333(systems,)]TJ/F22 10.9091 Tf 186.98 -16.123 Td [(Ax)]TJ/F15 10.9091 Tf 17.447 0 Td [(=)]TJ/F22 10.9091 Tf 11.515 0 Td [(b;)]TJ 0 g 0 G @@ -738,7 +738,7 @@ BT 0 g 0 G [(,)]TJ 1 0 0 rg 1 0 0 RG - [-263(19)]TJ + [-263(20)]TJ 0 g 0 G [(])]TJ 0 -13.549 Td [(are)-392(a)28(v)56(ailable,)-407(whic)28(h)-392(allo)28(w)-392(to)-391(de\014ne)-392(almost)-392(all)-391(the)-392(preconditioners)-392(in)-392(th)1(e)-392(pac)28(k)55(age,)-406(in-)]TJ 0 -13.549 Td [(cluding)-394(the)-394(m)28(ultilev)28(el)-394(h)28(ybrid)-394(Sc)28(h)27(w)28(arz)-394(ones;)-424(a)-394(sp)-28(eci\014c)-394(cycle)-394(is)-394(implemen)28(ted)-394(to)-394(obtain)]TJ 0 -13.55 Td [(m)28(ultilev)28(el)-498(additiv)28(e)-498(Sc)28(h)28(w)28(arz)-498(preconditioners.)-937(The)-497(Jacobi,)-539(h)28(ybrid)-498(forw)28(ard/bac)28(kw)28(ard)]TJ 0 -13.549 Td [(Gauss-Seidel,)-366(blo)-27(c)27(k-Jacobi,)-365(and)-359(additiv)28(e)-360(Sc)28(h)28(w)28(arz)-359(m)-1(eth)1(o)-28(ds)-359(are)-360(a)28(v)56(ailable)-359(as)-360(smo)-27(others.)]TJ 0 -13.549 Td [(An)-279(algebraic)-279(appr)1(oac)27(h)-279(i)1(s)-279(used)-279(to)-279(generate)-279(a)-279(hierarc)28(h)28(y)-279(of)-279(coarse-lev)28(el)-279(matrices)-279(and)-278(op)-28(er-)]TJ 0 -13.549 Td [(ators,)-283(without)-270(explicitly)-270(using)-270(an)28(y)-271(inf)1(ormation)-271(on)-270(the)-270(geometry)-270(of)-270(the)-271(original)-270(problem,)]TJ 0 -13.549 Td [(e.g.,)-256(the)-237(discretization)-237(of)-237(a)-237(PDE.)-237(T)84(o)-237(this)-237(end,)-256(the)-237(smo)-28(othed)-237(aggregation)-237(tec)28(hnique)-237([)]TJ 1 0 0 rg 1 0 0 RG @@ -746,7 +746,7 @@ BT 0 g 0 G [(,)]TJ 1 0 0 rg 1 0 0 RG - [-236(25)]TJ + [-236(26)]TJ 0 g 0 G [(])]TJ 0 -13.55 Td [(is)-377(applied.)-575(Either)-376(exact)-377(or)-377(appro)28(ximate)-377(solv)28(ers)-377(can)-377(b)-28(e)-377(used)-376(on)-377(the)-377(coarsest-lev)28(el)-377(sys-)]TJ 0 -13.549 Td [(tem.)-441(Sp)-27(eci\014cally)83(,)-324(di\013eren)28(t)-322(sparse)-322(LU)-322(factorizations)-321(from)-322(external)-322(pac)28(k)55(ages,)-324(and)-321(nativ)27(e)]TJ 0 -13.549 Td [(incomplete)-285(LU)-285(factorizations)-285(and)-285(Jacobi,)-295(h)28(ybrid)-285(Gauss-Seidel,)-294(and)-285(blo)-28(c)28(k-Jacobi)-285(solv)28(ers)]TJ 0 -13.549 Td [(are)-333(a)27(v)56(ailable.)-444(All)-334(smo)-28(oth)1(e)-1(r)1(s)-334(can)-333(b)-28(e)-333(also)-334(exploited)-333(as)-333(one-lev)27(el)-333(preconditioners.)]TJ 16.937 -14.408 Td [(MLD2P4)-267(is)-267(written)-268(in)-267(F)84(ortran)-267(2003,)-281(follo)28(wing)-267(an)-267(ob)-56(ject-orien)28(ted)-267(design)-268(th)1(rough)-268(the)]TJ -16.937 -13.549 Td [(exploitation)-338(of)-337(features)-338(suc)28(h)-338(as)-337(abstract)-338(data)-338(t)28(yp)-28(e)-337(creation,)-339(t)28(yp)-28(e)-338(extension,)-338(functional)]TJ 0 -13.549 Td [(o)28(v)28(erloading,)-326(and)-325(dynamic)-324(memory)-325(managemen)28(t.)-441(The)-325(parallel)-324(implemen)28(tation)-325(is)-324(based)]TJ 0 -13.549 Td [(on)-424(a)-424(Single)-424(Program)-424(Multiple)-424(Data)-424(\050SPMD\051)-424(paradigm.)-717(Single)-424(and)-424(double)-424(precision)]TJ 0 -13.549 Td [(implemen)28(tations)-486(of)-486(MLD2P4)-486(are)-486(a)28(v)56(ailable)-486(for)-486(b)-27(oth)-486(the)-486(real)-486(and)-486(the)-486(complex)-485(cas)-1(e,)]TJ 0 -13.55 Td [(whic)28(h)-334(can)-333(b)-28(e)-333(used)-333(through)-333(a)-334(single)-333(in)28(terface.)]TJ 16.937 -14.407 Td [(MLD2P4)-229(has)-230(b)-27(e)-1(en)-229(designed)-229(to)-230(implemen)28(t)-230(scalable)-229(and)-229(easy-to-use)-230(m)28(ultilev)28(el)-230(precon-)]TJ -16.937 -13.549 Td [(ditioners)-349(in)-349(the)-350(con)28(text)-349(of)-349(the)-349(PSBLAS)-349(\050P)27(arallel)-349(Sparse)-349(BLAS\051)-349(computational)-349(frame-)]TJ 0 -13.549 Td [(w)28(ork)-360([)]TJ 1 0 0 rg 1 0 0 RG @@ -908,7 +908,7 @@ BT 0 g 0 G [(,)]TJ 1 0 0 rg 1 0 0 RG - [-424(17)]TJ + [-424(18)]TJ 0 g 0 G [(])-425(Man)28(y)-425(v)28(endors)-424(pro)27(v)1(ide)-425(optimized)-425(v)28(ersions)-425(of)-424(BLAS;)-425(if)-424(no)-425(v)28(endor)]TJ -11.105 -13.55 Td [(v)28(ersion)-523(is)-524(a)28(v)56(ailable)-523(for)-523(a)-524(giv)28(en)-523(platform,)-570(the)-524(A)84(TLAS)-523(soft)28(w)27(are)-523(\050)]TJ 0 1 0 0 k 0 1 0 0 K @@ -928,11 +928,11 @@ BT 0 g 0 G /F15 10.9091 Tf 30.697 0 Td [([)]TJ 1 0 0 rg 1 0 0 RG - [(16)]TJ + [(17)]TJ 0 g 0 G [(,)]TJ 1 0 0 rg 1 0 0 RG - [-340(22)]TJ + [-340(23)]TJ 0 g 0 G [(])-340(A)-341(v)28(ersion)-340(of)-340(MPI)-340(is)-341(a)28(v)56(ailable)-341(on)-340(most)-340(high-p)-28(erformance)-340(computing)-340(sys-)]TJ -3.424 -13.549 Td [(tems.)]TJ 0 g 0 G @@ -1018,7 +1018,7 @@ BT 0 g 0 G /F15 10.9091 Tf 28.388 0 Td [([)]TJ 1 0 0 rg 1 0 0 RG - [(18)]TJ + [(19)]TJ 0 g 0 G [(])-417(A)-416(sparse)-417(LU)-416(factorization)-417(pac)28(k)55(age)-416(a)28(v)55(ailable)-416(from)-417(the)-417(same)-416(site)]TJ -55.002 -13.549 Td [(as)-366(Sup)-28(erLU;)-366(it)-367(pro)28(vides)-366(parallel)-366(factorization)-367(and)-366(triangular)-366(system)-367(solution)-366(for)]TJ 0 -13.549 Td [(double)-384(precision)-384(real)-384(and)-384(complex)-384(data.)-596(W)83(e)-384(tested)-384(v)28(ersions)-384(3.3)-384(and)-384(4.2.)-596(If)-384(y)28(ou)]TJ 0 -13.549 Td [(installed)-384(BLAS)-384(f)1(rom)-384(A)83(TLAS,)-384(remem)28(b)-28(er)-384(to)-383(de\014ne)-384(the)-384(BLASLIB)-384(v)56(ariable)-384(in)-384(the)]TJ 0 -13.549 Td [(mak)28(e.inc)-401(\014le)-401(and)-401(to)-401(add)-402(t)1(he)]TJ/F45 10.9091 Tf 142.011 0 Td [(-std=c99)]TJ/F15 10.9091 Tf 50.193 0 Td [(option)-401(to)-401(the)-401(C)-401(compiler)-401(options.)-648(Note)]TJ -192.204 -13.55 Td [(that)-432(this)-432(library)-432(requires)-433(t)1(he)-433(P)28(arMETIS)-432(library)-432(for)-432(parallel)-432(graph)-432(partitioning)]TJ 0 -13.549 Td [(and)-374(\014ll-reducing)-374(matrix)-374(ordering,)-385(a)28(v)56(ailable)-374(from)]TJ 0 1 0 0 k 0 1 0 0 K @@ -1891,11 +1891,11 @@ BT 0 g 0 G [(,)]TJ 1 0 0 rg 1 0 0 RG - [-313(23)]TJ + [-313(24)]TJ 0 g 0 G [(,)]TJ 1 0 0 rg 1 0 0 RG - [-313(21)]TJ + [-313(22)]TJ 0 g 0 G [(])]TJ 0 -13.549 Td [(for)-333(details.\051)]TJ 16.937 -14.105 Td [(MLD2P4)-329(uses)-330(a)-329(pure)-330(algebraic)-329(approac)28(h,)-331(b)1(as)-1(ed)-329(on)-329(the)-330(smo)-28(othed)-329(aggregation)-330(algo-)]TJ -16.937 -13.549 Td [(rithm)-298([)]TJ 1 0 0 rg 1 0 0 RG @@ -1903,11 +1903,11 @@ BT 0 g 0 G [(,)]TJ 1 0 0 rg 1 0 0 RG - [-298(25)]TJ + [-298(26)]TJ 0 g 0 G [(],)-305(for)-298(building)-298(the)-298(sequence)-298(of)-298(coarse)-298(matrices)-298(and)-298(transfer)-298(op)-28(erators,)-305(start-)]TJ 0 -13.549 Td [(ing)-306(from)-306(the)-305(original)-306(one.)-435(A)-306(decoupled)-306(v)28(ersion)-306(of)-306(this)-306(algori)1(thm)-306(is)-306(implemen)28(ted,)-312(where)]TJ 0 -13.55 Td [(the)-316(smo)-28(othed)-316(aggregation)-315(is)-316(applied)-316(lo)-28(cally)-316(to)-316(eac)28(h)-316(submatrix)-316([)]TJ 1 0 0 rg 1 0 0 RG - [(24)]TJ + [(25)]TJ 0 g 0 G [(].)-438(A)-316(brief)-316(description)]TJ 0 -13.549 Td [(of)-333(the)-333(AMG)-333(prec)-1(on)1(ditioners)-334(implemen)28(ted)-333(in)-333(MLD2P4)-333(is)-333(giv)27(en)-333(in)-333(Sections)]TJ 0 0 1 rg 0 0 1 RG @@ -1955,7 +1955,7 @@ BT 0 g 0 G -398.511 -19.516 Td [(where)]TJ/F22 10.9091 Tf 32.496 0 Td [(A)]TJ/F15 10.9091 Tf 12.796 0 Td [(=)-423(\050)]TJ/F22 10.9091 Tf 17.342 0 Td [(a)]TJ/F23 7.9701 Tf 5.767 -1.636 Td [(ij)]TJ/F15 10.9091 Tf 7.265 1.636 Td [(\051)]TJ/F25 10.9091 Tf 8.857 0 Td [(2)]TJ/F34 10.9091 Tf 11.888 0 Td [(R)]TJ/F23 7.9701 Tf 7.878 3.959 Td [(n)]TJ/F26 7.9701 Tf 5.139 0 Td [(\002)]TJ/F23 7.9701 Tf 6.586 0 Td [(n)]TJ/F15 10.9091 Tf 10.223 -3.959 Td [(is)-421(a)-420(nonsingular)-420(sparse)-421(matrix;)-464(for)-420(ease)-421(of)-420(presen)28(tation)-421(w)28(e)]TJ -126.237 -13.549 Td [(assume)]TJ/F22 10.9091 Tf 37.697 0 Td [(A)]TJ/F15 10.9091 Tf 11.818 0 Td [(has)-333(a)-334(symmetric)-333(sparsit)28(y)-334(pattern.)]TJ -32.579 -13.549 Td [(Let)-468(us)-469(consider)-468(as)-468(\014nest)-469(ind)1(e)-1(x)-468(space)-468(the)-468(s)-1(et)-468(of)-468(ro)28(w)-469(\050column\051)-468(indices)-468(of)]TJ/F22 10.9091 Tf 361.856 0 Td [(A)]TJ/F15 10.9091 Tf 8.182 0 Td [(,)-502(i.e.,)]TJ -386.974 -13.55 Td [(\012)-377(=)]TJ/F25 10.9091 Tf 24.593 0 Td [(f)]TJ/F15 10.9091 Tf 5.454 0 Td [(1)]TJ/F22 10.9091 Tf 5.455 0 Td [(;)]TJ/F15 10.9091 Tf 4.848 0 Td [(2)]TJ/F22 10.9091 Tf 5.455 0 Td [(;)-167(:)-166(:)-167(:)-167(;)-166(n)]TJ/F25 10.9091 Tf 30.79 0 Td [(g)]TJ/F15 10.9091 Tf 5.455 0 Td [(.)-623(An)28(y)-393(algebraic)-393(m)27(ultilev)28(el)-393(preconditioners)-393(implemen)28(ted)-393(in)-393(MLD2P4)]TJ -82.05 -13.549 Td [(generates)-333(a)-334(hierarc)28(h)28(y)-333(of)-334(index)-333(spaces)-333(and)-334(a)-333(corresp)-28(onding)-333(hierarc)28(h)28(y)-334(of)-333(matrices,)]TJ 81.377 -23.491 Td [(\012)]TJ/F20 7.9701 Tf 7.879 4.505 Td [(1)]TJ/F25 10.9091 Tf 7.762 -4.505 Td [(\021)]TJ/F15 10.9091 Tf 11.515 0 Td [(\012)]TJ/F25 10.9091 Tf 10.909 0 Td [(\033)]TJ/F15 10.9091 Tf 11.515 0 Td [(\012)]TJ/F20 7.9701 Tf 7.879 4.505 Td [(2)]TJ/F25 10.9091 Tf 7.763 -4.505 Td [(\033)]TJ/F22 10.9091 Tf 11.515 0 Td [(:)-167(:)-166(:)]TJ/F25 10.9091 Tf 15.757 0 Td [(\033)]TJ/F15 10.9091 Tf 11.516 0 Td [(\012)]TJ/F23 7.9701 Tf 7.878 4.505 Td [(nl)-12(ev)]TJ/F22 10.9091 Tf 16.597 -4.505 Td [(;)-1167(A)]TJ/F20 7.9701 Tf 23.939 4.505 Td [(1)]TJ/F25 10.9091 Tf 7.763 -4.505 Td [(\021)]TJ/F22 10.9091 Tf 11.515 0 Td [(A;)-167(A)]TJ/F20 7.9701 Tf 21.212 4.505 Td [(2)]TJ/F22 10.9091 Tf 4.732 -4.505 Td [(;)-167(:)-166(:)-167(:)-167(;)-166(A)]TJ/F23 7.9701 Tf 32.424 4.505 Td [(nl)-12(ev)]TJ/F22 10.9091 Tf 16.597 -4.505 Td [(;)]TJ/F15 10.9091 Tf -328.044 -23.49 Td [(b)28(y)-282(using)-282(the)-282(information)-282(con)28(tained)-282(in)]TJ/F22 10.9091 Tf 180.373 0 Td [(A)]TJ/F15 10.9091 Tf 8.182 0 Td [(,)-292(without)-282(assuming)-282(an)27(y)-282(kno)28(wledge)-282(of)-282(the)-282(geom-)]TJ -188.555 -13.55 Td [(etry)-295(of)-294(the)-295(problem)-294(from)-295(whic)28(h)]TJ/F22 10.9091 Tf 150.888 0 Td [(A)]TJ/F15 10.9091 Tf 11.395 0 Td [(originates.)-431(A)-295(v)28(ector)-295(space)]TJ/F34 10.9091 Tf 126.348 0 Td [(R)]TJ/F23 7.9701 Tf 7.879 3.959 Td [(n)]TJ/F24 5.9776 Tf 5.138 -1.406 Td [(k)]TJ/F15 10.9091 Tf 8.285 -2.553 Td [(is)-295(asso)-27(ciate)-1(d)-294(with)-295(\012)]TJ/F23 7.9701 Tf 94.368 3.959 Td [(k)]TJ/F15 10.9091 Tf 5.12 -3.959 Td [(,)]TJ -409.421 -13.549 Td [(where)]TJ/F22 10.9091 Tf 31.714 0 Td [(n)]TJ/F23 7.9701 Tf 6.548 -1.777 Td [(k)]TJ/F15 10.9091 Tf 8.925 1.777 Td [(is)-349(the)-349(size)-348(of)-349(\012)]TJ/F23 7.9701 Tf 71.401 3.959 Td [(k)]TJ/F15 10.9091 Tf 5.12 -3.959 Td [(.)-491(F)84(or)-349(all)]TJ/F22 10.9091 Tf 43.449 0 Td [(k)-335(<)-304(nl)-19(ev)]TJ/F15 10.9091 Tf 41.907 0 Td [(,)-353(a)-348(restriction)-349(op)-28(erator)-349(and)-348(a)-349(prolongation)]TJ -209.064 -13.549 Td [(one)-333(are)-334(built,)-333(whic)28(h)-333(connect)-334(t)28(w)28(o)-334(l)1(e)-1(v)28(els)]TJ/F22 10.9091 Tf 188.273 0 Td [(k)]TJ/F15 10.9091 Tf 9.659 0 Td [(and)]TJ/F22 10.9091 Tf 21.212 0 Td [(k)]TJ/F15 10.9091 Tf 8.447 0 Td [(+)-222(1:)]TJ/F22 10.9091 Tf -101.285 -23.491 Td [(P)]TJ/F23 7.9701 Tf 8.519 4.504 Td [(k)]TJ/F25 10.9091 Tf 8.15 -4.504 Td [(2)]TJ/F34 10.9091 Tf 10.303 0 Td [(R)]TJ/F23 7.9701 Tf 7.879 4.504 Td [(n)]TJ/F24 5.9776 Tf 5.138 -1.405 Td [(k)]TJ/F26 7.9701 Tf 4.573 1.405 Td [(\002)]TJ/F23 7.9701 Tf 6.587 0 Td [(n)]TJ/F24 5.9776 Tf 5.138 -1.405 Td [(k)]TJ/F21 5.9776 Tf 4.075 0 Td [(+1)]TJ/F22 10.9091 Tf 10.239 -3.099 Td [(;)-1167(R)]TJ/F23 7.9701 Tf 24.125 4.504 Td [(k)]TJ/F25 10.9091 Tf 8.15 -4.504 Td [(2)]TJ/F34 10.9091 Tf 10.303 0 Td [(R)]TJ/F23 7.9701 Tf 7.879 4.504 Td [(n)]TJ/F24 5.9776 Tf 5.138 -1.405 Td [(k)]TJ/F21 5.9776 Tf 4.075 0 Td [(+1)]TJ/F26 7.9701 Tf 9.741 1.405 Td [(\002)]TJ/F23 7.9701 Tf 6.587 0 Td [(n)]TJ/F24 5.9776 Tf 5.138 -1.405 Td [(k)]TJ/F15 10.9091 Tf 5.071 -3.099 Td [(;)]TJ -283.114 -23.491 Td [(the)-282(matrix)]TJ/F22 10.9091 Tf 53.146 0 Td [(A)]TJ/F23 7.9701 Tf 8.182 3.959 Td [(k)]TJ/F20 7.9701 Tf 4.621 0 Td [(+1)]TJ/F15 10.9091 Tf 14.392 -3.959 Td [(is)-282(computed)-281(b)27(y)-281(using)-282(the)-282(previou)1(s)-282(op)-28(erators)-282(according)-281(to)-282(the)-282(Galerkin)]TJ -80.341 -13.549 Td [(approac)28(h,)-333(i.e.,)]TJ/F22 10.9091 Tf 165.163 -13.549 Td [(A)]TJ/F23 7.9701 Tf 8.182 4.504 Td [(k)]TJ/F20 7.9701 Tf 4.621 0 Td [(+1)]TJ/F15 10.9091 Tf 14.349 -4.504 Td [(=)]TJ/F22 10.9091 Tf 11.515 0 Td [(R)]TJ/F23 7.9701 Tf 8.368 4.504 Td [(k)]TJ/F22 10.9091 Tf 5.12 -4.504 Td [(A)]TJ/F23 7.9701 Tf 8.181 4.504 Td [(k)]TJ/F22 10.9091 Tf 5.12 -4.504 Td [(P)]TJ/F23 7.9701 Tf 8.519 4.504 Td [(k)]TJ/F22 10.9091 Tf 5.12 -4.504 Td [(:)]TJ/F15 10.9091 Tf -244.258 -19.516 Td [(In)-476(the)-477(curren)28(t)-476(implemen)28(tation)-477(of)-476(MLD2P4)-476(w)28(e)-477(ha)28(v)28(e)]TJ/F22 10.9091 Tf 261.479 0 Td [(R)]TJ/F23 7.9701 Tf 8.368 3.958 Td [(k)]TJ/F15 10.9091 Tf 10.749 -3.958 Td [(=)-516(\050)]TJ/F22 10.9091 Tf 18.358 0 Td [(P)]TJ/F23 7.9701 Tf 8.519 3.958 Td [(k)]TJ/F15 10.9091 Tf 5.119 -3.958 Td [(\051)]TJ/F23 7.9701 Tf 4.243 3.958 Td [(T)]TJ/F15 10.9091 Tf 11.801 -3.958 Td [(A)-476(smo)-28(other)-476(with)]TJ -328.636 -13.55 Td [(iteration)-441(matrix)]TJ/F22 10.9091 Tf 82.101 0 Td [(M)]TJ/F23 7.9701 Tf 11.773 3.959 Td [(k)]TJ/F15 10.9091 Tf 9.928 -3.959 Td [(is)-441(set)-441(up)-440(at)-441(eac)28(h)-441(lev)28(el)]TJ/F22 10.9091 Tf 113.517 0 Td [(k)-488(<)-457(nl)-20(ev)]TJ/F15 10.9091 Tf 45.251 0 Td [(,)-468(and)-440(a)-441(solv)28(er)-441(is)-441(set)-441(up)-440(at)-441(the)]TJ -262.57 -13.549 Td [(coarsest)-369(lev)28(el,)-378(so)-368(that)-369(they)-369(are)-369(ready)-368(for)-369(application)-369(\050for)-368(example,)-378(setting)-369(up)-368(a)-369(solv)28(er)]TJ 0 -13.549 Td [(based)-292(on)-291(the)]TJ/F22 10.9091 Tf 62.938 0 Td [(LU)]TJ/F15 10.9091 Tf 19.243 0 Td [(factorization)-292(means)-291(computing)-292(and)-291(storing)-292(the)]TJ/F22 10.9091 Tf 224.422 0 Td [(L)]TJ/F15 10.9091 Tf 10.605 0 Td [(and)]TJ/F22 10.9091 Tf 20.757 0 Td [(U)]TJ/F15 10.9091 Tf 11.819 0 Td [(factors\051.)-431(The)]TJ -349.784 -13.549 Td [(construction)-345(of)-344(the)-345(hierarc)28(h)27(y)-344(of)-345(AMG)-345(comp)-28(on)1(e)-1(n)28(ts)-345(d)1(e)-1(scrib)-27(ed)-345(so)-345(far)-345(corresp)-27(onds)-345(to)-345(the)]TJ 0 -13.549 Td [(so-called)-333(build)-334(ph)1(as)-1(e)-333(of)-333(the)-334(p)1(rec)-1(on)1(ditioner.)]TJ 16.936 -13.55 Td [(The)-359(com)-1(p)-27(onen)28(ts)-360(pro)-28(du)1(c)-1(ed)-359(in)-359(the)-360(build)-359(phase)-359(ma)27(y)-359(b)-28(e)-359(com)28(bined)-360(in)-359(sev)28(eral)-360(w)28(a)28(ys)-360(to)]TJ -16.936 -13.549 Td [(obtain)-306(di\013eren)28(t)-306(m)27(ultilev)28(el)-306(preconditioners;)-315(this)-306(is)-306(done)-307(in)-306(the)-306(application)-306(phase,)-312(i)1(.e)-1(.)1(,)-312(in)]TJ 0 -13.549 Td [(the)-391(computation)-391(of)-391(a)-391(v)27(ector)-391(of)-391(t)28(yp)-28(e)]TJ/F22 10.9091 Tf 178.081 0 Td [(w)]TJ/F15 10.9091 Tf 12.185 0 Td [(=)]TJ/F22 10.9091 Tf 12.566 0 Td [(B)]TJ/F26 7.9701 Tf 8.822 3.959 Td [(\000)]TJ/F20 7.9701 Tf 6.586 0 Td [(1)]TJ/F22 10.9091 Tf 4.732 -3.959 Td [(v)]TJ/F15 10.9091 Tf 5.68 0 Td [(,)-406(where)]TJ/F22 10.9091 Tf 39.631 0 Td [(B)]TJ/F15 10.9091 Tf 13.089 0 Td [(denotes)-391(the)-391(preconditioner,)]TJ -281.372 -13.549 Td [(usually)-334(with)1(in)-334(an)-334(iteration)-333(of)-334(a)-334(Kr)1(ylo)27(v)-333(solv)27(er)-333([)]TJ 1 0 0 rg 1 0 0 RG - [(20)]TJ + [(21)]TJ 0 g 0 G [(].)-446(An)-333(example)-334(of)-333(s)-1(u)1(c)27(h)-333(a)-334(com)28(bination,)]TJ 0 -13.549 Td [(kno)28(wn)-448(as)-448(V-cycle,)-476(is)-448(giv)28(en)-448(in)-447(Figure)]TJ 0 0 1 rg 0 0 1 RG @@ -1967,7 +1967,7 @@ BT 0 g 0 G [(],)-334(and)-333(a)-333(v)28(e)-1(r)1(s)-1(ion)-333(of)-333(the)-333(K-cyc)-1(l)1(e)-334(describ)-28(ed)-333(in)-333([)]TJ 1 0 0 rg 1 0 0 RG - [(19)]TJ + [(20)]TJ 0 g 0 G [(].)]TJ/F17 11.9552 Tf 0 -29.053 Td [(4.2)-1125(Smo)-31(othed)-375(Aggregation)]TJ/F15 10.9091 Tf 0 -20.595 Td [(In)-374(order)-374(to)-374(de\014ne)-374(the)-375(prolongator)]TJ/F22 10.9091 Tf 167.339 0 Td [(P)]TJ/F23 7.9701 Tf 8.519 3.959 Td [(k)]TJ/F15 10.9091 Tf 5.12 -3.959 Td [(,)-384(used)-375(to)-374(compute)-374(the)-374(coarse-lev)28(el)-375(matrix)]TJ/F22 10.9091 Tf 204.32 0 Td [(A)]TJ/F23 7.9701 Tf 8.182 3.959 Td [(k)]TJ/F20 7.9701 Tf 4.622 0 Td [(+1)]TJ/F15 10.9091 Tf 11.319 -3.959 Td [(,)]TJ -409.421 -13.549 Td [(MLD2P4)-319(uses)-320(the)-319(smo)-28(othed)-319(aggregation)-319(algorithm)-320(describ)-27(ed)-320(in)-319([)]TJ 1 0 0 rg 1 0 0 RG @@ -1975,7 +1975,7 @@ BT 0 g 0 G [(,)]TJ 1 0 0 rg 1 0 0 RG - [-319(25)]TJ + [-319(26)]TJ 0 g 0 G [(].)-440(The)-319(basic)-320(idea)]TJ 0 -13.549 Td [(of)-270(this)-271(algorithm)-270(is)-271(to)-270(build)-270(a)-271(coarse)-270(se)-1(t)-270(of)-270(indices)-271(\012)]TJ/F23 7.9701 Tf 243.122 3.959 Td [(k)]TJ/F20 7.9701 Tf 4.621 0 Td [(+1)]TJ/F15 10.9091 Tf 14.27 -3.959 Td [(b)28(y)-271(suitabl)1(y)-271(grouping)-270(the)-271(indices)]TJ -262.013 -13.549 Td [(of)-350(\012)]TJ/F23 7.9701 Tf 20.481 3.959 Td [(k)]TJ/F15 10.9091 Tf 8.934 -3.959 Td [(in)28(to)-350(disjoin)28(t)-350(sub)1(s)-1(ets)-349(\050aggregates\051,)-354(and)-350(to)-349(de\014ne)-350(the)-349(coarse)-1(-to-\014n)1(e)-350(space)-350(transfer)]TJ 0 g 0 G @@ -2038,7 +2038,7 @@ BT 0 g 0 G [-500(application)-333(of)]TJ/F22 10.9091 Tf 82.727 0 Td [(P)]TJ/F23 7.9701 Tf 8.519 3.958 Td [(k)]TJ/F15 10.9091 Tf 8.756 -3.958 Td [(and)]TJ/F22 10.9091 Tf 21.212 0 Td [(R)]TJ/F23 7.9701 Tf 8.368 3.958 Td [(k)]TJ/F15 10.9091 Tf 8.15 -3.958 Td [(=)-278(\050)]TJ/F22 10.9091 Tf 15.757 0 Td [(P)]TJ/F23 7.9701 Tf 8.519 3.958 Td [(k)]TJ/F15 10.9091 Tf 5.12 -3.958 Td [(\051)]TJ/F23 7.9701 Tf 4.242 3.958 Td [(T)]TJ/F15 10.9091 Tf 10.241 -3.958 Td [(to)-333(build)]TJ/F22 10.9091 Tf 41.212 0 Td [(A)]TJ/F23 7.9701 Tf 8.182 3.958 Td [(k)]TJ/F20 7.9701 Tf 4.622 0 Td [(+1)]TJ/F15 10.9091 Tf 11.319 -3.958 Td [(.)]TJ -243.343 -23.467 Td [(In)-407(order)-407(to)-407(p)-28(erform)-407(the)-407(coarsening)-407(s)-1(tep,)-425(the)-407(smo)-28(othed)-407(aggregation)-407(algorithm)-407(de-)]TJ -16.937 -13.549 Td [(scrib)-28(ed)-478(in)-478([)]TJ 1 0 0 rg 1 0 0 RG - [(25)]TJ + [(26)]TJ 0 g 0 G [(])-479(is)-478(used.)-879(In)-479(this)-478(algorithm,)-514(eac)27(h)-478(index)]TJ/F22 10.9091 Tf 271.801 0 Td [(j)]TJ/F25 10.9091 Tf 10.783 0 Td [(2)]TJ/F15 10.9091 Tf 12.939 0 Td [(\012)]TJ/F23 7.9701 Tf 7.879 3.959 Td [(k)]TJ/F20 7.9701 Tf 4.622 0 Td [(+1)]TJ/F15 10.9091 Tf 16.537 -3.959 Td [(corresp)-28(onds)-478(to)-478(an)]TJ -324.561 -13.549 Td [(aggregate)-374(\012)]TJ/F23 7.9701 Tf 57.445 3.958 Td [(k)]TJ 0 -7.014 Td [(j)]TJ/F15 10.9091 Tf 9.201 3.056 Td [(of)-374(\012)]TJ/F23 7.9701 Tf 20.747 3.958 Td [(k)]TJ/F15 10.9091 Tf 5.12 -3.958 Td [(,)-384(consisting)-374(of)-374(a)-374(s)-1(u)1(itably)-374(c)27(hosen)-374(index)]TJ/F22 10.9091 Tf 187.709 0 Td [(i)]TJ/F25 10.9091 Tf 7.529 0 Td [(2)]TJ/F15 10.9091 Tf 11.044 0 Td [(\012)]TJ/F23 7.9701 Tf 7.879 3.958 Td [(k)]TJ/F15 10.9091 Tf 9.201 -3.958 Td [(and)-374(indices)-374(that)-374(are)]TJ -315.875 -13.55 Td [(\050usually\051)-333(con)28(tained)-334(in)-333(a)-333(strongly-coupled)-334(n)1(e)-1(igh)28(b)-27(oro)-28(o)-28(d)-333(of)]TJ/F22 10.9091 Tf 274.122 0 Td [(i)]TJ/F15 10.9091 Tf 3.758 0 Td [(,)-333(i.e.,)]TJ -194.032 -31.214 Td [(\012)]TJ/F23 7.9701 Tf 7.879 4.505 Td [(k)]TJ 0 -7.202 Td [(j)]TJ/F25 10.9091 Tf 8.15 2.697 Td [(\032)-278(N)]TJ/F23 7.9701 Tf 22.073 4.505 Td [(k)]TJ -1.607 -7.202 Td [(i)]TJ/F15 10.9091 Tf 6.727 2.697 Td [(\050)]TJ/F22 10.9091 Tf 4.242 0 Td [(\022)]TJ/F15 10.9091 Tf 5.425 0 Td [(\051)-278(=)]TJ/F28 10.9091 Tf 18.788 15.382 Td [(\032)]TJ/F22 10.9091 Tf 8.181 -15.382 Td [(r)]TJ/F25 10.9091 Tf 8.255 0 Td [(2)]TJ/F15 10.9091 Tf 10.303 0 Td [(\012)]TJ/F23 7.9701 Tf 7.879 4.505 Td [(k)]TJ/F15 10.9091 Tf 8.15 -4.505 Td [(:)]TJ/F25 10.9091 Tf 6.061 0 Td [(j)]TJ/F22 10.9091 Tf 3.03 0 Td [(a)]TJ/F23 7.9701 Tf 5.766 4.505 Td [(k)]TJ 0 -7.202 Td [(ir)]TJ/F25 10.9091 Tf 7.438 2.697 Td [(j)]TJ/F22 10.9091 Tf 6.061 0 Td [(>)-278(\022)]TJ/F28 10.9091 Tf 16.939 13.424 Td [(q)]TJ ET @@ -2053,7 +2053,7 @@ BT 0 g 0 G -398.512 -31.214 Td [(for)-431(a)-430(giv)27(en)-430(threshold)]TJ/F22 10.9091 Tf 106.493 0 Td [(\022)]TJ/F25 10.9091 Tf 10.225 0 Td [(2)]TJ/F15 10.9091 Tf 12.074 0 Td [([0)]TJ/F22 10.9091 Tf 8.485 0 Td [(;)]TJ/F15 10.9091 Tf 4.848 0 Td [(1])-431(\050see)-431([)]TJ 1 0 0 rg 1 0 0 RG - [(25)]TJ + [(26)]TJ 0 g 0 G [(])-430(for)-431(the)-431(details\051.)-736(Since)-431(this)-431(algorithm)-430(has)-431(a)]TJ -142.125 -13.549 Td [(sequen)28(tial)-382(n)1(ature,)-394(a)-381(decoupled)-381(v)28(e)-1(r)1(s)-1(i)1(on)-382(of)-381(it)-381(is)-382(appli)1(e)-1(d,)-393(where)-381(eac)28(h)-382(pro)-27(ces)-1(sor)-381(indep)-28(en-)]TJ 0 -13.549 Td [(den)28(tly)-433(exe)-1(cutes)-433(the)-433(algorithm)-433(on)-434(the)-433(set)-433(of)-434(indices)-433(assigned)-433(to)-434(it)-433(in)-433(the)-433(initial)-434(data)]TJ 0 -13.549 Td [(distribution.)-442(Thi)1(s)-326(v)28(ersion)-325(is)-326(em)28(barrassingly)-325(parallel,)-327(since)-325(it)-326(do)-27(es)-326(not)-325(require)-325(an)27(y)-325(data)]TJ 0 -13.55 Td [(comm)28(unication.)-522(On)-359(the)-359(other)-359(hand,)-365(it)-360(ma)28(y)-359(pro)-28(du)1(c)-1(e)-359(some)-359(non)28(uniform)-359(aggregates)-359(and)]TJ 0 -13.549 Td [(is)-295(strongly)-295(dep)-27(enden)27(t)-294(on)-295(the)-295(n)28(um)28(b)-28(er)-295(of)-295(pro)-27(cess)-1(or)1(s)-295(and)-295(on)-295(the)-295(initial)-294(partitioning)-295(of)-295(the)]TJ 0 -13.549 Td [(matrix)]TJ/F22 10.9091 Tf 35.775 0 Td [(A)]TJ/F15 10.9091 Tf 8.182 0 Td [(.)-524(Nev)28(e)-1(rt)1(hele)-1(ss,)-366(this)-360(parallel)-360(algorithm)-360(has)-360(b)-27(ee)-1(n)-359(c)27(hosen)-360(for)-359(MLD2P4,)-367(since)-360(it)]TJ -43.957 -13.549 Td [(has)-333(b)-28(een)-333(s)-1(h)1(o)27(wn)-333(to)-333(pro)-28(duce)-333(go)-28(o)-28(d)-333(results)-334(in)-333(practice)-333([)]TJ 1 0 0 rg 1 0 0 RG @@ -2065,7 +2065,7 @@ BT 0 g 0 G [(,)]TJ 1 0 0 rg 1 0 0 RG - [-334(24)]TJ + [-334(25)]TJ 0 g 0 G [(].)]TJ 0 g 0 G @@ -2093,7 +2093,7 @@ BT 0 g 0 G [(,)]TJ 1 0 0 rg 1 0 0 RG - [-293(23)]TJ + [-293(24)]TJ 0 g 0 G [(].)-431(A)-294(simple)-293(c)28(hoice)]TJ 0 -13.549 Td [(for)]TJ/F22 10.9091 Tf 16.697 0 Td [(S)]TJ/F23 7.9701 Tf 7.318 3.959 Td [(k)]TJ/F15 10.9091 Tf 8.756 -3.959 Td [(is)-333(the)-334(damp)-27(ed)-334(Jacobi)-333(smo)-28(other:)]TJ/F22 10.9091 Tf 118.068 -22.041 Td [(S)]TJ/F23 7.9701 Tf 7.318 4.505 Td [(k)]TJ/F15 10.9091 Tf 8.15 -4.505 Td [(=)]TJ/F22 10.9091 Tf 11.515 0 Td [(I)]TJ/F25 10.9091 Tf 8.076 0 Td [(\000)]TJ/F22 10.9091 Tf 10.909 0 Td [(!)]TJ/F23 7.9701 Tf 7.182 4.505 Td [(k)]TJ/F15 10.9091 Tf 5.119 -4.505 Td [(\050)]TJ/F22 10.9091 Tf 4.243 0 Td [(D)]TJ/F23 7.9701 Tf 9.335 4.505 Td [(k)]TJ/F15 10.9091 Tf 5.119 -4.505 Td [(\051)]TJ/F26 7.9701 Tf 4.243 4.505 Td [(\000)]TJ/F20 7.9701 Tf 6.586 0 Td [(1)]TJ/F22 10.9091 Tf 4.733 -4.505 Td [(A)]TJ/F23 7.9701 Tf 8.181 4.505 Td [(k)]TJ 0 -7.202 Td [(F)]TJ/F22 10.9091 Tf 7.034 2.697 Td [(;)]TJ/F15 10.9091 Tf -258.582 -22.04 Td [(where)]TJ/F22 10.9091 Tf 32.045 0 Td [(D)]TJ/F23 7.9701 Tf 9.335 3.958 Td [(k)]TJ/F15 10.9091 Tf 9.255 -3.958 Td [(is)-379(the)-379(diagonal)-379(matrix)-379(with)-379(the)-379(s)-1(ame)-379(diagonal)-379(en)28(tries)-379(as)]TJ/F22 10.9091 Tf 276.813 0 Td [(A)]TJ/F23 7.9701 Tf 8.181 3.958 Td [(k)]TJ/F15 10.9091 Tf 5.12 -3.958 Td [(,)]TJ/F22 10.9091 Tf 7.291 0 Td [(A)]TJ/F23 7.9701 Tf 8.182 3.958 Td [(k)]TJ 0 -7.191 Td [(F)]TJ/F15 10.9091 Tf 10.896 3.233 Td [(=)-354(\050)-14(\026)]TJ/F22 10.9091 Tf 16.59 0 Td [(a)]TJ/F23 7.9701 Tf 5.766 3.958 Td [(k)]TJ 0 -7.014 Td [(ij)]TJ/F15 10.9091 Tf 7.266 3.056 Td [(\051)-379(is)]TJ -396.74 -13.55 Td [(the)-333(\014ltered)-334(matrix)-333(de\014ned)-333(as)]TJ 48.968 -26.039 Td [(\026)]TJ/F22 10.9091 Tf -0.156 0 Td [(a)]TJ/F23 7.9701 Tf 5.766 4.505 Td [(k)]TJ 0 -7.202 Td [(ij)]TJ/F15 10.9091 Tf 10.296 2.697 Td [(=)]TJ/F28 10.9091 Tf 11.515 15.382 Td [(\032)]TJ/F22 10.9091 Tf 13.163 -8.324 Td [(a)]TJ/F23 7.9701 Tf 5.766 3.959 Td [(k)]TJ 0 -7.015 Td [(ij)]TJ/F15 10.9091 Tf 17.228 3.056 Td [(if)]TJ/F22 10.9091 Tf 10 0 Td [(j)]TJ/F25 10.9091 Tf 8.147 0 Td [(2)-278(N)]TJ/F23 7.9701 Tf 20.862 3.959 Td [(k)]TJ -1.608 -7.015 Td [(i)]TJ/F15 10.9091 Tf 6.728 3.056 Td [(\050)]TJ/F22 10.9091 Tf 4.242 0 Td [(\022)]TJ/F15 10.9091 Tf 5.424 0 Td [(\051)]TJ/F22 10.9091 Tf 4.243 0 Td [(;)]TJ/F15 10.9091 Tf -81.032 -14.09 Td [(0)-1608(otherwise)]TJ/F22 10.9091 Tf 67.934 0 Td [(;)]TJ/F15 10.9091 Tf 27.153 7.032 Td [(\050)]TJ/F22 10.9091 Tf 4.243 0 Td [(j)]TJ/F25 10.9091 Tf 8.147 0 Td [(6)]TJ/F15 10.9091 Tf 0 0 Td [(=)]TJ/F22 10.9091 Tf 11.515 0 Td [(i)]TJ/F15 10.9091 Tf 3.758 0 Td [(\051)]TJ/F22 10.9091 Tf 4.243 0 Td [(;)]TJ/F15 10.9091 Tf 26.822 0 Td [(\026)]TJ/F22 10.9091 Tf -0.156 0 Td [(a)]TJ/F23 7.9701 Tf 5.767 4.505 Td [(k)]TJ 0 -7.202 Td [(ii)]TJ/F15 10.9091 Tf 9.294 2.697 Td [(=)]TJ/F22 10.9091 Tf 11.516 0 Td [(a)]TJ/F23 7.9701 Tf 5.766 4.505 Td [(k)]TJ 0 -7.202 Td [(ii)]TJ/F25 10.9091 Tf 8.689 2.697 Td [(\000)]TJ/F28 10.9091 Tf 10.909 10.364 Td [(X)]TJ/F23 7.9701 Tf 1.202 -23.717 Td [(j)]TJ/F26 7.9701 Tf 3.884 0 Td [(6)]TJ/F20 7.9701 Tf 0 0 Td [(=)]TJ/F23 7.9701 Tf 6.586 0 Td [(i)]TJ/F15 10.9091 Tf 4.085 13.353 Td [(\050)]TJ/F22 10.9091 Tf 4.243 0 Td [(a)]TJ/F23 7.9701 Tf 5.766 4.505 Td [(k)]TJ 0 -7.202 Td [(ij)]TJ/F25 10.9091 Tf 9.69 2.697 Td [(\000)]TJ/F15 10.9091 Tf 11.065 0 Td [(\026)]TJ/F22 10.9091 Tf -0.156 0 Td [(a)]TJ/F23 7.9701 Tf 5.766 4.505 Td [(k)]TJ 0 -7.202 Td [(ij)]TJ/F15 10.9091 Tf 7.265 2.697 Td [(\051)]TJ/F22 10.9091 Tf 4.243 0 Td [(;)]TJ 0 g 0 G @@ -2105,11 +2105,11 @@ BT 0 g 0 G [(].)]TJ -397.906 -13.549 Td [(In)-288(MLD2P4)-288(this)-287(appro)27(ximation)-287(is)-288(obtained)-288(b)28(y)-288(using)]TJ/F25 10.9091 Tf 250.336 0 Td [(k)]TJ/F22 10.9091 Tf 5.455 0 Td [(A)]TJ/F23 7.9701 Tf 8.181 3.959 Td [(k)]TJ 0 -7.192 Td [(F)]TJ/F25 10.9091 Tf 7.034 3.233 Td [(k)]TJ/F26 7.9701 Tf 5.454 -1.636 Td [(1)]TJ/F15 10.9091 Tf 12.107 1.636 Td [(as)-288(an)-288(estimate)-288(of)]TJ/F22 10.9091 Tf 82.683 0 Td [(\032)]TJ/F23 7.9701 Tf 5.641 3.959 Td [(k)]TJ/F15 10.9091 Tf 5.119 -3.959 Td [(.)-429(Note)]TJ -382.01 -13.549 Td [(that)-373(for)-373(systems)-374(coming)-373(from)-373(uniformly)-373(elliptic)-373(problems,)-384(\014)1(ltering)-374(the)-373(matrix)]TJ/F22 10.9091 Tf 379.26 0 Td [(A)]TJ/F23 7.9701 Tf 8.182 3.959 Td [(k)]TJ/F15 10.9091 Tf 9.191 -3.959 Td [(has)]TJ -396.633 -13.549 Td [(little)-306(or)-306(no)-306(e\013ect,)-312(and)]TJ/F22 10.9091 Tf 106.178 0 Td [(A)]TJ/F23 7.9701 Tf 8.182 3.958 Td [(k)]TJ/F15 10.9091 Tf 8.459 -3.958 Td [(can)-306(b)-28(e)-306(used)-306(instead)-306(of)]TJ/F22 10.9091 Tf 108.331 0 Td [(A)]TJ/F23 7.9701 Tf 8.182 3.958 Td [(k)]TJ 0 -7.191 Td [(F)]TJ/F15 10.9091 Tf 7.033 3.233 Td [(.)-435(The)-306(latter)-306(c)27(hoice)-306(is)-306(the)-306(default)-306(in)]TJ -246.365 -13.55 Td [(MLD2P4.)]TJ/F17 11.9552 Tf 0 -28.825 Td [(4.3)-1125(Smo)-31(others)-375(and)-375(coarsest-lev)31(el)-375(solv)31(ers)]TJ/F15 10.9091 Tf 0 -20.594 Td [(The)-294(smo)-28(others)-294(implemen)28(ted)-295(i)1(n)-295(MLD2P4)-294(include)-294(the)-294(Jacobi)-294(and)-294(blo)-28(c)28(k-Jacobi)-294(metho)-28(ds,)]TJ 0 -13.549 Td [(a)-344(h)28(ybrid)-343(v)28(e)-1(r)1(s)-1(ion)-343(of)-344(the)-343(forw)28(ard)-344(and)-344(b)1(ac)27(kw)28(ard)-344(Gau)1(s)-1(s-Seidel)-343(metho)-28(ds,)-346(and)-344(the)-343(additiv)28(e)]TJ 0 -13.55 Td [(Sc)28(h)28(w)27(arz)-333(\050AS\051)-333(ones)-334(\050see,)-333(e.g.,)-333([)]TJ 1 0 0 rg 1 0 0 RG - [(20)]TJ + [(21)]TJ 0 g 0 G [(,)]TJ 1 0 0 rg 1 0 0 RG - [-334(21)]TJ + [-334(22)]TJ 0 g 0 G [(]\051.)]TJ 16.936 -13.549 Td [(The)-481(h)28(ybrid)-480(Gauss-Seidel)-481(v)28(ersion)-481(is)-480(considered)-481(b)-27(ecause)-481(the)-481(origin)1(al)-481(Gauss-Seidel)]TJ -16.936 -13.549 Td [(metho)-28(d)-364(is)-365(inheren)28(tly)-364(sequen)27(tial.)-537(A)27(t)-364(eac)28(h)-365(iteration)-364(of)-365(the)-364(h)28(ybrid)-365(v)28(ersion,)-372(eac)27(h)-364(parallel)]TJ 0 -13.549 Td [(pro)-28(cess)-452(uses)-452(the)-451(mos)-1(t)-451(recen)27(t)-451(v)55(alues)-452(of)-452(i)1(ts)-452(o)27(wn)-451(lo)-28(cal)-452(v)56(ariables)-452(and)-452(the)-452(v)56(alues)-452(of)-452(the)]TJ 0 -13.549 Td [(non-lo)-28(cal)-418(v)55(ari)1(ables)-419(computed)-418(at)-419(the)-418(previous)-418(iteration,)-440(obtained)-418(b)28(y)-419(exc)28(hanging)-418(data)]TJ 0 -13.55 Td [(with)-333(other)-334(pr)1(o)-28(cesses)-334(b)-28(efore)-333(the)-333(b)-28(eginning)-333(of)-334(th)1(e)-334(curren)28(t)-333(iteration.)]TJ 16.936 -13.549 Td [(In)-372(the)-372(AS)-372(me)-1(th)1(o)-28(ds,)-382(the)-372(index)-372(space)-373(\012)]TJ/F23 7.9701 Tf 185.618 3.959 Td [(k)]TJ/F15 10.9091 Tf 9.18 -3.959 Td [(is)-372(divided)-372(in)28(to)]TJ/F22 10.9091 Tf 72.847 0 Td [(m)]TJ/F23 7.9701 Tf 9.578 -1.777 Td [(k)]TJ/F15 10.9091 Tf 9.18 1.777 Td [(subsets)-372(\012)]TJ/F23 7.9701 Tf 46.06 3.959 Td [(k)]TJ 0 -7.014 Td [(i)]TJ/F15 10.9091 Tf 9.18 3.055 Td [(of)-372(size)]TJ/F22 10.9091 Tf 33.939 0 Td [(n)]TJ/F23 7.9701 Tf 6.548 -1.777 Td [(k)-27(;i)]TJ/F15 10.9091 Tf 10.355 1.777 Td [(,)]TJ -409.421 -13.549 Td [(p)-28(ossibly)-432(o)28(v)28(erlapping.)-740(F)83(or)-432(eac)28(h)]TJ/F22 10.9091 Tf 155.272 0 Td [(i)]TJ/F15 10.9091 Tf 8.47 0 Td [(w)28(e)-432(consider)-432(the)-432(restriction)-432(op)-28(erator)]TJ/F22 10.9091 Tf 178.985 0 Td [(R)]TJ/F23 7.9701 Tf 8.367 3.959 Td [(k)]TJ -0.084 -7.014 Td [(i)]TJ/F25 10.9091 Tf 10.027 3.055 Td [(2)]TJ/F34 10.9091 Tf 12.095 0 Td [(R)]TJ/F23 7.9701 Tf 7.879 3.959 Td [(n)]TJ/F24 5.9776 Tf 5.138 -1.406 Td [(k)-21(;i)]TJ/F26 7.9701 Tf 9.506 1.406 Td [(\002)]TJ/F23 7.9701 Tf 6.587 0 Td [(n)]TJ/F24 5.9776 Tf 5.138 -1.406 Td [(k)]TJ/F15 10.9091 Tf -407.38 -16.102 Td [(that)-366(maps)-366(a)-365(v)27(ector)]TJ/F22 10.9091 Tf 95.448 0 Td [(x)]TJ/F23 7.9701 Tf 6.235 3.959 Td [(k)]TJ/F15 10.9091 Tf 9.11 -3.959 Td [(to)-366(the)-366(v)28(ector)]TJ/F22 10.9091 Tf 65.942 0 Td [(x)]TJ/F23 7.9701 Tf 6.235 3.959 Td [(k)]TJ 0 -7.015 Td [(i)]TJ/F15 10.9091 Tf 9.11 3.056 Td [(made)-366(of)-366(the)-365(com)-1(p)-27(onen)28(ts)-366(of)]TJ/F22 10.9091 Tf 134.56 0 Td [(x)]TJ/F23 7.9701 Tf 6.234 3.959 Td [(k)]TJ/F15 10.9091 Tf 9.111 -3.959 Td [(with)-366(indices)-366(in)]TJ -341.985 -13.549 Td [(\012)]TJ/F23 7.9701 Tf 7.879 3.959 Td [(k)]TJ 0 -7.015 Td [(i)]TJ/F15 10.9091 Tf 5.12 3.056 Td [(,)-301(and)-292(the)-293(prolongation)-292(op)-28(erator)]TJ/F22 10.9091 Tf 152.201 0 Td [(P)]TJ/F23 7.9701 Tf 8.519 3.959 Td [(k)]TJ -1.515 -7.015 Td [(i)]TJ/F15 10.9091 Tf 9.665 3.056 Td [(=)-278(\050)]TJ/F22 10.9091 Tf 15.758 0 Td [(R)]TJ/F23 7.9701 Tf 8.367 3.959 Td [(k)]TJ -0.084 -7.015 Td [(i)]TJ/F15 10.9091 Tf 5.204 3.056 Td [(\051)]TJ/F23 7.9701 Tf 4.242 3.959 Td [(T)]TJ/F15 10.9091 Tf 6.605 -3.959 Td [(.)-431(These)-293(op)-27(erators)-293(are)-293(then)-292(used)-293(to)-292(build)]TJ/F22 10.9091 Tf -221.961 -13.549 Td [(A)]TJ/F23 7.9701 Tf 8.182 3.958 Td [(k)]TJ 0 -7.014 Td [(i)]TJ/F15 10.9091 Tf 8.557 3.056 Td [(=)]TJ/F22 10.9091 Tf 11.923 0 Td [(R)]TJ/F23 7.9701 Tf 8.367 3.958 Td [(k)]TJ -0.084 -7.014 Td [(i)]TJ/F22 10.9091 Tf 5.204 3.056 Td [(A)]TJ/F23 7.9701 Tf 8.182 3.958 Td [(k)]TJ/F22 10.9091 Tf 5.119 -3.958 Td [(P)]TJ/F23 7.9701 Tf 8.519 3.958 Td [(k)]TJ -1.515 -7.014 Td [(i)]TJ/F15 10.9091 Tf 6.635 3.056 Td [(,)-361(whic)27(h)-355(is)-356(the)-356(restriction)-355(of)]TJ/F22 10.9091 Tf 133.83 0 Td [(A)]TJ/F23 7.9701 Tf 8.182 3.958 Td [(k)]TJ/F15 10.9091 Tf 9.001 -3.958 Td [(to)-356(the)-355(index)-356(space)-356(\012)]TJ/F23 7.9701 Tf 99.523 3.958 Td [(k)]TJ 0 -7.014 Td [(i)]TJ/F15 10.9091 Tf 5.119 3.056 Td [(.)-512(The)-355(class)-1(ical)-355(AS)]TJ -324.744 -13.55 Td [(preconditioner)]TJ/F22 10.9091 Tf 72.182 0 Td [(M)]TJ/F23 7.9701 Tf 11.773 3.959 Td [(k)]TJ -1.19 -7.192 Td [(AS)]TJ/F15 10.9091 Tf 16.074 3.233 Td [(is)-333(de\014ned)-334(as)]TJ 38.283 -31.315 Td [(\050)]TJ/F22 10.9091 Tf 4.243 0 Td [(M)]TJ/F23 7.9701 Tf 11.773 4.504 Td [(k)]TJ -1.19 -7.201 Td [(AS)]TJ/F15 10.9091 Tf 12.437 2.697 Td [(\051)]TJ/F26 7.9701 Tf 4.242 4.504 Td [(\000)]TJ/F20 7.9701 Tf 6.587 0 Td [(1)]TJ/F15 10.9091 Tf 7.763 -4.504 Td [(=)]TJ/F23 7.9701 Tf 13.362 14.072 Td [(m)]TJ/F24 5.9776 Tf 7.49 -1.406 Td [(k)]TJ/F28 10.9091 Tf -9.337 -2.303 Td [(X)]TJ/F23 7.9701 Tf 1.027 -23.45 Td [(i)]TJ/F20 7.9701 Tf 2.883 0 Td [(=1)]TJ/F22 10.9091 Tf 13.665 13.087 Td [(P)]TJ/F23 7.9701 Tf 8.519 4.504 Td [(k)]TJ -1.515 -7.201 Td [(i)]TJ/F15 10.9091 Tf 6.635 2.697 Td [(\050)]TJ/F22 10.9091 Tf 4.243 0 Td [(A)]TJ/F23 7.9701 Tf 8.181 4.504 Td [(k)]TJ 0 -7.201 Td [(i)]TJ/F15 10.9091 Tf 5.12 2.697 Td [(\051)]TJ/F26 7.9701 Tf 4.243 4.504 Td [(\000)]TJ/F20 7.9701 Tf 6.586 0 Td [(1)]TJ/F22 10.9091 Tf 4.732 -4.504 Td [(R)]TJ/F23 7.9701 Tf 8.368 4.504 Td [(k)]TJ -0.084 -7.201 Td [(i)]TJ/F22 10.9091 Tf 5.204 2.697 Td [(;)]TJ 0 g 0 G @@ -3531,7 +3531,7 @@ ET endstream endobj -513 0 obj +514 0 obj << /Length 2620 >> @@ -3564,7 +3564,7 @@ ET endstream endobj -518 0 obj +519 0 obj << /Length 3774 >> @@ -3729,9 +3729,9 @@ Q endstream endobj -523 0 obj +524 0 obj << -/Length 10371 +/Length 10624 >> stream 0 g 0 G @@ -3750,362 +3750,366 @@ q 0 g 0 G 0 g 0 G q -1 0 0 1 0 209.817 cm +1 0 0 1 0 216.592 cm []0 d 0 J 0.398 w 0 0 m 600.087 0 l S Q q -1 0 0 1 0 196.069 cm +1 0 0 1 0 202.843 cm []0 d 0 J 0.398 w 0 0 m 0 13.549 l S Q 1 0 0 1 -299.826 -121.521 cm BT -/F45 10.9091 Tf 305.803 321.655 Td [(what)]TJ +/F45 10.9091 Tf 305.803 328.429 Td [(what)]TJ ET q -1 0 0 1 422.332 317.59 cm +1 0 0 1 422.332 324.364 cm []0 d 0 J 0.398 w 0 0 m 0 13.549 l S Q BT -/F42 10.9091 Tf 428.31 321.655 Td [(d)22(a)67(t)67(a)-378(type)]TJ +/F42 10.9091 Tf 428.31 328.429 Td [(d)22(a)67(t)67(a)-378(type)]TJ ET q -1 0 0 1 521.055 317.59 cm +1 0 0 1 521.055 324.364 cm []0 d 0 J 0.398 w 0 0 m 0 13.549 l S Q BT -/F45 10.9091 Tf 527.032 321.655 Td [(val)]TJ +/F45 10.9091 Tf 527.032 328.429 Td [(val)]TJ ET q -1 0 0 1 598.207 317.59 cm +1 0 0 1 598.207 324.364 cm []0 d 0 J 0.398 w 0 0 m 0 13.549 l S Q BT -/F42 10.9091 Tf 604.185 321.655 Td [(def)89(a)22(ul)67(t)]TJ +/F42 10.9091 Tf 604.185 328.429 Td [(def)89(a)22(ul)67(t)]TJ ET q -1 0 0 1 692.367 317.59 cm +1 0 0 1 692.367 324.364 cm []0 d 0 J 0.398 w 0 0 m 0 13.549 l S Q BT -/F42 10.9091 Tf 698.344 321.655 Td [(comments)]TJ +/F42 10.9091 Tf 698.344 328.429 Td [(comments)]TJ ET q -1 0 0 1 899.912 317.59 cm +1 0 0 1 899.912 324.364 cm []0 d 0 J 0.398 w 0 0 m 0 13.549 l S Q q -1 0 0 1 299.826 317.391 cm +1 0 0 1 299.826 324.165 cm []0 d 0 J 0.398 w 0 0 m 600.087 0 l S Q q -1 0 0 1 299.826 262.995 cm +1 0 0 1 299.826 269.769 cm []0 d 0 J 0.398 w 0 0 m 0 54.197 l S Q BT -/F45 10.9091 Tf 305.803 307.707 Td [('MIN_COARSE_SIZE')]TJ +/F45 10.9091 Tf 305.803 314.481 Td [('MIN_COARSE_SIZE')]TJ ET q -1 0 0 1 422.332 262.995 cm +1 0 0 1 422.332 269.769 cm []0 d 0 J 0.398 w 0 0 m 0 54.197 l S Q BT -/F45 10.9091 Tf 428.31 307.707 Td [(integer)]TJ +/F45 10.9091 Tf 428.31 314.481 Td [(integer)]TJ ET q -1 0 0 1 521.055 262.995 cm +1 0 0 1 521.055 269.769 cm []0 d 0 J 0.398 w 0 0 m 0 54.197 l S Q BT -/F15 10.9091 Tf 527.032 307.707 Td [(An)28(y)-334(n)28(um)28(b)-28(er)]TJ/F22 10.9091 Tf 0 -13.549 Td [(>)]TJ/F15 10.9091 Tf 11.516 0 Td [(0)]TJ +/F15 10.9091 Tf 527.032 314.481 Td [(An)28(y)-334(n)28(um)28(b)-28(er)]TJ/F22 10.9091 Tf 0 -13.549 Td [(>)]TJ/F15 10.9091 Tf 11.516 0 Td [(0)]TJ ET q -1 0 0 1 598.207 262.995 cm +1 0 0 1 598.207 269.769 cm []0 d 0 J 0.398 w 0 0 m 0 54.197 l S Q BT -/F25 10.9091 Tf 604.185 307.707 Td [(b)]TJ/F15 10.9091 Tf 4.848 0 Td [(40)]TJ/F21 5.9776 Tf 13.939 3.669 Td [(3)]TJ/F25 10.9091 Tf -2.407 4.188 Td [(p)]TJ +/F25 10.9091 Tf 604.185 314.481 Td [(b)]TJ/F15 10.9091 Tf 4.848 0 Td [(40)]TJ/F21 5.9776 Tf 13.939 3.67 Td [(3)]TJ/F25 10.9091 Tf -2.407 4.188 Td [(p)]TJ ET q -1 0 0 1 629.656 315.783 cm +1 0 0 1 629.656 322.557 cm []0 d 0 J 0.436 w 0 0 m 6.548 0 l S Q BT -/F22 10.9091 Tf 629.656 307.707 Td [(n)]TJ/F25 10.9091 Tf 6.548 0 Td [(c)]TJ/F15 10.9091 Tf 4.848 0 Td [(,)-363(where)]TJ/F22 10.9091 Tf 38.789 0 Td [(n)]TJ/F15 10.9091 Tf -75.656 -13.549 Td [(is)-540(the)-540(dimension)]TJ 0 -13.549 Td [(of)-511(the)-511(matrix)-510(at)]TJ 0 -13.55 Td [(the)-333(\014nest)-334(lev)28(el)]TJ +/F22 10.9091 Tf 629.656 314.481 Td [(n)]TJ/F25 10.9091 Tf 6.548 0 Td [(c)]TJ/F15 10.9091 Tf 4.848 0 Td [(,)-363(where)]TJ/F22 10.9091 Tf 38.789 0 Td [(n)]TJ/F15 10.9091 Tf -75.656 -13.549 Td [(is)-540(the)-540(dimension)]TJ 0 -13.549 Td [(of)-511(the)-511(matrix)-510(at)]TJ 0 -13.549 Td [(the)-333(\014nest)-334(lev)28(el)]TJ ET q -1 0 0 1 692.367 262.995 cm +1 0 0 1 692.367 269.769 cm []0 d 0 J 0.398 w 0 0 m 0 54.197 l S Q BT -/F15 10.9091 Tf 698.344 307.707 Td [(Coarse)-475(size)-475(threshold.)-868(The)-475(aggregation)]TJ 0 -13.549 Td [(stops)-531(if)-531(the)-530(global)-531(n)28(um)28(b)-28(er)-531(of)-531(v)56(ariables)]TJ 0 -13.549 Td [(of)-354(the)-355(computed)-354(coarsest)-355(matrix)-354(is)-354(lo)27(w)28(er)]TJ 0 -13.55 Td [(than)-249(or)-248(equal)-249(to)-248(this)-249(threshold)-248(\050see)-249(Note\051.)]TJ +/F15 10.9091 Tf 698.344 314.481 Td [(Coarse)-475(size)-475(threshold.)-868(The)-475(aggregation)]TJ 0 -13.549 Td [(stops)-531(if)-531(the)-530(global)-531(n)28(um)28(b)-28(er)-531(of)-531(v)56(ariables)]TJ 0 -13.549 Td [(of)-354(the)-355(computed)-354(coarsest)-355(matrix)-354(is)-354(lo)27(w)28(er)]TJ 0 -13.549 Td [(than)-249(or)-248(equal)-249(to)-248(this)-249(threshold)-248(\050see)-249(Note\051.)]TJ ET q -1 0 0 1 899.912 262.995 cm +1 0 0 1 899.912 269.769 cm []0 d 0 J 0.398 w 0 0 m 0 54.197 l S Q q -1 0 0 1 299.826 262.795 cm +1 0 0 1 299.826 269.57 cm []0 d 0 J 0.398 w 0 0 m 600.087 0 l S Q q -1 0 0 1 299.826 194.85 cm +1 0 0 1 299.826 201.625 cm []0 d 0 J 0.398 w 0 0 m 0 67.746 l S Q BT -/F45 10.9091 Tf 305.803 253.112 Td [('MIN_CR_RATIO')]TJ +/F45 10.9091 Tf 305.803 259.886 Td [('MIN_CR_RATIO')]TJ ET q -1 0 0 1 422.332 194.85 cm +1 0 0 1 422.332 201.625 cm []0 d 0 J 0.398 w 0 0 m 0 67.746 l S Q BT -/F45 10.9091 Tf 428.31 253.112 Td [(real)]TJ +/F45 10.9091 Tf 428.31 259.886 Td [(real)]TJ ET q -1 0 0 1 521.055 194.85 cm +1 0 0 1 521.055 201.625 cm []0 d 0 J 0.398 w 0 0 m 0 67.746 l S Q BT -/F15 10.9091 Tf 527.032 253.112 Td [(An)28(y)-334(n)28(um)28(b)-28(er)]TJ/F22 10.9091 Tf 0 -13.55 Td [(>)]TJ/F15 10.9091 Tf 11.516 0 Td [(1)]TJ +/F15 10.9091 Tf 527.032 259.886 Td [(An)28(y)-334(n)28(um)28(b)-28(er)]TJ/F22 10.9091 Tf 0 -13.549 Td [(>)]TJ/F15 10.9091 Tf 11.516 0 Td [(1)]TJ ET q -1 0 0 1 598.207 194.85 cm +1 0 0 1 598.207 201.625 cm []0 d 0 J 0.398 w 0 0 m 0 67.746 l S Q BT -/F15 10.9091 Tf 604.185 253.112 Td [(1.5)]TJ +/F15 10.9091 Tf 604.185 259.886 Td [(1.5)]TJ ET q -1 0 0 1 692.367 194.85 cm +1 0 0 1 692.367 201.625 cm []0 d 0 J 0.398 w 0 0 m 0 67.746 l S Q BT -/F15 10.9091 Tf 698.344 253.112 Td [(Minim)28(um)-325(coarsening)-324(ratio.)-442(The)-324(aggrega-)]TJ 0 -13.55 Td [(tion)-480(stops)-480(if)-480(the)-480(ratio)-480(b)-27(et)27(w)28(een)-480(the)-480(ma-)]TJ 0 -13.549 Td [(trix)-364(dimensions)-364(at)-364(t)27(w)28(o)-364(consecutiv)28(e)-364(lev)27(els)]TJ 0 -13.549 Td [(is)-459(lo)28(w)28(er)-459(th)1(an)-459(or)-458(e)-1(q)1(ual)-459(to)-458(this)-459(threshold)]TJ 0 -13.549 Td [(\050see)-333(Note)-1(\051.)]TJ +/F15 10.9091 Tf 698.344 259.886 Td [(Minim)28(um)-325(coarsening)-324(ratio.)-442(The)-324(aggrega-)]TJ 0 -13.549 Td [(tion)-480(stops)-480(if)-480(the)-480(ratio)-480(b)-27(et)27(w)28(een)-480(the)-480(ma-)]TJ 0 -13.549 Td [(trix)-364(dimensions)-364(at)-364(t)27(w)28(o)-364(consecutiv)28(e)-364(lev)27(els)]TJ 0 -13.549 Td [(is)-459(lo)28(w)28(er)-459(th)1(an)-459(or)-458(e)-1(q)1(ual)-459(to)-458(this)-459(threshold)]TJ 0 -13.55 Td [(\050see)-333(Note)-1(\051.)]TJ ET q -1 0 0 1 899.912 194.85 cm +1 0 0 1 899.912 201.625 cm []0 d 0 J 0.398 w 0 0 m 0 67.746 l S Q q -1 0 0 1 299.826 194.651 cm +1 0 0 1 299.826 201.425 cm []0 d 0 J 0.398 w 0 0 m 600.087 0 l S Q q -1 0 0 1 299.826 153.804 cm +1 0 0 1 299.826 160.579 cm []0 d 0 J 0.398 w 0 0 m 0 40.648 l S Q BT -/F45 10.9091 Tf 305.803 184.967 Td [('MAX_LEVS')]TJ +/F45 10.9091 Tf 305.803 191.742 Td [('MAX_LEVS')]TJ ET q -1 0 0 1 422.332 153.804 cm +1 0 0 1 422.332 160.579 cm []0 d 0 J 0.398 w 0 0 m 0 40.648 l S Q BT -/F45 10.9091 Tf 428.31 184.967 Td [(integer)]TJ +/F45 10.9091 Tf 428.31 191.742 Td [(integer)]TJ ET q -1 0 0 1 521.055 153.804 cm +1 0 0 1 521.055 160.579 cm []0 d 0 J 0.398 w 0 0 m 0 40.648 l S Q BT -/F15 10.9091 Tf 527.032 184.967 Td [(An)28(y)-334(in)28(teger)]TJ 0 -13.549 Td [(n)28(um)28(b)-28(er)]TJ/F22 10.9091 Tf 39.728 0 Td [(>)]TJ/F15 10.9091 Tf 11.515 0 Td [(1)]TJ +/F15 10.9091 Tf 527.032 191.742 Td [(An)28(y)-334(in)28(teger)]TJ 0 -13.549 Td [(n)28(um)28(b)-28(er)]TJ/F22 10.9091 Tf 39.728 0 Td [(>)]TJ/F15 10.9091 Tf 11.515 0 Td [(1)]TJ ET q -1 0 0 1 598.207 153.804 cm +1 0 0 1 598.207 160.579 cm []0 d 0 J 0.398 w 0 0 m 0 40.648 l S Q BT -/F15 10.9091 Tf 604.185 184.967 Td [(20)]TJ +/F15 10.9091 Tf 604.185 191.742 Td [(20)]TJ ET q -1 0 0 1 692.367 153.804 cm +1 0 0 1 692.367 160.579 cm []0 d 0 J 0.398 w 0 0 m 0 40.648 l S Q BT -/F15 10.9091 Tf 698.344 184.967 Td [(Maxim)28(um)-244(n)28(um)28(b)-28(er)-244(of)-244(lev)28(els.)-415(The)-244(aggrega-)]TJ 0 -13.549 Td [(tion)-343(stops)-343(if)-343(the)-343(n)28(um)28(b)-28(er)-343(of)-343(lev)27(els)-343(reac)28(hes)]TJ 0 -13.549 Td [(this)-333(v)55(alue)-333(\050see)-334(Note\051.)]TJ +/F15 10.9091 Tf 698.344 191.742 Td [(Maxim)28(um)-244(n)28(um)28(b)-28(er)-244(of)-244(lev)28(els.)-415(The)-244(aggrega-)]TJ 0 -13.549 Td [(tion)-343(stops)-343(if)-343(the)-343(n)28(um)28(b)-28(er)-343(of)-343(lev)27(els)-343(reac)28(hes)]TJ 0 -13.55 Td [(this)-333(v)55(alue)-333(\050see)-334(Note\051.)]TJ ET q -1 0 0 1 899.912 153.804 cm +1 0 0 1 899.912 160.579 cm []0 d 0 J 0.398 w 0 0 m 0 40.648 l S Q q -1 0 0 1 299.826 153.605 cm +1 0 0 1 299.826 160.379 cm []0 d 0 J 0.398 w 0 0 m 600.087 0 l S Q q -1 0 0 1 299.826 85.66 cm +1 0 0 1 299.826 92.434 cm []0 d 0 J 0.398 w 0 0 m 0 67.746 l S Q BT -/F45 10.9091 Tf 305.803 143.921 Td [('PAR_AGGR_ALG')]TJ +/F45 10.9091 Tf 305.803 150.696 Td [('PAR_AGGR_ALG')]TJ ET q -1 0 0 1 422.332 85.66 cm +1 0 0 1 422.332 92.434 cm []0 d 0 J 0.398 w 0 0 m 0 67.746 l S Q BT -/F45 10.9091 Tf 428.31 143.921 Td [(character\050len=*\051)]TJ +/F45 10.9091 Tf 428.31 150.696 Td [(character\050len=*\051)]TJ ET q -1 0 0 1 521.055 85.66 cm +1 0 0 1 521.055 92.434 cm []0 d 0 J 0.398 w 0 0 m 0 67.746 l S Q BT -/F45 10.9091 Tf 527.032 143.921 Td [('DEC')]TJ/F15 10.9091 Tf 28.637 0 Td [(,)]TJ/F45 10.9091 Tf -28.637 -13.549 Td [('SYMDEC')]TJ +/F45 10.9091 Tf 527.032 150.696 Td [('DEC')]TJ/F15 10.9091 Tf 28.637 0 Td [(,)]TJ/F45 10.9091 Tf -28.637 -13.55 Td [('SYMDEC')]TJ ET q -1 0 0 1 598.207 85.66 cm +1 0 0 1 598.207 92.434 cm []0 d 0 J 0.398 w 0 0 m 0 67.746 l S Q BT -/F45 10.9091 Tf 604.185 143.921 Td [('DEC')]TJ +/F45 10.9091 Tf 604.185 150.696 Td [('DEC')]TJ ET q -1 0 0 1 692.367 85.66 cm +1 0 0 1 692.367 92.434 cm []0 d 0 J 0.398 w 0 0 m 0 67.746 l S Q BT -/F15 10.9091 Tf 698.344 143.921 Td [(P)28(arallel)-333(aggregation)-334(algorithm.)]TJ 0 -13.549 Td [(Curren)28(tly)83(,)-604(only)-550(the)-550(decoupled)-550(aggrega-)]TJ 0 -13.549 Td [(tion)-518(\050)]TJ/F45 10.9091 Tf 28.679 0 Td [(DEC)]TJ/F15 10.9091 Tf 17.182 0 Td [(\051)-518(is)-517(a)27(v)56(ailable;)-610(the)]TJ/F45 10.9091 Tf 94.568 0 Td [(SYMDEC)]TJ/F15 10.9091 Tf 40.01 0 Td [(op-)]TJ -180.439 -13.549 Td [(tion)-306(applies)-307(decoupled)-306(aggregation)-306(to)-307(the)]TJ 0 -13.55 Td [(sparsit)28(y)-334(p)1(atte)-1(r)1(n)-334(of)]TJ/F22 10.9091 Tf 92 0 Td [(A)]TJ/F15 10.9091 Tf 10.606 0 Td [(+)]TJ/F22 10.9091 Tf 10.909 0 Td [(A)]TJ/F23 7.9701 Tf 8.182 3.959 Td [(T)]TJ/F15 10.9091 Tf 6.605 -3.959 Td [(.)]TJ +/F15 10.9091 Tf 698.344 150.696 Td [(P)28(arallel)-333(aggregation)-334(algorithm.)]TJ 0 -13.55 Td [(Curren)28(tly)83(,)-604(only)-550(the)-550(decoupled)-550(aggrega-)]TJ 0 -13.549 Td [(tion)-518(\050)]TJ/F45 10.9091 Tf 28.679 0 Td [(DEC)]TJ/F15 10.9091 Tf 17.182 0 Td [(\051)-518(is)-517(a)27(v)56(ailable;)-610(the)]TJ/F45 10.9091 Tf 94.568 0 Td [(SYMDEC)]TJ/F15 10.9091 Tf 40.01 0 Td [(op-)]TJ -180.439 -13.549 Td [(tion)-306(applies)-307(decoupled)-306(aggregation)-306(to)-307(the)]TJ 0 -13.549 Td [(sparsit)28(y)-334(p)1(atte)-1(r)1(n)-334(of)]TJ/F22 10.9091 Tf 92 0 Td [(A)]TJ/F15 10.9091 Tf 10.606 0 Td [(+)]TJ/F22 10.9091 Tf 10.909 0 Td [(A)]TJ/F23 7.9701 Tf 8.182 3.959 Td [(T)]TJ/F15 10.9091 Tf 6.605 -3.959 Td [(.)]TJ ET q -1 0 0 1 899.912 85.66 cm +1 0 0 1 899.912 92.434 cm []0 d 0 J 0.398 w 0 0 m 0 67.746 l S Q q -1 0 0 1 299.826 85.46 cm +1 0 0 1 299.826 92.235 cm []0 d 0 J 0.398 w 0 0 m 600.087 0 l S Q q -1 0 0 1 299.826 31.064 cm -[]0 d 0 J 0.398 w 0 0 m 0 54.197 l S +1 0 0 1 299.826 24.29 cm +[]0 d 0 J 0.398 w 0 0 m 0 67.746 l S Q BT -/F45 10.9091 Tf 305.803 75.777 Td [('AGGR_TYPE')]TJ +/F45 10.9091 Tf 305.803 82.551 Td [('AGGR_TYPE')]TJ ET q -1 0 0 1 422.332 31.064 cm -[]0 d 0 J 0.398 w 0 0 m 0 54.197 l S +1 0 0 1 422.332 24.29 cm +[]0 d 0 J 0.398 w 0 0 m 0 67.746 l S Q BT -/F45 10.9091 Tf 428.31 75.777 Td [(character\050len=*\051)]TJ +/F45 10.9091 Tf 428.31 82.551 Td [(character\050len=*\051)]TJ ET q -1 0 0 1 521.055 31.064 cm -[]0 d 0 J 0.398 w 0 0 m 0 54.197 l S +1 0 0 1 521.055 24.29 cm +[]0 d 0 J 0.398 w 0 0 m 0 67.746 l S Q BT -/F45 10.9091 Tf 527.032 75.777 Td [('VMB')]TJ +/F45 10.9091 Tf 527.032 82.551 Td [('SOC1')]TJ ET q -1 0 0 1 598.207 31.064 cm -[]0 d 0 J 0.398 w 0 0 m 0 54.197 l S +1 0 0 1 598.207 24.29 cm +[]0 d 0 J 0.398 w 0 0 m 0 67.746 l S Q BT -/F45 10.9091 Tf 604.185 75.777 Td [('VMB')]TJ +/F45 10.9091 Tf 604.185 82.551 Td [('SOC1')]TJ/F15 10.9091 Tf 34.363 0 Td [(,)]TJ/F45 10.9091 Tf 6.667 0 Td [('SOC2')]TJ ET q -1 0 0 1 692.367 31.064 cm -[]0 d 0 J 0.398 w 0 0 m 0 54.197 l S +1 0 0 1 692.367 24.29 cm +[]0 d 0 J 0.398 w 0 0 m 0 67.746 l S Q BT -/F15 10.9091 Tf 698.344 75.777 Td [(T)28(yp)-28(e)-762(of)-762(aggregation)-762(algorithm:)-1301(cur-)]TJ 0 -13.55 Td [(ren)28(tly)83(,)-528(the)-489(scalar)-489(aggregation)-490(algor)1(ithm)]TJ 0 -13.549 Td [(b)28(y)-385(V)83(an)28(\024)472(ek,)-398(Mandel)-385(and)-385(Brezina)-385(is)-385(imple-)]TJ 0 -13.549 Td [(men)28(ted)-334([)]TJ +/F15 10.9091 Tf 698.344 82.551 Td [(T)28(yp)-28(e)-254(of)-255(aggregation)-254(algorithm:)-405(curren)28(tly)83(,)]TJ 0 -13.549 Td [(w)28(e)-355(implemen)28(t)-355(to)-355(measures)-355(of)-355(strength)-355(of)]TJ 0 -13.549 Td [(connection,)-595(the)-543(one)-542(b)28(y)-543(V)83(an)28(\024)472(ek,)-595(Mandel)]TJ 0 -13.549 Td [(and)-454(Brezina)-454([)]TJ 1 0 0 rg 1 0 0 RG - [(25)]TJ + [(26)]TJ +0 g 0 G + [(],)-484(and)-454(the)-454(one)-454(b)28(y)-454(Grat-)]TJ 0 -13.55 Td [(ton)-333(et)-334(al)-333([)]TJ +1 0 0 rg 1 0 0 RG + [(16)]TJ 0 g 0 G [(].)]TJ ET q -1 0 0 1 899.912 31.064 cm -[]0 d 0 J 0.398 w 0 0 m 0 54.197 l S +1 0 0 1 899.912 24.29 cm +[]0 d 0 J 0.398 w 0 0 m 0 67.746 l S Q q -1 0 0 1 299.826 30.865 cm +1 0 0 1 299.826 24.09 cm []0 d 0 J 0.398 w 0 0 m 600.087 0 l S Q q -1 0 0 1 299.826 -9.982 cm +1 0 0 1 299.826 -16.756 cm []0 d 0 J 0.398 w 0 0 m 0 40.648 l S Q BT -/F45 10.9091 Tf 305.803 21.181 Td [('AGGR_PROL')]TJ +/F45 10.9091 Tf 305.803 14.407 Td [('AGGR_PROL')]TJ ET q -1 0 0 1 422.332 -9.982 cm +1 0 0 1 422.332 -16.756 cm []0 d 0 J 0.398 w 0 0 m 0 40.648 l S Q BT -/F45 10.9091 Tf 428.31 21.181 Td [(character\050len=*\051)]TJ +/F45 10.9091 Tf 428.31 14.407 Td [(character\050len=*\051)]TJ ET q -1 0 0 1 521.055 -9.982 cm +1 0 0 1 521.055 -16.756 cm []0 d 0 J 0.398 w 0 0 m 0 40.648 l S Q BT -/F45 10.9091 Tf 527.032 21.181 Td [('SMOOTHED')]TJ/F15 10.9091 Tf 57.273 0 Td [(,)]TJ/F45 10.9091 Tf -57.273 -13.549 Td [('UNSMOOTHED')]TJ +/F45 10.9091 Tf 527.032 14.407 Td [('SMOOTHED')]TJ/F15 10.9091 Tf 57.273 0 Td [(,)]TJ/F45 10.9091 Tf -57.273 -13.549 Td [('UNSMOOTHED')]TJ ET q -1 0 0 1 598.207 -9.982 cm +1 0 0 1 598.207 -16.756 cm []0 d 0 J 0.398 w 0 0 m 0 40.648 l S Q BT -/F45 10.9091 Tf 604.185 21.181 Td [('SMOOTHED')]TJ +/F45 10.9091 Tf 604.185 14.407 Td [('SMOOTHED')]TJ ET q -1 0 0 1 692.367 -9.982 cm +1 0 0 1 692.367 -16.756 cm []0 d 0 J 0.398 w 0 0 m 0 40.648 l S Q BT -/F15 10.9091 Tf 698.344 21.181 Td [(Prolongator)-436(used)-435(b)27(y)-435(the)-436(aggregation)-436(al-)]TJ 0 -13.549 Td [(gorithm:)-609(smo)-28(othed)-416(or)-416(unsmo)-28(oth)1(e)-1(d)-415(\050i.e.,)]TJ 0 -13.549 Td [(ten)28(tativ)28(e)-334(prolongator\051.)]TJ +/F15 10.9091 Tf 698.344 14.407 Td [(Prolongator)-436(used)-435(b)27(y)-435(the)-436(aggregation)-436(al-)]TJ 0 -13.549 Td [(gorithm:)-609(smo)-28(othed)-416(or)-416(unsmo)-28(oth)1(e)-1(d)-415(\050i.e.,)]TJ 0 -13.55 Td [(ten)28(tativ)28(e)-334(prolongator\051.)]TJ ET q -1 0 0 1 899.912 -9.982 cm +1 0 0 1 899.912 -16.756 cm []0 d 0 J 0.398 w 0 0 m 0 40.648 l S Q q -1 0 0 1 299.826 -10.181 cm +1 0 0 1 299.826 -16.956 cm []0 d 0 J 0.398 w 0 0 m 600.087 0 l S Q q -1 0 0 1 299.826 -23.93 cm +1 0 0 1 299.826 -30.704 cm []0 d 0 J 0.398 w 0 0 m 0 13.549 l S Q BT -/F44 10.9091 Tf 305.803 -19.865 Td [(Note.)]TJ/F15 10.9091 Tf 35.053 0 Td [(The)-333(aggregation)-334(algorithm)-333(stops)-333(when)-334(at)-333(least)-333(one)-334(of)-333(the)-333(follo)28(wing)-334(criteria)-333(is)-333(met:)-445(the)-333(coarse)-334(size)-333(threshold,)-333(the)]TJ +/F44 10.9091 Tf 305.803 -26.639 Td [(Note.)]TJ/F15 10.9091 Tf 35.053 0 Td [(The)-333(aggregation)-334(algorithm)-333(stops)-333(when)-334(at)-333(least)-333(one)-334(of)-333(the)-333(follo)28(wing)-334(criteria)-333(is)-333(met:)-445(the)-333(coarse)-334(size)-333(threshold,)-333(the)]TJ ET q -1 0 0 1 899.912 -23.93 cm +1 0 0 1 899.912 -30.704 cm []0 d 0 J 0.398 w 0 0 m 0 13.549 l S Q q -1 0 0 1 299.826 -37.479 cm +1 0 0 1 299.826 -44.253 cm []0 d 0 J 0.398 w 0 0 m 0 13.549 l S Q BT -/F15 10.9091 Tf 305.803 -33.414 Td [(minim)28(um)-334(coarsening)-333(ratio,)-333(or)-333(the)-334(maxim)28(um)-333(n)27(u)1(m)27(b)-27(e)-1(r)-333(of)-333(lev)28(els)-334(is)-333(reac)28(hed.)-445(Therefore,)-333(the)-333(actual)-334(n)28(um)28(b)-28(er)-333(of)-333(lev)27(els)-333(ma)28(y)-334(b)-27(e)]TJ +/F15 10.9091 Tf 305.803 -40.189 Td [(minim)28(um)-334(coarsening)-333(ratio,)-333(or)-333(the)-334(maxim)28(um)-333(n)27(u)1(m)27(b)-27(e)-1(r)-333(of)-333(lev)28(els)-334(is)-333(reac)28(hed.)-445(Therefore,)-333(the)-333(actual)-334(n)28(um)28(b)-28(er)-333(of)-333(lev)27(els)-333(ma)28(y)-334(b)-27(e)]TJ ET q -1 0 0 1 899.912 -37.479 cm +1 0 0 1 899.912 -44.253 cm []0 d 0 J 0.398 w 0 0 m 0 13.549 l S Q q -1 0 0 1 299.826 -51.028 cm +1 0 0 1 299.826 -57.802 cm []0 d 0 J 0.398 w 0 0 m 0 13.549 l S Q BT -/F15 10.9091 Tf 305.803 -46.963 Td [(smaller)-333(than)-334(the)-333(sp)-28(eci\014ed)-333(maxim)28(um)-334(n)28(um)28(b)-28(er)-333(of)-333(lev)27(els.)]TJ +/F15 10.9091 Tf 305.803 -53.738 Td [(smaller)-333(than)-334(the)-333(sp)-28(eci\014ed)-333(maxim)28(um)-334(n)28(um)28(b)-28(er)-333(of)-333(lev)27(els.)]TJ ET q -1 0 0 1 899.912 -51.028 cm +1 0 0 1 899.912 -57.802 cm []0 d 0 J 0.398 w 0 0 m 0 13.549 l S Q q -1 0 0 1 299.826 -51.227 cm +1 0 0 1 299.826 -58.002 cm []0 d 0 J 0.398 w 0 0 m 600.087 0 l S Q 0 g 0 G BT -/F15 10.9091 Tf 459.779 -81.916 Td [(T)83(able)-333(3:)-444(P)27(arameters)-333(de\014ning)-333(the)-334(aggregation)-333(algorithm.)]TJ +/F15 10.9091 Tf 459.779 -88.691 Td [(T)83(able)-333(3:)-444(P)27(arameters)-333(de\014ning)-333(the)-334(aggregation)-333(algorithm.)]TJ 0 g 0 G 0 g 0 G ET @@ -4117,7 +4121,7 @@ Q endstream endobj -528 0 obj +530 0 obj << /Length 6126 >> @@ -4341,7 +4345,7 @@ Q BT /F44 10.9091 Tf 298.603 662.983 Td [(Note.)]TJ/F15 10.9091 Tf 35.053 0 Td [(Di\013eren)28(t)-334(th)1(res)-1(h)1(olds)-334(at)-333(di\013eren)28(t)-334(lev)28(els,)-333(suc)27(h)-333(as)-333(those)-334(used)-333(in)-333([)]TJ 1 0 0 rg 1 0 0 RG - [(25)]TJ + [(26)]TJ 0 g 0 G [(,)-333(Sec)-1(ti)1(on)-334(5.1],)-333(can)-333(b)-28(e)-333(e)-1(asily)-333(set)-333(b)28(y)-334(in)28(v)28(oking)-333(the)-334(rou-)]TJ ET @@ -4378,7 +4382,7 @@ Q endstream endobj -534 0 obj +536 0 obj << /Length 9225 >> @@ -4661,7 +4665,7 @@ Q endstream endobj -538 0 obj +540 0 obj << /Length 4941 >> @@ -4876,266 +4880,12 @@ Q endstream endobj -544 0 obj +435 0 obj << -/Length 7639 ->> -stream -0 g 0 G -0 0 1 rg 0 0 1 RG -BT -/F42 10.9091 Tf 93.6 740.002 Td [(6)]TJ -0 g 0 G - [-378(User)-377(Interf)88(a)23(ce)]TJ/F15 10.9091 Tf 401.542 0 Td [(31)]TJ -0 g 0 G -0 g 0 G -ET -1 0 0 1 299.826 121.521 cm -q -0 1 -1 0 0 0 cm -0 g 0 G -0 g 0 G -0 g 0 G -q -1 0 0 1 3.954 157.513 cm -[]0 d 0 J 0.398 w 0 0 m 585.666 0 l S -Q -q -1 0 0 1 3.954 145.359 cm -[]0 d 0 J 0.398 w 0 0 m 0 11.955 l S -Q -1 0 0 1 -299.826 -121.521 cm -BT -/F45 9.9626 Tf 309.757 270.467 Td [(what)]TJ -ET -q -1 0 0 1 417.782 266.88 cm -[]0 d 0 J 0.398 w 0 0 m 0 11.955 l S -Q -BT -/F42 9.9626 Tf 423.76 270.467 Td [(d)22(a)67(t)66(a)-377(type)]TJ -ET -q -1 0 0 1 513.423 266.88 cm -[]0 d 0 J 0.398 w 0 0 m 0 11.955 l S -Q -BT -/F45 9.9626 Tf 519.401 270.467 Td [(val)]TJ -ET -q -1 0 0 1 579.236 266.88 cm -[]0 d 0 J 0.398 w 0 0 m 0 11.955 l S -Q -BT -/F42 9.9626 Tf 585.214 270.467 Td [(def)89(a)22(ul)67(t)]TJ -ET -q -1 0 0 1 693.239 266.88 cm -[]0 d 0 J 0.398 w 0 0 m 0 11.955 l S -Q -BT -/F42 9.9626 Tf 699.216 270.467 Td [(comments)]TJ -ET -q -1 0 0 1 889.446 266.88 cm -[]0 d 0 J 0.398 w 0 0 m 0 11.955 l S -Q -q -1 0 0 1 303.78 266.681 cm -[]0 d 0 J 0.398 w 0 0 m 585.666 0 l S -Q -q -1 0 0 1 303.78 194.75 cm -[]0 d 0 J 0.398 w 0 0 m 0 71.731 l S -Q -BT -/F45 9.9626 Tf 309.757 258.113 Td [('SMOOTHER_TYPE')]TJ -ET -q -1 0 0 1 417.782 194.75 cm -[]0 d 0 J 0.398 w 0 0 m 0 71.731 l S -Q -BT -/F45 9.9626 Tf 423.76 258.113 Td [(character\050len=*\051)]TJ -ET -q -1 0 0 1 513.423 194.75 cm -[]0 d 0 J 0.398 w 0 0 m 0 71.731 l S -Q -BT -/F45 9.9626 Tf 519.401 258.113 Td [('JACOBI')]TJ 0 -11.955 Td [('GS')]TJ 0 -11.955 Td [('BGS')]TJ 0 -11.956 Td [('BJAC')]TJ 0 -11.955 Td [('AS')]TJ -ET -q -1 0 0 1 579.236 194.75 cm -[]0 d 0 J 0.398 w 0 0 m 0 71.731 l S -Q -BT -/F45 9.9626 Tf 585.214 258.113 Td [('FBGS')]TJ -ET -q -1 0 0 1 693.239 194.75 cm -[]0 d 0 J 0.398 w 0 0 m 0 71.731 l S -Q -BT -/F15 9.9626 Tf 699.216 258.113 Td [(T)28(yp)-28(e)-765(of)-766(smo)-27(other)-766(used)-765(in)-765(the)-765(m)27(ul)1(ti-)]TJ 0 -11.955 Td [(lev)28(el)-419(pr)1(e)-1(cond)1(itioner:)-615(p)-27(oin)27(t-Jacobi,)-439(h)28(ybrid)]TJ 0 -11.955 Td [(\050forw)28(ard\051)-519(Gauss-Seidel,)-566(h)28(ybrid)-519(bac)28(kw)27(ard)]TJ 0 -11.956 Td [(Gauss-Seidel,)-558(blo)-28(c)28(k-Jacobi,)-558(and)-513(Additiv)28(e)]TJ 0 -11.955 Td [(Sc)28(h)28(w)27(arz.)]TJ 0 -11.955 Td [(It)-333(is)-334(ignored)-333(b)28(y)-333(one)-1(-lev)28(el)-333(preconditioners.)]TJ -ET -q -1 0 0 1 889.446 194.75 cm -[]0 d 0 J 0.398 w 0 0 m 0 71.731 l S -Q -q -1 0 0 1 303.78 194.551 cm -[]0 d 0 J 0.398 w 0 0 m 585.666 0 l S -Q -q -1 0 0 1 303.78 86.755 cm -[]0 d 0 J 0.398 w 0 0 m 0 107.597 l S -Q -BT -/F45 9.9626 Tf 309.757 185.983 Td [('SUB_SOLVE')]TJ -ET -q -1 0 0 1 417.782 86.755 cm -[]0 d 0 J 0.398 w 0 0 m 0 107.597 l S -Q -BT -/F45 9.9626 Tf 423.76 185.983 Td [(character\050len=*\051)]TJ -ET -q -1 0 0 1 513.423 86.755 cm -[]0 d 0 J 0.398 w 0 0 m 0 107.597 l S -Q -BT -/F45 9.9626 Tf 519.401 185.983 Td [('JACOBI')]TJ 0 -11.955 Td [('GS')]TJ 0 -11.955 Td [('BGS')]TJ 0 -11.955 Td [('ILU')]TJ 0 -11.955 Td [('ILUT')]TJ 0 -11.956 Td [('MILU')]TJ 0 -11.955 Td [('MUMPS')]TJ 0 -11.955 Td [('SLU')]TJ 0 -11.955 Td [('UMF')]TJ -ET -q -1 0 0 1 579.236 86.755 cm -[]0 d 0 J 0.398 w 0 0 m 0 107.597 l S -Q -BT -/F45 9.9626 Tf 585.214 185.983 Td [(GS)]TJ/F15 9.9626 Tf 13.397 0 Td [(and)]TJ/F45 9.9626 Tf 18.987 0 Td [(BGS)]TJ/F15 9.9626 Tf 18.627 0 Td [(for)-295(pre-)-294(and)]TJ -51.011 -11.955 Td [(p)-28(ost-smo)-28(others)-417(of)-417(m)27(ul-)]TJ 0 -11.955 Td [(tilev)28(el)-677(pr)1(e)-1(cond)1(itioners,)]TJ 0 -11.955 Td [(resp)-28(ectiv)28(ely)]TJ/F45 9.9626 Tf 0 -11.955 Td [(ILU)]TJ/F15 9.9626 Tf 25.851 0 Td [(for)-1020(blo)-28(c)28(k-Jacobi)]TJ -25.851 -11.956 Td [(and)-676(Addi)1(tiv)27(e)-675(Sc)27(h)28(w)28(arz)]TJ 0 -11.955 Td [(one-lev)28(el)-685(precondition-)]TJ 0 -11.955 Td [(ers)]TJ -ET -q -1 0 0 1 693.239 86.755 cm -[]0 d 0 J 0.398 w 0 0 m 0 107.597 l S -Q -BT -/F15 9.9626 Tf 699.216 185.983 Td [(The)-719(lo)-28(cal)-720(solv)28(er)-719(to)-720(b)-28(e)-719(used)-719(with)-720(the)]TJ 0 -11.955 Td [(smo)-28(other)-458(or)-458(one-lev)27(el)-458(preconditioner)-458(\050see)]TJ 0 -11.955 Td [(Remark)-383(2,)-395(page)-383(24\051:)-544(p)-27(oin)27(t-Jacobi,)-395(h)28(ybrid)]TJ 0 -11.955 Td [(\050forw)28(ard\051)-519(Gauss-Seidel,)-566(h)28(ybrid)-519(bac)28(kw)27(ard)]TJ 0 -11.955 Td [(Gauss-Seidel,)-364(ILU\050)]TJ/F22 9.9626 Tf 82.539 0 Td [(p)]TJ/F15 9.9626 Tf 5.012 0 Td [(\051,)-364(ILU\050)]TJ/F22 9.9626 Tf 31.439 0 Td [(p;)-167(t)]TJ/F15 9.9626 Tf 13.037 0 Td [(\051,)-364(MILU\050)]TJ/F22 9.9626 Tf 40.571 0 Td [(p)]TJ/F15 9.9626 Tf 5.013 0 Td [(\051,)]TJ -177.611 -11.956 Td [(LU)-708(from)-709(MUM)1(PS,)-709(Sup)-28(erLU)-708(or)-708(UMF-)]TJ 0 -11.955 Td [(P)83(A)28(CK)-487(\050plus)-486(triangular)-487(solv)28(e\051.)-906(See)-487(Note)]TJ 0 -11.955 Td [(for)-333(details)-334(on)-333(h)28(ybrid)-333(Gauss-Seidel.)]TJ -ET -q -1 0 0 1 889.446 86.755 cm -[]0 d 0 J 0.398 w 0 0 m 0 107.597 l S -Q -q -1 0 0 1 303.78 86.556 cm -[]0 d 0 J 0.398 w 0 0 m 585.666 0 l S -Q -q -1 0 0 1 303.78 26.581 cm -[]0 d 0 J 0.398 w 0 0 m 0 59.776 l S -Q -BT -/F45 9.9626 Tf 309.757 77.988 Td [('SMOOTHER_SWEEPS')]TJ -ET -q -1 0 0 1 417.782 26.581 cm -[]0 d 0 J 0.398 w 0 0 m 0 59.776 l S -Q -BT -/F45 9.9626 Tf 423.76 77.988 Td [(integer)]TJ -ET -q -1 0 0 1 513.423 26.581 cm -[]0 d 0 J 0.398 w 0 0 m 0 59.776 l S -Q -BT -/F15 9.9626 Tf 519.401 77.988 Td [(An)28(y)-333(in)27(teger)]TJ 0 -11.955 Td [(n)28(um)28(b)-28(er)]TJ/F25 9.9626 Tf 36.28 0 Td [(\025)]TJ/F15 9.9626 Tf 10.516 0 Td [(0)]TJ -ET -q -1 0 0 1 579.236 26.581 cm -[]0 d 0 J 0.398 w 0 0 m 0 59.776 l S -Q -BT -/F15 9.9626 Tf 585.214 77.988 Td [(1)]TJ -ET -q -1 0 0 1 693.239 26.581 cm -[]0 d 0 J 0.398 w 0 0 m 0 59.776 l S -Q -BT -/F15 9.9626 Tf 699.216 77.988 Td [(Num)28(b)-28(er)-325(of)-325(sw)28(eeps)-325(of)-325(the)-325(smo)-28(other)-325(or)-325(one-)]TJ 0 -11.955 Td [(lev)28(el)-240(preconditioner.)-413(In)-240(the)-239(m)27(ultilev)28(el)-240(case,)]TJ 0 -11.955 Td [(no)-491(pre-smother)-491(or)-491(p)-28(ost-smo)-28(other)-491(is)-491(used)]TJ 0 -11.955 Td [(if)-375(this)-374(parameter)-375(is)-375(set)-374(to)-375(0)-375(t)1(o)-1(gether)-374(with)]TJ/F45 9.9626 Tf 0 -11.955 Td [(pos='PRE')]TJ/F15 9.9626 Tf 50.394 0 Td [(or)]TJ/F45 9.9626 Tf 12.205 0 Td [(pos='POST)]TJ/F15 9.9626 Tf 47.073 0 Td [(,)-333(resp)-28(ectiv)28(ely)83(.)]TJ -ET -q -1 0 0 1 889.446 26.581 cm -[]0 d 0 J 0.398 w 0 0 m 0 59.776 l S -Q -q -1 0 0 1 303.78 26.382 cm -[]0 d 0 J 0.398 w 0 0 m 585.666 0 l S -Q -q -1 0 0 1 303.78 2.272 cm -[]0 d 0 J 0.398 w 0 0 m 0 23.91 l S -Q -BT -/F45 9.9626 Tf 309.757 17.814 Td [('SUB_OVR')]TJ -ET -q -1 0 0 1 417.782 2.272 cm -[]0 d 0 J 0.398 w 0 0 m 0 23.91 l S -Q -BT -/F45 9.9626 Tf 423.76 17.814 Td [(integer)]TJ -ET -q -1 0 0 1 513.423 2.272 cm -[]0 d 0 J 0.398 w 0 0 m 0 23.91 l S -Q -BT -/F15 9.9626 Tf 519.401 17.814 Td [(An)28(y)-333(in)27(teger)]TJ 0 -11.955 Td [(n)28(um)28(b)-28(er)]TJ/F25 9.9626 Tf 36.28 0 Td [(\025)]TJ/F15 9.9626 Tf 10.516 0 Td [(0)]TJ -ET -q -1 0 0 1 579.236 2.272 cm -[]0 d 0 J 0.398 w 0 0 m 0 23.91 l S -Q -BT -/F15 9.9626 Tf 585.214 17.814 Td [(1)]TJ -ET -q -1 0 0 1 693.239 2.272 cm -[]0 d 0 J 0.398 w 0 0 m 0 23.91 l S -Q -BT -/F15 9.9626 Tf 699.216 17.814 Td [(Num)28(b)-28(er)-647(of)-646(o)28(v)28(e)-1(r)1(lap)-647(la)28(y)28(ers,)-725(for)-647(Additiv)28(e)]TJ 0 -11.955 Td [(Sc)28(h)28(w)27(arz)-333(only)83(.)]TJ -ET -q -1 0 0 1 889.446 2.272 cm -[]0 d 0 J 0.398 w 0 0 m 0 23.91 l S -Q -q -1 0 0 1 303.78 2.073 cm -[]0 d 0 J 0.398 w 0 0 m 585.666 0 l S -Q -0 g 0 G -BT -/F15 10.9091 Tf 382.719 -28.616 Td [(T)83(able)-333(7:)-444(P)27(arameters)-333(de\014ning)-333(the)-334(smo)-27(other)-334(or)-333(the)-333(details)-334(of)-333(the)-333(one-lev)28(e)-1(l)-333(preconditioner.)]TJ -0 g 0 G -0 g 0 G -ET -1 0 0 1 299.826 121.521 cm -Q -0 g 0 G -0 g 0 G -0 g 0 G - -endstream -endobj -435 0 obj -<< -/Type /ObjStm -/N 100 -/First 898 -/Length 12262 +/Type /ObjStm +/N 100 +/First 898 +/Length 12291 >> stream 434 0 422 54 431 111 445 217 428 423 429 569 436 713 437 865 438 1018 439 1165 @@ -5144,10 +4894,10 @@ stream 462 3305 467 3456 67 3510 464 3563 471 3734 468 3876 469 4021 473 4168 71 4222 470 4275 483 4381 481 4571 474 4717 475 4862 476 5007 477 5152 478 5297 479 5444 480 5589 485 5733 75 5787 482 5840 495 5959 486 6149 487 6294 488 6438 489 6585 490 6729 491 6874 492 7018 -493 7163 497 7308 498 7362 499 7415 500 7469 501 7523 494 7577 512 7696 510 7830 514 7976 -511 8030 517 8123 519 8237 423 8291 516 8350 522 8456 520 8598 504 8744 524 8907 525 8961 -521 9018 527 9176 505 9342 506 9492 507 9644 508 9792 509 9942 529 10104 530 10158 526 10215 -533 10360 531 10494 535 10640 503 10694 532 10752 537 10871 539 10985 540 11039 536 11098 543 11230 +493 7163 497 7308 498 7362 499 7415 500 7469 501 7523 494 7577 513 7696 511 7830 515 7976 +512 8030 518 8123 520 8237 423 8291 517 8350 523 8456 521 8606 504 8752 505 8915 525 9067 +526 9121 522 9179 529 9337 506 9503 507 9653 508 9805 509 9953 510 10103 531 10265 532 10319 +528 10378 535 10523 533 10657 537 10803 503 10857 534 10915 539 11034 541 11148 542 11202 538 11261 % 434 0 obj << /D [432 0 R /XYZ 92.6 752.957 null] @@ -5582,16 +5332,16 @@ stream /Font << /F15 160 0 R /F42 161 0 R /F44 205 0 R /F45 255 0 R /F18 307 0 R >> /ProcSet [ /PDF /Text ] >> -% 512 0 obj +% 513 0 obj << /Type /Page -/Contents 513 0 R -/Resources 511 0 R +/Contents 514 0 R +/Resources 512 0 R /MediaBox [0 0 595.276 841.89] -/Parent 515 0 R -/Annots [ 510 0 R ] +/Parent 516 0 R +/Annots [ 511 0 R ] >> -% 510 0 obj +% 511 0 obj << /Type /Annot /Subtype /Link @@ -5599,46 +5349,46 @@ stream /Rect [92.604 739.006 100.627 748.453] /A << /S /GoTo /D (section.6) >> >> -% 514 0 obj +% 515 0 obj << -/D [512 0 R /XYZ 92.6 752.957 null] +/D [513 0 R /XYZ 92.6 752.957 null] >> -% 511 0 obj +% 512 0 obj << /Font << /F42 161 0 R /F15 160 0 R /F18 307 0 R >> /ProcSet [ /PDF /Text ] >> -% 517 0 obj +% 518 0 obj << /Type /Page -/Contents 518 0 R -/Resources 516 0 R +/Contents 519 0 R +/Resources 517 0 R /MediaBox [0 0 595.276 841.89] -/Parent 515 0 R +/Parent 516 0 R >> -% 519 0 obj +% 520 0 obj << -/D [517 0 R /XYZ 85.4 752.957 null] +/D [518 0 R /XYZ 85.4 752.957 null] >> % 423 0 obj << -/D [517 0 R /XYZ -3855.021 590.914 null] +/D [518 0 R /XYZ -3855.021 590.914 null] >> -% 516 0 obj +% 517 0 obj << /Font << /F15 160 0 R /F42 161 0 R /F45 255 0 R /F25 257 0 R >> /ProcSet [ /PDF /Text ] >> -% 522 0 obj +% 523 0 obj << /Type /Page -/Contents 523 0 R -/Resources 521 0 R +/Contents 524 0 R +/Resources 522 0 R /MediaBox [0 0 595.276 841.89] -/Parent 515 0 R -/Annots [ 520 0 R 504 0 R ] +/Parent 516 0 R +/Annots [ 521 0 R 504 0 R 505 0 R ] >> -% 520 0 obj +% 521 0 obj << /Type /Annot /Subtype /Link @@ -5651,32 +5401,40 @@ stream /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[0 1 0] -/Rect [378.191 560.558 387.214 574.456] +/Rect [371.416 585.797 380.439 599.695] /A << /S /GoTo /D (cite.VANEK_MANDEL_BREZINA) >> >> -% 524 0 obj +% 505 0 obj << -/D [522 0 R /XYZ 92.6 752.957 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[0 1 0] +/Rect [384.966 566.316 393.988 580.214] +/A << /S /GoTo /D (cite.GrHeJi:16) >> >> % 525 0 obj << -/D [522 0 R /XYZ 489.714 324.808 null] +/D [523 0 R /XYZ 92.6 752.957 null] >> -% 521 0 obj +% 526 0 obj +<< +/D [523 0 R /XYZ 496.333 4405.505 null] +>> +% 522 0 obj << /Font << /F42 161 0 R /F15 160 0 R /F45 255 0 R /F22 225 0 R /F25 257 0 R /F21 366 0 R /F23 361 0 R /F44 205 0 R >> /ProcSet [ /PDF /Text ] >> -% 527 0 obj +% 529 0 obj << /Type /Page -/Contents 528 0 R -/Resources 526 0 R +/Contents 530 0 R +/Resources 528 0 R /MediaBox [0 0 595.276 841.89] -/Parent 515 0 R -/Annots [ 505 0 R 506 0 R 507 0 R 508 0 R 509 0 R ] +/Parent 516 0 R +/Annots [ 506 0 R 507 0 R 508 0 R 509 0 R 510 0 R ] >> -% 505 0 obj +% 506 0 obj << /Type /Annot /Subtype /Link @@ -5684,7 +5442,7 @@ stream /Rect [305.333 237.711 318.234 246.154] /A << /S /GoTo /D (equation.4.3) >> >> -% 506 0 obj +% 507 0 obj << /Type /Annot /Subtype /Link @@ -5692,7 +5450,7 @@ stream /Rect [305.333 166.335 318.234 183.263] /A << /S /GoTo /D (subsection.4.2) >> >> -% 507 0 obj +% 508 0 obj << /Type /Annot /Subtype /Link @@ -5700,7 +5458,7 @@ stream /Rect [249.4 276.931 263.639 285.374] /A << /S /GoTo /D (equation.4.5) >> >> -% 508 0 obj +% 509 0 obj << /Type /Annot /Subtype /Link @@ -5708,7 +5466,7 @@ stream /Rect [249.4 204.203 263.639 221.132] /A << /S /GoTo /D (subsection.4.2) >> >> -% 509 0 obj +% 510 0 obj << /Type /Annot /Subtype /Link @@ -5716,29 +5474,29 @@ stream /Rect [239.517 367.769 248.54 381.667] /A << /S /GoTo /D (cite.VANEK_MANDEL_BREZINA) >> >> -% 529 0 obj +% 531 0 obj << -/D [527 0 R /XYZ 85.4 752.957 null] +/D [529 0 R /XYZ 85.4 752.957 null] >> -% 530 0 obj +% 532 0 obj << -/D [527 0 R /XYZ 202.833 540.899 null] +/D [529 0 R /XYZ -3875.743 540.899 null] >> -% 526 0 obj +% 528 0 obj << /Font << /F15 160 0 R /F42 161 0 R /F45 255 0 R /F18 307 0 R /F25 257 0 R /F22 225 0 R /F44 205 0 R >> /ProcSet [ /PDF /Text ] >> -% 533 0 obj +% 535 0 obj << /Type /Page -/Contents 534 0 R -/Resources 532 0 R +/Contents 536 0 R +/Resources 534 0 R /MediaBox [0 0 595.276 841.89] -/Parent 515 0 R -/Annots [ 531 0 R ] +/Parent 516 0 R +/Annots [ 533 0 R ] >> -% 531 0 obj +% 533 0 obj << /Type /Annot /Subtype /Link @@ -5746,53 +5504,298 @@ stream /Rect [92.604 739.006 100.627 748.453] /A << /S /GoTo /D (section.6) >> >> -% 535 0 obj +% 537 0 obj << -/D [533 0 R /XYZ 92.6 752.957 null] +/D [535 0 R /XYZ 92.6 752.957 null] >> % 503 0 obj << -/D [533 0 R /XYZ 475.208 4356.566 null] +/D [535 0 R /XYZ 475.206 4356.566 null] >> -% 532 0 obj +% 534 0 obj << /Font << /F42 161 0 R /F15 160 0 R /F45 255 0 R /F22 225 0 R /F44 205 0 R >> /ProcSet [ /PDF /Text ] >> -% 537 0 obj +% 539 0 obj << /Type /Page -/Contents 538 0 R -/Resources 536 0 R +/Contents 540 0 R +/Resources 538 0 R /MediaBox [0 0 595.276 841.89] -/Parent 515 0 R +/Parent 516 0 R >> -% 539 0 obj +% 541 0 obj << -/D [537 0 R /XYZ 85.4 752.957 null] +/D [539 0 R /XYZ 85.4 752.957 null] >> -% 540 0 obj +% 542 0 obj << -/D [537 0 R /XYZ -3834.398 589.839 null] +/D [539 0 R /XYZ -3834.398 589.839 null] >> -% 536 0 obj +% 538 0 obj << /Font << /F15 160 0 R /F42 161 0 R /F45 255 0 R /F22 225 0 R /F25 257 0 R /F18 307 0 R >> /ProcSet [ /PDF /Text ] >> -% 543 0 obj + +endstream +endobj +546 0 obj << -/Type /Page -/Contents 544 0 R -/Resources 542 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 546 0 R -/Annots [ 541 0 R ] +/Length 7639 >> +stream +0 g 0 G +0 0 1 rg 0 0 1 RG +BT +/F42 10.9091 Tf 93.6 740.002 Td [(6)]TJ +0 g 0 G + [-378(User)-377(Interf)88(a)23(ce)]TJ/F15 10.9091 Tf 401.542 0 Td [(31)]TJ +0 g 0 G +0 g 0 G +ET +1 0 0 1 299.826 121.521 cm +q +0 1 -1 0 0 0 cm +0 g 0 G +0 g 0 G +0 g 0 G +q +1 0 0 1 3.954 157.513 cm +[]0 d 0 J 0.398 w 0 0 m 585.666 0 l S +Q +q +1 0 0 1 3.954 145.359 cm +[]0 d 0 J 0.398 w 0 0 m 0 11.955 l S +Q +1 0 0 1 -299.826 -121.521 cm +BT +/F45 9.9626 Tf 309.757 270.467 Td [(what)]TJ +ET +q +1 0 0 1 417.782 266.88 cm +[]0 d 0 J 0.398 w 0 0 m 0 11.955 l S +Q +BT +/F42 9.9626 Tf 423.76 270.467 Td [(d)22(a)67(t)66(a)-377(type)]TJ +ET +q +1 0 0 1 513.423 266.88 cm +[]0 d 0 J 0.398 w 0 0 m 0 11.955 l S +Q +BT +/F45 9.9626 Tf 519.401 270.467 Td [(val)]TJ +ET +q +1 0 0 1 579.236 266.88 cm +[]0 d 0 J 0.398 w 0 0 m 0 11.955 l S +Q +BT +/F42 9.9626 Tf 585.214 270.467 Td [(def)89(a)22(ul)67(t)]TJ +ET +q +1 0 0 1 693.239 266.88 cm +[]0 d 0 J 0.398 w 0 0 m 0 11.955 l S +Q +BT +/F42 9.9626 Tf 699.216 270.467 Td [(comments)]TJ +ET +q +1 0 0 1 889.446 266.88 cm +[]0 d 0 J 0.398 w 0 0 m 0 11.955 l S +Q +q +1 0 0 1 303.78 266.681 cm +[]0 d 0 J 0.398 w 0 0 m 585.666 0 l S +Q +q +1 0 0 1 303.78 194.75 cm +[]0 d 0 J 0.398 w 0 0 m 0 71.731 l S +Q +BT +/F45 9.9626 Tf 309.757 258.113 Td [('SMOOTHER_TYPE')]TJ +ET +q +1 0 0 1 417.782 194.75 cm +[]0 d 0 J 0.398 w 0 0 m 0 71.731 l S +Q +BT +/F45 9.9626 Tf 423.76 258.113 Td [(character\050len=*\051)]TJ +ET +q +1 0 0 1 513.423 194.75 cm +[]0 d 0 J 0.398 w 0 0 m 0 71.731 l S +Q +BT +/F45 9.9626 Tf 519.401 258.113 Td [('JACOBI')]TJ 0 -11.955 Td [('GS')]TJ 0 -11.955 Td [('BGS')]TJ 0 -11.956 Td [('BJAC')]TJ 0 -11.955 Td [('AS')]TJ +ET +q +1 0 0 1 579.236 194.75 cm +[]0 d 0 J 0.398 w 0 0 m 0 71.731 l S +Q +BT +/F45 9.9626 Tf 585.214 258.113 Td [('FBGS')]TJ +ET +q +1 0 0 1 693.239 194.75 cm +[]0 d 0 J 0.398 w 0 0 m 0 71.731 l S +Q +BT +/F15 9.9626 Tf 699.216 258.113 Td [(T)28(yp)-28(e)-765(of)-766(smo)-27(other)-766(used)-765(in)-765(the)-765(m)27(ul)1(ti-)]TJ 0 -11.955 Td [(lev)28(el)-419(pr)1(e)-1(cond)1(itioner:)-615(p)-27(oin)27(t-Jacobi,)-439(h)28(ybrid)]TJ 0 -11.955 Td [(\050forw)28(ard\051)-519(Gauss-Seidel,)-566(h)28(ybrid)-519(bac)28(kw)27(ard)]TJ 0 -11.956 Td [(Gauss-Seidel,)-558(blo)-28(c)28(k-Jacobi,)-558(and)-513(Additiv)28(e)]TJ 0 -11.955 Td [(Sc)28(h)28(w)27(arz.)]TJ 0 -11.955 Td [(It)-333(is)-334(ignored)-333(b)28(y)-333(one)-1(-lev)28(el)-333(preconditioners.)]TJ +ET +q +1 0 0 1 889.446 194.75 cm +[]0 d 0 J 0.398 w 0 0 m 0 71.731 l S +Q +q +1 0 0 1 303.78 194.551 cm +[]0 d 0 J 0.398 w 0 0 m 585.666 0 l S +Q +q +1 0 0 1 303.78 86.755 cm +[]0 d 0 J 0.398 w 0 0 m 0 107.597 l S +Q +BT +/F45 9.9626 Tf 309.757 185.983 Td [('SUB_SOLVE')]TJ +ET +q +1 0 0 1 417.782 86.755 cm +[]0 d 0 J 0.398 w 0 0 m 0 107.597 l S +Q +BT +/F45 9.9626 Tf 423.76 185.983 Td [(character\050len=*\051)]TJ +ET +q +1 0 0 1 513.423 86.755 cm +[]0 d 0 J 0.398 w 0 0 m 0 107.597 l S +Q +BT +/F45 9.9626 Tf 519.401 185.983 Td [('JACOBI')]TJ 0 -11.955 Td [('GS')]TJ 0 -11.955 Td [('BGS')]TJ 0 -11.955 Td [('ILU')]TJ 0 -11.955 Td [('ILUT')]TJ 0 -11.956 Td [('MILU')]TJ 0 -11.955 Td [('MUMPS')]TJ 0 -11.955 Td [('SLU')]TJ 0 -11.955 Td [('UMF')]TJ +ET +q +1 0 0 1 579.236 86.755 cm +[]0 d 0 J 0.398 w 0 0 m 0 107.597 l S +Q +BT +/F45 9.9626 Tf 585.214 185.983 Td [(GS)]TJ/F15 9.9626 Tf 13.397 0 Td [(and)]TJ/F45 9.9626 Tf 18.987 0 Td [(BGS)]TJ/F15 9.9626 Tf 18.627 0 Td [(for)-295(pre-)-294(and)]TJ -51.011 -11.955 Td [(p)-28(ost-smo)-28(others)-417(of)-417(m)27(ul-)]TJ 0 -11.955 Td [(tilev)28(el)-677(pr)1(e)-1(cond)1(itioners,)]TJ 0 -11.955 Td [(resp)-28(ectiv)28(ely)]TJ/F45 9.9626 Tf 0 -11.955 Td [(ILU)]TJ/F15 9.9626 Tf 25.851 0 Td [(for)-1020(blo)-28(c)28(k-Jacobi)]TJ -25.851 -11.956 Td [(and)-676(Addi)1(tiv)27(e)-675(Sc)27(h)28(w)28(arz)]TJ 0 -11.955 Td [(one-lev)28(el)-685(precondition-)]TJ 0 -11.955 Td [(ers)]TJ +ET +q +1 0 0 1 693.239 86.755 cm +[]0 d 0 J 0.398 w 0 0 m 0 107.597 l S +Q +BT +/F15 9.9626 Tf 699.216 185.983 Td [(The)-719(lo)-28(cal)-720(solv)28(er)-719(to)-720(b)-28(e)-719(used)-719(with)-720(the)]TJ 0 -11.955 Td [(smo)-28(other)-458(or)-458(one-lev)27(el)-458(preconditioner)-458(\050see)]TJ 0 -11.955 Td [(Remark)-383(2,)-395(page)-383(24\051:)-544(p)-27(oin)27(t-Jacobi,)-395(h)28(ybrid)]TJ 0 -11.955 Td [(\050forw)28(ard\051)-519(Gauss-Seidel,)-566(h)28(ybrid)-519(bac)28(kw)27(ard)]TJ 0 -11.955 Td [(Gauss-Seidel,)-364(ILU\050)]TJ/F22 9.9626 Tf 82.539 0 Td [(p)]TJ/F15 9.9626 Tf 5.012 0 Td [(\051,)-364(ILU\050)]TJ/F22 9.9626 Tf 31.439 0 Td [(p;)-167(t)]TJ/F15 9.9626 Tf 13.037 0 Td [(\051,)-364(MILU\050)]TJ/F22 9.9626 Tf 40.571 0 Td [(p)]TJ/F15 9.9626 Tf 5.013 0 Td [(\051,)]TJ -177.611 -11.956 Td [(LU)-708(from)-709(MUM)1(PS,)-709(Sup)-28(erLU)-708(or)-708(UMF-)]TJ 0 -11.955 Td [(P)83(A)28(CK)-487(\050plus)-486(triangular)-487(solv)28(e\051.)-906(See)-487(Note)]TJ 0 -11.955 Td [(for)-333(details)-334(on)-333(h)28(ybrid)-333(Gauss-Seidel.)]TJ +ET +q +1 0 0 1 889.446 86.755 cm +[]0 d 0 J 0.398 w 0 0 m 0 107.597 l S +Q +q +1 0 0 1 303.78 86.556 cm +[]0 d 0 J 0.398 w 0 0 m 585.666 0 l S +Q +q +1 0 0 1 303.78 26.581 cm +[]0 d 0 J 0.398 w 0 0 m 0 59.776 l S +Q +BT +/F45 9.9626 Tf 309.757 77.988 Td [('SMOOTHER_SWEEPS')]TJ +ET +q +1 0 0 1 417.782 26.581 cm +[]0 d 0 J 0.398 w 0 0 m 0 59.776 l S +Q +BT +/F45 9.9626 Tf 423.76 77.988 Td [(integer)]TJ +ET +q +1 0 0 1 513.423 26.581 cm +[]0 d 0 J 0.398 w 0 0 m 0 59.776 l S +Q +BT +/F15 9.9626 Tf 519.401 77.988 Td [(An)28(y)-333(in)27(teger)]TJ 0 -11.955 Td [(n)28(um)28(b)-28(er)]TJ/F25 9.9626 Tf 36.28 0 Td [(\025)]TJ/F15 9.9626 Tf 10.516 0 Td [(0)]TJ +ET +q +1 0 0 1 579.236 26.581 cm +[]0 d 0 J 0.398 w 0 0 m 0 59.776 l S +Q +BT +/F15 9.9626 Tf 585.214 77.988 Td [(1)]TJ +ET +q +1 0 0 1 693.239 26.581 cm +[]0 d 0 J 0.398 w 0 0 m 0 59.776 l S +Q +BT +/F15 9.9626 Tf 699.216 77.988 Td [(Num)28(b)-28(er)-325(of)-325(sw)28(eeps)-325(of)-325(the)-325(smo)-28(other)-325(or)-325(one-)]TJ 0 -11.955 Td [(lev)28(el)-240(preconditioner.)-413(In)-240(the)-239(m)27(ultilev)28(el)-240(case,)]TJ 0 -11.955 Td [(no)-491(pre-smother)-491(or)-491(p)-28(ost-smo)-28(other)-491(is)-491(used)]TJ 0 -11.955 Td [(if)-375(this)-374(parameter)-375(is)-375(set)-374(to)-375(0)-375(t)1(o)-1(gether)-374(with)]TJ/F45 9.9626 Tf 0 -11.955 Td [(pos='PRE')]TJ/F15 9.9626 Tf 50.394 0 Td [(or)]TJ/F45 9.9626 Tf 12.205 0 Td [(pos='POST)]TJ/F15 9.9626 Tf 47.073 0 Td [(,)-333(resp)-28(ectiv)28(ely)83(.)]TJ +ET +q +1 0 0 1 889.446 26.581 cm +[]0 d 0 J 0.398 w 0 0 m 0 59.776 l S +Q +q +1 0 0 1 303.78 26.382 cm +[]0 d 0 J 0.398 w 0 0 m 585.666 0 l S +Q +q +1 0 0 1 303.78 2.272 cm +[]0 d 0 J 0.398 w 0 0 m 0 23.91 l S +Q +BT +/F45 9.9626 Tf 309.757 17.814 Td [('SUB_OVR')]TJ +ET +q +1 0 0 1 417.782 2.272 cm +[]0 d 0 J 0.398 w 0 0 m 0 23.91 l S +Q +BT +/F45 9.9626 Tf 423.76 17.814 Td [(integer)]TJ +ET +q +1 0 0 1 513.423 2.272 cm +[]0 d 0 J 0.398 w 0 0 m 0 23.91 l S +Q +BT +/F15 9.9626 Tf 519.401 17.814 Td [(An)28(y)-333(in)27(teger)]TJ 0 -11.955 Td [(n)28(um)28(b)-28(er)]TJ/F25 9.9626 Tf 36.28 0 Td [(\025)]TJ/F15 9.9626 Tf 10.516 0 Td [(0)]TJ +ET +q +1 0 0 1 579.236 2.272 cm +[]0 d 0 J 0.398 w 0 0 m 0 23.91 l S +Q +BT +/F15 9.9626 Tf 585.214 17.814 Td [(1)]TJ +ET +q +1 0 0 1 693.239 2.272 cm +[]0 d 0 J 0.398 w 0 0 m 0 23.91 l S +Q +BT +/F15 9.9626 Tf 699.216 17.814 Td [(Num)28(b)-28(er)-647(of)-646(o)28(v)28(e)-1(r)1(lap)-647(la)28(y)28(ers,)-725(for)-647(Additiv)28(e)]TJ 0 -11.955 Td [(Sc)28(h)28(w)27(arz)-333(only)83(.)]TJ +ET +q +1 0 0 1 889.446 2.272 cm +[]0 d 0 J 0.398 w 0 0 m 0 23.91 l S +Q +q +1 0 0 1 303.78 2.073 cm +[]0 d 0 J 0.398 w 0 0 m 585.666 0 l S +Q +0 g 0 G +BT +/F15 10.9091 Tf 382.719 -28.616 Td [(T)83(able)-333(7:)-444(P)27(arameters)-333(de\014ning)-333(the)-334(smo)-27(other)-334(or)-333(the)-333(details)-334(of)-333(the)-333(one-lev)28(e)-1(l)-333(preconditioner.)]TJ +0 g 0 G +0 g 0 G +ET +1 0 0 1 299.826 121.521 cm +Q +0 g 0 G +0 g 0 G +0 g 0 G endstream endobj -550 0 obj +552 0 obj << /Length 6856 >> @@ -6050,7 +6053,7 @@ Q endstream endobj -558 0 obj +560 0 obj << /Length 2792 >> @@ -6091,7 +6094,7 @@ ET endstream endobj -567 0 obj +569 0 obj << /Length 4654 >> @@ -6137,7 +6140,7 @@ ET endstream endobj -578 0 obj +580 0 obj << /Length 5532 >> @@ -6186,7 +6189,7 @@ ET endstream endobj -583 0 obj +585 0 obj << /Length 8543 >> @@ -6254,7 +6257,7 @@ ET endstream endobj -589 0 obj +591 0 obj << /Length 1284 >> @@ -6283,7 +6286,7 @@ ET endstream endobj -597 0 obj +599 0 obj << /Length 3993 >> @@ -6323,7 +6326,7 @@ ET endstream endobj -604 0 obj +606 0 obj << /Length 5175 >> @@ -6373,7 +6376,7 @@ ET endstream endobj -609 0 obj +611 0 obj << /Length 658 >> @@ -6393,7 +6396,7 @@ ET endstream endobj -616 0 obj +618 0 obj << /Length 7499 >> @@ -6438,7 +6441,7 @@ ET endstream endobj -620 0 obj +622 0 obj << /Length 1207 >> @@ -6456,7 +6459,7 @@ ET endstream endobj -626 0 obj +628 0 obj << /Length 1780 >> @@ -6479,7 +6482,7 @@ ET endstream endobj -631 0 obj +633 0 obj << /Length 3978 >> @@ -6498,7 +6501,7 @@ ET endstream endobj -635 0 obj +637 0 obj << /Length 6503 >> @@ -6558,25 +6561,34 @@ ET endstream endobj -547 0 obj +548 0 obj << /Type /ObjStm /N 100 /First 892 -/Length 11495 +/Length 11574 >> stream -541 0 545 146 502 200 542 258 549 377 551 491 424 545 548 604 557 736 555 894 -552 1040 553 1194 554 1348 559 1495 79 1549 556 1602 566 1721 560 1887 561 2039 562 2192 -563 2346 564 2493 568 2646 83 2700 565 2753 577 2872 575 3054 569 3200 570 3351 571 3503 -572 3657 573 3811 574 3958 579 4112 87 4166 576 4219 582 4338 580 4472 584 4619 91 4673 -581 4726 588 4897 586 5039 585 5185 590 5331 95 5385 587 5438 596 5544 592 5694 593 5841 -594 5988 598 6141 99 6195 103 6248 107 6302 111 6356 595 6410 603 6542 601 6692 599 6838 -600 6985 605 7132 115 7186 119 7240 123 7294 602 7348 608 7480 606 7614 610 7761 607 7815 -615 7921 613 8071 611 8217 612 8369 617 8521 127 8575 614 8629 619 8761 621 8875 618 8929 -625 9022 623 9164 622 9310 627 9464 131 9518 624 9572 630 9678 632 9792 135 9846 629 9900 -634 10006 636 10120 139 10174 300 10228 231 10282 227 10335 347 10387 348 10441 403 10495 349 10549 -% 541 0 obj +545 0 543 134 547 280 502 334 544 391 551 510 553 624 424 678 550 737 559 869 +557 1027 554 1173 555 1327 556 1481 561 1628 79 1682 558 1735 568 1854 562 2020 563 2172 +564 2325 565 2479 566 2626 570 2779 83 2833 567 2886 579 3005 577 3187 571 3333 572 3484 +573 3636 574 3790 575 3944 576 4091 581 4245 87 4299 578 4352 584 4471 582 4605 586 4752 +91 4806 583 4859 590 5030 588 5172 587 5318 592 5464 95 5518 589 5571 598 5677 594 5827 +595 5974 596 6121 600 6274 99 6328 103 6381 107 6435 111 6489 597 6543 605 6675 603 6825 +601 6971 602 7118 607 7265 115 7319 119 7373 123 7427 604 7481 610 7613 608 7747 612 7894 +609 7948 617 8054 615 8204 613 8350 614 8502 619 8654 127 8708 616 8762 621 8894 623 9008 +620 9062 627 9155 625 9297 624 9443 629 9597 131 9651 626 9705 632 9811 634 9925 135 9979 +631 10033 636 10139 638 10253 139 10307 300 10361 231 10415 227 10468 347 10520 348 10574 403 10628 +% 545 0 obj +<< +/Type /Page +/Contents 546 0 R +/Resources 544 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 549 0 R +/Annots [ 543 0 R ] +>> +% 543 0 obj << /Type /Annot /Subtype /Link @@ -6584,50 +6596,50 @@ stream /Rect [92.604 739.006 100.627 748.453] /A << /S /GoTo /D (section.6) >> >> -% 545 0 obj +% 547 0 obj << -/D [543 0 R /XYZ 92.6 752.957 null] +/D [545 0 R /XYZ 92.6 752.957 null] >> % 502 0 obj << -/D [543 0 R /XYZ 435.989 4328.445 null] +/D [545 0 R /XYZ 436.309 248.064 null] >> -% 542 0 obj +% 544 0 obj << /Font << /F42 161 0 R /F15 160 0 R /F45 255 0 R /F22 225 0 R /F25 257 0 R >> /ProcSet [ /PDF /Text ] >> -% 549 0 obj +% 551 0 obj << /Type /Page -/Contents 550 0 R -/Resources 548 0 R +/Contents 552 0 R +/Resources 550 0 R /MediaBox [0 0 595.276 841.89] -/Parent 546 0 R +/Parent 549 0 R >> -% 551 0 obj +% 553 0 obj << -/D [549 0 R /XYZ 85.4 752.957 null] +/D [551 0 R /XYZ 85.4 752.957 null] >> % 424 0 obj << -/D [549 0 R /XYZ -3888.794 615.536 null] +/D [551 0 R /XYZ -3888.794 615.536 null] >> -% 548 0 obj +% 550 0 obj << /Font << /F15 160 0 R /F42 161 0 R /F45 255 0 R /F25 257 0 R /F22 225 0 R /F18 307 0 R >> /ProcSet [ /PDF /Text ] >> -% 557 0 obj +% 559 0 obj << /Type /Page -/Contents 558 0 R -/Resources 556 0 R +/Contents 560 0 R +/Resources 558 0 R /MediaBox [0 0 595.276 841.89] -/Parent 546 0 R -/Annots [ 555 0 R 552 0 R 553 0 R 554 0 R ] +/Parent 549 0 R +/Annots [ 557 0 R 554 0 R 555 0 R 556 0 R ] >> -% 555 0 obj +% 557 0 obj << /Type /Annot /Subtype /Link @@ -6635,7 +6647,7 @@ stream /Rect [92.604 739.006 100.627 748.453] /A << /S /GoTo /D (section.6) >> >> -% 552 0 obj +% 554 0 obj << /Type /Annot /Subtype /Link @@ -6643,7 +6655,7 @@ stream /Rect [364.686 526.079 377.588 535.102] /A << /S /GoTo /D (cite.PSBLASGUIDE) >> >> -% 553 0 obj +% 555 0 obj << /Type /Annot /Subtype /Link @@ -6651,7 +6663,7 @@ stream /Rect [199.125 485.431 212.027 494.454] /A << /S /GoTo /D (cite.PSBLASGUIDE) >> >> -% 554 0 obj +% 556 0 obj << /Type /Annot /Subtype /Link @@ -6659,29 +6671,29 @@ stream /Rect [402.247 454.268 409.694 467.901] /A << /S /GoTo /D (section.8) >> >> -% 559 0 obj +% 561 0 obj << -/D [557 0 R /XYZ 92.6 752.957 null] +/D [559 0 R /XYZ 92.6 752.957 null] >> % 79 0 obj << -/D [557 0 R /XYZ 93.6 715.095 null] +/D [559 0 R /XYZ 93.6 715.095 null] >> -% 556 0 obj +% 558 0 obj << /Font << /F42 161 0 R /F15 160 0 R /F17 148 0 R /F45 255 0 R /F18 307 0 R >> /ProcSet [ /PDF /Text ] >> -% 566 0 obj +% 568 0 obj << /Type /Page -/Contents 567 0 R -/Resources 565 0 R +/Contents 569 0 R +/Resources 567 0 R /MediaBox [0 0 595.276 841.89] -/Parent 546 0 R -/Annots [ 560 0 R 561 0 R 562 0 R 563 0 R 564 0 R ] +/Parent 549 0 R +/Annots [ 562 0 R 563 0 R 564 0 R 565 0 R 566 0 R ] >> -% 560 0 obj +% 562 0 obj << /Type /Annot /Subtype /Link @@ -6689,7 +6701,7 @@ stream /Rect [235.009 613.666 250.941 626.568] /A << /S /GoTo /D (subsection.6.3) >> >> -% 561 0 obj +% 563 0 obj << /Type /Annot /Subtype /Link @@ -6697,7 +6709,7 @@ stream /Rect [357.486 512.53 370.387 521.553] /A << /S /GoTo /D (cite.PSBLASGUIDE) >> >> -% 562 0 obj +% 564 0 obj << /Type /Annot /Subtype /Link @@ -6705,7 +6717,7 @@ stream /Rect [191.925 471.882 204.826 480.905] /A << /S /GoTo /D (cite.PSBLASGUIDE) >> >> -% 563 0 obj +% 565 0 obj << /Type /Annot /Subtype /Link @@ -6713,7 +6725,7 @@ stream /Rect [395.046 440.719 402.493 454.352] /A << /S /GoTo /D (section.8) >> >> -% 564 0 obj +% 566 0 obj << /Type /Annot /Subtype /Link @@ -6721,29 +6733,29 @@ stream /Rect [338.092 390.587 350.993 399.61] /A << /S /GoTo /D (cite.PSBLASGUIDE) >> >> -% 568 0 obj +% 570 0 obj << -/D [566 0 R /XYZ 85.4 752.957 null] +/D [568 0 R /XYZ 85.4 752.957 null] >> % 83 0 obj << -/D [566 0 R /XYZ 86.4 715.095 null] +/D [568 0 R /XYZ 86.4 715.095 null] >> -% 565 0 obj +% 567 0 obj << /Font << /F15 160 0 R /F42 161 0 R /F17 148 0 R /F45 255 0 R /F18 307 0 R >> /ProcSet [ /PDF /Text ] >> -% 577 0 obj +% 579 0 obj << /Type /Page -/Contents 578 0 R -/Resources 576 0 R +/Contents 580 0 R +/Resources 578 0 R /MediaBox [0 0 595.276 841.89] -/Parent 546 0 R -/Annots [ 575 0 R 569 0 R 570 0 R 571 0 R 572 0 R 573 0 R 574 0 R ] +/Parent 549 0 R +/Annots [ 577 0 R 571 0 R 572 0 R 573 0 R 574 0 R 575 0 R 576 0 R ] >> -% 575 0 obj +% 577 0 obj << /Type /Annot /Subtype /Link @@ -6751,7 +6763,7 @@ stream /Rect [92.604 739.006 100.627 748.453] /A << /S /GoTo /D (section.6) >> >> -% 569 0 obj +% 571 0 obj << /Type /Annot /Subtype /Link @@ -6759,7 +6771,7 @@ stream /Rect [334.588 640.765 350.52 653.666] /A << /S /GoTo /D (subsection.6.3) >> >> -% 570 0 obj +% 572 0 obj << /Type /Annot /Subtype /Link @@ -6767,7 +6779,7 @@ stream /Rect [374.629 640.765 390.561 653.666] /A << /S /GoTo /D (subsection.6.4) >> >> -% 571 0 obj +% 573 0 obj << /Type /Annot /Subtype /Link @@ -6775,7 +6787,7 @@ stream /Rect [364.686 485.431 377.588 494.454] /A << /S /GoTo /D (cite.PSBLASGUIDE) >> >> -% 572 0 obj +% 574 0 obj << /Type /Annot /Subtype /Link @@ -6783,7 +6795,7 @@ stream /Rect [199.125 444.784 212.027 453.807] /A << /S /GoTo /D (cite.PSBLASGUIDE) >> >> -% 573 0 obj +% 575 0 obj << /Type /Annot /Subtype /Link @@ -6791,7 +6803,7 @@ stream /Rect [402.247 413.621 409.694 427.254] /A << /S /GoTo /D (section.8) >> >> -% 574 0 obj +% 576 0 obj << /Type /Annot /Subtype /Link @@ -6799,29 +6811,29 @@ stream /Rect [345.292 363.489 358.194 372.511] /A << /S /GoTo /D (cite.PSBLASGUIDE) >> >> -% 579 0 obj +% 581 0 obj << -/D [577 0 R /XYZ 92.6 752.957 null] +/D [579 0 R /XYZ 92.6 752.957 null] >> % 87 0 obj << -/D [577 0 R /XYZ 93.6 715.095 null] +/D [579 0 R /XYZ 93.6 715.095 null] >> -% 576 0 obj +% 578 0 obj << /Font << /F42 161 0 R /F15 160 0 R /F17 148 0 R /F45 255 0 R /F18 307 0 R >> /ProcSet [ /PDF /Text ] >> -% 582 0 obj +% 584 0 obj << /Type /Page -/Contents 583 0 R -/Resources 581 0 R +/Contents 585 0 R +/Resources 583 0 R /MediaBox [0 0 595.276 841.89] -/Parent 546 0 R -/Annots [ 580 0 R ] +/Parent 549 0 R +/Annots [ 582 0 R ] >> -% 580 0 obj +% 582 0 obj << /Type /Annot /Subtype /Link @@ -6829,29 +6841,29 @@ stream /Rect [395.046 386.522 402.493 400.155] /A << /S /GoTo /D (section.8) >> >> -% 584 0 obj +% 586 0 obj << -/D [582 0 R /XYZ 85.4 752.957 null] +/D [584 0 R /XYZ 85.4 752.957 null] >> % 91 0 obj << -/D [582 0 R /XYZ 86.4 715.095 null] +/D [584 0 R /XYZ 86.4 715.095 null] >> -% 581 0 obj +% 583 0 obj << /Font << /F15 160 0 R /F42 161 0 R /F17 148 0 R /F45 255 0 R /F22 225 0 R /F26 363 0 R /F20 364 0 R /F18 307 0 R /F23 361 0 R >> /ProcSet [ /PDF /Text ] >> -% 588 0 obj +% 590 0 obj << /Type /Page -/Contents 589 0 R -/Resources 587 0 R +/Contents 591 0 R +/Resources 589 0 R /MediaBox [0 0 595.276 841.89] -/Parent 591 0 R -/Annots [ 586 0 R 585 0 R ] +/Parent 593 0 R +/Annots [ 588 0 R 587 0 R ] >> -% 586 0 obj +% 588 0 obj << /Type /Annot /Subtype /Link @@ -6859,7 +6871,7 @@ stream /Rect [92.604 739.006 100.627 748.453] /A << /S /GoTo /D (section.6) >> >> -% 585 0 obj +% 587 0 obj << /Type /Annot /Subtype /Link @@ -6867,29 +6879,29 @@ stream /Rect [399.894 589.76 407.341 603.393] /A << /S /GoTo /D (section.8) >> >> -% 590 0 obj +% 592 0 obj << -/D [588 0 R /XYZ 92.6 752.957 null] +/D [590 0 R /XYZ 92.6 752.957 null] >> % 95 0 obj << -/D [588 0 R /XYZ 93.6 715.095 null] +/D [590 0 R /XYZ 93.6 715.095 null] >> -% 587 0 obj +% 589 0 obj << /Font << /F42 161 0 R /F15 160 0 R /F17 148 0 R /F45 255 0 R >> /ProcSet [ /PDF /Text ] >> -% 596 0 obj +% 598 0 obj << /Type /Page -/Contents 597 0 R -/Resources 595 0 R +/Contents 599 0 R +/Resources 597 0 R /MediaBox [0 0 595.276 841.89] -/Parent 591 0 R -/Annots [ 592 0 R 593 0 R 594 0 R ] +/Parent 593 0 R +/Annots [ 594 0 R 595 0 R 596 0 R ] >> -% 592 0 obj +% 594 0 obj << /Type /Annot /Subtype /Link @@ -6897,7 +6909,7 @@ stream /Rect [395.046 559.996 402.493 573.629] /A << /S /GoTo /D (section.8) >> >> -% 593 0 obj +% 595 0 obj << /Type /Annot /Subtype /Link @@ -6905,7 +6917,7 @@ stream /Rect [395.046 223.562 402.493 237.195] /A << /S /GoTo /D (section.8) >> >> -% 594 0 obj +% 596 0 obj << /Type /Annot /Subtype /Link @@ -6913,41 +6925,41 @@ stream /Rect [338.092 173.43 350.993 182.453] /A << /S /GoTo /D (cite.PSBLASGUIDE) >> >> -% 598 0 obj +% 600 0 obj << -/D [596 0 R /XYZ 85.4 752.957 null] +/D [598 0 R /XYZ 85.4 752.957 null] >> % 99 0 obj << -/D [596 0 R /XYZ 86.4 715.095 null] +/D [598 0 R /XYZ 86.4 715.095 null] >> % 103 0 obj << -/D [596 0 R /XYZ 86.4 431.215 null] +/D [598 0 R /XYZ 86.4 431.215 null] >> % 107 0 obj << -/D [596 0 R /XYZ 86.4 365.879 null] +/D [598 0 R /XYZ 86.4 365.879 null] >> % 111 0 obj << -/D [596 0 R /XYZ 86.4 153.691 null] +/D [598 0 R /XYZ 86.4 153.691 null] >> -% 595 0 obj +% 597 0 obj << /Font << /F15 160 0 R /F42 161 0 R /F17 148 0 R /F45 255 0 R /F44 205 0 R /F18 307 0 R >> /ProcSet [ /PDF /Text ] >> -% 603 0 obj +% 605 0 obj << /Type /Page -/Contents 604 0 R -/Resources 602 0 R +/Contents 606 0 R +/Resources 604 0 R /MediaBox [0 0 595.276 841.89] -/Parent 591 0 R -/Annots [ 601 0 R 599 0 R 600 0 R ] +/Parent 593 0 R +/Annots [ 603 0 R 601 0 R 602 0 R ] >> -% 601 0 obj +% 603 0 obj << /Type /Annot /Subtype /Link @@ -6955,7 +6967,7 @@ stream /Rect [92.604 739.006 100.627 748.453] /A << /S /GoTo /D (section.6) >> >> -% 599 0 obj +% 601 0 obj << /Type /Annot /Subtype /Link @@ -6963,7 +6975,7 @@ stream /Rect [402.247 579.493 409.694 593.126] /A << /S /GoTo /D (section.8) >> >> -% 600 0 obj +% 602 0 obj << /Type /Annot /Subtype /Link @@ -6971,37 +6983,37 @@ stream /Rect [402.247 212.842 409.694 226.475] /A << /S /GoTo /D (section.8) >> >> -% 605 0 obj +% 607 0 obj << -/D [603 0 R /XYZ 92.6 752.957 null] +/D [605 0 R /XYZ 92.6 752.957 null] >> % 115 0 obj << -/D [603 0 R /XYZ 93.6 561.815 null] +/D [605 0 R /XYZ 93.6 561.815 null] >> % 119 0 obj << -/D [603 0 R /XYZ 93.6 481.328 null] +/D [605 0 R /XYZ 93.6 481.328 null] >> % 123 0 obj << -/D [603 0 R /XYZ 93.6 154.517 null] +/D [605 0 R /XYZ 93.6 154.517 null] >> -% 602 0 obj +% 604 0 obj << /Font << /F42 161 0 R /F15 160 0 R /F17 148 0 R /F45 255 0 R /F18 307 0 R /F44 205 0 R >> /ProcSet [ /PDF /Text ] >> -% 608 0 obj +% 610 0 obj << /Type /Page -/Contents 609 0 R -/Resources 607 0 R +/Contents 611 0 R +/Resources 609 0 R /MediaBox [0 0 595.276 841.89] -/Parent 591 0 R -/Annots [ 606 0 R ] +/Parent 593 0 R +/Annots [ 608 0 R ] >> -% 606 0 obj +% 608 0 obj << /Type /Annot /Subtype /Link @@ -7009,25 +7021,25 @@ stream /Rect [395.046 635.859 402.493 649.492] /A << /S /GoTo /D (section.8) >> >> -% 610 0 obj +% 612 0 obj << -/D [608 0 R /XYZ 85.4 752.957 null] +/D [610 0 R /XYZ 85.4 752.957 null] >> -% 607 0 obj +% 609 0 obj << /Font << /F15 160 0 R /F42 161 0 R /F17 148 0 R /F45 255 0 R >> /ProcSet [ /PDF /Text ] >> -% 615 0 obj +% 617 0 obj << /Type /Page -/Contents 616 0 R -/Resources 614 0 R +/Contents 618 0 R +/Resources 616 0 R /MediaBox [0 0 595.276 841.89] -/Parent 591 0 R -/Annots [ 613 0 R 611 0 R 612 0 R ] +/Parent 593 0 R +/Annots [ 615 0 R 613 0 R 614 0 R ] >> -% 613 0 obj +% 615 0 obj << /Type /Annot /Subtype /Link @@ -7035,7 +7047,7 @@ stream /Rect [92.604 739.006 100.627 748.453] /A << /S /GoTo /D (section.6) >> >> -% 611 0 obj +% 613 0 obj << /Type /Annot /Subtype /Link @@ -7043,7 +7055,7 @@ stream /Rect [334.005 662.511 349.937 675.413] /A << /S /GoTo /D (subsection.6.2) >> >> -% 612 0 obj +% 614 0 obj << /Type /Annot /Subtype /Link @@ -7051,46 +7063,46 @@ stream /Rect [394.361 145.502 410.293 157.191] /A << /S /GoTo /D (subsection.6.2) >> >> -% 617 0 obj +% 619 0 obj << -/D [615 0 R /XYZ 92.6 752.957 null] +/D [617 0 R /XYZ 92.6 752.957 null] >> % 127 0 obj << -/D [615 0 R /XYZ 93.6 715.095 null] +/D [617 0 R /XYZ 93.6 715.095 null] >> -% 614 0 obj +% 616 0 obj << /Font << /F42 161 0 R /F15 160 0 R /F17 148 0 R /F25 257 0 R /F45 255 0 R /F18 307 0 R >> /ProcSet [ /PDF /Text ] >> -% 619 0 obj +% 621 0 obj << /Type /Page -/Contents 620 0 R -/Resources 618 0 R +/Contents 622 0 R +/Resources 620 0 R /MediaBox [0 0 595.276 841.89] -/Parent 591 0 R +/Parent 593 0 R >> -% 621 0 obj +% 623 0 obj << -/D [619 0 R /XYZ 85.4 752.957 null] +/D [621 0 R /XYZ 85.4 752.957 null] >> -% 618 0 obj +% 620 0 obj << /Font << /F15 160 0 R /F42 161 0 R /F45 255 0 R >> /ProcSet [ /PDF /Text ] >> -% 625 0 obj +% 627 0 obj << /Type /Page -/Contents 626 0 R -/Resources 624 0 R +/Contents 628 0 R +/Resources 626 0 R /MediaBox [0 0 595.276 841.89] -/Parent 628 0 R -/Annots [ 623 0 R 622 0 R ] +/Parent 630 0 R +/Annots [ 625 0 R 624 0 R ] >> -% 623 0 obj +% 625 0 obj << /Type /Annot /Subtype /Link @@ -7098,7 +7110,7 @@ stream /Rect [92.604 739.006 100.627 748.453] /A << /S /GoTo /D (section.8) >> >> -% 622 0 obj +% 624 0 obj << /Type /Annot /Subtype /Link @@ -7106,90 +7118,86 @@ stream /Rect [277.347 583.943 290.248 592.966] /A << /S /GoTo /D (cite.PSBLASGUIDE) >> >> -% 627 0 obj +% 629 0 obj << -/D [625 0 R /XYZ 92.6 752.957 null] +/D [627 0 R /XYZ 92.6 752.957 null] >> % 131 0 obj << -/D [625 0 R /XYZ 93.6 715.095 null] +/D [627 0 R /XYZ 93.6 715.095 null] >> -% 624 0 obj +% 626 0 obj << /Font << /F42 161 0 R /F15 160 0 R /F17 148 0 R /F45 255 0 R >> /ProcSet [ /PDF /Text ] >> -% 630 0 obj +% 632 0 obj << /Type /Page -/Contents 631 0 R -/Resources 629 0 R +/Contents 633 0 R +/Resources 631 0 R /MediaBox [0 0 595.276 841.89] -/Parent 628 0 R +/Parent 630 0 R >> -% 632 0 obj +% 634 0 obj << -/D [630 0 R /XYZ 85.4 752.957 null] +/D [632 0 R /XYZ 85.4 752.957 null] >> % 135 0 obj << -/D [630 0 R /XYZ 86.4 715.095 null] +/D [632 0 R /XYZ 86.4 715.095 null] >> -% 629 0 obj +% 631 0 obj << /Font << /F15 160 0 R /F42 161 0 R /F17 148 0 R /F45 255 0 R >> /ProcSet [ /PDF /Text ] >> -% 634 0 obj +% 636 0 obj << /Type /Page -/Contents 635 0 R -/Resources 633 0 R +/Contents 637 0 R +/Resources 635 0 R /MediaBox [0 0 595.276 841.89] -/Parent 628 0 R +/Parent 630 0 R >> -% 636 0 obj +% 638 0 obj << -/D [634 0 R /XYZ 92.6 752.957 null] +/D [636 0 R /XYZ 92.6 752.957 null] >> % 139 0 obj << -/D [634 0 R /XYZ 93.6 722.069 null] +/D [636 0 R /XYZ 93.6 722.069 null] >> % 300 0 obj << -/D [634 0 R /XYZ 93.6 697.846 null] +/D [636 0 R /XYZ 93.6 697.846 null] >> % 231 0 obj << -/D [634 0 R /XYZ 93.6 630.21 null] +/D [636 0 R /XYZ 93.6 630.21 null] >> % 227 0 obj << -/D [634 0 R /XYZ 93.6 592.4 null] +/D [636 0 R /XYZ 93.6 592.4 null] >> % 347 0 obj << -/D [634 0 R /XYZ 93.6 554.287 null] +/D [636 0 R /XYZ 93.6 554.287 null] >> % 348 0 obj << -/D [634 0 R /XYZ 93.6 489.076 null] +/D [636 0 R /XYZ 93.6 489.076 null] >> % 403 0 obj << -/D [634 0 R /XYZ 93.6 425.986 null] ->> -% 349 0 obj -<< -/D [634 0 R /XYZ 93.6 374.324 null] +/D [636 0 R /XYZ 93.6 425.986 null] >> endstream endobj -640 0 obj +642 0 obj << -/Length 7130 +/Length 6525 >> stream 0 g 0 G @@ -7201,71 +7209,90 @@ BT 0 g 0 G [-500(J.)-450(J.)-450(Dongarra,)-479(J.)-450(Du)-450(Croz,)-480(S.)-450(Hammarling,)-479(R.)-450(J.)-450(Hanson,)]TJ/F18 10.9091 Tf 320.772 0 Td [(A)26(n)-466(extende)51(d)-465(set)-465(of)]TJ -298.348 -13.549 Td [(F)26(OR)76(TRAN)-355(Basic)-355(Line)51(ar)-356(A)26(lgebr)51(a)-355(Subpr)51(o)51(gr)51(ams)]TJ/F15 10.9091 Tf 221.802 0 Td [(,)-331(A)28(CM)-331(T)83(ransactions)-331(on)-330(Mathemat-)]TJ -221.802 -13.549 Td [(ical)-333(Soft)28(w)27(are,)-333(14)-333(\0501\051)-334(1988,)-333(1{17.)]TJ 0 g 0 G - -22.424 -21.087 Td [([13])]TJ + -22.424 -24.84 Td [([13])]TJ 0 g 0 G - [-500(S.)-1026(Filip)1(p)-28(one,)-1199(A.)-1026(Buttari,)]TJ/F18 10.9091 Tf 177.354 0 Td [(PSBLAS)-994(3.5.0)-995(User's)-995(Guide.)-994(A)-995(R)52(efer)51(enc)51(e)]TJ -154.93 -13.55 Td [(Guide)-1084(for)-1084(the)-1084(Par)51(al)-51(lel)-1084(Sp)51(ar)1(se)-1084(BLAS)-1084(Libr)51(ar)1(y)]TJ/F15 10.9091 Tf 257.737 0 Td [(,)-1320(2012,)-1320(a)28(v)55(ailable)-1122(from)]TJ/F45 10.9091 Tf -257.737 -13.549 Td [(https://github.com/sfilippone/psblas3/tree/master/docs)]TJ/F15 10.9091 Tf 309.269 0 Td [(.)]TJ + [-500(S.)-1026(Filip)1(p)-28(one,)-1199(A.)-1026(Buttari,)]TJ/F18 10.9091 Tf 177.354 0 Td [(PSBLAS)-994(3.5.0)-995(User's)-995(Guide.)-994(A)-995(R)52(efer)51(enc)51(e)]TJ -154.93 -13.549 Td [(Guide)-1084(for)-1084(the)-1084(Par)51(al)-51(lel)-1084(Sp)51(ar)1(se)-1084(BLAS)-1084(Libr)51(ar)1(y)]TJ/F15 10.9091 Tf 257.737 0 Td [(,)-1320(2012,)-1320(a)28(v)55(ailable)-1122(from)]TJ/F45 10.9091 Tf -257.737 -13.55 Td [(https://github.com/sfilippone/psblas3/tree/master/docs)]TJ/F15 10.9091 Tf 309.269 0 Td [(.)]TJ 0 g 0 G - -331.693 -21.087 Td [([14])]TJ + -331.693 -24.84 Td [([14])]TJ 0 g 0 G [-500(S.)-330(Filipp)-28(one,)-330(A.)-330(B)-1(u)1(ttari,)]TJ/F18 10.9091 Tf 143.238 0 Td [(Obje)51(ct-Oriente)51(d)-354(T)76(e)51(chniques)-354(for)-355(Sp)51(arse)-355(Matrix)-355(Com)1(puta-)]TJ -120.814 -13.549 Td [(tions)-424(in)-423(F)77(ortr)51(an)-424(2003)]TJ/F15 10.9091 Tf 104.62 0 Td [(.)-405(A)28(CM)-405(T)83(r)1(ansac)-1(tion)1(s)-405(on)-405(on)-405(Mathematical)-405(Soft)28(w)28(are,)-423(38)-405(\0504\051,)]TJ -104.62 -13.549 Td [(2012,)-333(art.)-334(23.)]TJ 0 g 0 G - -22.424 -21.088 Td [([15])]TJ + -22.424 -24.84 Td [([15])]TJ 0 g 0 G - [-500(S.)-312(Filip)1(p)-28(one,)-316(M.)-312(Cola)-56(j)1(anni,)]TJ/F18 10.9091 Tf 155.667 0 Td [(PSBLAS:)-338(A)-338(Libr)51(ary)-338(for)-337(Par)51(al)-51(lel)-338(Line)51(ar)-338(A)26(lgebr)51(a)-338(Com-)]TJ -133.243 -13.549 Td [(putation)-284(on)-284(Sp)51(arse)-284(Matric)51(es)]TJ/F15 10.9091 Tf 131.984 0 Td [(,)-269(A)28(CM)-253(T)83(ransactions)-253(on)-253(Mathematical)-253(Soft)27(w)28(are,)-269(26)-253(\0504\051,)]TJ -131.984 -13.549 Td [(2000,)-333(527{550.)]TJ + [-500(S.)-312(Filip)1(p)-28(one,)-316(M.)-312(Cola)-56(j)1(anni,)]TJ/F18 10.9091 Tf 155.667 0 Td [(PSBLAS:)-338(A)-338(Libr)51(ary)-338(for)-337(Par)51(al)-51(lel)-338(Line)51(ar)-338(A)26(lgebr)51(a)-338(Com-)]TJ -133.243 -13.55 Td [(putation)-284(on)-284(Sp)51(arse)-284(Matric)51(es)]TJ/F15 10.9091 Tf 131.984 0 Td [(,)-269(A)28(CM)-253(T)83(ransactions)-253(on)-253(Mathematical)-253(Soft)27(w)28(are,)-269(26)-253(\0504\051,)]TJ -131.984 -13.549 Td [(2000,)-333(527{550.)]TJ 0 g 0 G - -22.424 -21.088 Td [([16])]TJ + -22.424 -24.84 Td [([16])]TJ +0 g 0 G + [-500(S.)-303(Gratton,)-309(P)84(.)-303(Henon,)-309(P)83(.)-303(Jiranek)-303(an)1(d)-303(X.)-303(V)83(asseur,)]TJ/F18 10.9091 Tf 258.865 0 Td [(R)51(e)51(ducing)-330(c)52(omplexity)-330(of)-330(algebr)51(aic)]TJ -236.441 -13.549 Td [(multigrid)-349(b)1(y)-349(aggr)51(e)51(gation)]TJ/F15 10.9091 Tf 114.383 0 Td [(,)-325(Numerical)-324(Lin.)-323(Algebra)-324(with)-323(Applications,)-325(2016,)-326(23:501-)]TJ -114.383 -13.549 Td [(518)]TJ +0 g 0 G + -22.424 -24.841 Td [([17])]TJ 0 g 0 G [-500(W.)-413(Gropp,)-433(S.)-413(Huss-Lederman,)-433(A.)-413(Lumsdaine,)-433(E)1(.)-413(Lusk,)-433(B.)-413(Nitzb)-28(erg,)-433(W.)-413(Saphir,)]TJ 22.424 -13.549 Td [(M.)-349(Snir,)]TJ/F18 10.9091 Tf 43.142 0 Td [(MPI:)-372(The)-372(Complete)-372(R)51(efer)51(enc)51(e.)-372(V)77(olume)-372(2)-373(-)-372(The)-372(MPI-2)-372(Extensions)]TJ/F15 10.9091 Tf 318.187 0 Td [(,)-353(MIT)]TJ -361.329 -13.549 Td [(Press,)-333(1998.)]TJ 0 g 0 G - -22.424 -21.087 Td [([17])]TJ + -22.424 -24.84 Td [([18])]TJ 0 g 0 G [-500(C.)-347(L.)-347(La)28(wson,)-351(R.)-347(J.)-347(Hanson,)-350(D.)-347(Kincaid,)-350(F.)-347(T.)-347(Krogh,)]TJ/F18 10.9091 Tf 287.094 0 Td [(Basic)-370(Line)51(ar)-371(A)26(lgebr)51(a)-370(Sub-)]TJ -264.67 -13.549 Td [(pr)51(o)51(gr)51(ams)-395(for)-396(F)26(OR)77(TRAN)-396(usage)]TJ/F15 10.9091 Tf 149.357 0 Td [(,)-385(A)28(CM)-374(T)83(ransactions)-374(on)-375(Mathematical)-374(Soft)28(w)28(are,)-385(5)]TJ -149.357 -13.55 Td [(\0503\051,)-333(1979,)-334(308{323.)]TJ 0 g 0 G - -22.424 -21.087 Td [([18])]TJ + -22.424 -24.84 Td [([19])]TJ 0 g 0 G [-500(X.)-408(S.)-408(Li,)-427(J.)-408(W)1(.)-408(De)-1(mmel,)]TJ/F18 10.9091 Tf 147.871 0 Td [(Sup)51(erLU)]TJ ET q -1 0 0 1 276.516 415.221 cm +1 0 0 1 276.516 340.765 cm []0 d 0 J 0.398 w 0 0 m 3.345 0 l S Q BT -/F18 10.9091 Tf 279.861 415.022 Td [(DIST:)-426(A)-427(Sc)51(alable)-426(Distribute)51(d-memory)-426(Sp)51(arse)]TJ -171.037 -13.549 Td [(Dir)51(e)51(ct)-342(Solver)-343(for)-342(Unsymmetric)-342(Line)51(ar)-343(Systems)]TJ/F15 10.9091 Tf 222.383 0 Td [(,)-320(A)28(CM)-317(T)83(ran)1(s)-1(actions)-316(on)-317(Mathemat-)]TJ -222.383 -13.549 Td [(ical)-333(Soft)28(w)27(are,)-333(29)-333(\0502\051,)-334(2003,)-333(110{140.)]TJ +/F18 10.9091 Tf 279.861 340.566 Td [(DIST:)-426(A)-427(Sc)51(alable)-426(Distribute)51(d-memory)-426(Sp)51(arse)]TJ -171.037 -13.549 Td [(Dir)51(e)51(ct)-342(Solver)-343(for)-342(Unsymmetric)-342(Line)51(ar)-343(Systems)]TJ/F15 10.9091 Tf 222.383 0 Td [(,)-320(A)28(CM)-317(T)83(ran)1(s)-1(actions)-316(on)-317(Mathemat-)]TJ -222.383 -13.549 Td [(ical)-333(Soft)28(w)27(are,)-333(29)-333(\0502\051,)-334(2003,)-333(110{140.)]TJ 0 g 0 G - -22.424 -21.088 Td [([19])]TJ + -22.424 -24.84 Td [([20])]TJ 0 g 0 G - [-500(Y.)-466(Nota)27(y)84(,)-500(P)83(.)-466(S.)-467(V)83(assilevski,)]TJ/F18 10.9091 Tf 163.479 0 Td [(R)51(e)51(cursive)-480(Krylov-b)51(ase)51(d)-480(multigrid)-480(cycles)]TJ/F15 10.9091 Tf 191.67 0 Td [(,)-500(Numerical)]TJ -332.725 -13.549 Td [(Linear)-333(Algebra)-334(with)-333(Applications,)-333(15)-333(\0505\051,)-334(2008,)-333(473{487.)]TJ + [-500(Y.)-466(Nota)27(y)84(,)-500(P)83(.)-466(S.)-467(V)83(assilevski,)]TJ/F18 10.9091 Tf 163.479 0 Td [(R)51(e)51(cursive)-480(Krylov-b)51(ase)51(d)-480(multigrid)-480(cycles)]TJ/F15 10.9091 Tf 191.67 0 Td [(,)-500(Numerical)]TJ -332.725 -13.55 Td [(Linear)-333(Algebra)-334(with)-333(Applications,)-333(15)-333(\0505\051,)-334(2008,)-333(473{487.)]TJ 0 g 0 G - -22.424 -21.087 Td [([20])]TJ + -22.424 -24.84 Td [([21])]TJ 0 g 0 G [-500(Y.)-333(Saad,)]TJ/F18 10.9091 Tf 66.97 0 Td [(Iter)51(ative)-358(metho)52(ds)-358(for)-358(sp)51(arse)-358(l)1(ine)51(ar)-358(systems)]TJ/F15 10.9091 Tf 202.98 0 Td [(,)-333(2nd)-334(editi)1(on,)-334(SIAM,)-333(2003.)]TJ 0 g 0 G - -269.95 -21.088 Td [([21])]TJ + -269.95 -24.84 Td [([22])]TJ 0 g 0 G [-500(B.)-505(Smith,)-549(P)84(.)-506(Bjorstad,)-548(W.)-506(Gropp,)]TJ/F18 10.9091 Tf 200.295 0 Td [(Domain)-516(De)51(c)51(omp)51(osition:)-776(Par)51(al)-51(lel)-516(Multilevel)]TJ -177.871 -13.549 Td [(Metho)51(ds)-432(for)-432(El)-51(liptic)-433(Partial)-432(Di\013er)51(ential)-432(Equations)]TJ/F15 10.9091 Tf 244.309 0 Td [(,)-434(Cam)27(bridge)-414(Univ)28(ersit)28(y)-415(Pr)1(e)-1(ss,)]TJ -244.309 -13.549 Td [(1996.)]TJ 0 g 0 G - -22.424 -21.087 Td [([22])]TJ + -22.424 -24.841 Td [([23])]TJ 0 g 0 G - [-500(M.)-317(Snir,)-321(S.)-317(Otto,)-321(S.)-317(Huss-Lederman,)-321(D.)-317(W)83(alk)28(er,)-321(J.)-317(Dongarra,)]TJ/F18 10.9091 Tf 317.503 0 Td [(MPI:)-343(The)-343(Complete)]TJ -295.079 -13.55 Td [(R)51(efer)51(enc)51(e.)-357(V)76(olume)-357(1)-358(-)-358(The)-358(MPI)-357(Cor)51(e)]TJ/F15 10.9091 Tf 179.356 0 Td [(,)-333(second)-334(edition,)-333(MIT)-333(Press,)-334(1998.)]TJ + [-500(M.)-317(Snir,)-321(S.)-317(Otto,)-321(S.)-317(Huss-Lederman,)-321(D.)-317(W)83(alk)28(er,)-321(J.)-317(Dongarra,)]TJ/F18 10.9091 Tf 317.503 0 Td [(MPI:)-343(The)-343(Complete)]TJ -295.079 -13.549 Td [(R)51(efer)51(enc)51(e.)-357(V)76(olume)-357(1)-358(-)-358(The)-358(MPI)-357(Cor)51(e)]TJ/F15 10.9091 Tf 179.356 0 Td [(,)-333(second)-334(edition,)-333(MIT)-333(Press,)-334(1998.)]TJ 0 g 0 G - -201.78 -21.087 Td [([23])]TJ + -201.78 -24.84 Td [([24])]TJ 0 g 0 G [-500(K.)-303(St)-27()527(ub)-27(en,)]TJ/F18 10.9091 Tf 77.278 0 Td [(A)26(n)-330(Intr)51(o)51(duction)-329(to)-330(A)25(l)1(gebr)51(aic)-330(Multigrid)]TJ/F15 10.9091 Tf 183.285 0 Td [(,)-309(in)-302(A.)-303(Sc)28(h)-28()528(uller,)-309(U.)-303(T)84(rotten)27(b)-27(erg,)]TJ -238.139 -13.549 Td [(C.)-333(Oosterlee,)-334(Multigrid,)-333(Academic)-333(Press,)-334(2001.)]TJ 0 g 0 G - -22.424 -21.087 Td [([24])]TJ 0 g 0 G - [-500(R.)-408(S.)-408(T)83(uminaro,)-427(C.)-408(T)84(ong,)]TJ/F18 10.9091 Tf 152.548 0 Td [(Par)51(al)-51(lel)-426(Smo)51(othe)51(d)-427(A)51(ggr)51(e)51(gati)1(o)-1(n)-426(Multigrid:)-597(A)51(ggr)51(e)51(gation)]TJ -130.124 -13.55 Td [(Str)51(ate)51(gies)-369(on)-370(Massively)-369(Par)51(al)-51(lel)-370(Machines)]TJ/F15 10.9091 Tf 200.325 0 Td [(,)-349(in)-346(J.)-347(Donn)1(e)-1(l)1(le)-1(y)84(,)-349(e)-1(d)1(itor,)-350(Pro)-27(c)-1(eedin)1(gs)-347(of)]TJ -200.325 -13.549 Td [(Sup)-28(erComputing)-333(2000,)-333(Dallas,)-334(2000.)]TJ +ET + +endstream +endobj +646 0 obj +<< +/Length 1191 +>> +stream +0 g 0 G +BT +/F42 10.9091 Tf 93.6 740.002 Td [(References)]TJ/F15 10.9091 Tf 401.542 0 Td [(47)]TJ +0 g 0 G 0 g 0 G - -22.424 -21.087 Td [([25])]TJ + -401.542 -35.866 Td [([25])]TJ 0 g 0 G - [-500(P)83(.)-293(V)84(an)27(\024)473(ek,)-302(J.)-293(Mandel,)-301(M.)-293(Brezina,)]TJ/F18 10.9091 Tf 183.276 0 Td [(A)26(lgebr)51(aic)-321(Multigrid)-321(by)-321(Smo)51(othe)52(d)-321(A)51(ggr)51(e)51(gation)-321(for)]TJ -160.852 -13.549 Td [(Se)51(c)51(ond)-358(and)-357(F)76(ourth)-357(Or)51(der)-358(El)-51(liptic)-358(Pr)51(oblems)]TJ/F15 10.9091 Tf 205.92 0 Td [(,)-333(Computing,)-333(56)-334(\0503\051)-333(1996,)-333(179{196.)]TJ + [-500(R.)-408(S.)-408(T)83(uminaro,)-427(C.)-408(T)84(ong,)]TJ/F18 10.9091 Tf 152.549 0 Td [(Par)51(al)-51(lel)-426(Smo)51(othe)51(d)-427(A)51(ggr)51(e)52(gation)-427(Multigrid:)-597(A)51(ggr)51(e)51(gation)]TJ -130.125 -13.549 Td [(Str)51(ate)51(gies)-369(on)-370(Massively)-369(Par)51(al)-51(lel)-370(Machines)]TJ/F15 10.9091 Tf 200.326 0 Td [(,)-349(in)-346(J.)-347(Don)1(nelley)83(,)-349(editor,)-350(Pro)-27(ce)-1(edi)1(ngs)-347(of)]TJ -200.326 -13.549 Td [(Sup)-28(erComputing)-333(2000,)-333(Dallas,)-334(2000.)]TJ +0 g 0 G + -22.424 -22.516 Td [([26])]TJ +0 g 0 G + [-500(P)83(.)-293(V)83(an)28(\024)473(e)-1(k)1(,)-302(J.)-293(Mandel,)-301(M.)-293(Brezina,)]TJ/F18 10.9091 Tf 183.276 0 Td [(A)26(lgebr)51(aic)-321(Multigrid)-321(by)-321(Smo)51(othe)51(d)-320(A)51(ggr)51(e)51(gation)-321(for)]TJ -160.852 -13.549 Td [(Se)51(c)51(ond)-358(and)-357(F)76(ourth)-357(Or)51(der)-358(El)-51(liptic)-358(Pr)51(oblems)]TJ/F15 10.9091 Tf 205.92 0 Td [(,)-333(Computing,)-334(56)-333(\0503\051)-333(1996,)-333(179{196.)]TJ 0 g 0 G 0 g 0 G ET endstream endobj -659 0 obj +665 0 obj << /Length1 2154 /Length2 17514 @@ -7432,7 +7459,7 @@ a ¤­;­rýnLŠ0åŽiZzu“¦é‚™É=u'~ŽøIƒAî PFAjè@éþõ$–û¾ ¹Îö„žã×üuú†—3ÄÊx £àåqµX endstream endobj -661 0 obj +667 0 obj << /Length1 2180 /Length2 15410 @@ -7584,7 +7611,7 @@ gL(H óUléX&_H7¢“òÀKã(C~¶@h«TT ÒEIG¥ x±¢6²ÙÃ$a„ÐmÙDÍ‘6MÔzÌháÉÞ¤Âb¶¬7‡—¡Ó[ȼ"äÃà÷Ù”RO¨¹kQpDß‚X†›¿žYÜP†KL:&Z’ IZ Å«H\£’´ùžE½cÆŠ9Šg­/ʵ,Ižkž™Èî3‹Ì¹’¥·1Ë܃ÇzZĉV£baÞw )!v¯ 1ôrœu|[·øZ9¿Z}´+,$xÔR¼K®ÞƒHœ7ö§²jR—…[UçâÏ endstream endobj -663 0 obj +669 0 obj << /Length1 2067 /Length2 14426 @@ -7738,7 +7765,7 @@ L ŽCpÙÔ#¿mRuWVf}š/ÀfsgšB9ˆÜÅ°ñˆ±Qa!X¼|n`¬ûpû´"õ•ÎI¸!Îô„Ä\9œêDÆÓÓ윮¶CÑÄ9¶‹Ñû31 endstream endobj -665 0 obj +671 0 obj << /Length1 1539 /Length2 6948 @@ -7818,7 +7845,7 @@ W K—ñdÐßü…åýÊN늦)ŸÌ^âÜübIªÿ|úÔÙÙ_|Kż7mÐfÕ:=ã"®<d‹Ú„¡Ç`PcŽÄðÀ9¶$+ïÇôû+ á«ÔÿwgêD¢' endstream endobj -667 0 obj +673 0 obj << /Length1 1946 /Length2 13085 @@ -7961,7 +7988,7 @@ r%lw ±³> endstream endobj -669 0 obj +675 0 obj << /Length1 1418 /Length2 6498 @@ -8038,7 +8065,7 @@ JVz 9ÿ j‘u,—ÚÊl_P!V%ý*<ù"Œ²-" ªö©8¥“qŸ, Þ{Pô²¶v©¤:ø‰ë®v endstream endobj -671 0 obj +677 0 obj << /Length1 1594 /Length2 8979 @@ -8141,7 +8168,7 @@ E ‡ Ð6ÏÀúŽølÔÓ‚ò >X—4’ËHÂswP…>OÜдÝ@ é²Îßwš_¹ò˜ú9´3Ê/ endstream endobj -673 0 obj +679 0 obj << /Length1 2717 /Length2 23393 @@ -8373,12 +8400,12 @@ V, –8dz1©Y«}M¢•±~2°ÒÙwû^fǸM¬ýI/Á,ô3ÿ=–Ü÷ÂýÅó(5ŽÇ©¾c’…¡CuTP!ŽØC±·+†QýµSéùf°µ +Y ûƒík›µLÓ1bVÀ„\Ä Oñ=®Ú‹CåÃ!â‰Xó!°³Í‹²é1ã=Ó¦x>²sJsÊec„ôn”ºOfÓÖ œÁiù¸D q¦” Ðú®K ‚¥@ •_q߯®Ð\>3¯üò$æ©ÐGOÚ ¼œ;«ÚPöŒT:LŸ“úô«‚ŽZ¦‚Ë„ï"C1/1-6âûz,ef´b™Èü‡.·K;Ü9ZŽ˜§°P–¢£?l÷jÓXÚОåÒi¡ŸgR%(ÌW6¾3¯5EZq‡€ËZÖ£€²®‹e”zï¬cÒygÖ! 2EMR½ßÜé}Z~µŠ­ÿÝ;r­‹™Ñ`‰ûŽ]Šù{žÚ_ IyÑO‰õ!óåöÒÊJZó:>À3Öf(R±4}øª±AfîhŠ<ãJæô­ÇJfh¬çfæ#,î¦ÀM'Çâ®6ØÇÜ­¸Lia<žFM!]¤Â¹rÞ,½P™ÓŸâUûëD"Ík_Qœ¹½"œ)¯Š–è~d·¾h¯©3Ž<‚ Ú“²£¢ß 4ùqßQvN«~_mZFíû·~í ƒ6ˆÉ# Z“À5<Ĭ'÷ endstream endobj -675 0 obj +681 0 obj << /Length1 1996 -/Length2 13118 +/Length2 13162 /Length3 0 -/Length 15114 +/Length 15158 >> stream %!PS-AdobeFont-1.0: CMR12 003.002 @@ -8398,7 +8425,7 @@ FontDirectory/CMR12 known{/CMR12 findfont dup/UniqueID known{dup 11 dict begin /FontType 1 def /FontMatrix [0.001 0 0 0.001 0 0 ]readonly def -/FontName /SNVSAK+CMR12 def +/FontName /OIRSPO+CMR12 def /FontBBox {-34 -251 988 750 }readonly def /PaintType 0 def /FontInfo 9 dict dup begin @@ -8430,6 +8457,7 @@ dup 58 /colon put dup 44 /comma put dup 100 /d put dup 101 /e put +dup 56 /eight put dup 102 /f put dup 12 /fi put dup 103 /g put @@ -8446,7 +8474,6 @@ dup 92 /quotedblleft put dup 34 /quotedblright put dup 114 /r put dup 115 /s put -dup 55 /seven put dup 116 /t put dup 51 /three put dup 50 /two put @@ -8481,34 +8508,32 @@ a`O ED ´pèCr:ñ°óåÔìQ=£ä‘èâÌWµ8{‘mCUØ·;·Qtþã[®ŠZߪjÆš´|YQ4ÈæC<ZeÏØîoäåúD…r%`Ôʶ@B¦ˆ‹>ð:Õo%1+A±%1òÐë{$ÞvKÙ* ë1u+†ôSpÄŠ))2"yLÞoŸ¨)5 ?©=› t³pºB,áî›ÎRbÅItßh*ÅNAoÙŸ£(Òž/'¹JÀ 2ãnbq„Ê»°oHœôµs˜TòV}1´ˆ¶aøÄ^½/°ðîJ!ˆÃÜÒFæŸb,ìôàŸ%Øu·Î¦*¢} M-Éóë8³ããp—y‘|»Ï/µr,gÿZŽhç½ÍV|È1íx·ASt­W[*äÓáVÖ{×~±öR‰)Ÿsoßÿ@±œío1¤Ë ÔĆl†Åñ<¤T«]Å4Xùró{—8hßSb° ?8xâ3Ÿ2EëvŠÑlßF(ÕûêlõmSF¶¶ÁÚØØ3)—_J¡†˜/GÚGÓ‰ /ùz6­}EÑæ3N™1yÄÕ]¬‚ãûÎU2ÇdÞè:I ¹ËûÏb’ô%ó“©Jë®eU»EÜ/Ö>1;Ï æ‚Ùžl¶#¡[êŒâŸÈxXÀCVâ)à5PU’Ç|„ðøÎþìÓåÌ–Za×2¨{¤È¾\ç:qy<ƒiv<þ)‡­üõë‚ê&ÒgéÛ’ùþ¥ƒ…­g ´ÉŠþö"pݱ¥ÃCšWÃïµÛîï¬ÙLyÂǯ›iJïzã)³ìA•l‰ˆ¡ÑÖ ü{J©¥?ëó¦Þ@A)ó$Q½ƒø·ç*1sÓÿ꜄4Øo6êç$O{>&Ì&„ á‘p%<ÇkFjà|o{ÜPyæHt‘ºzTΫ°?¨D‹vZTeÛ-óŸ4•îUŽV€Ï•}€kÛyZÿždk¯xE¡ù½CIm „rV û—Û Gú;±Ò¨*Ç8ûx=NS˜¬È¶˜ˆ@¬p¼e÷ŠJ³gst.i> ˆ¹Yž¶++´ÉÙkí¨Bɸ*þòŽÙ{Ô·4|Ç Q)#‡ûß_Ae·ðÀƒ/¶²ÝwD­¨Çz"—ÀnÛbùŒªìÖL”B—êSΆaóð…îc¡­TשýB³ù hüH$ÆDøQµq½¡íî•N§›=…RÑ|t ¯àD­Îr\}¬cŠ*,ý3|âÏU ÙÛïaÇImؤð‹T"&s&,IÕýÞrãËס~ ¶ÅJrï£ðß/ÿ$%¦\˜Œ—%±³`ìxã´à†Ò”§Ìdm0©W4áBm0Lj#8NçcMM%™§Fdâ-¤#)©î,›&ÿ0˜@Hó“±ä1´ACaÎ1²J^’ Å KHìí#ù'J…MäÎåd}w'=¶å*öùÐ=×UÑ\&:ë–.éŸ/X¨êšÅ. Ûÿø¹2Í©Q¼5jBñ·Q\x@é)oBlrb_PÔ¤K}ÏFƒ¤Ï †-¨‰Ó²§µÂO-ž³/;àÿÌrÓã' 8ÍŒ8 äê°¸éÏc¾7¥ÑfߌJšƒêD_æYJÓ²–ΚvM± ™9¾Îö {ê;=aŒÜA½¤ÿöç¶is¯²Lͦ¯S;à½õ¶r·½¥½[§Ëc9çi³(*3«Â¼©¸^H"1ò¸R†ø pÍ/ÚÇZà£VЖo=§mÈŽ7Ø8íxsZð¤yFš^“åÖó5Oê‚·’Žl9 -P*¹Œ1v–§ƒØx« ¶>VãsHLÑÀTÞøÝÞñoˆ{›§¥÷¸t:¨–‹ùà FgÚ ‹+4Bcúë>orQž w©¥ÿ±Ø|Lkô·mdg ÜÄàO¢»øàâ¡NáµJ%£¥®N‘YqC{Ê%mK§AM %;õLÝ…ólÊ„‘T*–2 ƒ:È5 hæÛéN®­Z¸k°›»gø1„E“û·Õž Ç Ã—¥éL²µ¼3{L(ÔΫQp>"¾×¦ÞÚHi*òa–±ç¡pD‰(?9Ø}¢-…$E«[ý¿}Ë? T¸(“Ð?ˆ¹ ò¯Ì­°Ö^ -/F:£}ì°Ã‘Ìâ`²¼Iæ£qÒ"5zîJÊ Èdw^Êç½ —Ò”ÃZì""Aªéo¢#Þñn‚-^‚¦}ÏÎz.mÖ1›Ø‹§Áâ%¨+¡ pÊ×ËÜWRöľœˆ'ØUcC¬Ûu>O®aê>-¨ïñAvBw ê39í[@x"Ýn߇ñÎX<ÎŒóú°…åºÇ(ÿȨ‹Îû¾}_£ûäÒ©JÔˆÑ#£2 Y+ò—ZR˜E]ò œ$àÿóL+æ‚ê“h•%¶ã(vJ#ߤ)KèƒÒÔÏ07×øœ)ææ¢Æ a‚_;AC á’Î,ø-5™ôLá•ÀTôŠª.:a»r§Fìóû¥eâ°ÕhîÉH{S£Š4ŸìË6™cÁú"ÒÂ8Á—Ú+0¦+Ρe35ÐÎ6 •‚P$¸óyëkÝPÎãÛŒA ËC|æ€×kô¸¾1ht²Áy¤ðèO™Á0Þ{ -n4%6BÛæpËû¼……^擄Œ?H’`$%’¼ÈM`ÛϬ4døwÒÊ ›I%¡®Øö±q\qÓFš18æ:Ë32ŠË‘Ç æsÓ¦€è£"ðëë7kèû8ÂñÈxf)ÏžñØ´£4KRÜ­‰ @ãúKœ?™„"9è é‘ÉoV¸c‘‡ü;r®ªÐ) FùÈÈQdË$-ãØ^»;TËÕ*’جßÀùÇ"49vI -öuFƒžŽl³[ÙÈ»wR’÷ÒOÈ -9‘ÂÕBå -{” lEf@¥«²j`?Œ!š]#'/ -0;’üë3ŠHqIÙQÐ)® 2˜,U‚¬ò7FQÉWR;ŠY±ï[¨†Mè>«á }¦p‚ƒ”È4'()Ä›wÚVg-ã‘G¨ÅJ€ÓþC(WÊ‹rƒ*ŠïÃÛ8„õ$çÙ‰û…©çˆÁeЖ¿›s R7G¤Gžoª^›q´ΪŽð™Ä5æß÷L%räYÕu¿@·´R I-V³xë*ªLðªkH‘ÿÅël^m{¼I‹`øÿ@¸Þ>#6v¾O‚l ”ÔqRò™Ÿ§Qó¢: w—Tx-.1|LøŠÉ ½(éFèÜišWeT~heR5 ˜M9…»ÏŠòŽ­xœ#UYÔŠ»˜E¾ùwÑWlÌÀìÕ4n˳Ó2Xê¤PœZJâ)ô øm^û2B4j|¦aŽî¿]AÔ;“æ­þB—j’ð÷hTM›¨Í„hM‘;I­€­œzèpmdBœJÇxIŒ­' |‡ÞÞ~¥ƒ(ç|˜9ËBrõÔ[6Ë£„)Þ”#@¤ -±tOý}ã PIœ·¢ÞÚ¨ù¶¿I']y -\3 <^SçÎø‡ûÿ¾|‚ÎSc¤ðçPx¦ -ñ?0c>7š¼Xͺ² NUÄÜb2aØQ¢ÓÓ:Ž#w Þ0e1I3t_Ã'"Á²œ)*á[ù4Ö X8¥Œ×1e~âÈ! /íjn«r9A14DU•e³CãÔáQ8–Š€ÄHÇ—¡§©’³ÀñjØÁ]2”ÑkíâãëZÆã"îßZÌ(¨ UyþZä+æƒüa#1!ÞŒa6¸ãÒi£’9ê*zù -'žxɱLQ-Æßt“qÔdõHY8®)K9ï1AõŒã‡ßˆœ³£ÚOºeˆöDì{·ß‰WOY'»Š3–ãÝyä–rCžÆ‚]ÒâýÚaaDÒGUƒî†MLðM>F"M[³´·bæÔ‰ØÐEv©«Ç)¾hîPÐ]÷ElÔp—¾j}V/×üeDÏ.ß‹¥ha¤Ô,émc_-`‡,Ðí Eÿƒ¸Ä›#ëq"£TmNÛE°’¼Bm¥ï†ÄDë÷^§UÓ]ßø(azΖ@³Foµ:IZ©§Ù/}Í͈•Œíª»£jZpŒÞWÚnàèÄ› (þºÅèYüŠm=âòÞvƒÊ£\ÆGSv–Q<UX±Z•…ä_Uá-‡wp´C*±uFW]y‰A¼ éÒ÷ùñÛØ5O$‡ÍöpõåàӲƹx³ÓDÙmô‘Üž—Ÿí­õz¡ÄHl³gÍZŸg³Vœ‹ -}SGã‰Y ¹Ø-¦4dNL÷Ko=»òßdZ¸ua¥”éã¶L—#®ÎØì H44T¹–`5lMè%‘æ­ØÕæ¯<ÝðV–í€ ÜȘô[Ñ?]ígzvjl>d®mákÍ MŽ 2ú¬Q£'_IʿJì\n÷Mm˜â×KV5èYÌq@`B?î…YŸ’"IÏ¿L¹åû˜5ÚQ8é¡Øœ‰bÜ"؃‚.ƒM4âûdjd±³ë³.&[M²ùI]ç¡Q²5–4þk{ä"ä´{¦ä͹I§é†³Ä®ÃVÊ„Ç¿ûåØÐóڑ࣠E·3l=#)½ქvCœ¤¶=/`‹è}¨*›Ÿ˜5[ëyû½ê½6çjÍ;·.×S<©‡…ºCµÕO‰IêÓ^­`yBÂÀ‰ÙæñëÜ›.&§áD»%êÖD® $±"JÅ»Ýö’l,‰à‡ÕácÌôÈt™Ÿ¢‹p­^bý#Ç Þ5…+@M¨ß<3 dM*šRf*X ‡#<+–£å‰ÅõtË€²+é×M‹Ìøûª-**26ŠEOd†¿qëmÀÉhÝçæ‡;tó¸´jºœŸý̼\ÓÕÕ$éçèÅ8ï -»µn¢JLB§™ƒQÊ È&±ÌR3Ñ®l¡´Y%Ís;ãå ³Éˆº>^™ö„ÑZNËcSÅúŒôçÓ Ày˜1÷#_"dËvâSe•YóÏ—ÿñyqZzø2‚º@•ËŠ}L¹ˆYþ6£ÐºD~_Ûg[6ùº×@NI-½åš£>˜‡Ôf½Çr““¿7#qJ{·¿¨ÆÇâSÐùÁqôñ n ŒêìBwW¥h¾³˜Nµ8-·þÈÄDšÑ7í?Ӯγ‡ï{kZœ;jehJí‹êæU•®óx;ÊRö‹•ô·üŽ»lWjúš/úUyhz:íU ¿O·º=‘–‹¾æücç5õ2Ä£ˆõoJ d·ÀFÀÊôµ+*¡Ý¸PÙ±®o¸ºû™Þµ¯.À6/3žÔ ^9Þÿ»µáã¿ãßi³½þÚç¸áÊÕ›³ç±äÉêá2Á ™‘ ?Z2ºñ‰UGYò YèêJUpA½"¶?Jb•¯C_ëÈmæåYýY«ZWÒ§$3>Ë3VíÜï!€ïyOѳ•>1­¬ÎðÇcQø#Û¥eô?ÅÇ1eÜtÒ°úp8m”w];¿TŸL©hV› QaèÆÁRrð´C-mÍ^r×S[ZO±ðWtá1GcÓ±ñëõâo8™ç ”iøŸ„=&hbœ‘îÑ€ã]9Ç>nÜêõ€ö{Û"1„“¤t†"ȾW¯MãúŽ¢i*èáË%§²LÕ{4çÎ*Ê –ˆŒ¯—´Sªaþ¡31(^°…[ti?d^Ûã@§3úQ"—á?dÚt%Àd‘–,Og&,“^cdäe5;"˜ù$a:ÜÀŒë/.ŸüÝIí}„ÐA%þÞ›pvÇ—Ds§/µ„|;È'!Å嶊1àUt¾éAúˆæ>o»ßx»§…G -€Þ2j7×K ЛzX”7ô8x÷×n[ã Šã”Éùׇ¼ú^;“Ül âäY~Â0ŠªP‘“,ƒLz,õ ¡Á€,é›ïú~‡ò>šì/,*ö«•tÏF41Ç·ýU«XÿLû{küçf£D¦ÌâËç‘™l±A•Â¾iÍNŒ½ðUÛ5ƒ:8P -‰îkÈ–É–0WÞsŒž ALàkñ7\õq»¸À~˜L#¬®–—ãx–NÃã‚þ”ç+šYX²°²b£ƒM«‰Ýk*m¿|m, Òh¦"ÿ£ßȾpx°ðè +ŽðÂÍL›Zùî]5Fž«—uÎâ.naÕ-•p Þ†”¯…«Ûb¾\ôG˜ñRÿe6Àîá*µ²ZÂÇF²Du%„RŠ0ƒ>/‡Œ-LoCʹ[›ÍÎÞ²@K¡-z:g÷àé£æn3¡z ê<‚k­ß_â-VB^ïü‡àQºÉn‡ʦéíÊX/äƒmE³‡4Ï@ 0—/ÅU¶a$PK(7E]òŒº1Ö‰JG•_Frƒo~ûMîSzš'žª_B¡~³`d0Ãb R¶$è9ïÁ3ԎèÛÙ5BôMä/§òhÅšŸSµ~›h\<æ ™ä« Öìè´ÇÛ5¦“Ūèñü%’ƒ’eÖds»¼©>“Hì"—ÏE᡾»ÚréXw3W—4ÄŸ>öMîS:NñE}`a²ÍHV%êÚ¼~í&”/—öÿ>D­4ZñB%ãË|2þnA,iæ^^÷ë‡dJh§‡œÝlô£2›Ð(VF~¬a©A°‹ñCL]˶¢@c0à?ùîB“ àØ4æ'5 %I7þš¸tšRhèU®Z¾¬:Â.5Œù'…èo.Jˆ«ïÑ™º‚ökäŃû)â/S‹Š½š(ùŒÍw­‚¥O.Ç…È 3ô‘âÜ-Oßäè$ÆÆÓ·’¤¯Ij{ ß•Ÿ,s…{£¯˜Ô çšg}ÚÌ·¨Îeùç=†r4€ óN‚àSÔÍDe¹…cËnŒá—ÔDعSã®7•¢û«ä¡Z P=Ò®ãýtKCœ[H^”ðv0n)ÛZ t+óÝßðJÄä -X“Oì L¯9Æ΄e¿ ´5XŸ'WM)~âÉ:*„ۻɕ—yáÝ y«)yÃt­òÙÐg{ÞŒqí…p3‰¹‹˜ö¼>͆³j×­ã¨@^‰Í*ôº~†Åµ}ëËÙÛ½R¤“¿Æä€÷;8ˆ‘áÌØ=Aivù¥ > 3•\‰›àýþb£œˆ'€\ îï€_‚ Ò{ÅëP…¤ ð9õ»Ý8ñÛøç¨oii)©ÉUÒ÷Á7뜆2”&§(šÀ‰^p"öÐvûð£Ø¤~ÕïÈ@ßœÿ¼‰åâlr‹~aéÐsC·¯žßrõv¢PT}®C–c!™¯BÑ ²—Ñ[‹ÏŒ0€{½”?¡JÀ×Æ2m[}£Ø2Ê%FHý¯ÎtfÜ¡{'k!y=Ê[¦%:¼Cˆ \y!Ï,غ¢#°iéšÍ™ÐüÇòÊ2?™Ç…º¬bóÜ£vöÍ^ï}XÛ -Ñ.áç7ûÔ<¢*_› D´³Ÿy ‡R®Á¼9Ü3h¿ Pt’§ZuA¢z$Ÿ» ‹àIÁÔŸUÖ¡í$ñ˜4­ !ØI— r³xùøí.5¤˜©] -8 ™÷†súzýˆ5ܽ§ˆqƒÈð=`³/VŒÂ|>0§æ\­^"Ê)ýC‘á(R\êtzô\ ÚÏ%T^k´0LeÔr;ôÆã5P½d`áü#x1RÀhâ³Ô“àÍüü¨0<øàNãÚo-˜=ÊwŽó -Ìïxã Ωšký·õ¨ª40-&äaŠ -ôfF¨³¹§§ÐÂÐ\ÎëV(ïËìLþqŸ¥¯Ø%Üн­>e'ãןT…3ÔFKQ Ÿ ËÇNK,mÄ ¨~\ÅO~ Qwÿd¤Ó«µÄ\ ­ænaòª0q>éÚ¯ÔE;œùkà‡\›y3ÛO!©÷s1¥Çä.VãsHLÑÀTÞøÝÞñoˆ{›§¥÷¸t:¨–‹ùà FgÚ ‹+4Bcúë>orQž w©¥ÿ±Ø|Lkô·mdg ÜÄàO¢»øàâ¡NáµJ%£¥®N‘YqC{Ê%mK§AM %;õLÝ…ólÊ„‘T*–2 ƒ:È5 hæÛéN®­Z¸k°›»gø1„E“û·Õž Ç Ã—¥éL²µ¼3{L(ÔΫQp>"¾×¦ÞÚ +À*Ü5%&_cRTu9?"mU±Íìžã隌-Iuù'Ùp· ç2ñhŠ*½yJj-4äl6LîÒ^ +Ni%/Ài–¬¤Û‹‡y+®¡×%:&“B e½~xÂN€gÕ>“-³H¹‘ÛzÊY+wƒn*B÷uÙ$±£C¡}¸=~hîÀxÛ€©1éö—}¼ânÁRÙ}7-Ù1åL¤Å¨¶™™ÙA|Ãè1Äô#cS©ì~çib). {8ñ@‚Sˆ\$¹è»Æ¶ÄǦ÷$£üß4»H@kú4¦yúöVÌ€Á²…‘y-]SŠÞYÈ+µà(;‹`x«y—3tñWlž6T Ô€™¾¡ÁC#¹™)öX=~ÜUøœOÓÉ—ïl´Pà)ÆYØ­©Ñl²§oðÁ1™-£šŸ[Ý=úÞ[›ì;·V¬¾7—ýé,7ÄKõ“ñy +o±ÎSˆŽƒ:²²a>FrÖ;ê9[ÕÙ/~,ZÏ3J7ç/™ØÁ¡ÈY+ëȤødŽgÅ)#ûä§2˜†KBb¼œý¯C{ØûT“ûê_±Òg‰”uA}›wL$ëtA #GnÛ‡²e˜ –âoðÌÊKyQRÑSþ¬ïË6¹WéÂÀësºÜ®•oò¥…z A«ã¼/ƸNso%¾€<ãL{éB)é­³œÜ€alƈGf¾)àѵÑ?öyùƒ÷u/7úKÜN2.ü™NUl4ãkwÌ£Õj‚|îD#o­7>ŽñnÃ9S¶)èýg +÷=›¦ãÒ¾k(à‚’8˜ã›1cdÅÊèmé¥ý¥GænóG`³•F(I |†ŒÆŠð¨mt\z-ó²&](7ÇSË[AesJa$ª;/œˆä%Ôu v½hçlD£.¤ÑέÙ\Õ·â<áû¨Mv•ñ u¢u4ÁT3k=:2xš` ¤¶À_"A­Üo#¹¢ž µ6Aè–_ÙG4V0l9/˜ïK9xí˜_‘FJ¡x$*ýˆÏ?Q„x²ªÙÎ ØŸó//Í|§Åð6Ýí­ÊèCveÓp‡ë½¥+Ò,0®<Û-ùÒ+ ˆr(Yò½²Û°â™¹UŒ…’Š(­IÉÀ(̪Âú䥱µæÏ2}ý¹‡a¸€ŸÞÜGGH¬£Ås¼õn²³Enþ6æ‡òUc~'`1 +O³sµÇG«£mB ÊÚA–  +‹aˆ_ýÞþ…M×øf`}hÀ¾1ÍAËã u!“@Ðiqx>b•˜ÝSÉ…jòt;=§]‹¯_?NÜ5‘lä½­žeZ¬Q^¾ÅoúYÓ ²ØÑVÿ|ôÎ[¹]²z#ÞÕ–-Fݧ0„E­½f²Ž³øF0óMñ÷ÚE¸×þï̶ޢ›šÖ,@<ÃKÜÈe܇Uqì-¤#ôCL Þ—~•a¼#=ðé{NÊe‚‚_†÷ÑŒPßÉLXÛîÜ-Û3 +ëT¯ªH‹;YHä4¹!!vb¦¨ZB—óëÓ‘ä?¶‹‰ÚÈŸrñÿOýaN§ImXÎAmyyµ­–ýj‡vÐ 8['³ú +yå^ÈNœ¸†,äM’ºÒˇxö/ÂÚÁ$ÁHؾŽ„5Ãr³¬wWääõaç(é]ªvÕFã{ØDc¸["ëL«ºfã[Á#É\¬ù3¬÷‹"¡uÿHjÅW»yŸö—Q¹ô=QÈ-=¨™wÒ÷<Êû…¥¿^D…ˆòÅU§®#­‹>ôw<ÇÉvŸ5t°Žšxäå¼ñ²„¶‘ö)ýËïÛn)}ËÁIaKG›9TÚcZxýDQ«®O±ÛôÐ õ~ÉZùöŽí‚wp˜ü®­fÓò}G1ZænNr0mg2B®º»žÁ +pµžç£Ëó}¯šœ—®ÞxžGëªD¸ò¥£6ŠÑËì~ 2£a÷1Bô¡›AFGÆl0ÆvæІÔèARb³)Ö{âÁ)`* vŒž|ºªô¼ +¼>תØfÅ©ØÔ_8Nµ®ÿVRç ÝÕ˜èoI535›mg•æí>¡W-,½•9.@)þ€ObK7g6:Âæé01G×ÙåšöĀDŽ…Aˆ“‹j+²é*ڟȹ ¥•tCmÝˬüþ_IU!J1Ë敨-bàùl¡¬ µDÍcŽÿ¡-/'ߺ´ÁÑ\ãÌèºæ –Lò{ŒpÇ@Á¼Ük>ÔÅY9 ½@ƒï=‚P4*\‰L ¸^nÇgt³¾í:ŸZPu¬'(^2Z/ÂþÏnת5“ï‰V›H}€õ('°Þ„8Õò-ʬ “!±öã7Og¥JO`4(ɪÚ”—£˜ð©ÚèæñyÒK9D¦ÇuD®ì,¢Lò#Ó1TtwÒ³uÄDÕmW båçƒ ú$´m Í»»ÃÆŸDÅëí§›=1²Ïš"½à"ðR1ãk>¹Š§ü»øº5ãã¤Zé¿VÂw\ŸÍDEBüÉãë¿s¤·;’YM«±;Ô kˆ¿Åe +ùÅi”jŸÏþ+Í¿§xuúÃZè´CÃj†*+!EÁäùÙ›à…é½:žžË¬FÒìÌÄ~](6œXqT÷¯-UÄAÜqéÂFK̪!™;°`ö]d©î2*`ÓW¡•`A"öÑ` NL>×;º÷ÅO#6wO…Z±‘6& •«X$Ü€$¶}Ú{0k½ ‹j]i¦lG‘±ºh•˜ ôfÞ/åUA~ÛÙLUÂw YˆÆ/Ýô éë^â¬âÃl ohˆq ªöæNš¶DTSñéC| Ó Tm>£Z±¦ïý“üj¸"H!õŒ¶³ôç^8<ç…ç’dl»ªUsÇñ¼q3çGNHaM÷®8È`~È£âàLž +' É9$›½d7™íZ¿}ZýÁ’Eá»=Yþ ›ôš°ºÖï^lU"„»©BÇz‰mmìn”IŸÖI—¥[k‚ö…þ NÕçÓ[GovÝyS‹X®'ú9ö.ôøjþºC‘”–ø¤ Þf„E…ÄË—ãÙiîv‘¦£ƒ¡ÜJ¿wߣ¡fÕo¥@„eò Aï»ÈtPżíp^¾x—Ö5ôGG‹¾uÊ@·*àë¬`Ñãšuø¨~¢t¥þÖD (<&Å«\ÃÑj-–û‹öQa›É\ leÞØÆ‘•ßÛv‘÷¹ÑàÈßóK[†&xR¼¾Zjæƒ +JðÒÌ:H0¨AXk6…áS²6Ò}€ñÓd9UüÍÃKÄVAZÏ)[üåþð2!ü­ÉVÅÌe‡RˆèÀí_X>dzÑN’»ÄÚ¦²V +gÅ.Óz×»Òº¼}¤!E ¼ó¾ÓI§U¶5ÊdV£ÑŒ Þn³ÿ°õ>'Øžé³gQG´ò‰)7òB\nƉÖò¦Zü×nòƒ›á7Xyìk•‘>õkG×guµMý7;S¯‚¼–Hœ Bê†NžOÅYôßIü~U³N€;Ú$}Ftœv±;˜Ï‹!—Ün¦©|LpuN§`çtÀW2)yXÞ]uòù¯}ßxÔ¾Š‹Ã¡°ãà³’Àôš¶O}j¿JžïÑ$¥$飴 ؆)]¬/=…%[cÚGÚ%úZÊ–¿p2ŠÙ= þŠgEeÖ&v›vàÀ2œçÏF¦ÁL¥Äín6‘7ÿѲX@ÖEœ†²¬M71zšœ5ã‡O ‘y¹ £)~Œº…ð\²—µùqmµäO‚EÛÐõ—Ë…ÊöJ§¤ì×òdïúIÑíûÑ”ii¦ËKä ð„¹Nq“^·ºõk ²ºrå:×ó»Ÿ –y20‰^µsfð1rÑÃ1‡Rø!_pÅGUåŠþú©ÂRݼªBÔÃû½»Ï0öŠ¼+=ѽ!å<ý¾<6CD´ =ÉEBа¾{‹à!ž•TØ#l´Ô,]79^ľßý´Ii'·¹ÐãfXëùR(µ_ÜLjÛÀLçKnm{Ó°9ˆ´°@ï»9ŽÇÊGžIWë€Zµtu[»2ÝÒ‰ÙܲÈàSºf’†¨QÝÕJœóʽŠÝNx–0úôR†Í]Þ”¼Ô°ñ¨¾‚ùƒ\O Ë6’^ä1K¿À <é6³Ó$ øX“Ì©Æшa¸î[Z +Ý{þ´'>áª>*øþ,¨»Ã›”‚-¯áë+Âÿƒ¬<(‰rúc±2¯í]ž¤ õµÒÇ-]0' ‰TcÁK½ »“*oç‹ûQCÜ]Xp ¢ ÑøŒ¾m«ê[²5ï>ggŠ»·½QÄÇ2—c§ñϵ3äcšg¦Óø4a§¶€†q%ï½½ŸsºeîƲÌÿˆÃ—™9£<áñ…U6Ô”Ò}ÐÁˆš}˜³”Ñ\m ’tî}L4k˜KgCÞVââ>Çöþ¾Úº=ä®Øº%ÐÍÓÐ÷¤ò,´ì`çôÖÄž©†©ÈÑ¿%KÛŽãß «©=ºÕU÷ªv¦¥‘5C˜ïᮃ½+4p8EH¼\i„n_›ò\xæ¦mû‚{"a»’á[ôµÛXË‹?5øìÀí^ö“µä×ÏEô …N7]9"ºNþEEbÔ'lF*ïèÓ§åûÌ@{ùÆõ2³úMb±ôç=ɪ;Q3m3œ&M’ô‹€Zõ(6ûaŠÓúÊo™ìÁœ”«cbˆf»•o‘28Ø!Þ}–¶P/¥{Ü;¨÷Éhö×b×üvØ7çvxŸh‚v þâiÊ0|Ðw´"ˆMPk£ÔGÄüy”},i&ÊÒ…˜ÝýaÅ#A?…$Ú‚š¹¯ÔºÁI%Ö¥oJªÁäÑ´yâû”•éx¢ÛwI“`kÕîû£NÝ([ +mÇNùZ˜‡Ò!H;nŸeo r‡ºrÓBØƼX R ˜zužšjålA"Ð-BÊl ©kg´3 tð:>ÄÆ_0Û/|Ö±ó; ŒÈ:¨™ÇxÝ:ãßÿ÷µ@4¶|7â;Õ~ÓHËÒ\ÃwïÖÈwqÛ‰aœn„1¦+–Ñ`ö‘”U$ª] yÝ6÷_¬À?¢Y·–€üïyê“çX:=Õp¨øW½ä8¦þ^ʤK‡Ý~<ƒÎG^½&ýÇ,A˜©Ú ã,xûy¨Î"ûÿG í4íVr¤%(Qç5Ï4f#IUf÷JJÓÊ‘ î}\ñ@e,"$2xÿíhîôxEiª[›Y¢+Þ:Φ +ø•;F8IwÊ4ƒ&¢CRŔ٤ŠÕ`ÈÅX†‹¬lâêë>ª!{¨|þ/‡'»ŠãÙ»‘Öà“ÆiÉiMþ‚ŸSØMc'ƒ´¼’ÇŸ- î[lÂt¾²6Ùˆ]^Q‚¹£ŠF#L=ú~» endstream endobj -677 0 obj +683 0 obj << /Length1 1392 /Length2 6243 @@ -8580,7 +8605,7 @@ B i«Üsªù‡ۂ÷ k’}_ÓŠSÕgŸmøS¦ÓM F7«ƒºÂŠãrjh×cÙ%0xï[Yü$ðWCOå¨ÞÑ?š#~‰Œ—3½€AX±EŽ€¸îë·ÅšGâdã±aÍZìÍjë†LEOß1¤=Ô¬¢lG#)ý%mÊÓ¼/žJ9pÒ—`eL‰ñï¿ÂÐ…Ô)Ȩ@“y7ÝèçLêªK|ØÑäa+$ç?½c|wÔQ`x[ÿÍÎç(~‰ÁB ~@ %3Ÿüšü(ºöÀ¿¾ë­t§$'±Pzœ»’ëkí+÷hDaŽ?Ÿ"€Gî oZS89sÈíeVZÞ,6n‡m*3]MJÌFÛwxL¼©ÒÌ,åè!™ðŽúÔ×­âóDÉßRqè™XzàdQB}¼ÁU£'­œ¸æjk±Ëçyƒã›ÜféÃúŠz<8Phu[ endstream endobj -679 0 obj +685 0 obj << /Length1 1408 /Length2 6296 @@ -8655,7 +8680,7 @@ c •*Χo ©Þ‹ëG ‰½4YÆìÚúe¥å¤:dmvBÎÚ\)/­¤Y «“‡C¸q0QÓB÷Šï'4Anr í2v»lý@P²Ü?ÔC¡+7ÒÁÃ;u÷×±^`¹ŠIAä‹sðÃÛ®(\ák^ž0P?š«=˼{‹þ䘜¾›.å~´4ëº,.}ùNm*LŽ%ë~¢æ Wæ/q>Í*:»CãºÂ¬^oĪcµÕÊOÁ=|,ñŠîÁÆ7Ül0ѳq Ä„-@M¼÷bÇœ²Ûá7÷iFCAlL¹‹( ÑóPæG­I–çÝ—œöêkˆ endstream endobj -685 0 obj +691 0 obj << /Length1 2278 /Length2 19476 @@ -9000,7 +9025,7 @@ ZPQb \¸ ™rÌó2dˆÝqw´.Û”¢Ápd¯½;æ`¨h•¢Èõñö"ÑŸËüù>H H+-`Mq…ù¸fpÁ”÷Ÿ¢™‘à•i«wê/e20Næ³ó"A”Q…ÿqÞv8õätuTçµ.ãWZÏc;}F/×vwôN$×;ß‹¦ódô¥eÁ~`ü¡…±¯ÂY8­ŽYl/àIS1Õa6†å€ùÒH®^ÂÞ°}4M6(óà(Æð·ªi€ËKB!š‘_¤u‘Ù3¾_üa»L´Œ¥twÚ29b£W£S×çM5šBrŒ 9þé¨å¬\•;µ})Ü¢e7©ÊP ô”Þí²éë2 6Ö²£ïýÛ>Už“ŸÔÁÚAÈë1oB9ónx> hæK Ì6û˼* endstream endobj -687 0 obj +693 0 obj << /Length1 1786 /Length2 11772 @@ -9122,7 +9147,7 @@ fv à¯mfj÷—Ý[-âƒ~oA—u›3í¨™9Q»²:×b?°jjòNKÇ¡ÂmÐ5 ±LFq÷ÖñÿLQºÃó…cˆqÄ®«€*,–w¥`1SøÒˆwdP µ´ ôس¯Ð fŽïºUôÌwù&”?☄ÄÝú#ùÀÇFø0§å佃~LNØ !?žÁÑÏûî >¾evĘÊ*êü_V…«Wöç\7Å„„ Óñqr µ¿AÛ;=žð§rm£Á¬oš»¶ri¬]ý%f;•¦}!sŸï©îM#Ý=8H#U¼v–ˆ|–|ôÀrEl,ÿ^3T:ô·EEoIHÕËçàÖy<&ûQ©MáäܵòŽ$Ç0dJÓÖÅ_ºó—ºihRà€d©TõIží8;¨¥ËÏ×—Ú­8lÝïÚµ"áûÍ“VjbwÜ£äPóVÎÄÒ^Í:jÐû­ߧ˜"Œfò`õù¬fó×-w’ñh¯o‰ÀÉ5v›\P…ôS endstream endobj -689 0 obj +695 0 obj << /Length1 2769 /Length2 19845 @@ -9330,7 +9355,7 @@ bV wt´€YÃÿD7·yÛ¤•¸Wg.Cه˸ì|ó“Ù)òy—dI”òÎÀX%›ÏVúÝ·C<Æ9ûB*¶…{‹~ÀÞ)€çÿ»Î£vÃ9ÞHÛX<¾Ø%M‡7§sØ`.C™ endstream endobj -691 0 obj +697 0 obj << /Length1 1306 /Length2 1345 @@ -9380,153 +9405,178 @@ currentfile eexec €·jYÿ® çÏrÜ["ÒNŠh ¡íÏÅ,KC"m`ù´Ö \3´½¬ú¡3”8tÅ5(ƒ‰½;‰•½LrSÊ ¸Ua¶Í{Óú¶P®ƒƒ¬jèxÛ$Ç”¯(‰mRò£°çëîΠ֖Ƈ©†žÎ ¬alC_-ŽþûcIó¾#gÛÃì6R2ÄÑ·£ ¸²¾±E0Ï9Vm4æ†w‚%õ{‹-÷ŠOñåÖ†@Ñ·oBœJGÿ5… rg÷HÊ(üÏûtiJòÏÀôŒç&lR:UF©,Œ¶/SĈ¤†žfôÕƒ¥:¬ï P8áõó˜ÌAò£ƒ9íÓ¨ÌVq5Ç;úœÓœ»Î’’z£¸åAuuÈw$AÒŠ^Y ¾”Œú§M·Šº—½˜/ã Üö^v"ñ ÉåÄ endstream endobj -637 0 obj +639 0 obj << /Type /ObjStm /N 100 -/First 934 -/Length 20264 +/First 933 +/Length 20196 >> stream -248 0 299 54 301 108 278 162 633 216 639 335 641 449 279 503 283 557 234 611 -233 665 281 719 280 772 302 826 230 880 367 934 229 988 282 1042 228 1096 346 1150 -232 1204 638 1258 642 1364 643 2060 644 2128 645 2432 646 2560 647 2914 648 2934 649 3306 -650 3970 651 4613 652 5003 653 5595 654 6223 655 6730 656 7375 657 7970 658 8254 660 8886 -662 9243 664 9612 666 9949 668 10258 670 10579 672 10802 674 11050 676 11597 678 11947 680 12173 -682 12403 684 12775 686 13027 688 13415 690 13688 692 14258 205 14470 148 14609 161 14748 379 14888 -225 15026 365 15165 361 15303 160 15441 150 15579 366 15717 364 15853 257 15989 363 16127 307 16263 -149 16402 255 16541 362 16680 151 16818 226 16930 314 17042 384 17154 457 17266 515 17378 546 17490 -591 17602 628 17714 693 17810 694 17923 695 18012 696 18077 140 18145 136 18217 132 18303 128 18389 -124 18474 120 18548 116 18636 112 18724 108 18812 104 18886 100 18998 96 19083 92 19166 88 19248 +349 0 248 54 299 108 301 162 278 216 635 270 641 389 643 503 279 557 283 611 +234 665 233 718 527 772 281 826 280 880 302 934 230 988 367 1042 229 1096 282 1150 +228 1204 640 1258 645 1364 647 1478 346 1532 232 1586 644 1640 648 1733 649 2429 650 2497 +651 2801 652 2929 653 3283 654 3303 655 3675 656 4339 657 4982 658 5372 659 5964 660 6592 +661 7099 662 7744 663 8339 664 8623 666 9255 668 9612 670 9981 672 10318 674 10627 676 10948 +678 11171 680 11419 682 11966 684 12316 686 12542 688 12772 690 13144 692 13396 694 13784 696 14057 +698 14627 205 14839 148 14978 161 15117 379 15257 225 15395 365 15534 361 15672 160 15810 150 15948 +366 16086 364 16222 257 16358 363 16496 307 16632 149 16771 255 16910 362 17049 151 17187 226 17299 +314 17411 384 17523 457 17635 516 17747 549 17859 593 17971 630 18083 699 18187 700 18300 701 18389 +702 18454 140 18522 136 18594 132 18680 128 18766 124 18851 120 18925 116 19013 112 19101 108 19189 +% 349 0 obj +<< +/D [636 0 R /XYZ 93.6 374.324 null] +>> % 248 0 obj << -/D [634 0 R /XYZ 93.6 319.935 null] +/D [636 0 R /XYZ 93.6 319.935 null] >> % 299 0 obj << -/D [634 0 R /XYZ 93.6 268.273 null] +/D [636 0 R /XYZ 93.6 268.273 null] >> % 301 0 obj << -/D [634 0 R /XYZ 93.6 216.611 null] +/D [636 0 R /XYZ 93.6 216.611 null] >> % 278 0 obj << -/D [634 0 R /XYZ 93.6 164.948 null] +/D [636 0 R /XYZ 93.6 164.948 null] >> -% 633 0 obj +% 635 0 obj << /Font << /F42 161 0 R /F15 160 0 R /F17 148 0 R /F18 307 0 R /F45 255 0 R >> /ProcSet [ /PDF /Text ] >> -% 639 0 obj +% 641 0 obj << /Type /Page -/Contents 640 0 R -/Resources 638 0 R +/Contents 642 0 R +/Resources 640 0 R /MediaBox [0 0 595.276 841.89] -/Parent 628 0 R +/Parent 630 0 R >> -% 641 0 obj +% 643 0 obj << -/D [639 0 R /XYZ 85.4 752.957 null] +/D [641 0 R /XYZ 85.4 752.957 null] >> % 279 0 obj << -/D [639 0 R /XYZ 86.4 715.095 null] +/D [641 0 R /XYZ 86.4 715.095 null] >> % 283 0 obj << -/D [639 0 R /XYZ 86.4 670.542 null] +/D [641 0 R /XYZ 86.4 668.665 null] >> % 234 0 obj << -/D [639 0 R /XYZ 86.4 622.659 null] +/D [641 0 R /XYZ 86.4 617.03 null] >> % 233 0 obj << -/D [639 0 R /XYZ 86.4 574.776 null] +/D [641 0 R /XYZ 86.4 565.394 null] +>> +% 527 0 obj +<< +/D [641 0 R /XYZ 86.4 513.455 null] >> % 281 0 obj << -/D [639 0 R /XYZ 86.4 526.59 null] +/D [641 0 R /XYZ 86.4 463.638 null] >> % 280 0 obj << -/D [639 0 R /XYZ 86.4 478.405 null] +/D [641 0 R /XYZ 86.4 409.578 null] >> % 302 0 obj << -/D [639 0 R /XYZ 86.4 429.613 null] +/D [641 0 R /XYZ 86.4 357.034 null] >> % 230 0 obj << -/D [639 0 R /XYZ 86.4 381.427 null] +/D [641 0 R /XYZ 86.4 305.095 null] >> % 367 0 obj << -/D [639 0 R /XYZ 86.4 346.791 null] +/D [641 0 R /XYZ 86.4 266.706 null] >> % 229 0 obj << -/D [639 0 R /XYZ 86.4 325.703 null] +/D [641 0 R /XYZ 86.4 241.865 null] >> % 282 0 obj << -/D [639 0 R /XYZ 86.4 280.245 null] +/D [641 0 R /XYZ 86.4 192.654 null] >> % 228 0 obj << -/D [639 0 R /XYZ 86.4 243.487 null] +/D [641 0 R /XYZ 86.4 152.144 null] +>> +% 640 0 obj +<< +/Font << /F15 160 0 R /F42 161 0 R /F18 307 0 R /F45 255 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 645 0 obj +<< +/Type /Page +/Contents 646 0 R +/Resources 644 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 630 0 R +>> +% 647 0 obj +<< +/D [645 0 R /XYZ 92.6 752.957 null] >> % 346 0 obj << -/D [639 0 R /XYZ 86.4 208.851 null] +/D [645 0 R /XYZ 93.6 715.095 null] >> % 232 0 obj << -/D [639 0 R /XYZ 86.4 160.665 null] +/D [645 0 R /XYZ 93.6 670.434 null] >> -% 638 0 obj +% 644 0 obj << -/Font << /F15 160 0 R /F42 161 0 R /F18 307 0 R /F45 255 0 R >> +/Font << /F42 161 0 R /F15 160 0 R /F18 307 0 R >> /ProcSet [ /PDF /Text ] >> -% 642 0 obj +% 648 0 obj [458.3 458.3 416.7 416.7 472.2 472.2 472.2 472.2 583.3 583.3 472.2 472.2 333.3 555.6 577.8 577.8 597.2 597.2 736.1 736.1 527.8 527.8 583.3 583.3 583.3 583.3 750 750 750 750 1044.4 1044.4 791.7 791.7 583.3 583.3 638.9 638.9 638.9 638.9 805.6 805.6 805.6 805.6 1277.8 1277.8 811.1 811.1 875 875 666.7 666.7 666.7 666.7 666.7 666.7 888.9 888.9 888.9 888.9 888.9 888.9 888.9 666.7 875 875 875 875 611.1 611.1 833.3 1111.1 472.2 555.6 1111.1 1511.1 1111.1 1511.1 1111.1 1511.1 1055.6 944.4 472.2 833.3 833.3 833.3 833.3 833.3 1444.4 1277.8 555.6 1111.1 1111.1 1111.1 1111.1 1111.1 944.4 1277.8 555.6 1000 1444.4 555.6 1000 1444.4 472.2 472.2 527.8 527.8 527.8 527.8 666.7 666.7 1000 1000] -% 643 0 obj +% 649 0 obj [935.2 351.8 416.7 351.8 611.1 611.1 611.1 611.1 611.1] -% 644 0 obj +% 650 0 obj [379.6 963 638.9 963 638.9 658.7 924.1 926.6 883.7 998.3 899.8 775 952.9 999.5 547.7 681.6 1025.7 846.3 1161.6 967.1 934.1 780 966.5 922.1 756.7 731.1 838.1 729.6 1150.9 1001.4 726.4 837.7 509.3 509.3 509.3 1222.2 1222.2 518.5 674.9 547.7 559.1 642.5 589 600.7 607.7 725.7 445.6 511.6 660.9] -% 645 0 obj +% 651 0 obj [826.4 295.1 354.2 295.1 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 295.1 295.1 295.1 826.4] -% 646 0 obj +% 652 0 obj [826.4 295.1 826.4 531.3 826.4 531.3 826.4 826.4 826.4 826.4 826.4 826.4 826.4 1062.5 531.3 531.3 826.4 826.4 826.4 826.4 826.4 826.4 826.4 826.4 826.4 826.4 826.4 826.4 1062.5 1062.5 826.4 826.4 1062.5 1062.5 531.3 531.3 1062.5 1062.5 1062.5 826.4 1062.5 1062.5 649.3 649.3 1062.5 1062.5 1062.5 826.4 288.2 1062.5 708.3 708.3 944.5 944.5 0] -% 647 0 obj +% 653 0 obj [722.2] -% 648 0 obj +% 654 0 obj [295.1 826.4 531.3 826.4 531.3 559.7 795.8 801.4 757.3 871.7 778.7 672.4 827.9 872.8 460.7 580.4 896 722.6 1020.4 843.3 806.2 673.6 835.7 800.2 646.2 618.6 718.8 618.8 1002.4 873.9 615.8 720 413.2 413.2 413.2 1062.5 1062.5 434 564.4 454.5 460.2 546.7 492.9 510.4 505.6 612.3 361.7 429.7 553.2 317.1 939.8 644.7 513.5 534.8 474.4 479.5 491.3 383.7 615.2 517.4] -% 649 0 obj +% 655 0 obj [613.3 562.2 587.8 881.7 894.4 306.7 332.2 511.1 511.1 511.1 511.1 511.1 831.3 460 536.7 715.6 715.6 511.1 882.8 985 766.7 255.6 306.7 514.4 817.8 769.1 817.8 766.7 306.7 408.9 408.9 511.1 766.7 306.7 357.8 306.7 511.1 511.1 511.1 511.1 511.1 511.1 511.1 511.1 511.1 511.1 511.1 306.7 306.7 306.7 766.7 511.1 511.1 766.7 743.3 703.9 715.6 755 678.3 652.8 773.6 743.3 385.6 525 768.9 627.2 896.7 743.3 766.7 678.3 766.7 729.4 562.2 715.6 743.3 743.3 998.9 743.3 743.3 613.3 306.7 514.4 306.7 511.1 306.7 306.7 511.1 460 460 511.1 460 306.7 460 511.1 306.7 306.7 460 255.6 817.8 562.2 511.1 511.1 460 421.7 408.9 332.2 536.7 460 664.4 463.9 485.6 408.9] -% 650 0 obj +% 656 0 obj [777.8 277.8 777.8 500 777.8 500 777.8 777.8 777.8 777.8 777.8 777.8 777.8 1000 500 500 777.8 777.8 777.8 777.8 777.8 777.8 777.8 777.8 777.8 777.8 777.8 777.8 1000 1000 777.8 777.8 1000 1000 500 500 1000 1000 1000 777.8 1000 1000 611.1 611.1 1000 1000 1000 777.8 275 1000 666.7 666.7 888.9 888.9 0 0 555.6 555.6 666.7 500 722.2 722.2 777.8 777.8 611.1 798.5 656.8 526.5 771.4 527.8 718.7 594.9 844.5 544.5 677.8 762 689.7 1200.9 820.5 796.1 695.6 816.7 847.5 605.6 544.6 625.8 612.8 987.8 713.3 668.3 724.7 666.7 666.7 666.7 666.7 666.7 611.1 611.1 444.4 444.4 444.4 444.4 500 500 388.9 388.9 277.8 500 500 611.1 500 277.8 833.3] -% 651 0 obj +% 657 0 obj [525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525] -% 652 0 obj +% 658 0 obj [469.4 353.9 576.2 583.3 602.5 494 437.5 570 517 571.4 437.2 540.3 595.8 625.7 651.4 622.5 466.3 591.4 828.1 517 362.8 654.2 1000 1000 1000 1000 277.8 277.8 500 500 500 500 500 500 500 500 500 500 500 500 277.8 277.8 777.8 500 777.8 500 530.9 750 758.5 714.7 827.9 738.2 643.1 786.2 831.3 439.6 554.5 849.3 680.6 970.1 803.5 762.8 642 790.6 759.3 613.2 584.4 682.8 583.3 944.4 828.5 580.6 682.6 388.9 388.9 388.9 1000 1000 416.7 528.6 429.2 432.8 520.5 465.6 489.6 477 576.2 344.5 411.8 520.6 298.4 878 600.2 484.7 503.1 446.4 451.2 468.7 361.1 572.5 484.7 715.9 571.5 490.3 465] -% 653 0 obj +% 659 0 obj [638.9 638.9 958.3 958.3 319.4 351.4 575 575 575 575 575 869.4 511.1 597.2 830.6 894.4 575 1041.7 1169.4 894.4 319.4 350 602.8 958.3 575 958.3 894.4 319.4 447.2 447.2 575 894.4 319.4 383.3 319.4 575 575 575 575 575 575 575 575 575 575 575 319.4 319.4 350 894.4 543.1 543.1 894.4 869.4 818.1 830.6 881.9 755.5 723.6 904.2 900 436.1 594.4 901.4 691.7 1091.7 900 863.9 786.1 863.9 862.5 638.9 800 884.7 869.4 1188.9 869.4 869.4 702.8 319.4 602.8 319.4 575 319.4 319.4 559 638.9 511.1 638.9 527.1 351.4 575 638.9 319.4 351.4 606.9 319.4 958.3 638.9 575 638.9 606.9 473.6 453.6 447.2 638.9 606.9 830.6 606.9 606.9 511.1] -% 654 0 obj +% 660 0 obj [319.4 436.1 436.1 552.8 844.4 319.4 377.8 319.4 552.8 552.8 552.8 552.8 552.8 552.8 552.8 552.8 552.8 552.8 552.8 319.4 319.4 844.4 844.4 844.4 523.6 844.4 813.9 770.8 786.1 829.2 741.7 712.5 851.4 813.9 405.6 566.7 843 683.3 988.9 813.9 844.4 741.7 844.4 800 611.1 786.1 813.9 813.9 1105.5 813.9 813.9 669.4 319.4 552.8 319.4 552.8 319.4 319.4 613.3 580 591.1 624.4 557.8 535.6 641.1 613.3 302.2 424.4 635.6 513.3 746.7 613.3 635.6 557.8 635.6 602.2 457.8 591.1 613.3 613.3 835.6 613.3 613.3] -% 655 0 obj +% 661 0 obj [722.2 583.3 555.6 555.6 833.3 833.3 277.8 305.6 500 500 500 500 500 750 444.4 500 722.2 777.8 500 902.8 1013.9 777.8 277.8 277.8 500 833.3 500 833.3 777.8 277.8 388.9 388.9 500 777.8 277.8 333.3 277.8 500 500 500 500 500 500 500 500 500 500 500 277.8 277.8 277.8 777.8 472.2 472.2 777.8 750 708.3 722.2 763.9 680.6 652.8 784.7 750 361.1 513.9 777.8 625 916.7 750 777.8 680.6 777.8 736.1 555.6 722.2 750 750 1027.8 750 750 611.1 277.8 500 277.8 500 277.8 277.8 500 555.6 444.4 555.6 444.4 305.6 500 555.6 277.8 305.6 527.8 277.8 833.3 555.6 500 555.6 527.8 391.7 394.4 388.9 555.6 527.8 722.2 527.8 527.8 444.4 500 1000 500 500 500] -% 656 0 obj +% 662 0 obj [544 544 816 816 272 299.2 489.6 489.6 489.6 489.6 489.6 734 435.2 489.6 707.2 761.6 489.6 883.8 992.6 761.6 272 272 489.6 816 489.6 816 761.6 272 380.8 380.8 489.6 761.6 272 326.4 272 489.6 489.6 489.6 489.6 489.6 489.6 489.6 489.6 489.6 489.6 489.6 272 272 272 761.6 462.4 462.4 761.6 734 693.4 707.2 747.8 666.2 639 768.3 734 353.2 503 761.2 611.8 897.2 734 761.6 666.2 761.6 720.6 544 707.2 734 734 1006 734 734 598.4 272 489.6 272 489.6 272 272 489.6 544 435.2 544 435.2 299.2 489.6 544 272 299.2 516.8 272 816 544 489.6 544 516.8 380.8 386.2 380.8 544 516.8 707.2 516.8 516.8] -% 657 0 obj +% 663 0 obj [726.9 688.4 700 738.4 663.4 638.4 756.7 726.9 376.9 513.4 751.9 613.4 876.9 726.9 750 663.4 750 713.4 550 700 726.9 726.9 976.9 726.9 726.9 600 300 500 300 500 300 300 500 450 450 500 450 300 450 500 300 300 450 250 800 550 500 500 450 412.5 400 325 525 450 650 450 475] -% 658 0 obj +% 664 0 obj [625 625 937.5 937.5 312.5 343.7 562.5 562.5 562.5 562.5 562.5 849.5 500 574.1 812.5 875 562.5 1018.5 1143.5 875 312.5 342.6 581 937.5 562.5 937.5 875 312.5 437.5 437.5 562.5 875 312.5 375 312.5 562.5 562.5 562.5 562.5 562.5 562.5 562.5 562.5 562.5 562.5 562.5 312.5 312.5 342.6 875 531.2 531.2 875 849.5 799.8 812.5 862.3 738.4 707.2 884.3 879.6 419 581 880.8 675.9 1067.1 879.6 844.9 768.5 844.9 839.1 625 782.4 864.6 849.5 1162 849.5 849.5 687.5 312.5 581 312.5 562.5 312.5 312.5 546.9 625 500 625 513.3 343.7 562.5 625 312.5 343.7 593.7 312.5 937.5 625 562.5 625 593.7 459.5 443.8 437.5 625 593.7 812.5 593.7 593.7] -% 660 0 obj +% 666 0 obj << /Type /FontDescriptor /FontName /WOELMG+CMBX10 @@ -9539,9 +9589,9 @@ stream /StemV 114 /XHeight 444 /CharSet (/A/B/C/D/E/F/G/H/I/K/L/M/N/O/P/R/S/U/a/b/c/colon/d/e/eight/f/fi/five/four/g/h/i/j/k/l/m/n/nine/o/one/p/period/r/s/seven/six/t/three/two/u/v/w/z) -/FontFile 659 0 R +/FontFile 665 0 R >> -% 662 0 obj +% 668 0 obj << /Type /FontDescriptor /FontName /XCHSJH+CMBX12 @@ -9554,9 +9604,9 @@ stream /StemV 109 /XHeight 444 /CharSet (/A/B/C/D/E/F/G/H/I/L/M/O/P/R/S/U/a/b/c/d/e/eight/f/fi/five/four/g/h/hyphen/i/j/k/l/m/n/nine/o/one/p/period/q/quoteright/r/s/seven/six/t/three/two/u/v/w/x/y) -/FontFile 661 0 R +/FontFile 667 0 R >> -% 664 0 obj +% 670 0 obj << /Type /FontDescriptor /FontName /EYIYGL+CMCSC10 @@ -9569,9 +9619,9 @@ stream /StemV 72 /XHeight 431 /CharSet (/A/B/C/D/E/G/I/L/M/O/P/R/S/U/a/b/c/d/e/eight/f/five/four/g/h/i/k/l/m/n/o/one/p/parenleft/quoteright/r/s/six/t/three/two/u/v/w/y) -/FontFile 663 0 R +/FontFile 669 0 R >> -% 666 0 obj +% 672 0 obj << /Type /FontDescriptor /FontName /YJJMFD+CMEX10 @@ -9584,9 +9634,9 @@ stream /StemV 47 /XHeight 431 /CharSet (/braceleftbigg/bracerightbigg/parenleftbig/parenrightbig/radicalBig/summationdisplay/summationtext) -/FontFile 665 0 R +/FontFile 671 0 R >> -% 668 0 obj +% 674 0 obj << /Type /FontDescriptor /FontName /VFYBNB+CMMI10 @@ -9599,9 +9649,9 @@ stream /StemV 72 /XHeight 431 /CharSet (/A/B/D/I/L/M/P/R/S/U/a/b/comma/e/greater/i/j/k/l/less/m/n/o/omega/p/period/r/rho/slash/t/theta/u/v/w/x/y/z) -/FontFile 667 0 R +/FontFile 673 0 R >> -% 670 0 obj +% 676 0 obj << /Type /FontDescriptor /FontName /PNUTJM+CMMI6 @@ -9614,9 +9664,9 @@ stream /StemV 85 /XHeight 431 /CharSet (/comma/i/k) -/FontFile 669 0 R +/FontFile 675 0 R >> -% 672 0 obj +% 678 0 obj << /Type /FontDescriptor /FontName /TWBVYQ+CMMI8 @@ -9629,9 +9679,9 @@ stream /StemV 78 /XHeight 431 /CharSet (/A/C/F/S/T/comma/e/i/j/k/l/m/n/r/v) -/FontFile 671 0 R +/FontFile 677 0 R >> -% 674 0 obj +% 680 0 obj << /Type /FontDescriptor /FontName /DKEMOU+CMR10 @@ -9644,12 +9694,12 @@ stream /StemV 69 /XHeight 431 /CharSet (/A/B/C/D/E/F/G/H/I/J/K/L/M/N/O/Omega/P/R/S/T/U/V/W/X/Y/a/b/bracketleft/bracketright/c/caron/colon/comma/d/dieresis/e/eight/endash/equal/f/ff/ffi/fi/five/fl/four/g/h/hyphen/i/j/k/l/m/macron/n/nine/o/one/p/parenleft/parenright/period/plus/q/quotedblleft/quotedblright/quoteright/r/s/semicolon/seven/six/slash/t/three/two/u/v/w/x/y/z/zero) -/FontFile 673 0 R +/FontFile 679 0 R >> -% 676 0 obj +% 682 0 obj << /Type /FontDescriptor -/FontName /SNVSAK+CMR12 +/FontName /OIRSPO+CMR12 /Flags 4 /FontBBox [-34 -251 988 750] /Ascent 694 @@ -9658,10 +9708,10 @@ stream /ItalicAngle 0 /StemV 65 /XHeight 431 -/CharSet (/A/C/I/J/K/L/N/R/S/U/V/a/colon/comma/d/e/f/fi/g/hyphen/i/l/m/n/o/one/p/period/quotedblleft/quotedblright/r/s/seven/t/three/two/u/v/w/y/zero) -/FontFile 675 0 R +/CharSet (/A/C/I/J/K/L/N/R/S/U/V/a/colon/comma/d/e/eight/f/fi/g/hyphen/i/l/m/n/o/one/p/period/quotedblleft/quotedblright/r/s/t/three/two/u/v/w/y/zero) +/FontFile 681 0 R >> -% 678 0 obj +% 684 0 obj << /Type /FontDescriptor /FontName /VROLGE+CMR6 @@ -9674,9 +9724,9 @@ stream /StemV 83 /XHeight 431 /CharSet (/one/plus/three) -/FontFile 677 0 R +/FontFile 683 0 R >> -% 680 0 obj +% 686 0 obj << /Type /FontDescriptor /FontName /ABQBBP+CMR8 @@ -9689,9 +9739,9 @@ stream /StemV 76 /XHeight 431 /CharSet (/equal/one/plus/two) -/FontFile 679 0 R +/FontFile 685 0 R >> -% 682 0 obj +% 688 0 obj << /Type /FontDescriptor /FontName /NSLWFJ+CMSY10 @@ -9704,9 +9754,9 @@ stream /StemV 40 /XHeight 431 /CharSet (/N/bar/bardbl/braceleft/braceright/bullet/element/equivalence/floorleft/floorright/greaterequal/minus/negationslash/propersubset/propersuperset/radical/union) -/FontFile 681 0 R +/FontFile 687 0 R >> -% 684 0 obj +% 690 0 obj << /Type /FontDescriptor /FontName /JHSYKM+CMSY8 @@ -9719,9 +9769,9 @@ stream /StemV 46 /XHeight 431 /CharSet (/infinity/minus/multiply/negationslash) -/FontFile 683 0 R +/FontFile 689 0 R >> -% 686 0 obj +% 692 0 obj << /Type /FontDescriptor /FontName /FPIMLF+CMTI10 @@ -9734,9 +9784,9 @@ stream /StemV 68 /XHeight 431 /CharSet (/A/B/C/D/E/F/G/I/K/L/M/N/O/P/R/S/T/U/V/a/b/c/colon/comma/d/e/eight/f/ff/fi/five/four/g/h/hyphen/i/j/k/l/m/n/nine/o/one/p/period/q/quoteright/r/s/t/three/two/u/v/w/x/y/z/zero) -/FontFile 685 0 R +/FontFile 691 0 R >> -% 688 0 obj +% 694 0 obj << /Type /FontDescriptor /FontName /YRQLNB+CMTI12 @@ -9749,9 +9799,9 @@ stream /StemV 63 /XHeight 431 /CharSet (/A/B/D/L/M/P/S/T/a/b/c/d/e/f/g/h/i/k/l/m/n/o/p/r/s/t/u/v/y) -/FontFile 687 0 R +/FontFile 693 0 R >> -% 690 0 obj +% 696 0 obj << /Type /FontDescriptor /FontName /SBOMTR+CMTT10 @@ -9764,9 +9814,9 @@ stream /StemV 69 /XHeight 431 /CharSet (/A/B/C/D/E/F/G/H/I/J/K/L/M/N/O/P/Q/R/S/T/U/V/W/X/Y/Z/a/asciitilde/asterisk/b/backslash/bracketleft/bracketright/c/colon/comma/d/dollar/e/eight/equal/exclam/f/five/four/g/greater/h/hyphen/i/j/k/l/less/m/n/nine/o/one/p/parenleft/parenright/percent/period/plus/q/quotedbl/quoteleft/quoteright/r/s/semicolon/seven/six/slash/t/three/two/u/underscore/v/w/x/y/z/zero) -/FontFile 689 0 R +/FontFile 695 0 R >> -% 692 0 obj +% 698 0 obj << /Type /FontDescriptor /FontName /QDTWCG+MSBM10 @@ -9779,262 +9829,262 @@ stream /StemV 40 /XHeight 463 /CharSet (/R) -/FontFile 691 0 R +/FontFile 697 0 R >> % 205 0 obj << /Type /Font /Subtype /Type1 /BaseFont /WOELMG+CMBX10 -/FontDescriptor 660 0 R +/FontDescriptor 666 0 R /FirstChar 12 /LastChar 122 -/Widths 653 0 R +/Widths 659 0 R >> % 148 0 obj << /Type /Font /Subtype /Type1 /BaseFont /XCHSJH+CMBX12 -/FontDescriptor 662 0 R +/FontDescriptor 668 0 R /FirstChar 12 /LastChar 121 -/Widths 658 0 R +/Widths 664 0 R >> % 161 0 obj << /Type /Font /Subtype /Type1 /BaseFont /EYIYGL+CMCSC10 -/FontDescriptor 664 0 R +/FontDescriptor 670 0 R /FirstChar 39 /LastChar 121 -/Widths 654 0 R +/Widths 660 0 R >> % 379 0 obj << /Type /Font /Subtype /Type1 /BaseFont /YJJMFD+CMEX10 -/FontDescriptor 666 0 R +/FontDescriptor 672 0 R /FirstChar 0 /LastChar 113 -/Widths 642 0 R +/Widths 648 0 R >> % 225 0 obj << /Type /Font /Subtype /Type1 /BaseFont /VFYBNB+CMMI10 -/FontDescriptor 668 0 R +/FontDescriptor 674 0 R /FirstChar 18 /LastChar 122 -/Widths 652 0 R +/Widths 658 0 R >> % 365 0 obj << /Type /Font /Subtype /Type1 /BaseFont /PNUTJM+CMMI6 -/FontDescriptor 670 0 R +/FontDescriptor 676 0 R /FirstChar 59 /LastChar 107 -/Widths 644 0 R +/Widths 650 0 R >> % 361 0 obj << /Type /Font /Subtype /Type1 /BaseFont /TWBVYQ+CMMI8 -/FontDescriptor 672 0 R +/FontDescriptor 678 0 R /FirstChar 59 /LastChar 118 -/Widths 648 0 R +/Widths 654 0 R >> % 160 0 obj << /Type /Font /Subtype /Type1 /BaseFont /DKEMOU+CMR10 -/FontDescriptor 674 0 R +/FontDescriptor 680 0 R /FirstChar 10 /LastChar 127 -/Widths 655 0 R +/Widths 661 0 R >> % 150 0 obj << /Type /Font /Subtype /Type1 -/BaseFont /SNVSAK+CMR12 -/FontDescriptor 676 0 R +/BaseFont /OIRSPO+CMR12 +/FontDescriptor 682 0 R /FirstChar 12 /LastChar 121 -/Widths 656 0 R +/Widths 662 0 R >> % 366 0 obj << /Type /Font /Subtype /Type1 /BaseFont /VROLGE+CMR6 -/FontDescriptor 678 0 R +/FontDescriptor 684 0 R /FirstChar 43 /LastChar 51 -/Widths 643 0 R +/Widths 649 0 R >> % 364 0 obj << /Type /Font /Subtype /Type1 /BaseFont /ABQBBP+CMR8 -/FontDescriptor 680 0 R +/FontDescriptor 686 0 R /FirstChar 43 /LastChar 61 -/Widths 645 0 R +/Widths 651 0 R >> % 257 0 obj << /Type /Font /Subtype /Type1 /BaseFont /NSLWFJ+CMSY10 -/FontDescriptor 682 0 R +/FontDescriptor 688 0 R /FirstChar 0 /LastChar 112 -/Widths 650 0 R +/Widths 656 0 R >> % 363 0 obj << /Type /Font /Subtype /Type1 /BaseFont /JHSYKM+CMSY8 -/FontDescriptor 684 0 R +/FontDescriptor 690 0 R /FirstChar 0 /LastChar 54 -/Widths 646 0 R +/Widths 652 0 R >> % 307 0 obj << /Type /Font /Subtype /Type1 /BaseFont /FPIMLF+CMTI10 -/FontDescriptor 686 0 R +/FontDescriptor 692 0 R /FirstChar 11 /LastChar 122 -/Widths 649 0 R +/Widths 655 0 R >> % 149 0 obj << /Type /Font /Subtype /Type1 /BaseFont /YRQLNB+CMTI12 -/FontDescriptor 688 0 R +/FontDescriptor 694 0 R /FirstChar 65 /LastChar 121 -/Widths 657 0 R +/Widths 663 0 R >> % 255 0 obj << /Type /Font /Subtype /Type1 /BaseFont /SBOMTR+CMTT10 -/FontDescriptor 690 0 R +/FontDescriptor 696 0 R /FirstChar 33 /LastChar 126 -/Widths 651 0 R +/Widths 657 0 R >> % 362 0 obj << /Type /Font /Subtype /Type1 /BaseFont /QDTWCG+MSBM10 -/FontDescriptor 692 0 R +/FontDescriptor 698 0 R /FirstChar 82 /LastChar 82 -/Widths 647 0 R +/Widths 653 0 R >> % 151 0 obj << /Type /Pages /Count 6 -/Parent 693 0 R +/Parent 699 0 R /Kids [143 0 R 153 0 R 157 0 R 163 0 R 201 0 R 208 0 R] >> % 226 0 obj << /Type /Pages /Count 6 -/Parent 693 0 R +/Parent 699 0 R /Kids [222 0 R 246 0 R 252 0 R 272 0 R 294 0 R 304 0 R] >> % 314 0 obj << /Type /Pages /Count 6 -/Parent 693 0 R +/Parent 699 0 R /Kids [310 0 R 316 0 R 321 0 R 326 0 R 343 0 R 357 0 R] >> % 384 0 obj << /Type /Pages /Count 6 -/Parent 693 0 R +/Parent 699 0 R /Kids [376 0 R 391 0 R 400 0 R 413 0 R 432 0 R 445 0 R] >> % 457 0 obj << /Type /Pages /Count 6 -/Parent 693 0 R +/Parent 699 0 R /Kids [454 0 R 459 0 R 465 0 R 471 0 R 483 0 R 495 0 R] >> -% 515 0 obj +% 516 0 obj << /Type /Pages /Count 6 -/Parent 693 0 R -/Kids [512 0 R 517 0 R 522 0 R 527 0 R 533 0 R 537 0 R] +/Parent 699 0 R +/Kids [513 0 R 518 0 R 523 0 R 529 0 R 535 0 R 539 0 R] >> -% 546 0 obj +% 549 0 obj << /Type /Pages /Count 6 -/Parent 694 0 R -/Kids [543 0 R 549 0 R 557 0 R 566 0 R 577 0 R 582 0 R] +/Parent 700 0 R +/Kids [545 0 R 551 0 R 559 0 R 568 0 R 579 0 R 584 0 R] >> -% 591 0 obj +% 593 0 obj << /Type /Pages /Count 6 -/Parent 694 0 R -/Kids [588 0 R 596 0 R 603 0 R 608 0 R 615 0 R 619 0 R] +/Parent 700 0 R +/Kids [590 0 R 598 0 R 605 0 R 610 0 R 617 0 R 621 0 R] >> -% 628 0 obj +% 630 0 obj << /Type /Pages -/Count 4 -/Parent 694 0 R -/Kids [625 0 R 630 0 R 634 0 R 639 0 R] +/Count 5 +/Parent 700 0 R +/Kids [627 0 R 632 0 R 636 0 R 641 0 R 645 0 R] >> -% 693 0 obj +% 699 0 obj << /Type /Pages /Count 36 -/Parent 695 0 R -/Kids [151 0 R 226 0 R 314 0 R 384 0 R 457 0 R 515 0 R] +/Parent 701 0 R +/Kids [151 0 R 226 0 R 314 0 R 384 0 R 457 0 R 516 0 R] >> -% 694 0 obj +% 700 0 obj << /Type /Pages -/Count 16 -/Parent 695 0 R -/Kids [546 0 R 591 0 R 628 0 R] +/Count 17 +/Parent 701 0 R +/Kids [549 0 R 593 0 R 630 0 R] >> -% 695 0 obj +% 701 0 obj << /Type /Pages -/Count 52 -/Kids [693 0 R 694 0 R] +/Count 53 +/Kids [699 0 R 700 0 R] >> -% 696 0 obj +% 702 0 obj << /Type /Outlines /First 4 0 R @@ -10110,6 +10160,32 @@ stream /Parent 104 0 R /Next 112 0 R >> + +endstream +endobj +737 0 obj +<< + /Title (MultiLevel Domain Decomposition Parallel Preconditioners Package based on PSBLAS, V. 2.2) /Subject (MultiLevel Domain Decomposition Parallel Preconditioners Package) /Keywords (Parallel Numerical Software, Algebraic Multilevel Preconditioners, Sparse Iterative Solvers, PSBLAS, MPI) /Creator (pdfLaTeX) /Producer ($Id: userguide.tex 2008-04-08 Pasqua D'Ambra, Daniela di Serafino, Salvatore Filippone$) /Author()/Title()/Subject()/Creator(LaTeX with hyperref package)/Producer(pdfTeX-1.40.17)/Keywords() +/CreationDate (D:20180514140750+01'00') +/ModDate (D:20180514140750+01'00') +/Trapped /False +/PTEX.Fullbanner (This is pdfTeX, Version 3.14159265-2.6-1.40.17 (TeX Live 2016) kpathsea version 6.2.2) +>> +endobj +703 0 obj +<< +/Type /ObjStm +/N 59 +/First 491 +/Length 8047 +>> +stream +104 0 100 112 96 197 92 280 88 362 84 444 80 526 76 608 72 690 68 759 +64 879 60 935 56 1053 52 1122 48 1204 44 1273 40 1391 36 1460 32 1542 28 1624 +24 1706 20 1775 16 1893 12 1974 8 2054 4 2119 704 2211 705 2379 706 2536 707 2736 +708 2945 709 3164 710 3392 711 3592 712 3785 713 3953 714 4118 715 4282 716 4447 717 4611 +718 4776 719 4939 720 5100 721 5262 722 5444 723 5621 724 5836 725 6051 726 6267 727 6504 +728 6669 729 6760 730 6869 731 6976 732 7082 733 7188 734 7252 735 7350 736 7383 % 104 0 obj << /Title 105 0 R @@ -10152,32 +10228,6 @@ stream /Prev 84 0 R /Next 92 0 R >> - -endstream -endobj -729 0 obj -<< - /Title (MultiLevel Domain Decomposition Parallel Preconditioners Package based on PSBLAS, V. 2.1) /Subject (MultiLevel Domain Decomposition Parallel Preconditioners Package) /Keywords (Parallel Numerical Software, Algebraic Multilevel Preconditioners, Sparse Iterative Solvers, PSBLAS, MPI) /Creator (pdfLaTeX) /Producer ($Id: userguide.tex 2008-04-08 Pasqua D'Ambra, Daniela di Serafino, Salvatore Filippone$) /Author()/Title()/Subject()/Creator(LaTeX with hyperref package)/Producer(pdfTeX-1.40.17)/Keywords() -/CreationDate (D:20180127175957Z) -/ModDate (D:20180127175957Z) -/Trapped /False -/PTEX.Fullbanner (This is pdfTeX, Version 3.14159265-2.6-1.40.17 (TeX Live 2016) kpathsea version 6.2.2) ->> -endobj -697 0 obj -<< -/Type /ObjStm -/N 52 -/First 430 -/Length 7383 ->> -stream -84 0 80 82 76 164 72 246 68 315 64 435 60 491 56 609 52 678 48 760 -44 829 40 947 36 1016 32 1098 28 1180 24 1262 20 1331 16 1449 12 1530 8 1610 -4 1675 698 1767 699 1935 700 2092 701 2292 702 2499 703 2732 704 2946 705 3148 706 3337 -707 3504 708 3669 709 3833 710 3998 711 4161 712 4324 713 4489 714 4648 715 4819 716 4999 -717 5191 718 5406 719 5621 720 5854 721 6067 722 6230 723 6339 724 6446 725 6551 726 6657 -727 6747 728 6780 % 84 0 obj << /Title 85 0 R @@ -10346,194 +10396,205 @@ stream << /Title 5 0 R /A 1 0 R -/Parent 696 0 R +/Parent 702 0 R /First 8 0 R /Last 140 0 R /Count -11 >> -% 698 0 obj +% 704 0 obj << /Names [(Doc-Start) 147 0 R (Item.1) 380 0 R (Item.10) 498 0 R (Item.11) 499 0 R (Item.12) 500 0 R (Item.13) 501 0 R] /Limits [(Doc-Start) (Item.13)] >> -% 699 0 obj +% 705 0 obj << /Names [(Item.2) 381 0 R (Item.3) 382 0 R (Item.4) 416 0 R (Item.5) 417 0 R (Item.6) 418 0 R (Item.7) 419 0 R] /Limits [(Item.2) (Item.7)] >> -% 700 0 obj +% 706 0 obj << /Names [(Item.8) 420 0 R (Item.9) 421 0 R (appendix.A) 135 0 R (cite.BREZINA_VANEK) 231 0 R (cite.Briggs2000) 227 0 R (cite.CAI_SARKIS) 403 0 R] /Limits [(Item.8) (cite.CAI_SARKIS)] >> -% 701 0 obj -<< -/Names [(cite.MLD2P4_TOMS) 248 0 R (cite.MPI1) 282 0 R (cite.MPI2) 281 0 R (cite.MUMPS) 300 0 R (cite.Notay2008) 230 0 R (cite.PSBLAS3) 234 0 R] -/Limits [(cite.MLD2P4_TOMS) (cite.PSBLAS3)] ->> -% 702 0 obj -<< -/Names [(cite.PSBLASGUIDE) 283 0 R (cite.SUPERLU) 301 0 R (cite.SUPERLUDIST) 302 0 R (cite.Saad_book) 367 0 R (cite.Stuben_01) 228 0 R (cite.TUMINARO_TONG) 346 0 R] -/Limits [(cite.PSBLASGUIDE) (cite.TUMINARO_TONG)] ->> -% 703 0 obj -<< -/Names [(cite.UMFPACK) 299 0 R (cite.VANEK_MANDEL_BREZINA) 232 0 R (cite.aaecc_07) 348 0 R (cite.apnum_07) 349 0 R (cite.blas1) 280 0 R (cite.blas2) 279 0 R] -/Limits [(cite.UMFPACK) (cite.blas2)] ->> -% 704 0 obj -<< -/Names [(cite.blas3) 278 0 R (cite.dd2_96) 229 0 R (cite.para_04) 347 0 R (cite.psblas_00) 233 0 R (equation.1.1) 224 0 R (equation.4.2) 360 0 R] -/Limits [(cite.blas3) (equation.4.2)] ->> -% 705 0 obj -<< -/Names [(equation.4.3) 383 0 R (equation.4.4) 394 0 R (equation.4.5) 395 0 R (figure.1) 368 0 R (figure.2) 448 0 R (figure.3) 449 0 R] -/Limits [(equation.4.3) (figure.3)] ->> -% 706 0 obj -<< -/Names [(figure.4) 450 0 R (figure.5) 451 0 R (page.1) 146 0 R (page.10) 328 0 R (page.11) 345 0 R (page.12) 359 0 R] -/Limits [(figure.4) (page.12)] ->> % 707 0 obj << -/Names [(page.13) 378 0 R (page.14) 393 0 R (page.15) 402 0 R (page.16) 415 0 R (page.17) 434 0 R (page.18) 447 0 R] -/Limits [(page.13) (page.18)] +/Names [(cite.GrHeJi:16) 527 0 R (cite.MLD2P4_TOMS) 248 0 R (cite.MPI1) 282 0 R (cite.MPI2) 281 0 R (cite.MUMPS) 300 0 R (cite.Notay2008) 230 0 R] +/Limits [(cite.GrHeJi:16) (cite.Notay2008)] >> % 708 0 obj << -/Names [(page.19) 456 0 R (page.2) 155 0 R (page.20) 461 0 R (page.21) 467 0 R (page.22) 473 0 R (page.23) 485 0 R] -/Limits [(page.19) (page.23)] +/Names [(cite.PSBLAS3) 234 0 R (cite.PSBLASGUIDE) 283 0 R (cite.SUPERLU) 301 0 R (cite.SUPERLUDIST) 302 0 R (cite.Saad_book) 367 0 R (cite.Stuben_01) 228 0 R] +/Limits [(cite.PSBLAS3) (cite.Stuben_01)] >> % 709 0 obj << -/Names [(page.24) 497 0 R (page.25) 514 0 R (page.26) 519 0 R (page.27) 524 0 R (page.28) 529 0 R (page.29) 535 0 R] -/Limits [(page.24) (page.29)] +/Names [(cite.TUMINARO_TONG) 346 0 R (cite.UMFPACK) 299 0 R (cite.VANEK_MANDEL_BREZINA) 232 0 R (cite.aaecc_07) 348 0 R (cite.apnum_07) 349 0 R (cite.blas1) 280 0 R] +/Limits [(cite.TUMINARO_TONG) (cite.blas1)] >> % 710 0 obj << -/Names [(page.3) 254 0 R (page.30) 539 0 R (page.31) 545 0 R (page.32) 551 0 R (page.33) 559 0 R (page.34) 568 0 R] -/Limits [(page.3) (page.34)] +/Names [(cite.blas2) 279 0 R (cite.blas3) 278 0 R (cite.dd2_96) 229 0 R (cite.para_04) 347 0 R (cite.psblas_00) 233 0 R (equation.1.1) 224 0 R] +/Limits [(cite.blas2) (equation.1.1)] >> % 711 0 obj << -/Names [(page.35) 579 0 R (page.36) 584 0 R (page.37) 590 0 R (page.38) 598 0 R (page.39) 605 0 R (page.4) 274 0 R] -/Limits [(page.35) (page.4)] +/Names [(equation.4.2) 360 0 R (equation.4.3) 383 0 R (equation.4.4) 394 0 R (equation.4.5) 395 0 R (figure.1) 368 0 R (figure.2) 448 0 R] +/Limits [(equation.4.2) (figure.2)] >> % 712 0 obj << -/Names [(page.40) 610 0 R (page.41) 617 0 R (page.42) 621 0 R (page.43) 627 0 R (page.44) 632 0 R (page.45) 636 0 R] -/Limits [(page.40) (page.45)] +/Names [(figure.3) 449 0 R (figure.4) 450 0 R (figure.5) 451 0 R (page.1) 146 0 R (page.10) 328 0 R (page.11) 345 0 R] +/Limits [(figure.3) (page.11)] >> % 713 0 obj << -/Names [(page.46) 641 0 R (page.5) 296 0 R (page.6) 306 0 R (page.7) 312 0 R (page.8) 318 0 R (page.9) 323 0 R] -/Limits [(page.46) (page.9)] +/Names [(page.12) 359 0 R (page.13) 378 0 R (page.14) 393 0 R (page.15) 402 0 R (page.16) 415 0 R (page.17) 434 0 R] +/Limits [(page.12) (page.17)] >> % 714 0 obj << -/Names [(page.i) 159 0 R (page.ii) 165 0 R (page.iii) 203 0 R (page.iv) 210 0 R (section*.1) 7 0 R (section*.2) 204 0 R] -/Limits [(page.i) (section*.2)] +/Names [(page.18) 447 0 R (page.19) 456 0 R (page.2) 155 0 R (page.20) 461 0 R (page.21) 467 0 R (page.22) 473 0 R] +/Limits [(page.18) (page.22)] >> % 715 0 obj << -/Names [(section*.3) 256 0 R (section*.4) 139 0 R (section.1) 11 0 R (section.2) 15 0 R (section.3) 19 0 R (section.4) 43 0 R] -/Limits [(section*.3) (section.4)] +/Names [(page.23) 485 0 R (page.24) 497 0 R (page.25) 515 0 R (page.26) 520 0 R (page.27) 525 0 R (page.28) 531 0 R] +/Limits [(page.23) (page.28)] >> % 716 0 obj << -/Names [(section.5) 59 0 R (section.6) 67 0 R (section.7) 127 0 R (section.8) 131 0 R (subsection.3.1) 23 0 R (subsection.3.2) 27 0 R] -/Limits [(section.5) (subsection.3.2)] +/Names [(page.29) 537 0 R (page.3) 254 0 R (page.30) 541 0 R (page.31) 547 0 R (page.32) 553 0 R (page.33) 561 0 R] +/Limits [(page.29) (page.33)] >> % 717 0 obj << -/Names [(subsection.3.3) 31 0 R (subsection.3.4) 35 0 R (subsection.3.5) 39 0 R (subsection.4.1) 47 0 R (subsection.4.2) 51 0 R (subsection.4.3) 55 0 R] -/Limits [(subsection.3.3) (subsection.4.3)] +/Names [(page.34) 570 0 R (page.35) 581 0 R (page.36) 586 0 R (page.37) 592 0 R (page.38) 600 0 R (page.39) 607 0 R] +/Limits [(page.34) (page.39)] >> % 718 0 obj << -/Names [(subsection.5.1) 63 0 R (subsection.6.1) 71 0 R (subsection.6.2) 75 0 R (subsection.6.3) 79 0 R (subsection.6.4) 83 0 R (subsection.6.5) 87 0 R] -/Limits [(subsection.5.1) (subsection.6.5)] +/Names [(page.4) 274 0 R (page.40) 612 0 R (page.41) 619 0 R (page.42) 623 0 R (page.43) 629 0 R (page.44) 634 0 R] +/Limits [(page.4) (page.44)] >> % 719 0 obj << -/Names [(subsection.6.6) 91 0 R (subsection.6.7) 95 0 R (subsection.6.8) 99 0 R (subsection.6.9) 103 0 R (subsubsection.6.9.1) 107 0 R (subsubsection.6.9.2) 111 0 R] -/Limits [(subsection.6.6) (subsubsection.6.9.2)] +/Names [(page.45) 638 0 R (page.46) 643 0 R (page.47) 647 0 R (page.5) 296 0 R (page.6) 306 0 R (page.7) 312 0 R] +/Limits [(page.45) (page.7)] >> % 720 0 obj << -/Names [(subsubsection.6.9.3) 115 0 R (subsubsection.6.9.4) 119 0 R (subsubsection.6.9.5) 123 0 R (table.1) 422 0 R (table.2) 423 0 R (table.3) 525 0 R] -/Limits [(subsubsection.6.9.3) (table.3)] +/Names [(page.8) 318 0 R (page.9) 323 0 R (page.i) 159 0 R (page.ii) 165 0 R (page.iii) 203 0 R (page.iv) 210 0 R] +/Limits [(page.8) (page.iv)] >> % 721 0 obj << -/Names [(table.4) 530 0 R (table.5) 503 0 R (table.6) 540 0 R (table.7) 502 0 R (table.8) 424 0 R (title.0) 3 0 R] -/Limits [(table.4) (title.0)] +/Names [(section*.1) 7 0 R (section*.2) 204 0 R (section*.3) 256 0 R (section*.4) 139 0 R (section.1) 11 0 R (section.2) 15 0 R] +/Limits [(section*.1) (section.2)] >> % 722 0 obj << -/Kids [698 0 R 699 0 R 700 0 R 701 0 R 702 0 R 703 0 R] -/Limits [(Doc-Start) (cite.blas2)] +/Names [(section.3) 19 0 R (section.4) 43 0 R (section.5) 59 0 R (section.6) 67 0 R (section.7) 127 0 R (section.8) 131 0 R] +/Limits [(section.3) (section.8)] >> % 723 0 obj << -/Kids [704 0 R 705 0 R 706 0 R 707 0 R 708 0 R 709 0 R] -/Limits [(cite.blas3) (page.29)] +/Names [(subsection.3.1) 23 0 R (subsection.3.2) 27 0 R (subsection.3.3) 31 0 R (subsection.3.4) 35 0 R (subsection.3.5) 39 0 R (subsection.4.1) 47 0 R] +/Limits [(subsection.3.1) (subsection.4.1)] >> % 724 0 obj << -/Kids [710 0 R 711 0 R 712 0 R 713 0 R 714 0 R 715 0 R] -/Limits [(page.3) (section.4)] +/Names [(subsection.4.2) 51 0 R (subsection.4.3) 55 0 R (subsection.5.1) 63 0 R (subsection.6.1) 71 0 R (subsection.6.2) 75 0 R (subsection.6.3) 79 0 R] +/Limits [(subsection.4.2) (subsection.6.3)] >> % 725 0 obj << -/Kids [716 0 R 717 0 R 718 0 R 719 0 R 720 0 R 721 0 R] -/Limits [(section.5) (title.0)] +/Names [(subsection.6.4) 83 0 R (subsection.6.5) 87 0 R (subsection.6.6) 91 0 R (subsection.6.7) 95 0 R (subsection.6.8) 99 0 R (subsection.6.9) 103 0 R] +/Limits [(subsection.6.4) (subsection.6.9)] >> % 726 0 obj << -/Kids [722 0 R 723 0 R 724 0 R 725 0 R] -/Limits [(Doc-Start) (title.0)] +/Names [(subsubsection.6.9.1) 107 0 R (subsubsection.6.9.2) 111 0 R (subsubsection.6.9.3) 115 0 R (subsubsection.6.9.4) 119 0 R (subsubsection.6.9.5) 123 0 R (table.1) 422 0 R] +/Limits [(subsubsection.6.9.1) (table.1)] >> % 727 0 obj << -/Dests 726 0 R +/Names [(table.2) 423 0 R (table.3) 526 0 R (table.4) 532 0 R (table.5) 503 0 R (table.6) 542 0 R (table.7) 502 0 R] +/Limits [(table.2) (table.7)] >> % 728 0 obj << +/Names [(table.8) 424 0 R (title.0) 3 0 R] +/Limits [(table.8) (title.0)] +>> +% 729 0 obj +<< +/Kids [704 0 R 705 0 R 706 0 R 707 0 R 708 0 R 709 0 R] +/Limits [(Doc-Start) (cite.blas1)] +>> +% 730 0 obj +<< +/Kids [710 0 R 711 0 R 712 0 R 713 0 R 714 0 R 715 0 R] +/Limits [(cite.blas2) (page.28)] +>> +% 731 0 obj +<< +/Kids [716 0 R 717 0 R 718 0 R 719 0 R 720 0 R 721 0 R] +/Limits [(page.29) (section.2)] +>> +% 732 0 obj +<< +/Kids [722 0 R 723 0 R 724 0 R 725 0 R 726 0 R 727 0 R] +/Limits [(section.3) (table.7)] +>> +% 733 0 obj +<< +/Kids [728 0 R] +/Limits [(table.8) (title.0)] +>> +% 734 0 obj +<< +/Kids [729 0 R 730 0 R 731 0 R 732 0 R 733 0 R] +/Limits [(Doc-Start) (title.0)] +>> +% 735 0 obj +<< +/Dests 734 0 R +>> +% 736 0 obj +<< /Type /Catalog -/Pages 695 0 R -/Outlines 696 0 R -/Names 727 0 R +/Pages 701 0 R +/Outlines 702 0 R +/Names 735 0 R /PageMode/UseOutlines/PageLabels<>2<>6<>]>> /OpenAction 142 0 R >> endstream endobj -730 0 obj +738 0 obj << /Type /XRef -/Index [0 731] -/Size 731 +/Index [0 739] +/Size 739 /W [1 3 1] -/Root 728 0 R -/Info 729 0 R -/ID [<37C6B93B1FC7FB0B6EF4F2D85DDA8EE2> <37C6B93B1FC7FB0B6EF4F2D85DDA8EE2>] -/Length 3655 +/Root 736 0 R +/Info 737 0 R +/ID [<3899C85B41B440C76C6602BE660690F2> <3899C85B41B440C76C6602BE660690F2>] +/Length 3695 >> stream -ÿ;&J¹Q¹Î&¹Î9¹ÎN¹  -ÎO¹  Î^¹ Î_¹ 9¹ 9¹ 9 ¹ -9*¹ 9,¹9E¹9U¹³¹ ³ ¹!"³&¹#$³2¹%&#¹'(#¹)*#"}c+,#'}b-.#-}a/0#4}`12#5}_34#6}^56#7}]78#>}\9:#?}[;<#@}Z=>#K}Y?@#T}XAB#X}WCD#\}VEFGKHI}9}F}@}INLMROÑP}?}:US=TWXYZ[\]^_`abcÎÎÎÎÎÎÎÎÎÎ Î -Î Î Î ÎÎÎÎÎÎÎÎVÎÎ}8á ÎÎW”ÎÎÎÎÎ Î!Î"Î#Î$Î%ÎÎ(ÎX_Î'}<}J#_}}}#^}} -} Î*Î+Î,Î-Î.Î/Î0Î1Î2Î3Î4Î)w}Î7Î6Î;Î5Œ‚Î8}GÎ:}CÎ=Î>Î?Î@ÎAÎBÎDÎFÎGÎHÎIÎJÎKÎPÎ<™ÊÎMÎCÎEÎL}}} } }}ÎSÎTÎUÎVÎWÎXÎZÎ[ÎRÎ`ÎQ·³Î]ÎYÎ\}#]}} ÎcÎaÐÆÎb}E999R9x}K99*999 -9:Í9 9 99 Ii9 99999999999999!9_9}#`#a#c9#9$9%9&9'9(9-9";9)9+}>}H}D}B}=}A}9690919293949/9;9.«ú95};9798999:}L9=9>9?9@9A9F9<Øó9B9C9D9I9J9H9L9G•9K#b9N9O9P9Q9R9S9_9`9\9M2±9T9V9W9X9Y9Z9[³³I#9a9b9c³³9^³9]Sâ³ó”³³³³ ³ -³ ³ ³ ³³«–³³³³³³³³Íê³}M³³Û/³³³³!³çå³³#³$³'³"ó%³*³+³,³-³.³/³0³)³3³(W³1³5³6³7³8³9³:³;³<³B³4$R³=³>³?³@³A#³]³M³R³S³T³U³V³D³F³CCX³E}N³J³GMгH³L³P³K\ʳN³O³Y³Q…‰³W³X³[³^³Z³³\³b³_Áø³`³a##³cÕ#}OD###Ö## -# # # ##>Ú# #######Iþ####### ####\h#!#%#(#$r@#&#+#*#.#)“Û#,}P#0#1#2#8#/™#3#;#<#:#A#9¨ð#=#C#E#B½c#D#H#I#G#L#FÀ1#J#O#Mݸ#N#R#Q#U#Pâ«#S}Q#Y#VéÛ#W}#Zù¡#[çÃ}}@‡}}}}}}}}}}}} }!}"}#}$}%}&\}'©Õ}(îï})/À}*QJ}+Œe},«´}-Õd}.;Æ}/w4}0•j}1³å}2ÚÉ}3ù“}4Nñ}5„K}6Ý}7}R}S}T}U :¹¹¹¹¹¹¹¹¹¹¹¹ ¹!¹"¹#¹$¹%¹&¹'¹(¹)¹*¹+¹,¹-¹.¹/¹0¹1¹2¹3 7G WI +ÿ;&J¿Q¿Î&¿Î9¿ÎN¿  +ÎO¿  Î^¿ Î_¿9¿9¿9 ¿9*¿9,¿ 9E¿ 9U¿ ³¿ + ³ ¿ !"³&¿#$³2¿%&$¿'($¿)*$#¿+,$(¿-.$.¿/0$5¿12$6¿34$7c56$8b78$?a9:$@`;<$A_=>$L^?@$U]AB$Y\CD$][EFGKHI>KENNLMROÑPD?US=TWXYZ[\]^_`abcÎÎÎÎÎÎÎÎÎÎ Î +Î Î Î ÎÎÎÎÎÎÎÎVÎÎ=á ÎÎW”ÎÎÎÎÎ Î!Î"Î#Î$Î%ÎÎ(ÎX_Î'AO$`$_  +Î*Î+Î,Î-Î.Î/Î0Î1Î2Î3Î4Î)wÎ7Î6Î;Î5Œ‚Î8LÎ:HÎ=Î>Î?Î@ÎAÎBÎDÎFÎGÎHÎIÎJÎKÎPÎ<™ÊÎMÎCÎEÎL  ÎSÎTÎUÎVÎWÎXÎZÎ[ÎRÎ`ÎQ·³Î]ÎYÎ\$^ÎcÎaÐÆÎbJ999R9xP99*999 +9:Í9 9 99 Ii9 99999999999999!9_9$a$b9#9$9%9&9'9(9-9";9)9+CMIGBF9690919293949/9;9.«ú95@9798999:Q9=9>9?9@9A9F9<Øó9B9C9D9I9J9H9L9G•9K$c9N9O9P9Q9R9S9_9`9\9M2±9T9V9W9X9Y9Z9[³³I$9a9b9c³³9^³9]Sâ³Ö~³³³³ ³ +³ ³ ³ ³³«–³³³³³³³³Íê³R³³Û/³³³³!³çå³³#³$³'³"ó%³*³+³,³-³.³/³0³)³3³(W³1³5³6³7³8³9³:³;³<³B³4$R³=³>³?³@³A$³^³M³N³S³T³U³V³W³D³F³CCX³ES³J³GMгH³L³Q³K\ʳO³P ³Z³R††³X³Y³\³_³[ž°³]³c³`Âõ³a³b$$$Ý$^T$$$ð$$ $ $ $ +$$ ?ô$$$$$$$$K$$$$$$ $!$$$$]‚$"$&$)$%sZ$'$,$+$/$*”õ$-U$1$2$3$9$0š5$4$<$=$;$B$:ª +$>$D$F$C¾}$E$I$J$H$M$GÁK$K$P$NÞÒ$O$S$R$V$QãÅ$TV$Z$Wêõ$X$[ú»$\ëÞAð[© !"#$%&'()*+`Œ,­Ä-òÞ.3¯/U90T1¯£2ÙS3?µ4{O5™…6¸7Þä8ý®9S :ˆf;á <WXYZ =ú¿¿¿¿¿¿¿ ¿!¿"¿#¿$¿%¿&¿'¿(¿)¿*¿+¿,¿-¿.¿/¿0¿1¿2¿3¿4¿5¿6¿7¿8¿9¿: ; ]Ä endstream endobj startxref -612169 +613828 %%EOF diff --git a/docs/src/Makefile b/docs/src/Makefile index 94459c2d..73e70b30 100644 --- a/docs/src/Makefile +++ b/docs/src/Makefile @@ -139,7 +139,7 @@ PDF = $(join $(BASEFILE),.pdf) PS = $(join $(BASEFILE),.ps) GXS = $(join $(BASEFILE),.gxs) GLX = $(join $(BASEFILE),.glx) -TARGETPDF= ../mld2p4-2.1-guide.pdf +TARGETPDF= ../mld2p4-2.2-guide.pdf BASEHTML = $(patsubst %.tex,%,$(HTMLFILE)) HTML = $(join $(HTMLFILE),.html) HTMLDIR = ../html diff --git a/docs/src/bibliography.tex b/docs/src/bibliography.tex index e935635a..d6716846 100644 --- a/docs/src/bibliography.tex +++ b/docs/src/bibliography.tex @@ -116,6 +116,12 @@ S.~Filippone, M.~Colajanni, {\em PSBLAS: A Library for Parallel Linear Algebra Computation on Sparse Matrices}, ACM Transactions on Mathematical Software, 26 (4), 2000, 527--550. +% +\bibitem{GrHeJi:16} +S. Gratton, P. Henon, P. Jiranek and X. Vasseur, + {\em Reducing complexity of algebraic multigrid by aggregation}, +Numerical Lin. Algebra with Applications, 2016, 23:501-518 + % \bibitem{MPI2} W.~Gropp, S.~Huss-Lederman, A.~Lumsdaine, E.~Lusk, B.~Nitzberg, W.~Saphir, M.~Snir, diff --git a/docs/src/userguide.tex b/docs/src/userguide.tex index 7584dd9e..70e4fab1 100644 --- a/docs/src/userguide.tex +++ b/docs/src/userguide.tex @@ -27,7 +27,7 @@ \pdfcompresslevel=0 %-- 0 = none, 9 = best \pdfinfo{ %-- Info dictionary of PDF output /Author (PD, DdS, SF) /Title (MultiLevel Domain Decomposition Parallel Preconditioners Package - based on PSBLAS, V. 2.1) + based on PSBLAS, V. 2.2) /Subject (MultiLevel Domain Decomposition Parallel Preconditioners Package) /Keywords (Parallel Numerical Software, Algebraic Multilevel Preconditioners, Sparse Iterative Solvers, PSBLAS, MPI) /Creator (pdfLaTeX) @@ -125,9 +125,9 @@ based on PSBLAS} \vspace{\stretch{1}} \noindent\hspace*{\centeroffset}\makebox[0pt][l]{\begin{minipage}{\textwidth} \flushright -\large Software version: 2.1\\ +\large Software version: 2.2\\ %\today -\large July 31, 2017 +\large July 31, 2018 \end{minipage}} %\addtolength{\textwidth}{\centeroffset} \vspace{\stretch{2}} diff --git a/docs/src/userhtml.tex b/docs/src/userhtml.tex index 5a979980..86d4cf93 100644 --- a/docs/src/userhtml.tex +++ b/docs/src/userhtml.tex @@ -26,7 +26,7 @@ \pdfcompresslevel=0 %-- 0 = none, 9 = best \pdfinfo{ %-- Info dictionary of PDF output /Author (PD, DdS, SF) /Title (MultiLevel Domain Decomposition Parallel Preconditioners Package - based on PSBLAS, V. 2.1) + based on PSBLAS, V. 2.2) /Subject (MultiLevel Domain Decomposition Parallel Preconditioners Package) /Keywords (Parallel Numerical Software, Algebraic Multilevel Preconditioners, Sparse Iterative Solvers, PSBLAS, MPI) /Creator (pdfLaTeX) @@ -102,9 +102,9 @@ based on PSBLAS}\\[3ex] \large Cranfield University, Cranfield, United Kingdom \\[10ex] %\today -Software version: 2.1\\ +Software version: 2.2\\ %\today - July 31, 2017 + July 31, 2018 \clearpage \ \\ \thispagestyle{empty} diff --git a/docs/src/userinterface.tex b/docs/src/userinterface.tex index 0e3de52d..82a13bfa 100644 --- a/docs/src/userinterface.tex +++ b/docs/src/userinterface.tex @@ -319,10 +319,14 @@ be applied. of $A+A^T$.\\ \hline %\verb|mld_aggr_type_| \par \verb|'AGGR_TYPE'| & \verb|character(len=*)| \hspace*{-3mm} - & \textbf{\texttt{'VMB'}} & \textbf{\texttt{'VMB'}} - & Type of aggregation algorithm: currently, the scalar aggregation - algorithm by Van\v{e}k, Mandel and Brezina is implemented - \cite{VANEK_MANDEL_BREZINA}. \\ \hline + & \textbf{\texttt{'SOC1'}} & + \textbf{\texttt{'SOC1'}}, + \textbf{\texttt{'SOC2'}} + & Type of aggregation algorithm: currently, + we implement to measures of strength of + connection, the one by Van\v{e}k, Mandel + and Brezina~\cite{VANEK_MANDEL_BREZINA}, + and the one by Gratton et al~\cite{GrHeJi:16}. \\ \hline %\verb|mld_aggr_prol_| \par \verb|'AGGR_PROL'| & \verb|character(len=*)| \hspace*{-3mm} & \texttt{'SMOOTHED'}, \texttt{'UNSMOOTHED'} & \texttt{'SMOOTHED'} From b7e8a921d895ac79364b209db9ccab1b05d363e2 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Mon, 14 May 2018 14:50:52 +0100 Subject: [PATCH 33/33] Fixed docs. --- docs/html/img1.png | Bin 2455 -> 2801 bytes docs/html/img10.png | Bin 234 -> 252 bytes docs/html/img11.png | Bin 404 -> 461 bytes docs/html/img12.png | Bin 196 -> 212 bytes docs/html/img13.png | Bin 233 -> 294 bytes docs/html/img14.png | Bin 781 -> 1028 bytes docs/html/img15.png | Bin 278 -> 299 bytes docs/html/img16.png | Bin 531 -> 668 bytes docs/html/img17.png | Bin 510 -> 559 bytes docs/html/img18.png | Bin 278 -> 300 bytes docs/html/img19.png | Bin 265 -> 277 bytes docs/html/img2.png | Bin 350 -> 370 bytes docs/html/img20.png | Bin 173 -> 197 bytes docs/html/img21.png | Bin 216 -> 218 bytes docs/html/img22.png | Bin 5817 -> 7344 bytes docs/html/img23.png | Bin 365 -> 419 bytes docs/html/img24.png | Bin 217 -> 230 bytes docs/html/img25.png | Bin 240 -> 256 bytes docs/html/img26.png | Bin 292 -> 319 bytes docs/html/img27.png | Bin 405 -> 430 bytes docs/html/img28.png | Bin 295 -> 324 bytes docs/html/img29.png | Bin 347 -> 381 bytes docs/html/img3.png | Bin 203 -> 219 bytes docs/html/img30.png | Bin 179 -> 201 bytes docs/html/img31.png | Bin 1745 -> 1978 bytes docs/html/img32.png | Bin 390 -> 447 bytes docs/html/img33.png | Bin 511 -> 571 bytes docs/html/img34.png | Bin 1542 -> 1607 bytes docs/html/img35.png | Bin 246 -> 263 bytes docs/html/img36.png | Bin 475 -> 533 bytes docs/html/img37.png | Bin 483 -> 534 bytes docs/html/img38.png | Bin 248 -> 270 bytes docs/html/img39.png | Bin 760 -> 837 bytes docs/html/img4.png | Bin 689 -> 745 bytes docs/html/img40.png | Bin 257 -> 280 bytes docs/html/img41.png | Bin 242 -> 263 bytes docs/html/img42.png | Bin 538 -> 572 bytes docs/html/img43.png | Bin 2405 -> 2817 bytes docs/html/img44.png | Bin 230 -> 253 bytes docs/html/img45.png | Bin 480 -> 497 bytes docs/html/img46.png | Bin 235 -> 259 bytes docs/html/img47.png | Bin 502 -> 547 bytes docs/html/img48.png | Bin 378 -> 414 bytes docs/html/img49.png | Bin 289 -> 319 bytes docs/html/img5.png | Bin 643 -> 668 bytes docs/html/img50.png | Bin 256 -> 275 bytes docs/html/img51.png | Bin 292 -> 310 bytes docs/html/img52.png | Bin 269 -> 290 bytes docs/html/img53.png | Bin 573 -> 606 bytes docs/html/img54.png | Bin 227 -> 243 bytes docs/html/img55.png | Bin 255 -> 278 bytes docs/html/img56.png | Bin 527 -> 598 bytes docs/html/img57.png | Bin 533 -> 664 bytes docs/html/img58.png | Bin 374 -> 406 bytes docs/html/img59.png | Bin 1167 -> 1295 bytes docs/html/img6.png | Bin 537 -> 614 bytes docs/html/img60.png | Bin 273 -> 296 bytes docs/html/img61.png | Bin 389 -> 422 bytes docs/html/img62.png | Bin 283 -> 314 bytes docs/html/img63.png | Bin 282 -> 309 bytes docs/html/img64.png | Bin 266 -> 303 bytes docs/html/img65.png | Bin 547 -> 617 bytes docs/html/img66.png | Bin 415 -> 454 bytes docs/html/img67.png | Bin 239 -> 257 bytes docs/html/img68.png | Bin 299 -> 301 bytes docs/html/img69.png | Bin 458 -> 579 bytes docs/html/img7.png | Bin 1059 -> 1308 bytes docs/html/img70.png | Bin 605 -> 657 bytes docs/html/img71.png | Bin 622 -> 699 bytes docs/html/img72.png | Bin 180 -> 212 bytes docs/html/img73.png | Bin 203 -> 228 bytes docs/html/img74.png | Bin 201 -> 242 bytes docs/html/img75.png | Bin 249 -> 276 bytes docs/html/img76.png | Bin 442 -> 469 bytes docs/html/img77.png | Bin 192 -> 219 bytes docs/html/img78.png | Bin 199 -> 231 bytes docs/html/img79.png | Bin 309 -> 387 bytes docs/html/img8.png | Bin 272 -> 274 bytes docs/html/img80.png | Bin 321 -> 372 bytes docs/html/img81.png | Bin 209 -> 223 bytes docs/html/img82.png | Bin 206 -> 218 bytes docs/html/img83.png | Bin 272 -> 283 bytes docs/html/img84.png | Bin 254 -> 281 bytes docs/html/img85.png | Bin 166 -> 207 bytes docs/html/img86.png | Bin 574 -> 608 bytes docs/html/img87.png | Bin 248 -> 259 bytes docs/html/img88.png | Bin 188 -> 218 bytes docs/html/img89.png | Bin 209 -> 218 bytes docs/html/img9.png | Bin 253 -> 277 bytes docs/html/img90.png | Bin 506 -> 607 bytes docs/html/img91.png | Bin 547 -> 638 bytes docs/html/img92.png | Bin 300 -> 339 bytes docs/html/img93.png | Bin 558 -> 642 bytes docs/html/node13.html | 46 +++++++++++++-------------- docs/html/node14.html | 64 +++++++++++++++++++------------------- docs/html/node15.html | 18 +++++------ docs/html/node18.html | 6 ++-- docs/html/node20.html | 14 ++++----- docs/html/node24.html | 14 ++++----- docs/html/node3.html | 2 +- docs/mld2p4-2.2-guide.pdf | 6 ++-- 101 files changed, 85 insertions(+), 85 deletions(-) diff --git a/docs/html/img1.png b/docs/html/img1.png index 82537736e6ffc08f71c0011830d9113d1c584bd5..6e9422be46dd5feaabe1234912e6636eebaa92c4 100644 GIT binary patch literal 2801 zcmVkhHB-6?dgDFf-Vx+Aw-J+pJ<#8SjKdfCVK@4YHuu-cb zD}NY_Axr?F=A!lc-tJxRuGf~H*gwpEa`*Pld*AncpZ9&=@0;(;0A~Wb^&Gu5pUR38Gj|we);kVl0atAQ{*nYpv5cWSZ0M^sL-!vDUE8hcXT;)cfH+&J zS{mbZ)l!<(tErObG%$Bet1nv(ct8ehEW>NYZXNDJ?q~>?g&$&l<>U>xXPf^*h!!=f z&c$jtcMKud7l4VCn1to9Nd|_zFR=R#%fcG%pcKv9o?d6TgB;}VoVFZ?Jn1Pc?`M(Y z%N?E;;oLg@0WPV7lOvp|J%h{!aE7(RA zhWONjz;56<#()~EoIPn#*ChHQ4*$kPNv>+3CwQ1D4CclNyQsntl~a%??)GsN#+j5W zJiD_2j=br?e7uh%sU`g%-^j8R!4ppX$x0fzc`0Z6OwQen$mg~?9DBLjaGPw9yL+*Z zyfHydD~FXc*x$ovGKM7NA18$Fo`nDRFGQ{OBx4VyEj ziF3_vmSqrLM(B?CQ-0t|RwNZ`6@k=H1lR*m%u@m9HxNNcchh23-jH}-S{JNtw(Lq< z(jq)!YmlKYcp>i)vww*IJmb?*G-M*a0V9Q$YN5sA@DR2+n~?KGkecbcA<6=WAtF-c zY2k9A%$$hGi9{s0j`X*OY4L{4N%m(cJzP|jc@5R`f#|1^S?M+2UKYkq@QIq5c^0Z)vKs0Pgff+a_T1jf}^2k}m3 z**eoUOQa&;(!$k4EZ59$$mFI?ic^*CJX=SrHBc3`|ZEVV5>#aQ^f0($gM+&FV7aB5Q=M;cw79g~CYkEhLu6vDwl0Aeps6(niRi1+ z{0%Sg5%XB2Sv;7~+<6Vxz`Lf{+1HA2>#Nj60+MNdCdzaIevS`1oNc%96X*vG_3q)Jd&4hAIM8s7Was1Q>iw{o74T-9IkVqA0xdy z=W|DwL(?~@__jq}M%q1xuE~P0;_;vdLZ((tX(?| z&X(p;96;A&4EwxMPTO5eS8?lE?1dY;k)o-)m}9J+(24LSMZ}HI}Q;GI@D_n}I zL(aIC2Op(OvuiAm9yh_7pXnxl%v>e)cHL)27jUfh>Hm2$e;;E>4gJ{JN7rA&Wu&j7 zRj8wuUQ`D2DT{Ue@pzDviq#9GQfBVNw)cUB5H* z!f-C!=w2LRjk*|{X)b;6+ZxOp097zUDZ<8 z-8>mL`H6y1rok^i-LlNdz*JtC4^JU72V2{}g;|r+qe*jph}GIwWchRLm%wfGLf-;> zcea70C<677_2={$#!oiY6p>m}P|7ls$D2?1#%Pmw+_FHTd|*aE*>%s{Z<`8#Szy{y z1FWUZj*hqH=I_m=>iM0D)4U~+>l<{xNi`-PltvSL9vF5TIH%J1!zE)Jnc7%`9vOCk z3eD~JsFNOUGZ)rUDWX@-+Z}e1fmZ-4XtS7@`tptbEdAs1Z`ht~U@3|f&o3i#2g&xN zbt#8dTZuw#TdJng+Y19?!4TM&{2*tfux_peR^mK2y{ZSGdtbDkoZz@&GxS)Tf z*8BV3vRs3t#&}E5pnJb+`l95Z)%sC6k0NMiKQ;B<#<4wt+b8vI9|)DYTYe}@+5a{Q z72Mm9{9eA?mBHw%v7{XOQ&<8y*p8)T_TE$}les=h0sMT6g`BCqT2|Ngx7S`g8pvJU z&*GlcN#ob`$T@)fSs~B`%Xk>ThS097rQ+<9d1wjpYjG>gH)9u!QW;NS16bl5*fF6;#JcUGm(%~Q zaH>%Vn9Vg&JQgTwmap`X-&`x3pl$yw#~}=6)&_<@<&*tklmD#sGOteH&v?(r!Ir+! z7XzsNU*X)lVfu<+75V`n+IwlkImp<1!T4 z%n_VRGsMOD1n6XetXeTXL#^4EOzP~Xh@WbO&t*^|Fr~FeNeLOsAp-|>Xw6yHJOn&7 z=3Z2r6~a<9>%*xl-;-MJrk}T)s_Wb0&sx*U*cNXc&U1Uet`Vb+tA66-{% zlN&*yFpg4$O(46Nv7+We>6r@YG@~Z@C|q~so{$^~Y#_hb5Gqf}#oC>C0vQ$T@*SB_ z{RNuk(->6zSS&4(^;%=4pQoCy24AnrKl(8|(?w$q8F$5LB1G6UrC4Tgy$+Lp}0d+3Ndk3_{Fi8#^qQ|ZkZK6Wf&N%2lv&hPxC zG;o%I*Egg!tl1tcMV$mJRK5poi+l7%P4jzGarRYaz!<e^T z!dBqvpW?(J5!V2}U7sj40RVgsR%XVI_-7la`6soP1(hBk;zcdvd7INjr-jZ?40VCX zt?^EM;JPo29}z!6HUryIpFhWr9*9Ls7+5gR+5Dsa^vA)|+mYyXb|VLLeh*E1PKLhI znm>vf*B}2Mvaap*Pu9lK2wcHU8^m{CQE?Jm(5$Z^c1t<$H(EF2c%#)=3lBdcy~^^2 z-q6EPb;|^4|91>fb%MoN`v7aSHso>2C?6N9eS~Q*{_rx6#2E)LP~25+uKLjfo1u3% zjo8=??OA`zVk}FtOjuf<3;ECrk^xfiiCPB|QTK6c+b*E;$n{dp%X=+JwpHnl1H=(7 zUH?QQ5P!hU#L~%aRk7X-Z8t{wixb)?-8tQuU|XI=9cUS4U^#i$E?5%LP6F5m7-D|r zXez+9uAj}>vkr`Egde5E^xosddvVTf-vTd22POvkR_8k#Q2HAp>Oy~hdd4IeniwLW zL`j1Wq5h5M2LhvV+8ArkXFE^MFN(wWG% zQ`arJKEdR#iPrN(0I0Tdm%$-IqOy9^iXW<8UIl##ypCOG?VSvZdA1!aUFX&EinbMM zH{P2<9r~pc0n=FW=_ja{`p6vNZ_!qA%unRK9O+mHyFy)H?~h6V$gsaz-Z&g}?Z7&a zxzmf~#5XyWBt!Yjrzp-w+R-6XQ;o|e+_ghCbO&wV!o_CiBILI$8~kKr^RqkX02_}f zF?{POIVaJI%HnnVH55m=_iBIjixNzv*V+9~mi4M{kG#-28o%1n3{nHIG1UfA*V#4M zZ0=fi6P+OgDUQjaQRj<;eJh&7&lgR`#K&*p~ZJ#@imM zGz)hrA|u(OLX#eUn~a5@+u*uS(1zjpB(z;IABi6fH^4$3tYEa9(X)J4K@|mI6^*?X zkf57SwfSVmsctGN6wbPBb2-Ey*~+ttr)zS)sajICtos=K2TUGHRmc z`;Aps6R;+8yOeA}{~d46)I5y?EFRdiAIXoy62p+;57j|q-$}%3D0F#Nm+>Ohb80fX)YKClPo|0{1c(=Kfs#E=6Lw>> z$QbsEsOJT0vxh|^^vT;vqG}tu(UMAcb5`R&D-fOKCF;10`6S&FS1!BxL$>`QcQ0V4 z=~FBoSPV(mis(SPL-B|7Qr+}rkbN18s={Km)oq$uHmw@GmaNe1^7~5mN-5p)f~iAj z3glfeC+&t+ZYoc;&x_;8U&#gyk|N(l&TBdhqHPZ|o7OFKkQG_JKP+(Uo3@hT2akFZ zUJoHEa(2Upxq>fa0UUD$Q=HY7Oi`e=E_S$b1s&_9p zi`%BWkE4=F8(e@X%Sq-{_5F3HK4svQ_n42;)}mUX8#uX$z?^K*&s1zs#EnVSzM-co zp`TrS6hpBwf3<4p3GyG8@L+8P6qK35Pu*)oNlTYk(2VOSp$bMsY(eQ_y%rkYwI!o? z$r@VBwWw1h*?aJwOd5WOojD$E1J{h>@l|cpPI_m0&d`=CIIBLZml@grxGjrKfi6GQ z@QqPs6pCj5yVwy=wW;(4=}fGf1P)XX>q8E+U@V_1!=YGevOb~OgQM4)r}GPP)yw2AH_E@gls~1@-RUG(P1NA`@d5c~h9=(Z$@jbkmvF*8aeS@! zaWX7MTYyodnj2IWe%qSyuQV)V<3x%d`rHx}G-~e_#rV0{RD5&;C+qkvq6=A> zu9l3?T)D4ARjS7hiiN6lw0ov}651Tyly+%=y*ZU5P~WyX{z#K0`dY-#Sw^=1z`=W~ z{o?w?q+@rW$aZBrCi2VEf0z{p&dg{w)T0`Syzh9@h6+bmw$@ z;eQ9r+q?s*IGdr`VrjP2mo!+sbc^6-I+<*+NZ`+N>1 z$bPXUm6S2_4oYd&xD}6=N;e@PfI@@bb*{ZgW}6_e_vQvYtb%*p-e< zA$lM(Qi1?o1y3T`*@Ot1w3pYZLQB2+IES1sx}^i@;C*q}C(@0@;*>lifyRe)%;`Z7 zrhUonVTz%uJ7TNT7=O4A>YO_U(=v}Gz80~2H_5RD$btN(JbDP!USv&;Z{PF?v@&o2 zioLYm_i7@Rz1*-9eRM4SAwQptU>!4pcjkj^Ru;a1_e_u4my3SOUPpIOe@+ZhWq(}> zRv{%G%#E0qyxsbh^J9Uuus4cZ*|giVz03aef8uYBvfx;QrAF0?e;=2XIl`>Y1e5Sz Dq$ diff --git a/docs/html/img10.png b/docs/html/img10.png index 1b225d49a5381f028c451c32efaf5d02c7223a5e..9568c1114f265172bd56d70a067ea39728b48dad 100644 GIT binary patch delta 232 zcmaFG_=j~Ky?NK1A{?;Pl)UP|Nm#soLOF89vT|@?%g|MW8*Vt&Ik$$u3ELK zqoX4&Ee)v9#l_|B-MdOkO1pROmX}qW3KU{23GxeOaCmkDBwyv};us<^H8}wY5*-*A zRm_;VkF&6q9N;~Y!{yNQlBrEb=s{wV215{+4d4tpRVlmI9zy= grn^LV(CtJ9?hL_cYFVdQ&MBb@0Cmw;5C8xG delta 214 zcmV;{04e|c0qOye9De}*S4;i?001peOjJex|Nj600PgPY-QC^H%*?yHyQ-?HnVFe( zc6Nw}h-GDER8&+$Lqjq$G9e)$J~oM%00001bW%=J06^y0W&i*HYe_^wR2Y?GV4xRZ zZDF4Y=cvU^;+O#A6xAtkG%#2+fH?*$7aZZL9w`vdvsJe3!Lr(!j83O|g1H;JN)QxOAiu+IiH-h;AO1p6atpL*VSQrZA`87a7 z8%_d=B@7Jw-0})yBOo4V@A`k3F z2iT*QOmGmJAa?>XkN*Lj$-4;7R7TOkDyt9#W^gQW08t93E&$WoHU_Q`28I9J4ALO6 zZbPsNru9%gz8e_+FfbV~L@Ui;aL|Ngp+No(*FZEQL@g*QL~wYgIn;wV8^HOA{{V}T z0MuoxK$#DiaTYc3XfQY_DKan!YY^@Akqa=A6ea)wL}g`ND*wyo00000NkvXXu0mjf D7x$~q literal 404 zcmV;F0c-w=P)KBu^BopJ=8XlY0$td&G8&-rk0Y24a8?|eCSf?M zwgH#%tPj|xL0C0lcd)jw&jcIKQklR!lfeTl#j#<^9uUpc3vsJj+$4?(Amh6jnmKqK z62XEzGYnEdYPtg;<`vZ`a5S(!VBmbf&{S-wzzgxmQ7}~xRl{Jgf`PYyV*vyIiJ1-t z-3%NMe^?vtFgSvAU1wm2`a_frtm*_r6|)e-99BgW1xFA^h#?so zOadVgZ|(pGAo~S|1HypwPrdntcZjd yZ@|C`3o>R^0000qgi#B_1|sWB6Ij&5|sj>IF2O!PC{xWt~$(6989hMm+!k delta 181 zcmcb@c!Y6+c)bV2y?fQFRWoPKEGsMP z=;%mIO$`YNadviAR8;)vc3>t@9b-w5UoeBivm0qZj<=_aV+hC0SU;qL(1_ao>dp83**u8rLjL8&$AqxlWK+MX(z@@;zz<!p@PXYRumM$! z8;N$~M6frUM3tuo(1Owq3=rq?0PzPPR?tVVH?knuYY=K!{E^f%K-n|`yAgnN%?D9< zj5?6u=6?VcfI6EWBFrkQ5QIgz+Yqc*Nl8yhNdO@n$iLwlrfU8JEJgxI!u&d$6i9dW eU;(?a0sv96HW9gV+|9>F!?%lg*&Yao3d-tkUt7gueSyooo z(b18bni>)k;_U3KsHphS?Z8Z+I>wS9zhDN3XE)M-oB~f5#}JK)$q5TIA6PW22{0_w z3S@~~#iG!Y8_>wK!XhMsW3|C)#%p0Zhu(0{3Qrb%7MvH(aZKsV4px_K7E5RoLG|(D-4d4ugR}*R4GOhi)n?9w`%-BT6YMFiU)vmcQ*M=LX1; z8Gs<#x4OdqIYfd@Qa-vk`pnfi#jr`gqBN4o;hCi`q(l4>r|?~kwh{e$27GY48~0Oe z(g4S8fCKC^$+Jwt-D2Da^r;L%(?TJgAXdCfX{;PFmfa)PM4>u98eFaiq+k;>(BeOU zXt2qEpHd6=TL+kX?!ionAEAp0+~JF zG|IA`roj^+T5Y(r-$uvdkGm*#C<+mr1expP4v7zSJvT`Pw7UHHWSPzN9LaXc_46p* z!*}y4ZA7?Gw&^H8qSzr*{1m)69)lBjZRod628xInHhV9s59TJ zmR1<8xPf=fUp+^HSn2?5@NS@oKEFCa7EjzifFRyxSY$islU$uqRapzkxu zIF@7#8$_mOG?ri#piNGFXB$vQa_`(AY8*$pwTt!wxI>TlsTs+DkI=I@#IJ-VGPL%I zFmL%v@+aIor^Q?HoixlApBHQM%UM8YIUN}*1yM6@kn?#cE){=Q_yIpYV(nDiYwv!t zEK>xH@j`!fjegLUhb@9G-&?r7IoNg3%aqSwO+4{+Lmgi38o|!8U;qv)3TVs^AZtBEB7pPzDeH0000WdP)KmCtL_U>L`rrD^jfjazSmr{E9Ju4uQz$gw>Prl)u) z7Q9q1L);+@Wd}V}hc(VBQSiq>aD-`xr=XXD9)dVFv>-zSz4;FaJBlaY{CMA_&5v$v z!Arl8=KVg&^Ld~5&65;htg*%#%T-GI-;hxhFcf4f;aUdZ_|Ood8Zf1(cy3M!Pkec? zXrDQiF{nvW5`<_4@=^pV{b|t*m+rgXo-(SD% z6k+xkx6ac&KJU%3P*H^Ew}S>-aXMr&Ul^VN% zaJyrOXeC1I0uVm(Qp<_KbjsU;M*!m9MP}P+i=_t1MOhGwg=?87H$af!H8s%%yabpq z6CtDk1B99#gDV%jKKKAIqk0_tXvprJ%{wEs#rV@;!)Q(Iakzl@xCYYLk&u(x&OHeQ zA5l}0;FLZ118Lek(?D|B&3Dd76z2UL$3*VH-%8c!1Mzl%%Gyxi7TziLh}Muu@F~fi z{PEo#W%=uVj$?2ETt|g2v4<;b{UCVqo59z_e5Sw&eCBh3;Db)5V>!jka_=IEP(+O1 zgF|{BNIiy^wF2f2DPBa?@JG#6Dhgu4B%L4z689aQ3RZTG=7RY)CLt1{!wlsd5K<1V zR8VQ|LP1K*TMDiSe+JIiYXd>#-BvKNS+ak*&ktA8{cnl6mvnzD@7{$ot2A%`Na#7U zO{ahMBfZ-)l|dkJjkXV^N`vQ8W%~ZZ$BQ4q{6j&Gj-r5(K!(#lR8+<>4YYE~00000 LNkvXXu0mjf_*ZOC diff --git a/docs/html/img15.png b/docs/html/img15.png index b13cea97be4262373ff79727726d8c17860fb992..63669b778a1ae2118891453132dfb4e205a0db71 100644 GIT binary patch delta 285 zcmV+&0pk9a0;>X$7k?520{{R4M*#`|0000mP)t-s|NsA)nVENYcU4tY?(Xh0Gc(N0 z%n=b0s;a7ph=^upW&i*HL_|d0-Q6N0BD=f09~~i;00001bW%=J06^y0W&i*HsYygZ zR2Y?GU;qIo1qK-4=3!vqfiRgkfP^#y69W=>045s@ln_F^41d_b0WJmxn5i2+#6#I^ z3>&bjMguG$+Y2BX8o(xi-NO*Xpriz0&%f~O0#uxZ?E_pR2i#5uh6xM@h_MR@_}^m{ z<_!RmAOpGKVmt>Jn8emyKojQuw1L69V*bOR7G!bMpH7=IW9%mUDbc?B3)kECxv z7oIN4z;PUCYsZO>0)#NrR8a<=84c)Wb0~{3FtQvdKobsUkYI>rI&J_KW^ZhV3O4|S zVJrk--_h|K$}~U{)?i>b!+;5z7#Q|qin0P-(1;<*vhWCl#lu!qK>#(w9R-=*CIJ8d O002ovPDHLkU;%6XOpUz%$6(q3{>Nc4{vVFmaG^z$k|gx9`i38l9W z=rE{j(jJp)MGq=Z>n>`infx@4^CxH?JC;G8OYfN4yf)oI{s=h6 zcM{yeVPdfrWk z**&p-23e>E0f)Cmzt-@X*c$atm!h2v{c#$$*We#eXV~!vWpOIUcmFo^$sUQ*!Rl+H zDPELiwbbwA@Shug)t(x57uby}&2e05J-f!PxKO?{{UR_89%N!Lm)P=+el#uv2ZpYJ z8QS4Bg-e4k#gPX7K3LWrnXO>{!F!`}-r~&_zmK0>cx8M`H#6P<0000CXP)F6XfTqBr0me$eFO9@x?m$t)0hTCWV5k(pW&}qA zHYTbOJOLmQB#YGuh%`F$D2f_J=2Uz}K%~)`0%maISQ!{%+^X>z0g*;h3FaJ0-vCn( z$iUE301Tau6CDNUMzHqm=vWGpMpDVZ5OKPryMg04LfJ(IhLhl+!R8A72@H-2Cp*wo z{$yY}%`>9`riimJfI+~A9fuK)4h%d8AkqkxEFugHjf^Y@ppIkE3=Cl1pi>MnqC%no z)rk4P5ZnrpMyTWjT68{|>9_$@QIlZ;l-0n133dZb!BEM4fPq;Yp@y}95vJ7uE*1&` zVD7Kbh(#DG`5PEwkX*~b05<|*EZhhd@z5>>43&;6I+Bo-S9kPpV897DKQQo4z)(36 zMGaE}FvM{i!M%ZjuK`2l9uzek3JlyAFf^V4fdmF{vM_AGQ27HzbvRHCYodk#V6q5o zNI+A`A_|w!F<|hLabWI~2*9Qr1S~GLGw3&i0|TLwxmOAv9r+Hptw#W+P-0Y30su2e VYL(e50O0@t002ovPDHLkV1nh%%h&(_ diff --git a/docs/html/img17.png b/docs/html/img17.png index f49a2b76cf0fd4723ea1799005175ba6acc3372a..ab9d063be08fa7bea5b8c1b76ece11f65d322295 100644 GIT binary patch delta 542 zcmV+(0^$As1Fr;-9Df1q6uJBW001yhOjJex|NohpnRj=0RaI5)?(Q=)GtA7)5fKrp zs;Y>Hh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchCBa9 z=)ez%#KHvlE(xUH3uWq)?#}kJ6Z>KZNMO^lq#%GMrXxf}dGZ;&0^0&U-XX}T;UC8H zT<4&p_9_@X#y%m@!~LrXxNw+2dB5d}&8lAszS_>6m4VFAQU=1uKdXn%1lP~zHyxQp>P=Efp8^`5B5 zn+`@})niA&XuyD0i4#+l{Zb)zFQaUZf@eF!k*Tv}+uQ<$=BIHS!}VcY zX56OOp8OxGk-ioiQL5*r9X&YxsR3rLu3UiG1?y|$0oF}YLJHTPc;q-nvn&P+16V7k g=!;*l!WX~d8;ONRqBP9y`Tzg`07*qoM6N<$f=U?yvj6}9 delta 492 zcmVlHpQdV1H-ep1|q=7Kk|A(G|cT zU>1O)!HR)_wP#1i4hE16(*g!&27U)7sN7Em7BSW%=^IcqYyx8b2@E|tOqEC9=ZEc^nOTN>J>5Y2Sl0LTsnfnXrR79{h7f%P~8 zScdrmLx)5HRD)w_#3GnxxP};z=cGE?6rd6UNVd;sV7SSE4nP_>kyIgT*v-K30;>k@ z1K2hEWMGznvG<$-f@46256E*3a5YRH5bA-^z$(FpZe;@_5IZ8`o)uvkbFV}J(+^8@ z4crb478jSpxttSFrBwsa)HAT7s^Bp|SAYQypzy2+s%MBq;cX(Ufz1Jl!|s4X6*53} iH8T@Ks0000gz~}=f zL*~0SUY-hu6EVwpdFJa|Fi7S|ONh)6YjEK!$a%1j!KmJe=}KD+JEOte14ld0+ZZH7 zHtQ8J9gCQI;J|||t&R2xLPuiGt>)s%DHk*NaHiqcgwB@?&WGP~^UROz(Q9CR_9;Ih w#iI4mlV15B-w*BFQ`N|$_UBcmdKI;Vst0RCBWk^lez literal 278 zcmeAS@N?(olHy`uVBq!ia0vp^@<1%i!VDy5Ih`&9QU(D&A+G=b{|7SPy?b}}?%gwI z&g|a3d)2B{GiS~$D=X{h=txaX4G9Txc6K&0GE!7j6c7+dda1q(sDZI0$S;_|;n|He zAZLoFi(`ny)Z~N(dK)qvgdaGFKj3V*u;wm%Ly8|evvRSPOH1^O#>ULWOwK*grY;A3 zr!+S1o!+=`Im4>*OT}z$52Sf`)U6jV@v2MA=sF@H!BTT$A=6!+oE#^fHPR(r2WzIa z$gzp{adW)36lId+s+cHq^q|0sbqi)R=p2YRG+{-907vqJ_yZTZpB&%MdWTE!|Ez^E Z42?^qkDFTF`2}`~0{{R4c9T*$0000mP)t-s|NsA)nVENYcU4tY?(Xh0Gc(N0 z%n=b0s;a7ph=^upW&i*HL_|d0-Q6N0BD=f09~~i;00001bW%=J06^y0W&i*HlSxED zR0x@4U|?Y2S7LyI4IqMl1B}ZM0OWyaZU#mMWN?7NgJA-Y=6?Zcxd3G7DKBtRV89Ca zKQJgTEI?Mw4K^4o@}+?j#Q4w92DXU5NSi_F19o$Swkk3(=xkD8(_RSXGl87R3bZs4 zBF_!7zuSR<0qPEI5D~<{z$O6UZvtxJ-@?Ga#Q@XJ_JH9$10zTp0MD-&mKRkb+yDRo M07*qoM6N<$g5)!3oB#j- delta 250 zcmV~00{{R3^AytI0000mP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001bW%=J06^y0W&i*HheHh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchCe7P9vMI3B$MtjvlQ4yNtzj(2Ggx#eL1`8N zVDjZucGNf`$BDw8=qLn>?*#JZg64)|ml7ywphB)h{Y5i0-y002ovPDHLkV1hhbhnWBX delta 331 zcmV-R0kr<|0^S0U9De|0pQ|_k001yhOjJex|Nj600PgPY-QC^H%*?yHyQ-?HnVFe( zc6Nw}h-GDER8&+$Lqjq$G9e)$5D*Yz=_k4X0004WQchCq01e?SK#^5c;QRnKSb>520+4F}3b8$BfZ!OA5zoNg0Fn&{DiC1%P{sT%Pagi qqhaH={DzHI34Tmk$wr9@3=AhF*cV0d1zrIf&EVhv+1c61$VfmyV3vWpGEk1OB*-tA!Qt7BG$6;p)5S4_V`g%~0rnYpon#br+%(Q6 zWH6*!91>Z2P(sNd_D}#@Hv@AsQ^&z+2M#=7Fl{@@nAKzD;kER_(XDeE85tP1u>QW2 S_~a$fECx?kKbLh*2~7au);5j+ diff --git a/docs/html/img21.png b/docs/html/img21.png index 5f0acfca5eac6675d93d9c28977bd34db3953fe0..a8fb8e21e36820ec51cb8adb61033e4843baebe9 100644 GIT binary patch delta 203 zcmV;+05t#D0onnO7k>`~0{{R4Y_GDn0000jP)t-s|NsA)nVENYcU4tY?(Xh0Gc(N0 z%n=b0s;a7ph=^upW&i*HL_|d0-QBypyS_Xe%K!iX0d!JMQvg8b*k%9#09#2!K~xBt zV_<-SCNRkk;czoBumGt9m?RUJ8NeU_Vk&5(67Z2ml1|3Vaypo16du002ovPDHLk FV1hUaOQ-+< delta 201 zcmcb`c!P0*c)b7%GXn#|OAVuZAf+4N6XN>+|9>F!-Me>p@7_Ig=FINhyH~ARHFM_7 zva+&{j*isS)R2%6XJ=<4BO^scMLV<389>#HB|(0{3=Yq3qyagRo-U3d95a&>6d08J zwi}ep4`A3drmI@t3q^F!3*DoKTIUP0(_OHdG9A6bvuvFFar8^c zYVfEm?ctH)LJu~(CC5vJDB<^Lr3Kl+g~T)TWCFLsoI<$E86)BWmf6$7c70V2$HdO~ zg%nNmEL{t~<$ZiOo^C=ZI=iFjSjP1>&4;1`yiC_BaX-m7_=4ReX5y=pr$T#DwL^iD zIPRi4Zk%5eQ#5d~Z%4uvQ+WJ&9^bV!aetv~_#87UW{9opRl!uc7k0^CZNzp}a3kg= zxlUov;ZLPLX7ar|7fIHSN=E1VlYkM{>7t|@2mP?Zh{)lLuc^fp4=ZC(3Jj7MHd z5H(H3UMOgK72GYrjzhb`J$4?|pYOWI9Z`{S87IQwxFOn<2%I?+IT1TThXK&He-5C0R_}le+j8J-`W`n-vtOFR*@P zyw7kjqPmI3?%Q_JTltqft1@4Fl%Fskcy*Q?>69ErkcZpNR0>H-e{@y;^j%Y!^;78RiR8~fv==bSuHjyOg@^@Nx2c{jA zWhy6yoaB?dPxjRQl)OAmN1-%4e79X=JnJP|R%6E}UdF$xwJWiQ81D4h*Y<|&mn>PJ zSyW(a$$<*XcwYTIgUz<7N{zQ=xU+QL{^fzF_Y?ZPo@2~LZhDCW<`-02Vj}j{W=B(6f&IJmMh~Kv+hw@fQr=(lMe!df!S#mQqcM zy`Qqm#=zzCRUO40&}hLxF|F74-*Wa@_oO%;3yn&BA8vvZYH)!mFDBGiD3ftgUv+Y8 z$> zH-H)i;5xq|9T>#S6a9%< zw{gCWgrQ6UumgLq)`Vr5q8VDPu14)OK}y^Im?Pavkz!uj65wAq=^FyKJ~`^F!cj&en=wlejij zG3tZ+LTNJ}5BS8&tE$s|q;o)~+k>{VUKFA9TWw*x>xp5{cS&#Ow7nLqX)t>+-<9(ym^lAy2S6@FGF(&Wket5A463oOybG2Rfx101Q$QNK zrbnDQ(WSf1}7Nee*OQxmVSS%v+hlVqzSvQ(FVGgc&B# zjI_&qT~x33rb8K20)KvHmEU1V7`bg5?=VQXfY&WX+M~$6-li*adNK3qz^zKV_*9{o zf7@rm$_T`=sy~D;?cZ-w`FS#bThrwpfT)>9Jl%sben8nmu~#i?bQagBpKMZ@h{-#2 zG@yeUw21FWs&_3|>Ht|IqtcYhw_v`dp<1kJfgdKzU|7yFGYc!)nRxiSZRuj|2*nWnz|V#o81(>Y3ZxY6z)6r%8SY#~+YA zyDFRi_346vLnjAT_TwDXhlM#sDs4?Zhp}QTi5;aCYD-mIR6xy7zFJHU+wy+-Su+n$ zwc=HxyZm|XBje`b@jypDiSooR#uu?y?`Jcw|;M!D=P zgxh%4e+m{VDZ(WWc~OoFPtdz;a@5~28fz=H?vsk5vj1vaw>hyXe%t#6k0{1Q&yJYc z5ml2h5wBtFWBJ7KKDE9!D+0>`)1U1h05ocT7MR!;o`|YFS?wkd8z26qhLS^9T}5Wr zPohrWb7o;P$w+}L$LQUb1g5Zk=Cu-m>)5Pz6G5XimUlC*newWl+0vP#SwTMu-2Ipy zjpfv+=QT!lNp2mFhW4K{R_+p?y<0+Yu4so@CY~P$w7s%Cx#lnl$5e4m1mb}>MOOEo zmXRQ_k=h&BC@R1<#%74tiG=&SNN*ec?|fH%zoY^Aqe2&atCuKLxxN5-opI}O#TCe6 z?GvFQ?473td7>^~KCyKiP~O(R!a1aYz9f+an_?SF76?&?*_7FQ5jL~7G{)v9)-l%} z;h2+1nzM^rZwiN|rS)OClh&~PsAm;H;Yhtme0DtXM!x1WFlaokD{&9e@iaoInXp*; zaQ$8=s-D7(e{$pT9yh-!#m_+I;Qf~z>Dy`@QM_Qx*>o}sGURF;6umTt&r#ULGw~sx zad@gegezJ(PPpG(;TB)gD+nE4iRz79&#-6Y))zQ5b|sIN!gs93 z!H$nd{3tuCXTG&W*LWZlX%!9Z^^qv=S_6nz8FHqhC-gTgG`uj@%x(Yb9YX||87gcY zeJP1lM9T857fo>fgf?TQx;nz)jRa@ebg#^Y86o7p)mpP#y8R)XUaqeDTXQJsV6|Yo z@UTOJ&&4>UJ%|f~^*fY+81`-g->$DCqdC^(pce^*0g#v25wDulCvpk#3})9NkH~6| z()pQPK7mZ(u{UJUs-MxfSkI(YjBfI~>eG1pP+gq1F3f4e?I)XV$zn)AbK+F*8*K)V z=Q2_duU(o_&t5F!&5g>hqPk zKKdLgaeBgwzrOm8?G!}BO<$YNj7!Ab9rq-xej^1-x*6ugit<#a41|d*zxdxsqYC)_ zR7Zb{0Z{Z)I9<4HNw*Qk=@Xpk!BIfDqrw_AOKh(swD%|7{vIKHE1pnA6i?bNx$!+c z^p~oPp)TjM+_+=ju4J((7x97f(I1nMGh1XTf z6DU#)GLR2NE-~X~9?K4RYp%8@sIHS=+3&`$X2x%3d(kCvvFbnk_!K+1EC}^ti?Ptr}zTAXfJ->Kqi)5-jp(` zn``Jn@|>aiu+_8qH@rZl#s2~@U{VCFOsA$dy=lBTDDBZ-WUArV@i)A2Z%CFkT879) zfK(Kg@`m6~ML0NTmsYMVOED>sG+$-Ko>j2GLaGJaSg8bMAT=IvmLz4J>UtDGHcQQL zHWU`We7pg=aqS1KJ=%$IHqh`K(To21p5AkE*+{*3AQqevVpcvbalF4kN>GQ+QGB*L zk~7G0Wl0uOLNDi|%xFfzWWhco{Dzsf0aP!u{?>#{RaB4HJTgmgiN!a8Iw7c@)wzIN%3jd z1)+Kdj_ebR*3?OR7-&_@cEH5s7Xr7+)1_-PnIV1!-QkwyguEK5vKE$(ypPsG@epA& zC;?;9=z+1=w>OJgeTIj8${NjMru&m&ik`U2GGr0=e6#jnNQC$@!4X~*jNy>n?h?^< zHrCMe?0}OUnrflVC$qzKD0~M1O&C!JmJ*>MtZ*C5?#^`w$?|7;QN(Gc(YoSXi&DB( z(T=w7)y+lu$*%2K?hUEq6Gpe~WkIyTDii#vrguU(N&X&#Sl`wNPP<_n+6Ja;WQd32nL|-fqM=n5! z54cn2NnmMg22lS;=r1YhgYiR7H5^4A9SL6oYIZC4l8_>b5d2Jt?GnuT1+=KQfJK_c8Vvw$a~c{_|=L1HDMj3Ldwy1yw|r0>3QsBhDP5W)}v7SVf7*P zDFlRIF1;Z+(z?o=i%fWOprF%xq870(NB(H)_U0Z!Udl}5$!T`|zBx^kB9GqKaAg=` ztPV|c6|;r2_LAqLO~)PYzjanvcktHs6R;&Z}dQvYz&lwV!avg*w1_5 z#}RnF$d`9=MXG&y4I@BLtQ@9fnByB4_<;+O6<-NtdmTuhLWnqKMN4WCYu%tq@ zm6;XE9Lgr{>H5=b1Y~d_cmg?x7xO^LP2#wIeygE^aT5My1K$qyG-W3d2Nw{hVFvNa zUVHf>#NILP0`yv57yYjL6`i@*Mv)qzLbxC;o&pwNY7dN4CW?g|EG=+&?lcT;TdYM| zZdFzs_240^t;5L_c-4dBa|;ozqg#>y=?*1X_RG+PnaNanbaWd+t(Y1X-CLJEC^0+n zojKs+qZrMnaB);Kv{;*({M53fsC-+eJRPGipx2kK3^eH(qKf5U5K70);)gFE8}oja z`|KJ0Yy-4;LZ=1 zl7_#{6uJl~bsb;xhu(^{Ghp=ZwixvB&Oy~TFNy8*q8-wR4jEqtFapA@HXXs4B~<8X zrMmMP%v!K1Z)_d4K#3qPxbv!Cy?;RDxg=VBa!CRa0gUR?s=S#CG!>O*TalGW#ud%a zPffb_O)4k+W{_2PkN4gf9WCtlw9j});DdzPgivuo+>7JP^c--7ol2k zPhR~v*oN)omYfmJi4xj;Wqz^PfM9RZV7yOwusUP-m+M_kWFwGEE#D%GWlyYk_rR=v zHxJ47GXkv{H1cbDMJnO9YZO=k`SuA1{>3@!f|4$%Q;ho9`EwlQKs_(2HxbrhkuilD zDbzfo#zt|;#?&8h^O5J2Obx#zn0{N<$FU1RuulP2>w0HZSAXPeW#iwcG)kgx?m}~H z#=EwVQy#1G_scIbCDpD14XE2%f5WT|5WW9Hv7-NJr!`Pg{#3AV$SSx_aYvz-Ify=; z!$+0|tOX};NH0adJOTI!$oX;X+|jp#6g$htox7T^e){hEMooW=H&S}_m)MS$gtutz zbq?Nt8YW`GEnubZ2eco?6QbJ)K^U(c7b)z#;iD#`s+BcunhMV@f80|f?DD^1@FsTd znC7nUg$h&s3Al!Wh}w(lO@C1!U18mHT~zBfl}6dNh8yFiat9#)POA_cmw9 z>)Ws{WN?wheE`i3a)99^@nkGP0gS9(xavMxmtmSSGtj#Pt7#AS7K^cP121!XfRvmzg*L~L zjq$X^xSBsXw8KVqx^=-FeSU&@%XY9vq)!U12d2<6!q!iFrf5j#Ft##@?ir1*_7@A7 zY`fUh%kGbuStb5IBz4MG>`9^y`}0c(clCwSV_VTDC`@4-C#yi!U&^AA-&NOEr$};!ICMu_I!z|5-M<^zL%)u0ivcAgaqyi*w zxeQ_kOF3O(BZV)CkbKN_$DyOLO#HY7#Sop?9M2@zuv(8oiJ7Q5q%_OM%S7n6CH90U z6F-);O@QuPtVs?}vVD+o7|+z6+SnK%M(bpeC>TRX!>2>M$f0#dVqT%jEs`k$siar)aaw|S}&i2HF(NgIpO?&sn3~qn(3mN${ zM=}Z0$DcE)zRV}_gDXT-rdda%355)0%+(D`0Oj}7%%rZU)j&2;z#ihmvfx>klt9U6 zSH>!jJMY_Z4J{!`yZfKkv6D6~F6enN2v%Pq*B0MnoUh2niFqM2pM|d)Uogj>iMciC z&A7J?YXUp$yRWHTzJ0LRQo&y+YWm=ar&kX@?Uom^6~FB}T-4Fyzic*VaJdqj(|+^K zRL#WJxEuCjEHAo#xQ<-6N@e07>BwCB6phYhh#n9(2OmTyp|ye*yy6}+3wm^oEipFh zdM+rxHtk5j>Tu9Yv{@ZvivF0N$e$C9J-)JNESfc{!#wJD7%Y8CaL9r<`k5PkRmV*T zS-a?_`VQ%JO4HP3;H}npUm83rMQs)uH8y66(UkSWDW$W;6pAlGc`Mk969x{PzJ%3` z$L3o{2a-{NQ8<&r=7b#V?uhVogs;1#c=LWUN|f|Yo6uv{cy%qD)6>;@ADud8*oXwy zrutC;okkXWrY00vvUfXyfKxra&%}NB@N7#~R}ri0AR6%P)WSI-U7fdYZBH+G3CsDf z`0i}2_&JIXiZSx*{WGZ!?`=>2SFHHw!0~n7@0TRfW32tl`@>G@80pWrJ&;z6uf*oU zId$;A+#Y|(NzO{?^f(^%jF|3;JT#{02477^wYj8YD6AxBDFjkA7YJnki)iSGaId?h z^O)(!AImC*bt=yv2Sopine|^ejv6n3daqPMZxQ`v=%U`unj*(ndmr_`ei2m1@4IT2 zW%mu5HWjT5UvSCbsq9x=G%)<$w)%I6x9tLb&Uf5BO}qMz?B7QJ>*PF{RiZ}QXK9e)DGRBXQ6f177kk%BV9MdXwZx8hE3W2o$AJc%(rFzPJ?a3JA;ZH?N zfgl#N%mJu9LE9-^kJLH7 z`7*p`YaTMZEC^t}=ghNQM-ZhWZ$JAH<|FrOnXrCShtMy5tjDo{Drt}b+D$=0yMmP| zQe42hrX)&tOs``qS^3i-*8}NDrnsPg{dH|no8K)V9h=J?XM-Ysiln%Jal`P~Z#4AA zuEh+)J_kLN`S)RGp=fV`MQWAwf3m`BwA44lf3kw&imL-!|L{1`iWsXuUdw%aV1PbQ zD~60>?&gz-heBm}CPlg4D&0{>?ln1Pm;?Rzw!`W2SA#h^n?Md?VN8ZCwMHuX2? zpJ{=$2dA{QGXIZb9(8w1CCwgd*Da(JX*(#rT6L{5&{jq+1xek%GqWX|8!##yo3}Npk|E8`vt#Zp0|tbPHA{ zyQb>IE8pRru@zj#o5N6bIWGz}lx_oEFcw){TZ9I`#(J^5W+p?#!$O=OWoHc_3s+a8 z0P||k^~hNR0RLff-~q;0@ddgwe(9{3-%X@%cu<>vn|8|)IM0-oZZP54BVlzI zc0Ot*R zSzZh-A_H(ZIZP_&fr!ufnx`!=Erc(TZ`fNtlUe`^JQEx`VbEx}BVTr_%kiOkgdZlk>jzhlF}2$sq6~P~!Tmo%~{m0{0n1ks6D9#YJH| zL+wudGaGLq9=??Qwzwb8&NK9#w7hIDz~)YFaCw*clb8GiXGRPmeSEBHFWVpLm8uqZ zRaY#8$3&@n-%H+cS{;lyz}CA)ROG*Y=?`U^?gYqnFckUdhCkbcl6<)*Up!oRBt9@> zr@#iVz)JLX61?9Z?UrEfvjSC07*$}3-oyiM?M7{}mW|~{Vj`5I17^r!oFee|NuGK- zhwdfzG zTM_t&G(FUU8R!e5wadW=8pqS8eo~r?$cl@ubM@7aCXxjsggsAO1CnyB zTKACdHR)jIFG=7TYMj!fbFfJ$uwayJL|o5>jE2b&~VCjL@)Wu-QTSHMLrC zkRR~roE?LqVW&%Owt3$rc-7yTT3~%gTK;xPb)q(NhWpq`mJVqm6WJ7nXvEV<#x3qh7<@B|CP+Z)$kTNSk|n$)I@yiUmV{j9fGra2m==wDIO47vkGxiFL+E zsysJ`OTM<95&6_Dza zPpr$;?ro7P+r)wIlky+aTQUm!TUOJ~3etQdHuoCzRrJ#RsfLcj(!(N|#U}@UD|YX^ zliAJy9ZBA<0pMy?4OJ?Z;;!{OWRwOKCyCkxCk3;1?PBR!>aU675QIu!uZ+EU79=ZL zCZ;yZX#3sVXPi$8SM{AOISc#0){G!QVz~J8IQcHJLd?l0V@eLwweyhmj1N{D0 zY?SsVHXg+m$FZ4%y@^e4f2$D?9DPXj3P-2Yk4{II(^gIC399eF>1@0)80KFPm2ZJiN1s-v4-L9ffk|e6v1-mNl?C=JBW5c%bg4aucrHMflbGIfCvyp!_iFbhNi?_Z8Q{qs0_)Za@cU3z)f z7%aP@+l3pZo(fdG(p2}{ZhVbz|6SW9%`3|Y)JX_-Z3dp(b-^vW4F3eb=DA0zJp5lQcj?z)g+~@tB=qbVVjUWYbFQ-M35;E zesAA0(RBLhf}wKRTVaG}h~nLAMY7I~ftZ^y@P6oAu*_&IoTc;)yL3{C7>fd8)cpF7 zJLJFpiHnf-IA}hU0%4#tZ>#U@eRjk(n>@81? zF;aW3@m7-`A|Z=aPtPTmy0Fd$H z7^h|dmU0hdJO9{rN787Qp#72XKL%g>BVP0jJ*59j%@XR~AU!6=(=f>TzHk-u{taCB z&GUjFY1~DWw@Npwlj#oZjWIFiAO{$*L#>y|D=9GgTTfsSUVffRNvxz%-Bb}|9LiB0 ziL{uB&aRJ&vn|(ImJ(wWDdw_)gG-#Pz*$f>KjYk=BYrlRgEV&{1nw;XFbkI0+*PCF z{*y6#;fha3Z+&tm#5Cd4)7bdaX<*5 zYR$};{-tm#1P6=WXvemeEqd5%v#P~^<<+el*qTAU@|DA$-Sp4-jMLA^ksId^yen+? zx8?ghSvg61YQzqbMvd?hvu1=&s-1x>@WjYYjXToKg4+=yc26J&;T-{wFE&ex) zSKvxYEJ1c4bTpjQF0V<|l`t)yPL$WX5C+-*>lkC=L7xxt)&LfRVxv0KPq;C2s78{rV?X#h6NL%vh zkf&BP>~(CFCgL6K-^Zu|>8+kGe#P#)FTuC7ESTkQ&)owoRuVH?7!aELPM;F;I@BR% z3ZrDkbx3Tca!ZP;Y96*go~juGYj^{U#Q`d2qiWuWTlG+ba=FK(`RPv=UJysfpC^;O z+$_u(&7MwabS~=ufL>kL%#TXgqHcf21@^vocRQJ=;3c0WkhzHvevdL*zQBAZ-qzgv zZM%__7XU1uYC??4ySaaP^257^`=}Qy30{?s2|32cqQXkrtcotbk?PcuI;01G4F2cC z9wDTnzbVE8#g*4AH0BPbVfv;pjRvtsHW0K&LvbK-%MMs5FCuoDx zk{3vhlG|uupD~qpJ;8Z5goRoiyQ4go!a2O>Jk;uG*1MPsSWsQh#p5Z9@F*W0hom*p2Jfb-!J>i1(bRa@yan-{ZjEgkbZU zVZ4^n(WbE#fd?tz7BtEURF|a3sI5;2Mk;=Dw^`fv-W5 zdcAo~6I5doxY_iJWN1P3-%cn0_|Ui&9b*vtD3+Ssi}yB{O1*Rv55{UQz?XTQxr^2O zO>?*U>3t)AJN-JI!zdz4%JFrONxai>Tba)-A<-G8IRe?le;BpksV|iZeI5aEwTf!r$GdnIRyb$ zvt1^D?=Wi7Q(G!E;Dvbc`TA!o8B-6OJ5GuB&d?)PvSJ48!RFbv#>m-sw8W{%n@8f0 z@8kFk62#Z=9AYebs{bL1xXSUqVrr%j(IndPBCCiT7x&oH`?#Lp$T*G*-8@_j=4u%C z*K!r_3ag!R2xiCiX$qf}CDWJ{WsSdoN5QYa|CJBr1F`YDN^s^3Gt@G23sCHO?&p6N zH21pA3Faaj_ZNGdGmKr!NJg}E7*=<>iR0sk1s@~aI>Z5g1dOjgfJlIHhFRwVN&d@k zh#HuhMW2Xy?PT z*;RZWa3kA#PJf3!;XKI{y3!H!V%XAATSH;QPUTP%JYez9>Jp!$@~&*S&+QfyHT^F zyu}p)cvFy4TLle2M-m;eNBV~1X*VYL$X09nasaA4QOK?xcRs=3xwb97NanQ2?l=tF z3Ok?R_S{~$tcOj=XUlc;)QQrVdN1k!F(GckH0JBdzg5jzhwJz4eA3y`SYCLUhQe1r z@@w*j1uvORiuvy}cK%e%}dP6caIO zz)k^{&Y$~zoxl%oLjk!Vp-QN5F-agR%d|;%VHF`-{#e#osoPI|i&=ik%b;T`hcRyY zy_Y{a4mLl+R%*;F<61w^zmkw%$5{#l8#Xif%Q8 z0dKDk{&t*ewdoxd?^n4%HvG{jB?*?9h1VWLzB5|0$^uYfm*nYgdUOVO=P0JP6o`+g ztRLN_VtoxZWt;YB5$(riz5lUO^3P@Ue;XHkwWJ0B&%{zA6pZ?E10&X61)AMC?#|Hi75AH-6EPFq;|-vRmvi XEDS}nK+s(;8beuLL#|TBD)fHSU_b%<3=9j9xZEEY7}9_=F9QZ(14=nCFzkkd4VY>e z7~p~mASUY}ASG(e@f86JQr#s-l4Hv}}m z)GC1K00)rhh7S^XF1|A?(GEIO4_itcq za5A8n33Mjk0)$3x29670M;#I}YCtxTS9z0?jtY_hqa`Sku*C;f0065IY-9t+Ycl`< N002ovPDHLkV1jNUkEQ?s literal 365 zcmV-z0h0cSP)q$gGR49>SU>MvWfmnr=0z{ihC6%n*J33Y<5M?I+1O}c9>>V8) z&4g4sIxuj+RNz-RpMin<0ftKEnG9?S5vVG6GceRUK$sO01wa)ZASNfT1EWJD$RD8~ zU;q;P6!!*@R%H!92oEdW{^Aple;lJmVg*l00000 LNkvXXu0mjfqaumC diff --git a/docs/html/img24.png b/docs/html/img24.png index a561fcc08bb42e93d3c9490c48ff671be6d7de76..71aa6915b5360c3c53e0a0d5fdbda5862f5653cf 100644 GIT binary patch delta 210 zcmcb~_>6IaOg&?B?#)gH1_s>#pAgso|NoblmxqRizI*r1*x2~YnKOcdf~!`o>gec5 zOG^W)a&d9Fd-txAlG5(oyR|;@eFF+HmIV0)GdMiE0g_Mmba4#fn3+L$vAxzE>3=I1qOzsT~>|Y>E{ywGQD-x15UsUBA5=Duz_e! z2JTl3VD%XXKs2`!L=h8I@f6(V0D(FRPZLVB?PFlDV%ae30>nC?xwcFi3J|&M2P~ou r>CZD`h*fm7cP6000000NkvXXu0mjfsIOZI delta 225 zcmZo*`oK6ryk3}vnSp_!CY!+&Na+Ungt-3y{~ySF_wL=@yLZo=IkS8B?p3Q+&73*2 ztgNh~qa!snH6$d&+1c61$Vfmypht#rJ5V)aNswPKgTu2MX+Tb)r;B5V#MI=31p)@; z3km`&-4#W$&-eAo^6)UFF(&BUXJMPmyT<*Jc|&Di6d#Walg#mjR%%8DA8a1XyvXqI zZDN9fPC|-h0K>Dr2?@661kRS+VK|aF@l{4}L-Y~Nh8*4Rj45*Q%tq%889I{-3oYmH ZGH|AgeW~P3odUF-!PC{xWt~$(696&1Qy2gM diff --git a/docs/html/img26.png b/docs/html/img26.png index e4413138bba66902cfda31dbb67b6209b181385d..c7bfe75bdffa16e21d79344d5e5c99342fedfd79 100644 GIT binary patch delta 305 zcmV-10nYxU0>1)~7k?520{{R4M*#`|0000mP)t-s|NsA)nVENYcU4tY?(Xh0Gc(N0 z%n=b0s;a7ph=^upW&i*HL_|d0-Q6N0BD=f09~~i;00001bW%=J06^y0W&i*Hy-7qt zR2Y?GU;qIo0R|XQp17#Mi@4S$q?Y+hcl5CeLKxTz8JNV@T|f~o1!8Xl?~Vzms^ft8wt^Cy z5k&aXCS9;F4=PYuB&J;nx(rMX0vO__H!*PUM)L;%s7@mkoPuXg00000NkvXXu0mjf D?{;nO delta 278 zcmV+x0qOp~0;B?v7k?830{{R3`&#KU0000mP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001bW%=J06^y0W&i*HqDe$S zR2Y?GV4wrAXn?U2kcBzG!UYTrl>#s!R|N(Jo&XRFBnK5{T7MNMHu8=4I z3l};tFzkam749dXiyIi2zCzgs2w~<24D1Uq0)yG1g@H>U0YiLgCIeS!1BUQH2?j>N c08}vmgMT7krw^CyrT_o{07*qoM6N<$g8YAG%>V!Z diff --git a/docs/html/img27.png b/docs/html/img27.png index fbacaa3d1c67bc01a13b5fb2f2c855452e3c8408..ea594f480102e567ecb5d9965bcabdd916769cf8 100644 GIT binary patch literal 430 zcmV;f0a5;mP)V1QNzBIJ2xdX;x!=nnUh#iO~VwYzL0uo0-EDj)MgqfXy ztVU~T_%Q|s0kZ&9MO+(@)G*y(VDK+sJ(9iwRS^`ph6aFi2mvL9IgT?hSakGsw4*7? zX#*=_Jix%fD#0_O0o6^c)4)Di0O3ItF|r&eKv9&!=Kv(Np$77PU|`@Bi)K1*09M4_ z*bWw+zz9+_4XTJ;gn@zk0ffzgaEwAci0nOc=F9;Q;{*ePegHIVkeu8NB3fZQI|ha- z225}gM0i0tCL9h7i?BqP2#DY+fN;3NCNM0Gz)-{b0ZgrM08>1I4Ge;!7>YO`vBJ^= zaX3~mnXdq+9NaR|Sp?NEFq8!lp=cD00-^u_XEZP$xto~h00000NkvXXu0mjfqfV8B diff --git a/docs/html/img28.png b/docs/html/img28.png index d111c43d9f56b2b2b97c6b69290337174f51e3d2..fea484031994fc353d480de96e22924c48351eda 100644 GIT binary patch delta 305 zcmV-10nYxX0>lE49Df0Su+AF*001yhOjJex|NohpnRj=0RaI5)?(Q=)GtA7)5fKrp zs;Y>Hh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchC(jQojAiO<5%zfY=TkHoAPZ}sEegUSP_W%Q%0RzN) z3=H;-3`{>JpekCxrgQ+A%eerVcO8k%TeO4{kKh3S*H9%=nx`F500000NkvXXu0mjf DshV|a delta 276 zcmV+v0qg$60;d9y9De`^xBiU)001yhOjJex|Nj600PgPY-QC^H%*?yHyQ-?HnVFe( zc6Nw}h-GDER8&+$Lqjq$G9e)$5D*Yz=_k4X0004WQchCJ41|HHGi155U8%vpr-($QU-_v z8%}m0^8|d@!MyuGJTY~HPBEBQ=)l0R4{k3{0|V1nIFI=O1N#C71~vsS$DxIROCf=Q z+W;)LG?RfV6zHh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchCeov6-*I%8x50F#X_G20e@82|tP07*qo IM6N<$g1?H2<^TWy delta 328 zcmV-O0k{7B0^0(R9De|^6n5sRcH;6FJKk`;&EL-lG1HpV1N0}zo0FdTsU|{+Rcfd0c(F)}-KY&}yz`*(epCy6-0000gec5OG^VPba8RHd-v|{-MjbM$eaf98B2ovf*Bm1-2h3( zc)B=-aLi0jNJx0VoWz#L#wMq5^i%_b4~N=)Hi4BaO5q>H3>Pp=Fl+Nxcyy0>fto6- zz~zR literal 203 zcmeAS@N?(olHy`uVBq!ia0vp^LO{&V!VDy(S2QUCDT4r?5ZC|z{{xxt-o3kf_wJc9 zXLj%2y=v8}nKNgWm6dgLbfl)HhJ=JTJ3AX087V3%3J3@!y;R=?)WBF0{an^LB{Ts5s9Z<< diff --git a/docs/html/img30.png b/docs/html/img30.png index cf23a26fade08d82eb1a237269d6254b42d4994f..79d5c4c51be1b2ecc486acb4f8199c5e6f391077 100644 GIT binary patch literal 201 zcmeAS@N?(olHy`uVBq!ia0vp^+(0bE!py+H$PvSN0mxAg@CkAK|NsBYnKR4F%R@s$ z-@SWhY;1hy%$ZfIR&{iAq@|?+RVgVc?cTk6ef8X_Kn`O`kY6x^!?PP8nE+20#}JO0 z$q5Wip$<9+HZUAXVH4!>;o*r%IHt8hf#n0kMzyBX2e=kS$TUD2EOM!%HVVZv8__`+#OMc)I$ztaD0e0s!t6L9_q> literal 179 zcmeAS@N?(olHy`uVBq!ia0vp^AhrMtGmyL+__-KJ=?3_Oxc>kDAIN<7?%mzHch8(T zvwQdMRjXFboH?_stgNG>BQ-TOBqYSh$VgF9Q9wXoVgJu%K-G*TL4Lsu4$p3+0XZg~ zE{-7_Gm{ezu$?*ZM5-k5G^fI*ha3|U%*B`{osp4tP};+(VARL!QdZD#VvUf%$u$QU Z7#=TUi`0-{+6&ar;OXk;vd$@?2>?Z|K0W{d diff --git a/docs/html/img31.png b/docs/html/img31.png index d28942beb9f79ca85d4ceb9108b3647683d12fe6..abff1e55b4b95ffa6e4e618a18ae33c21531fa6f 100644 GIT binary patch delta 1977 zcmV;q2S)hO4Z07I7k@AW0{{R4c4Rx)0000mP)t-s|NsA)nVENYcU4tY?(Xh0Gc(N0 z%n=b0s;a7ph=^upW&i*HL_|d0-Q6N0BD=f09~~i;00001bW%=J06^y0W&i*OI7vi7 zRA_w_4qA#3#OYG1&;^4P1g#~HMJfaZUzV1hbAKk2NwS;7{b{L( z-N~JM&pqGy?mhS1dlP`!#0W~&YSn9R@#*1;svDx-ff|*PymshmuA<03*r-As3mGW3 z;|w6^nk;7dM}JbjmjWeI_?b3M19YH2Ch0)qC4fBG{Xwf;Tih=7UYGiiG-@_XLB+Od zC|Qp&s4;)b$O4uVYQ4pt?Lq=a8vUu{sm{WVZUf2a$h!fKN<5#jG%^mJ1J(du^(=E~ ztBZ6W_I9Z<@p|`48gKS6*>m@-J%b+BYDoEDD=;LhE`KS8P0Pg=?>@%*O(_1>pSZ*+!V@Gd8#YWYdMTihhmIAeJ~nN z0pBJjFm;_wAq*`PCV3cM32BGAnL`TMF=6zGTElKxVp6v`YR=woX~T-kI=Or`dwPZK z6)Gy%`RwTMBU^ypC(?J74FS{lW4y{V6w02&;eR(=xW0}`rh!`8-FQHp^&tCpzz0%O zKDKCyIuF%dtGF9!_q@6iFvl4mlYBr z0nIJ?o)FrCv%d{LKfB88koV=DWq{1rXO}@TUw?giiY2ugmY(*)ei3GToePAS0ZGO} z<$s~>2tjhu{8lA*R)o;NDaqERjtEhcdHGN}BBVy4VT*DdDozE@$rYy^VNKbP8&$T6 zr4(hUC=mPr!G&I70PLa&|_*P`R79fz}+44W19W%Mh}7Nn{?6$A21} z6le|$LmkHDZI9e5@W$7zuc!id=uOLOK*wZQkFgyCc52wP8yiaRaRh^UEJa7PiXmd< zFJLpBvcN_z#7yq#!rP-hgeA>(^L4@rm${z2h_3t!dqc6*5Vzv6J-q!|Ebg3EgotFy z#n2m9(HxuRybwZg+4^Pp;WJ-EdVk0oXV^3D+Ok3-^mY>H0by;lVo@^Rq9P2k$GLrJ zAL<`KAB6XP`G1Rk=06X!VeU-LxPC%kg5f?1usTE`J>k2TiMG zl^6!I1JJb*dhUBzyvE)JZ5JrJqW=AYUVI7JoA?pK^WQS91h;#juz4MfZHK>4L@5Y> zRthOgPI6v0Y2N2`UL}U16NU5mzXD)dylz0#@sg3Q(~kw(WKF7#)iF5U_R?-!xV5dwWVH@LK6Kt3V*CQXd(9gkP8i>5m z+v2d+p|TdNO|yw5C?p=ji&v)6j2U+$r0rLQesdOVP|n$+jI(eM{(!bwFbMfNNBx$o z>ds?$$7u;TKkLCxd4Cra6t1yvRQJPG^uciXb&~W(vv3tsk7%vE7d&ueNS^%0}kt`DzIhE>ZFsgDvZR1`qTm7-U zub{75Q{WWt2);3j8Bjf*Qc3U7anbPUlbcpd-Wq>nMR+-KVST@un+x62J563_4Zro{>OMhy@AgYDf6^O7@Xt zYKqei-h*)0;v?+)3crKG1dAilq`qIf#Yb$IvFJ!)4~w$w`fy$P!0}$ZiOSp@FpRbf z_&fp4pXDBo(lY;c3X2M~U=+^In`L8xzO9%~9CblBtaTRxWijO+DH@?N(~%QB00000 LNkvXXu0mjfbLFR> delta 1742 zcmV;<1~K`%577;f7k@DX0{{R3%0Jla0000mP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001bW%=J06^y0W&i*NPf0{U zRA_slF;=b(g8j z9I2wCfT*`u4}UA!Frd_fKB9V#f|3|jJuI`_SgEF?_>eQTaugr(!df|s54o#Wj^aZu z-LfNf=KvLtI5&fQJ=}l}xM*eERN7Vpc`(XgmqETBt~>?9mZ_*VtBk_Q$kOpnre$E8 zGRW7%MLUp^c2jPf`TA{83fhx+tDhW-RkiT{Td7WMM}LhD{9C3KGK@xUwt{eCXXPcK zZB~+jrZjTWd7cs`Cmffi)A77=>=?&H*#$=H`Iw(?m-70D`65el_2uIU#ADj%ZTf+PR@I;4kDjZ8I25bQA!480< z09ktxtbeG0!bAtOKfn*iLlY%I3Jla$5>?b@B)s2z6xar?Qf&DDfIpa+c>XX(X5Mso zwmF~YJ-PWZ0Jg^&?9K$T*#&KowL%nb^XHn$@Ez3Il5^qQs6`3Os4ffxB~gnm1!^-w z=l#YgXro*tLsIY_P=^(XF?CvrOjo@mDRhknK!30Gb969UK)C{Iz>w%djDBAREt%n1 z2JJ{VkAf&+8SP_n9wJZ@z2H(fBWJPbH#&J-tboE|nFXup@Bxy_PQJYap^czul+X_>d((O^m z;(vfijTV{vy!f0~EmfT1r=ix#{5ep+!Av60gvFqoW4HE;!yTXHkNAJBATnE8$g$}( zO7cVj)c2^T2^1a|)?AO;j8dZCh=TcTfWi_C@2p2b#{r%07n!{-gG8aJL$`Sv2W;K; zJiZ*%2Pmv&9`p(QDa&Wsi8h}~ka67c3xAN6!-`V?bvNTcpz5!fS|8G5Dba8I2)n=F zr*Ihbhj0o%AlKj1JpD9FZ+9sekS(G5ctN2xmmI+$!f&`t^!M8P`rxcU|Px&b5SETXX%*XfK zt!O=X7>_3hl0tvB>v$F@e@+qUIm}yQ4iua=knUqbaW}D!oMibeRl5sJs}Q7654$v( z;g7}J00byxi;(R0^pZ}}@mmmuR)1R>)82&qmSD(DLdBfd4Lu8B9x0h}%;vV@WbA?j z+2@54U&oO6erhM3OiBh%nO!>B}_gZB~>(8ppFjhA6=4}Z(0Z7`n4 z5L2PA49St;oj?zB%g@F@U4xuvYiw$}mzV9_I=4rk*k0lkHoeZP36yP+8F2MrKK>}R z_PaK`_}0c(%+%@myKO;X@lQB-iFcgOWnkYjP<6Hm~s2HF~NX(VUhESKNC+HC}Fn@xSBlHMJENpm13|Pz^ zdH{wVAv+6xcHAa)id3m$;2->+zx;XevmKx%HbIB7oar&iL*_ptlp-o)g^s7&C1d~r zNS!VoX3S&^0Tq+G)bZ6nsFQRF3{CcViN0NI3Pc9U!lIy34((Czo7%0X!^#Aqm)0vy z8Z(}O-$0Y1M1PoQ646A^Fj>-85|NgON+O=C1_}8B+$8HX8-^I delta 376 zcmV-;0f+v-1BL^T7k?rI0{{R3`%($`0000mP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001bW%=J06^y0W&i*I1W80e zR5*=eU>JnJ37Nxx9GS;)2109PIUtGhFfeGQLD>mlE(ly82|vn WVlS~IijUj?0000Hh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchC&<97G=D)r;U{ty1XV`>%OhtvJkTYIUP9EYV3$*qjwV}Jd@C@uq zqg0wTdy837G>xu7GBZ31q)?~Fv`xA}&U13H#GnhUBPkmUu3etG#q%qVD&h^9;0A_T zrb`c#V4D&aA+CrJYKJ~2Wle{csx%iE_sJ*F!GFd2kAGA>XHH)pvmfTJf|I#}cUpl| z{!*(QQ6I1#JVE4Lsy|+1Rk`5bjmaf+^XWYgsuL0FM(RtX%`m8^hIeF>Z$>?mYY$o0 zSC(q25YSkhpdwmcP-m)$K}~^NDp( s?Kn0c%Olz9_1lQsAv&uLI`|FV04`fnnjWmzv;Y7A07*qoM6N<$f>FBzt^fc4 delta 493 zcmV zKwS0$rbTcL3gDl>ptFJXNcsjOu?QZ9wj~TjH(58ZGy%EgS_%jb5HP_^adcqd5a2it z<++9iK=fL0Fc>{xU%+qxoO2o47WLv{mH^+W~+o)0`TAl#fbm|hNU2DSxU2}~P| z7#OscGaxuXy?-1qy?YoK3=0@p4itcVwgB#CPb~(H0zFQ)snrZji?|Bl92C7j7+8-p zL^B-+`9T}*UzQb{8F&nIN;r-(F>om`EQ4{FI(j-L!Su37b+jqK!e|;yFW-%;5Ec)Y zD4j_{KR9`bk_hmwQ(Ev*i jIIKp&C>RB!fEEA%NE%$qQy}0c>$?R;cR8X|1lU_7w$u_AEMWmy)f`6o7+6VDLaIi>04Gn#3 zUtA+%B^86zmsVv=MX`vENzsxLvy>u&g4^Kb$#yAHd=ZZ+tzy9VpEI|!nc2x^yU~|? z?9RFTx9{A~48YPT0uZyd$^ys$#S8(GmIVwTp94^09krhVb+&DYlLjkw!3#oA9Vn*>K^J%K77w1X$SwNKUaSK2@SVqJYB3E4)J8h{yJ?QV zh}+9vxC3>xY)@AxiNwM`4!B~)>KEZdkz&Klj&dER4Grl3j%+bOSXzc7v3*3^eEcG= zDz)<#9635DMbLn63TmhotOOIF!yPXdZ3&K4Q&j47J??vA8*(!D47uVI{@K$~n=_yJ zxkUD3Vt;mLLLC)|s)UjEu7e@SmWz`Q%VAj|l8W7{}8b?uJXLG%>8 zfm4<8!MEj( zhGmno4hcZBCsb)3J?XbnIC8@7?9NT-cYlKM_{5(#Zac%)C|xnmcF2XJ@s3m|I=Xq& za-2-=QD6mCt3ZPgj)JRzif54ybG-V!oxpNEjk<9i(VzWNTCvXRz-;P3)dpsE!$amW z93^6`K}Sm+keMaqAyyB_RV1UoIkWIG+FDFDX@~dzm4NCkAbo4h;!aV>-{fn0lYd;h z#e#zrHod>1d_a%iY@`Ekulw?lK8r`+BsiB-|2>}>P#H$Qoy$_xts~P|GZCZw4~vbU z|6VuvmL~b+d8E#75hiBdT71-c_#r;17W4Au;lAehz)t?Im+}sWltSSd9ILz)sLg(3 z7~jE$=YFfTcF$L`?h`yRgV#n0ihpymT91#`HL)#XFgJOnXFH~bn7fa-3go;4JyRn4 zsvqPqI@);dwOZ>vZZdFeOe)DB_eM#orKny*V3)D0yt_gU`}Tf957fHf1#t3>?t+ow z->)ER*9b?7Z+_4YHi=igZJmmpmd>-|J1 znw`RZB>hrFo`p4h=4;+OWPjWh$7gw1TUQdKBx0=tIKu>Ii8X-nk->_B~{{rnwMSXD%w=n?#bU1h?Q8+yX7o0xhTp{_Zy|&;l*c0xi%27a{z{9z1b!oUGYvWhS;I9@|0^Vp#m( z1ngfA;Mw@lbBYf=r})rwiVrh@qR0Q7d>te{(nb10x|q8Glg0@whgizerEcUo5cE7Q9l^Gre~AOM0w`f$Mdw{EPHNm*pm5h=VKt zhPCI7Lr33=)t&dBq$jTE(cZH$bgK;unh|lLKWS)2C9giiMe$2Yx6$JxOf~}pCyY0E z9!uzUeJvUyXKr!XU7YVb^fW5nMo$Xylg+@kO`pwX@_$HXlSppq+2_@#xF~)_={|aF zH|3LV?U}ucfU8S}BC*}YY&+cN)myk_=v#=(rVPHV55#@+Bx{}QRjvcKv_|DGyRc}( zCz7xY3tRwzfNEa7fnV~!6c4RCq}P3r*p?m-oC#>yq+(3>=|dDMjMQ#=D8Vg6Im3h} zGL}2DCVxLOY)S-(;tsC^7qz^41Ip9OYFvpMb)-WWSMcjTGAh>dF8tE49V}h*sz+pn_r2dT(+LXv}?mq8{*WSdG`N)1gh-y-Tn&%5;3L3YiHIe zN`IBtF+=g6_RA@M4t!_YI3rOFb5)FyZ_wzgOmZmsvLu`5G>AcKN^}8R1t~f-T zQFjz)1)os-q$7F)7T44^w1n=g_qtBCm)z5RY0nqHE)IkY#H6p#+i3GEF3BdDmf2fq zT~ zdporFR#zSN)pD55tt2;sH2It;Ovz@kn*(}^4k@|U2cY{sSIWxuwQx_bJ+w?xuv)0N zTrK3WxRKmFjh2$lvRU=@RWs=nCHcw_cJyQ$Z`-epD6gPplA${6%k)^4w$9_o1%FjH zDA_EBN_FFzb&68|s{XN~Ctt(st^SNq0>S$gyXlE zhMlpchqkC~J29&?gcK?moH-1ZPB$D-*=iKK z;iRIPY~G>sK0S0Wq4-RX$raV~z>}j!OZ53NyTp+Rg%s*p?2dz+TC#bE&Ym8ebPGMS zNlNk)J%QN8lR-cySRSMepq3C_juM!bbsa}T8^wOpITu|+L$U~k9*ZpCdw<9kW47S7 z(4&V4u8*^u30n5U@)i6ZdSX6{f`-J$$0oe)R+(&xifLCgwCm)Wgov#LM zHRqxHjaQ*0XGQG6^u*yxg8VJ;?!olf?XTy49O}WYIeCV|I^EA8#jYpQ6TSQg#}z9) nnx21;4?U;&&~u6pJ*W5|4rD@M_uFWt00000NkvXXu0mjfpf36H diff --git a/docs/html/img35.png b/docs/html/img35.png index f3d1e010fe768105d1d471aa18612d1e06eb37c4..7c9551ebc1faaf33cf4bec54e4500a8a14a127c9 100644 GIT binary patch delta 248 zcmeyy*v>RTyk3ZfnSp`vfWc!n1_lO$0G|-o|NsBboH?_+ygW2C^xeC6#>U2H&YTex z6kN4xRYylhT3Q-Vp^J;l-Me>{l$3Vw-YqYyI29k-8GdZ< z;&~FjO0qkcY!`A76b|_)BGdLkOOr8l)#8p!r_61Cd3eHfq|ur7k?830{{R3d}{zT0000jP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBOYl5R4oFw*UYD0d!JMQvg8b*k%9#0C!15K~xx( zV_+a3u!M#NGcb1`^B6i%R2+p+tUWtAb}%pqm<52jd=nUSHej$GN#6kGIXWX^vD!1I7-MgxSmhk?PcfRW`u0hsrKf%P~;G}Cbduys-$Z3=LUI0cZcHh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchCQWV4bjae;#i@I7tAB$O`~xY1u8swli=aZt z(0^cDMWi@6ICyTFJ_2o}_*nFV+??+`?m745ML zWzyoKh|8UEyMBhjJynrdm&~@NsDQ*B8G5n8s+2@HN@V*=s!7orp-;nUQn8F`<-R0Q zsq-)lJG5n7T7Pt(L-#n4S_qX5aY%1bh$1TY_-_1c<-dwxq@^@mts}@rz17^)a~V=0 z@nkWg3Cz~W-Z3gE1*pSvEh6crOe}0$lBpz9+ifN+^f?H=?*g_>PhC(oNlQDlgfViw z;WJ^N$a7HIpY*){_+Cug6S=FVnQfiKRCCWS_iKH6OnhS%k7)p9?6MBY`kr`k4qno> zoOPNTzhipg78!CtlY=0Y+y&?6zH&aSJGtJ1wa_^lTuw)nth z*Cj_Zz^of%_wu}!$F$%E>UNLxYg6+VV}fFcdhn0Gg%7YwTB2A_%S-?O002ovPDHLk FV1lPl^1c87 delta 457 zcmV;)0XF`X1lt3U9De}h!ke1_001yhOjJex|Nj600PgPY-QC^H%*?yHyQ-?HnVFe( zc6Nw}h-GDER8&+$Lqjq$G9e)$5D*Yz=_k4X0004WQchCDij9Z3(2$})!6+C7LmU7A@zi5}@Y)oz00000NkvXXu0mjfN6@jN diff --git a/docs/html/img37.png b/docs/html/img37.png index 6795fb99b55527f35c5e3061f83983e16e475936..5c33696239176d80f258397c74fca66ac5d2531a 100644 GIT binary patch literal 534 zcmV+x0_pvUP)*R6R?>Kp1|KwCP7$TAW;ja5~slF!%$ci-=n%T{E~j zSo#YB{((9dq&SEmLM%c>M2bUae}bDJ6pA7^iT7TvN!nhJE`kr-llLB;yZ7$Rn*b6` zK5PnnKE@QM5y9kR8_*1oOs)?lO28xJx)KbvDH)#NRG0VwXagBKQEsn*uC!=^8$`N| z%|$aP&<>-lV9JPNoO@C|EaYuia2QSe9b(4#lg>fnJ$MOAl;yt@I|h>+qiOhn6<&9s#GiH{$jjf1kC2>z9Sz0*<`dGnn_`(f9{# z-c2UC9$Qx&+1%(q%iN4bn~8tH9C-U$vRhhly;E1YZ;%?w+_#}vQ8^Q#|89w4Wg$0y Y0P?g&c{UR%1poj507*qoM6N<$f)0P?*8l(j literal 483 zcmV<90UZ8`P)F4h379*uiCQ#ZV}bxy*TCEC&iulrIMw z%OK#x&cMJT!obi7VS>O!U|tOqL^T-% z-X_3U+y@w##Ss!e7+B%{3o!D zv53M2a|{?PE-uHW{A6nc#8&2BDR{6XPQa!V1Pn}rv54YSjukLFkffZGB-IQ`q$y`$ Z005hHPj1@+bnpNG002ovPDHLkV1i(#x!(W) diff --git a/docs/html/img38.png b/docs/html/img38.png index 76e1f9c1839c928bc73fd043e79655442e44023e..6f37179c17eb55e0922e508dead3913fc49a7e9a 100644 GIT binary patch literal 270 zcmeAS@N?(olHy`uVBq!ia0vp^l0YoP!py+HsLdY13gj3B_=LFr|NnpH%$eoo<)NXW z@7}#LHa0$U=8T}A;Hp)tIyySi($atmU0hu5-o2}&q_lhYZh2Y7sX!sdk|4ie28U-i zK=M7FE{-7_Gm{e-ni$wP5|R@v7*dVSG#E4PZ5Wcoma=j;h$tUsVpceM>cIJ5jg5`hrF8x`O8aP9BwgoY`fsQ3dEFriJ5HV| zp03Dz#XYh-Je@k$Rtt+R?e;e?&{R2m_e(Wn%znEG<&5X7cX;e%JjKGW-dsj%=c8$F Qf$n1PboFyt=akR{0DbLRvj6}9 literal 248 zcmeAS@N?(olHy`uVBq!ia0vp^5(8WIxX?Cfl0WTdF5C?Ft^^iq8nPy=I0kY6x^!?PP{ zKu(#bi(`ny)Z_#Od4qC=&ktmtDX6tBHu(0bBa4-BGlPM9c;mw9Up;=Y8Khe>JF^@w zT(Rjn4^N_vv6RA`?VLP3Jv!`M2j;jO%;mZ0bDURU*;fuWg_{}o8IpGz8GJZk87wJL t@$gicfkDba(>Xc44Xcw340zi%G5okCey3uke>~6y44$rjF6*2UngAcMTKWJ0 diff --git a/docs/html/img39.png b/docs/html/img39.png index 1aa74cf383b818824e5bda46d458a728946afb0f..126db528cf239c1c3ffb24694b781ba0042682fa 100644 GIT binary patch literal 837 zcmV-L1G@Z)P)KR!wLVK@|Qn*=)Mqq#LTIp2qF1^(ROW1i_Wkn}@15 zK?#B&D%wkrLhvH>6cF$6q!%HCqJoNxryg>Mr3Y`_L(ekwHq8DMc#e0=I##o%Z+!EEWhB)fjQn z551b}c#;eL5O^cu6)Nvha5)Mjv{RWInML>5c^}UP22zRZHT85;$ZGNr2`5Y%j@=DaC@__7b#(pJ@Y|9O3m)#b4657`C z^Tn9rrsM`)81!Rz6xj!M2$BqS=6v5zm0M`abj!+*Gu#tL^?m{Ueh5*I@nMAdyh0HO zH&qUGBv|88nc?J68FfY@Vm>{3tf%Y#GwD>XFG)vD(A#29+%xickG5pZcmm9h=4tEX z`T$Fl$p7uH+FURN$ur7X~+YUZZ-pcLbrccQc@8 z131|57cZc6p8D3+8{-dRVLOaj(p~}gz3A>R;l5=1B#tP`xagNiHa6} z+SM#&8^VwvTh4iHnt7yJm#N4<0Zc1-xsQh9ea_DM#mAN@+{-%Z1>|XF4=9y#J)5aE zt7d;0dXGm=o8`XcZMwm%Rw{IfN*|{1J(Z8Qu5a+Ku&$X2=f^s6@Z;P?-K3?EX}t`z zn_UWLpvJ4zu2@*9nVOSrHSd-JgK;Q#WO&t0ZH=sBjricJ`8(!-f69IX%TkD(l3oL< P00000NkvXXu0mjf9x0E2 literal 760 zcmVzP90000mP)t-s|Ns90 z008dp?%mzp%*@QYySu8Ys+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001 zbW%=J06^y0W&i*Jc1c7*R7i>Kls#w^K^TU={kz@GZEz1fxmYb&XrXYRk;BGVs7;FX z|4@-AikRxaLM0ZP=;07@uogiZ@hl{wO$Z_Z5e^cGAy-5#Y-435q!APwznT4Eb|;%n z8moI@hk0+_edhaiXAhvKo_fkt&CAayWD{G+NEurI1If1fn1A*33DH9JT#9dMup%Os7d2o+mTJ%A#u@ee@DVfI$C;(j|wG0k8JU=Qo5zRLnw zQacT}h!b@uB0OgModozvIY=@6064GB?!TSt+ZMo=#NKfAw(a4grhuN z4pK}%M+5}zyTiLdydJU{GNFiXr!Ux8YbUDNvx{?AOYfqoc8-c|D0%!H5Aga;C(0@g zJAB-D4PqbbLgLLRQ>EzOao|(@kyYp}cUXcpa%>1U4ogiuF)#JXk0z=MG){;6T@?0h zI&ufj#^C3)Pgex%^W-o7?R+9{s5_2rZ2(^3jR~3uehhw(R~JO^KK8S=21V+o@#sWt z7iopv5jq{fx-eTH|w6rZB_Vhyil6^{41Eg1*KIXucKAdk3;Hj1?dHl9De~2gkYEe001yhOjJex|NohpnRj=0RaI5)?(Q=)GtA7)5fKrp zs;Y>Hh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchC!1OCx28*H8|B}@CfKMOqxpKk*BSieu*yRQ zdCGigASpOM-G4v|xcjPcQq-r~7R-4L{g)^;Q|tIBB^dLPM=Rnu6lmaZTwX%r+|hNa zxtz#b;$5@!+>X?oh+$Ij0{Rve^Tg{0qt^?eg({1dmxqO3qSbqmo(@HjU_8Yam=kCN z>rOJ^qy$OMvkzi8!MrWtxf7(#>FU?ofgPB@)u(RP1b@(vkQSH8C5>qr|l4LRpSZ86g33ritvL+Q2>>9!oFQa z0oPcEc3$z5g@)iL(Dyc~^-+Y&e1K*A+-^I=quB)?^5q|>{3{$zl4odGxP90Wvl1r;XA@Fb(z=2kz6c&00000 LNkvXXu0mjfN7P|! delta 673 zcmV;S0$%;;1+fK?9De|3gHR3t001yhOjJex|Nj600PgPY-QC^H%*?yHyQ-?HnVFe( zc6Nw}h-GDER8&+$Lqjq$G9e)$5D*Yz=_k4X0004WQchCz{Th6$hg@6wFXTs7REmOK?)#VicvmdoLt4=3)iANWQ~y@B96IKfL>KKt~;Q)Y1PW z#ti=KAN3vBW3&hO+ka7V33G-n zVK*~_%o(|XL4S4=ab^O0GlrI~?~2>OY=xQebSPtZ`Oq0=L1jm#WuAKVV?uDXZ@H@E z-gC}PE9LA`F#Ea^?W(dK4CZVo<;#nq`_*fv81ihwxmNt{o0Q|_XII!FjN3PHom$yUr`hPP^5L?riA zeZS$;M-jMn{5r^HK>MCH1b35-0VJTiVn*1KYe3{A!uzurZswk-b3=s;0_D;(kU4(Z zb>)lb@sa%vuCN97Bvx^A2VORF2Mk5-7s|)?=ypLwFP!(jg!i~}zQGkXDQd2FpHWr*r`qcII^&r7_9%Y@}jFl2S+Hk7<$?$7!#N78+x$rN71@@(${J ztNc!>RQMy;f2fP|*xDd}CADhBm;NnM>d@N{)*5z{~`)m4|_e`vS;R26nI-9;p6&pi}SwmNlsS6EMb328Q$t`~j05 zfO$*>Aj~sE0V2r`qlw1=b_!8*9Kk77+#p-Ug22P{o`d z7#KJ%@XTm{aJhksxC9tk4itd7{1X@$cpgME9X9}T9UT}L7#F}ToDal_0dVeaAU=a| s4$xZ8OK={GD99CXpY%#}tSW$V0DPAk+s*P$egFUf07*qoM6N<$g1VSn8vp8<1lV;1lBd|NsA)GiR2UmxqRi zzI*r1*x2~YnKOcdf~!`o>gec5OG^VPba8RHd-txAlG5(oyX9pSrvil-OM?7@862M7 z0Liy{x;Tb#%uG&jV7kM@V`H$*B<2evvvV`!jH9O;nD`1DU+~I5YE+Rv%*H0u!0NNf z(4-+#txdte_Wz;H+zOuC_!IQlo0(?JJ5azd-I9mr&-;m$dl(DU&NH&9Z7daE@Myl7 zK}ESwgV*1u_s=gllE(7TKvOfrl literal 242 zcmeAS@N?(olHy`uVBq!ia0vp^l0YoX!VDy*$Lux(QU(D&A+G=b{|7SPy?b}}?%gwI z&g|a3d)2B{GiS~$D=X{h=txaX4G9Txc6K&0GE!7j6c7+dda1q(sDZI0$S;_|;n|He zAg937#W6%;YI4E?fd~_Y&lUnUVQg&k7%cQBG&WAO6g{^4!~ucFVZ2WZ#MlhJh#XjA z!ptn;S9YMnw~dpB$?i>nFt>zsg!u~*=e0=*E}M4kT3pXO=kS#S2Z|XUs&7g+RfnU>gTe~DWM4fr^-~} diff --git a/docs/html/img42.png b/docs/html/img42.png index 14f3d892ac5b671e16fe91641ddf79318dac8a97..77bd82e9babb6de4bd3a0a8ba5e3dd0c098b3458 100644 GIT binary patch literal 572 zcmV-C0>k}@P)D;LVtQISX;GRhlMM?+ftZv1@ zIp9B#KOu^Ph(j!0wc_N^A%8+f5ryKYAilf&=ou4q6#BuvyZ7$Pd+*-895Bab$00p;beY;KT zFd_qF_ZxoTRK$KxKNXVWl(y!6zVE{K~mpa^B$?*N8hQ9w3 zmSkm^tdcudz)Kt+gSy3y%rj>A?|yiH`fN33ldju<=monyB=yZO=)Rb;Uxny3-MF8} zQO+>z_>{^@&^-pjRbrPy_-hO#rei_Y7>jL65 zZ(}E=7Xsk$2dfiKT_GV_;&Ovz39ymH8`Y0r3R~6i`{3;Wpd=0000< KMNUMnLSTZDX9wf} literal 538 zcmV+#0_FXQP)P)S-i$t9B8$?k-+(Ny%L))=~6>XpRI1o<8cw%zF& c{nszo7sPi|y5vjAg8%>k07*qoM6N<$g1{H^OaK4? diff --git a/docs/html/img43.png b/docs/html/img43.png index 3e1916f810131b8d601d700d2187c26416fd9918..588abb24516e6a14508b6cdaa2745d54ea3c3471 100644 GIT binary patch literal 2817 zcmV+c3;y(pP)d$s00DGTPE!Ct=GbNc019nML_t(|ob6qUnzJYmhJaLe!TtGN z?*CSo03t`V({?(Y&-Z!8wh%caA%uVqAy0$0eB24^t+anu`-#}D{62NHp zWx(%*ujy&?sQ++zEW2BfInO4`Ub8F|S=3@_^#R@Q1G4E0z2?cM6{6)g*NGZrSUgQG ze=AkIZV79qBL5~gLd;!)Kv5<7pjAq&!t20PWJ{trkqS6@8H`oPSK>&yUkSPDj!}-c z?x($g9g(V|4_^nQ3ga+rI)%1jHuj^`0lEo2&9XLT`wX9nAf+Qu^(Z~v=h*pd$Bv6!o*@!U`JGQY|zi?pW5Iy_xJt#Hn)9`XD z5JrZdg55|=6pd=M(J#~$SNjBBKcyX%*Z^1GgjZ_@%nQ{AYln=(!IDh!wB9sqM$7#P z1`S{+$i{r;E8KtH2;Xj6iPA(zD?qr# zQpNeTB+>PA8ya;mx+$sDTl%`2fmt~*KFwoZ50f*sNo7r&tZXF|MrkQTMwBK}0-+s) zs6G8Pp}`g@tw8}|g!R`gXS4!yGXn)_o%hiIhrVOja)@`w`Y^WmSp}J*wPH~vnhf=c z2cBut^|8uPcro}1fmBj9xo;EPZDk(@+whFy9_+wJ2WZCDl=q|Y)?nP*VC^3KZ4L6D zw-JQ+wpj0l3%?b2#i3srwEh;bWMaF+XlnZL7B<_>7HL?|`qRw2hq?PXVxNU4MsG&a zkBrG>&Y&tCn@pjnuyB%t>#-x|!O#7`$tL!kS{DJb)sJ=A{a(0FjO#^o+i{sA+!l1&)8C7=$wpVJQWa!Qix>sp68s5~`QatNNvt}_)V-W;1n1Wx)EevA4A6YqdF~O(E*z3Kn^|k7tWk7YK_{10Bk41kQXu z?xQZP4piY$lBjveGo?7OG$T`zW@s;0Q)r#18roA9q-D!oq*;Tv+k0I{G$V?Q*y+~Z zP)Re0IVU8R<;kw61AfaF=&hht4|{P5y^a$DxUR%6Sb1-6BJl^dma%qIHhtGvV8e1H ziP{&`iouSh{hNx{M zZJd40bfifb=2qr^`HH5oD|40TPi&bYnm45omDC-!l-2M}6TQrRFn214MHG7X{0gm^ zbF`%fTfxbUV70n=V+a@L^@nJAzrAjM#D%S`xKoNGaf{A2HdEMEPVcbt{c1r8Z5))_ zGjMinHe=7F+*O+CfE1Mt4vCw^hI&>_JejhG6HHbU>@dMoM@(89u)shUOE(ZVINMqlE0GihlgBbEDJvI@OeSa-Qy=wG{DKG0?q<+usjG~2cSq8}#?g0$px8xvmqkkf^LuE@#2x*jC;&qf28HZe`Noxuyrue1ftN;dwJ&V*w`SYIyd zx1cL?vk)=py@OHRHw%b?7V-zGwqqHwT{1(mNG{{YQ+WaQaVdZ zTl*`e%>6m409l66+zC>ns2}EAfqtCdZ0hU>zz-PbaC&+7TixcPj%b*v18-sr05 zIx!%4BBn)j3$+JQwEgt5=m@eRdpRJgG0I7|dEzI4|Dpa=OZ#a^6@@B}{fi*s&w} zi>;(l-K@o(9$?RQJCz?v{EzC$(#BdI?`Bw@eH_c6F--_4y> zwkb_K#f@vC@vN2~AIE6U=5IkzPD(^!c~WBmvBCFwgYK0~!x{CykHMtn%Bef6>`}%C z)}0gV^1TZtckNFv?D_+-oq5lFjeLGEOG$nP1`m#UL27i3cbHZ%SReY_WBa-IvdVr* zUCOm!>i~0BKg!?7-49H>3o>YDG0bV+RmJ_(;cWY9hnVBJzneb_cYu2t+!$2Owx6%E zN9k-kP2EA~dMuuS6WaG{>*&Jj*~7}DRY0c{_G1|gW)@|{%@oL*?0r|jV?GKUy6HOV-~i;~8e zNkv0pogF!Zw<}{ly{QH4{g%o+|K-m=3hWK>_LC@O?uMV)-(wMOlT2HG()j0Grk!*#OvcSGMmI+yJ_&3oa(g-7upZBR)_ TvE~i000000NkvXXu0mjfJN|>f literal 2405 zcmV-r37YnaP)g00002bW%=J0RLN& zBDDYj2_8vAK~#90?OeN+C!!Cx~f`l_`D0e$AxON+;}&juWrDNPsh#q`{CyN{qRiAB_U5N z?Q=?gM_l8amMQo+W^T@(h%20nVUooMBY&(hMJPr-sN{FW13cK>}43kL%>H@5mlzIH*lZ#{ge9C4fz0Ag z(vq<;QJo$^%nS;$Ti=Zmp29hwsnS7rTGU9(8NJzHbAqCUfX^YE(=0BNrN{OaOxKd_ zAPgL6z4)gSm?piON|=;-d=t30rig+R6^(|9ch^D>NjO&D2J=K82PHqYvkyZo8gCWellp2fhaFy6}PJj8O7ianhsW z^7&wuvCFP;&SAQ;-n7!rS60fUx18(h))k#(83MF~YHCST>=HQFKQPWa@HJ@Hg%2zz zl!Z;w7562NRT;aiP2kKqU(DtSn70)amD!y0agEhtJDQEyraElHIa}K;R?by#D^cC@ z)o9m+4=h!OGKy(YfOxD*l)OKbPM4f>X&9jDAfV@*qY$fc@}KqeHeJ_gej3hw0VwRz zVCJ*27Fa~JQJa1~BI35Wt;Lcflxdt^YEF7`rOMF7h=o1rG-=qTHZn6xh^C2~c5${P zYO&iiseeqN={%mHIAWKg(N1jD8xtONcQR&#&i;4v457WE#!0_^WGZjGQ-FsLh`5bz zYqBJ$(iNGs?^2bai^vLKT<%M!aWPrYkyqIS5RVAjTsuCm2?Y{ruv|FYbox?WQd1kQ@MXWh0mS;`Leg@$Z;a#&EgalVVu z+I}pZ8j!yB#Hnd`=eW#4uN8CiYMO|2Je`kr{8#2Eu7#q(rGdHyZA?L;VjYrf!Adr&QlU>6_*U~tqWNq`%xMwVdacQA zXB@0Udd_Bdw#uR<58K`mz^t#1;_Ia6kAPc~HsqOy`|mY(xSI^C1eJVduY(CBeS@L33Z z#&laKQy=$^gHxPGUNdfE^~G)L;2l#7k*)2fC)+CPL{%*V=Zlw4x0u2yPZ-9cdS&9( zAXd(U$_rik?T@%idJQn|&WX5HujM}5ac~i8$kq%oo+_ti>AQ%6bh;y>#lXMJiS;^j z6Gb7FwBQiJ-pc^L)>YgMBEgx{R4S~S8mm21gQ2kVM0u4vMAa;P7tt!6w#sNMJ2q7_ zJKmBf;6uwwDjvMxI60@J;T)&UXV`A|%$BXH;${efvvyk|6;@4+)xPNx&I=Qmo+MT7 z5>>JET|}#N+A5=E+N&H?;c`p%6+2BmcEOT?;B;bjB|4+)-F2Rmln=dYY40X{I^wkae4K2L!qML z?g8A^Hsp=fzA4QlVB6euB-k<<^v=X`?PBEnMj0*R+o0wAM<m`wHVvNVIiV-xfJ|LQQQxQq2oJ%m+%o4J>feIo#A|cx57+4w6i=f zfpdFJT_+ZfbA@!)(TkOHJ;!yf&sVb>kK+lPW8knq7?CDDnTQGO^Ab3>QscaGzDzxQ zA5Hki5qPZk)XuC~9KBJ;6F65RKfYwICd$p=z=X1eV}v=M5YZXiMEI=pdHum;tqeon zVJd>VvSeZ$R48ZGE{@));>zC~$iH328)lz!Lq%qCeL9Ae`{zF?_vc8Q+0FUGxR4tS zjgs4k;DR{%OCelXF*(iNU5v}Pz&Wq}agk5Jcc13r9)$Vc$>9ZyE4Z=;V%?Wrd3&GC z{qUUqIxg*dW$}>r#>0s2L6`vgF~q-t*757W-foZ}IsWwnj+>4ySX{%+`3oVs2VuXH z)pTBZ8aL-J1#`OrzIE}h{&D8|(HY#FzZ76z>$Uyw-(h`ky^C=cH|MVee-DDV9b4O7 zjI+2oe0PM^XK~xE6_W%F@07*qoM6N<$f^Pd&TL1t6 delta 215 zcmV;|04V?c0pHh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchCJE2 z6L{`Wac75=KM9bS5TE4xKilU!0}MaZNAQ6T-os(yeJ}%>R-vHs{LZKXh&~B>i_p-V zqDvOK!c8S{;o&L!GWk1bAYs-)i&?9Hb`U*Mfn)GNQGtZY4E(0H@y<+8iD{N@lOl~t zf%h13`mbE+M}O$9Ma9H3^@JKyATQ{?Q*MZ>F%giYA58ewrFN<0b`osJ9x@VjgOf-5 zR4XV7IwWH`r%gb9h+YnXcs!G+y4Hg*v}!n?s<=_G@A)UuO? VMj0*4e`x>!002ovPDHLkV1kNz-Z20G delta 462 zcmV;<0WtpZ1KWGsz~|fRMu2t%dzIN)Ux~HWmi7QHuzI2o~EJt$!j21_cSCU?Xf3Y(ucL zNMVR&u+dVitR%lcoX6%N7S@8dxHI#e`)x@+Q$RwQf2Ir z!bzk}%&k~qw9m>^T*!Edy7QzZ@vzfmH{v&n7hoN?C#JOIbXA^d5Z_b$7#gIiVp41F zwbY!z#JY;Np?|Lqvc6R*$Kve(VJ>i?xTs_InuqCzayfcY(}g>dmkS|hSGOiFRUdwbt4G`c%&fw*7>NFm7luJtxq&!8 z#A>>FM$!_m1F<#Y<|f;k2a%R6j=1S$Gj88c|Mn;C3$rssIhb_m*#H0l07*qoM6N<$ Ef@GH2aR2}S diff --git a/docs/html/img46.png b/docs/html/img46.png index bbfec924ad1d8a92ad80f69ac9b7e58a8b229727..2e5b8d8288334c4688c0857336dd0633f836c1cc 100644 GIT binary patch delta 239 zcmVWSr0HUCTw6}nSftA0|OU?VpjlZWCyb~48W8DA!x0bzzagLL8uD~U}_oI zP0S`BUIE0h6ZV3sMF|jf5Eqbc9SJ}Qi9H3uWQuTrFnE=$Ik^uAfS4>t7;eJkxe^$R pVeFe5m=$2`007Qz5urcP{K)_S002ovPDHLkV1h0mS-SuL delta 215 zcmV;|04V>10_y>g9De}$yrlpD001peOjJex|Nj600PgPY-QC^H%*?yHyQ-?HnVFe( zc6Nw}h-GDER8&+$Lqjq$G9e)$J~oM%00001bW%=J06^y0W&i*HY)M2xR2Y?GV4xT< zcOY?)*+-Gs0%id)ChL*(4KOyxafA|{84VByQ$+$J%Ygzg+fYa0Xf)Gt1F-NThAz0i z1q^#&Y~BKf7cjP>0;@2Loyfpb0AqJgT@JVBIxC#X1Xs+!!1e%%UBEDe0RW+Q6j$Tb R9Yz2E002ovPDHLkV1iL(Rn7na diff --git a/docs/html/img47.png b/docs/html/img47.png index d9ff9c2349a5602a286d725f6df1142773b5b9e8..242ad6522cff8569b601d8ece19d43d58e85b92c 100644 GIT binary patch delta 530 zcmV+t0`2|w1EU0x9Df1!C|Pm<001yhOjJex|NohpnRj=0RaI5)?(Q=)GtA7)5fKrp zs;Y>Hh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchC)-=`TPY6K@R+R2KbP&WXo4A#(4)#yzCUh#UE`PNxOd;Zy!-CE9|7jbM|~HWD2FKE)D85N?`x9VGK01O0USqD znDp#)8E8vx078fp4yPfJX;L-;+nO8e9xD-2`cFYiV;$OJL2Z~Yi#BYfec+nAJ{3?( zjJay4CTN2y_kYr>wS>EgdXyK-d4CNGskp@?3(cvj`%E<^zW!SIRz&Iq?*VwH28>s= zB~qWt93Y@a^yc;8(mjo!nWbW!-ivcW>?kcjUp^^Uj=ClcUcV>CyF8ZZO7_eSyRrr~ zHL2ILkQ{6yQK#QJhd+;_R4gtsZGhT&7?Mj9wytGLwB(Z@$5uVWkGMQIAI2dt70a!hpjI<{}JO8P_R=g U{}O~601E&B07*qoM6N<$f=ie1MF0Q* delta 484 zcmVy1!QAcq<}tfF3;chXLd|x@<4`KAyJPTLym|q$#V84_ z9^Ngj+@LwN|=A?v2BP8DfiwPqIPz?g5v#kr`Yv$>(qnz8L>W6yhFDxF)qJ~8<|t aztS)4`AsZfW$my40000 diff --git a/docs/html/img48.png b/docs/html/img48.png index 7c9c1ba825d0c415cdac3932193d98abfc26991d..71c0f11f12ded8ec9ede7a8a628d0bd778fe63dd 100644 GIT binary patch delta 396 zcmV;70dxNP0-ghq9De~h25qqb001yhOjJex|NohpnRj=0RaI5)?(Q=)GtA7)5fKrp zs;Y>Hh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchC5iSM>b^#3CsNe&Pp~rIoOy5_6GJlvEYz{yz;W>DKfHC+1 zFVF}cB(4H?1B!r>5(A2g-wx^*HeBK1;bj%L025=mfTD#yfDgeuZ~#cKqVf+gu0`ha zZ}6Ca%>S@K!2p@Bw1ELxKNCX$g8|Tgj2{xg{8hX~3^#zR3p@-Lp!P9wf|UAyfZ5MY zEsqT@z~_KPkbj2(65Tlr3|(Nx0U*Sb=g?+g2v)!?KjHTU{s*b|amhO}WW%xmHhH!N z25tog#xrNmC}5SJ3#5UfCm9$T!18nNEYNhBfZ~22;NPSJF&~&mZwo+kDv~^p058=3 qOr;AsixSX6f`7Fdmhc(Y003oHO$wysc;x^9002ovP6b4+LSTXtouU>1 delta 359 zcmV-t0hs=t1Ns7x9De{#0bM5m001yhOjJex|Nj600PgPY-QC^H%*?yHyQ-?HnVFe( zc6Nw}h-GDER8&+$Lqjq$G9e)$5D*Yz=_k4X0004WQchCx-EF8Oc<35IB<;|93o8-VgqfK8r#N5^k`@)`^b zXBZePPIRosF5kq!uooCc4}hTwmY-3;V9|n*X9c>u5$K5p44hzjj^MTGP3#UZd6tDo z7%U#PGVm0rGhl<|%^0|DFfdF&4nGiJTyYrUzF-E1Um!oB$;W|(fb!}LoVg2_3ee@d z7@*<9-oA|KOcw*X{B>;pXJJr+vMi*)5)MoX45MIp007;OLJwT~1DyZ>002ovPDHLk FV1lyyngIX+ diff --git a/docs/html/img49.png b/docs/html/img49.png index aa56bfa4cea71187ed63fbe64e0d89e26f9163ea..47d48775700f42b12a25133e2f2aa9f3ce8f946f 100644 GIT binary patch literal 319 zcmeAS@N?(olHy`uVBq!ia0vp^vOuiP!py+HSQed^2;>+9_=LFr|NnpH%$eoo<)NXW z@7}#LHa0$U=8T}A;Hp)tIyySi($atmU0hu5-o2}&q_lhYZh2Y7sX!sdk|4ie28U-i zK=OM%T^vI+CMG8|FvPK0JcvASAnQN_Po1{$0|tJF7M&@FSr(cUYPvD45$LLKKF(s` zoXPBxAet|Dn0JL#p3<3vod29(awkk`cjSF@$(zUez@OjpS4156!h#yKj1!U!5+2+? z6mt6PYX-3gOhWh8FV7k`4n6h%ac%WE8|4?oh%s*adqOSM zz#u0nVS;7xGXWP<1Br7C&52CR?3-5I_hJutW6!~>r}1N}W@Cwc03So(b>+*&jXP%m PJ;LDW>gTe~DWM4fV}+IYq^PJUARv(RQhgUt17k^$UoeBivm0qZ z&U{Z7#}JK)$q5VWHe@(FEK(?pl$5Ao61d~Q#^&}c#NxXWvvW_hY0vRUi31mc8Kz(1 z;YqN#$@tt%Qq6$l$A-gabQ5wC?k))C**vLH@Fwq7*}u{PHp|%9<}ve}v6YQYaO7iU zd&kYgQwY?TXA$7i(73R>F_CG)bJfQO?x+hMD44VI0K-X#m2xR^ubKHo{_7>UJ^Li4 h@Og&xbR!;bpht^kxp}|W8Uvlm;OXk;vd$@?2>@A`XF31? diff --git a/docs/html/img5.png b/docs/html/img5.png index c5d555b8cd309c79f33fd5ae244c79271f410071..87d06a09bbc4dac3e89d358d46a02695f60687d5 100644 GIT binary patch delta 657 zcmV;C0&e|-1)K$t7k?%M0{{R4bw`y~0000mP)t-s|NsA)nVENYcU4tY?(Xh0Gc(N0 z%n=b0s;a7ph=^upW&i*HL_|d0-Q6N0BD=f09~~i;00001bW%=J06^y0W&i*J8c9S! zR7i>KRKIJ~P#pgx_ma!qy)+qItOzkyk%AC9b_!A#Q9SFUgMSA90PW`D5Zr}0bf}Am zbSuTPbZfy3T7)|#i0%hYZbgcV2)>uRB=_zPFXtjyKP2Dp`|4}#y4CW9>~8}au7Wg%a(G;5Y18E5=(K6T zhgEv|s8vfbLx0g#9pg-qOa+?VYg-bS52JneHlEd(p(uBi(^xOtk&?y7Q zB$$wrbMdvt73m*Vt@B?;PIfa>PAX~dHj|+kQ-z6Ns79aJ)V94fy@L~c?0J&Sc~}gy zU@;HVbUJ~uqH1jWh%PAaswAV<>$t$x1J2{7m1Y4 z_{w;>iIJB(5$OW$JneDE*j@hP%l-GDM?-D9suzvr{>9;rD!mmk#nS_FZs{yAfBg;a zeQ`Z8V}6q#>_#MYFQg^i@bf5?qKhCqBIas{-O)Xo r0r`2ETlQx-FaL22F#S24j_xlN(8_H)c?QG)015yANkvXXu0mjfaTYlr delta 631 zcmV--0*L*b1%m~U7k?!L0{{R3gw)q>0000mP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001bW%=J06^y0W&i*J0ZBwb zR7iF5M1O%XRSqhLii*V>+V_;B05nvTSRbYk8(L&~MzJEP``h)>Pnp!afdjZoT z2DYSh1DG5ynkk!5?3{qii{N2sTf(k8A)0}qTuXtW=qBq1nACJpRHrRK;a&ohETN%L zQ!F@`^%$yv?mEQ4VDx|;rkH6eswrHk!PE|R(TP-;DIDAkSq#g7UR@3pUci+ARmPz# zhN6uh*b|oKTr?1_=-q3If4EhAj}UV0y*C z1hggz!e!b3H-%-zW`@H|#~rv7fDYm@&?$k+G@zLh!@$7)fZ;j=TLS~bW(EdEpb#g_ z-4T2@t}^nMsqX+;^;hVrD4C8`K;ka|=%o&JVEPpJpnxetLa0cC!KnJ!5K%X*% zIY3Q;1$YDxM??U+2_VqKz_1rY?*UqO<`|IS12lz!V}Ywz0Bh(01_phg5X%C%DGVDn zVKIainA{stM1YnXGUyc*^C_^fH-MeSz_1))iieH@h9N8qk1$v~Y(*C0c3|L`R?(pV zj9pM_m~aUa<7xp*v7hQ|=IFkR%}eNj9hl~g8H^aV6fp1stvw7D^f+?{zb*`L077j` z0Hqb?1tjW*fk-&30_Z;lGEHG~fY8j3fW9fgs}vuAl^Nv*2=*u#1*2dH00067YGM|R R_!R&E002ovPDHLkV1iHk0yqEw diff --git a/docs/html/img50.png b/docs/html/img50.png index dcc78c667d350c71459255c0ce91799f4ee303fa..cf9cddd74a84837bda67e5a01f779d71d955c71a 100644 GIT binary patch delta 255 zcmVHh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchCGnE z;ZQkAZ90s{l=@Pkqk$&@%4Ju7#L&aQGl97S%w^_kU^vde=w-kF;WF?gFbFf`F)$p3 za19k$A26(7V-PS40C8&>I2JI7n6n;9-vHuvFz^&G9Gk##9HQ8Ofti7Ug@I>A1F~xv mSq>B+aif`z8&KK5^Z@_^@ffgWq*hS?00009Df0Su+AF*001yhOjJex|NohpnRj=0RaI5)?(Q=)GtA7)5fKrp zs;Y>Hh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchC1$Q&-g~=P@)r|`% zAgB-?hn)`?7y=jylz_Yk3;|pX3=9YOK~Ci0*qbdz$Cx`b~*zCn|>n$*T)a2 pHcUEz%=2?V<{SkzP{9j?0RUqtAbp2=bLRj6002ovPDHLkV1m7ra>xJx delta 273 zcmV+s0q*{`0;B?v9De`^xBiU)001yhOjJex|Nj600PgPY-QC^H%*?yHyQ-?HnVFe( zc6Nw}h-GDER8&+$Lqjq$G9e)$5D*Yz=_k4X0004WQchCI+-999(pOulf{%i zOTN!f+;RLsAY0OAiw2KtoH|>1WY{=V-}2ni6OQ<=zyH92g@*3r?CnwlCC65{OaY-D7lsHkXX);R;Hnz1CvFPOpM*^M+Hr_a;H zF+^ixa)N}3!l8vlOh)rHzbl#k^78 zlW|i4;~@n``LeczymE{ArOkeZhxOi>gxD7>sy-zWtH2PO5WvV#VHh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchCB5wW^L?F5Sj8#{e7yGbr;Vsdw4;|Kfp&3oUs^D+Ad2w?%n0ONQO1$^T@ zlHURuxVxngRgzHBa(&W@r~%x%m6f3o8w0eiK}ujNfC`u}lEPk`mIg2%vM>H&-}b;7 zw>&G#fl`p?U4M^W3iM7E$TmeRmnlxtGu9E2JdG6i={c_Zqe?NGLn?&asQgxRCuB$?;YkqhMD#ARX`Cn+u_2dwy2)fWmlHQ{>G zi&CliB9@Ev2zk~BER=-yUh(N4MdhB$kNwPPLkRZ#et-4beQLPrMYwL(e8(#y(YE5l zc4F1X&YvaY@c3qTy^dva{HWKdblqPn2oAj2XbWtP}_q zMfc$Ju3?W{fW<0mAyw%(PfgMo23mnD5Y!m zs35TgdqxlVBJ)&LXB1Oa>iBcV65WKlr-X}0&1WQAc#i%ExzK8OE-gdl?XYXmKmDEV b9dC*Us>D~R0~{z>00000NkvXXu0mjfiufA- delta 556 zcmV+{0@MB81ib{19De{DB4BI)001yhOjJex|Nj600PgPY-QC^H%*?yHyQ-?HnVFe( zc6Nw}h-GDER8&+$Lqjq$G9e)$5D*Yz=_k4X0004WQchCVw`W!pMO4Kz`&N2ZU7TvFJM~4 zkfv6QP{coh!7(Amts2>|2p)#EB@9J3SvRmWf%rxY4CPu1?79=886W~c;OM}>bD*aH z!eI#wh3d25U@&^XzJTEXh#w4e!yyJ{J%%aYkxTdLl(m_2Cx7K>;`Hz5b$9Kv8xd7^weVDDA40%n+o)R*#QQoMO+08 z?Mx3QfCWI{S7^i{)(tu!A2V%$>tk85nSsYZr-b7u69a?s1_mw#pk0TVjyr$_Kt2)= z?NWe+V**Sc-;Jvf77v#zGXqBoBFKOO5Vao|cqc%`IDhV(IdcYLpM?cPh?}#NdjdC7 zBmo5=^acjL1_mauO&qY;kKo~mK%|5O1}p#=eTEGTYz<&HFF=ILhD|UPYzmmVz|j}j z05fqpLZ62YR^>2Yaj~62zj;D9gvZqarr1yQHFI=d#-|Sim_k{-puX{dgbT5NnGdg{ uaDytsN+qy@Ed}K1+m=A4g`;2;i~;~D#bF!cF_A+60000y0uVwBOhB9fqy!j{fdfe9688lVyIp|+8(@M^+z^Ttq+zlW z!$Tm&$N?7O1Ct!w{8+UEf!6^f4iB;|Upe&6^~0000OyOkjK94p(l#u>eUkFS1FB2COh9+lNAiP&ntu9Dq{vGC<_3T=Mnl;az=Up O0000Hh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchC-TK{coxp8!6c zSO6b{VuetQYr&KU$o)><3I<3D*tmcs$D##LeR(Kup#|V`K(M=z#Df*U6sNMI7XO3P z`yfXMa4BTK@6^WyS#12ZJf`hRD0Ab@3qNrc&c>n+a07*qo IM6N<$g2O^yh*gFgC|=gc6<^4Pe@HQf2`o%VdE9Ad{saH%vI1>9_%q z&B>6*QUJ4(p$p0E>p-jqVKNCb1TbWPnfdGjtS~!sGMAMxutIb*8?Y!age*m9H+Y0# lvoAofx!sZ2X$(UL000gs78tbjnPvb0002ovPDHLkV1mtBT~7c2 diff --git a/docs/html/img56.png b/docs/html/img56.png index efbf778c31110a6c45fa39b94815c24dab439589..6a787014224645f06b10925410f52c0c576e8165 100644 GIT binary patch delta 581 zcmV-L0=oT=1l9zQ9Df1q6uJBW001yhOjJex|NohpnRj=0RaI5)?(Q=)GtA7)5fKrp zs;Y>Hh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchCY5PkRI#WUHQKVe-hf{Fw?1u;#)MmQA2@(@JCCci)ec7KA9pAf`WI0VH;Okt-* ztSn7oqt#(yW8>^@?o7@TKZu?0*zC@}ow>I&a{)B+G~5@UEfBVmjR1FQ=2@iIorlMO zk^{kEM$KD!G@`-ii9QLN1%1|pNdZP?lyTir;RQrQt9njrCZlF3o@vkG58m>9uy_$D zSq7pODMQW5*MIfC3xpP_<*pW0p@W4%w=;Z~(-Dlf8%OASr9^b|@|TuWMc_`D2LP%GKU*-?$dpVUOJ z3|sa}7zeH)_AtB#h4JM+TX{e4vRSOtT<_X;8Hp-t|9|(=SxKp+x<^%&fBXW)%4f`; zo)%chxLQ4*it!`tr;gc8Vs^#&1lGvfpl`$C&_TU3`lhhT`yHw@oJ(T7r-0n42ex9W z&;mR6I-B=>4vRFb7M!a>5K`Gmz+6nd9*X)$<+9&)#EjoHdpq(*{;({Ed4NPMryQiv z43H$}0zTf!u)b(IC+>9Gp&Bo?r7GJ`(e^{yL8etf{>f5WQy3~`>iUBE$Dr^A)E7-n T+IbST00000NkvXXu0mjfD^eD9 delta 509 zcmVq2L(ALD3xF46_b5HIr0seD%>o;;dzg;ay`acQ*;Z4cy(FhC!E-fM*r1iuS}3hBSb1fIbPP?gIO(t* z(T<`E7Rx2JgOvzMsvW{=hrmY=-$8rn9{ diff --git a/docs/html/img57.png b/docs/html/img57.png index 05ab9fffb52eee367d376f0bb543e40884dbb8eb..9427a62e0c1290a90d911f9afa3248188480fb2b 100644 GIT binary patch delta 648 zcmV;30(bqD1egVo9Df15fQp|0001yhOjJex|NohpnRj=0RaI5)?(Q=)GtA7)5fKrp zs;Y>Hh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchC z_WdF{pl1Lhd{1GIs$zCU9bT}O_h*~=hd8ciI+t!D?W4>yseAJ7+qknxnsU?yK?OTL@^=g8*zz4qUyvy76+WYf6G)HU;O@aH8EzfA~rk!1DWDX`c zD@N5X1rk;)Z85anN!mmc4}e#8(h%HB=7rm9^FH9zlEV2Ut}O{wWr8VuH~rdD?<+G$ izQV_q(i8j#_z8O-Zuf)tcI*HE002ovPDHLkU;%>W$22Jb delta 515 zcmV+e0{s1$1(gJl9De}Hhq?&>001yhOjJex|Nj600PgPY-QC^H%*?yHyQ-?HnVFe( zc6Nw}h-GDER8&+$Lqjq$G9e)$5D*Yz=_k4X0004WQchCz4zu0{(zpLgp=@rL33m8vaI26zf;DxYPJFs!8ath=u3Tn?b@mZG1>3u-yY;TER!G``hyVJtJ~h z|DRLL7z5;Cl4K?prBl<&(?jXRw8hqfV)sB;j@iH8L`2DO-uOvtwHj?1Dh(u~21tEG zJC^SAhKOHrN`~IDZ+sYinNu?KuEbq#a!Nk!r=NcK`2mBbYnE_NP7MG6002ovPDHLk FV1nuD@reKc diff --git a/docs/html/img58.png b/docs/html/img58.png index b278a263cd405a1a9cdf74e803c5dcef282f2aeb..0a20920a46d748e73c7e7bce520bbb9553916223 100644 GIT binary patch delta 387 zcmV-}0et@U0+s`i9De~9Lrfz8001yhOjJex|NohpnRj=0RaI5)?(Q=)GtA7)5fKrp zs;Y>Hh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchC0FxhhAv}E!27Dl4!vr9C;=Ta`1Ao&71_L3Gm;zoMXy5>p zzQk~gVG@MN$qg4}P-SL%%W#*0nFY${WKc+$K#KVU0m}gdy8%LNU{K*_f>;;8c7O*W z%A~-sf!PVnZC@^?%3ovl=K0xwSA~38H^w2F)VB6cm zuo1-i1+r360c@-Q!z%{P2S65M9|Hq716u>CrUvc{3~cKPQ3Y=>@JwK2U|>fP{BxE; hG>}J03(bJR1pshoGFpw@;E@0T002ovPDHLkV1m|Tmi_<$ delta 355 zcmV-p0i6Dp1NH)t9De{{M0~XX001yhOjJex|Nj600PgPY-QC^H%*?yHyQ-?HnVFe( zc6Nw}h-GDER8&+$Lqjq$G9e)$5D*Yz=_k4X0004WQchCyh*g2!BDAM4*z23k)2`kxk&# zD_~%?ZD8P;(SRh%!PCH?u9(2U$a0_nNt9y)LqehgLp0NI1B9p>#{m|HUUX+pVijO# zxPdO(z$#S4BnEal&_Oe%Pk@Lrh&!+efmml47(5ubz+PcZVEDzraRJC;&t+g(%D@2< zWbVJtu!*(*1zga2H%A7BH33X$7EE9?V9*w9Ko#Un4Fnp=_6${2oq?x-oq?eZ%>V}O z25tt1O(=rVhZ$Hh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchCWO z_aYJ(I*H24AUk*oSM|QC-m9u< zU>sUwxtwp&GvL1v@bI$amc`T5gXS`X?*q;s@*UPttpW{0@v9Z|bkiIocVDPwca`KM zNW;JhPA)AV!G9qK?^45LlIKDBEN4d#W}Q8AHy50*x9h#KD_wjRC}Qyw*$^dy*Yq@> zH#+M@2u97K=$Yyf<1c6tgVA$#>RM6-Bk?#1jf!o{>U z?8Q3|PJLsTLDg~Gqn28vGUd9Wq(;2KOb|}s7RQzW=MUrGvQNx zvF@zZWRzNz83&qLP+57u=kqLS4SGI&pl}`^VagN=*m{+0xt(-I2!q@P*Np;#x~}Y? zDt5t^Ae_+tEghgvMZWhH>AgSEbwala{^F>cGlF5`Fn!+oD?Cwm|bI1_( z8}2sVWPgLgar-%qKEeo=j8-v^Tz%n6Da>cGl~3$};;$jvoz$Vpzeg09vwDCMuax}4$3}vDV0~!o`}-t8yJtnk%6Pv zgxyz@(Hd0R(M>Iu;8>z52km{)b;}@1+V2OQ^g5V{L57s;$1Lr110S!lRCu0#=>7Jc zxPPy>fK2dNDIL%5&VreDzs?J5=OLL0b{;YU=DIAGTuys@x#|~o9`*|~v z4RJD<#?69{t;ra(dPb)>jZ>4nKRKPR9=_|^N;kqDXuCPgcw&&IyLv}ki9dZl8{eULRChjxy2~-T zJFi?!Qp+Jsze;xpSra!H1eFpm2XKB+s;N-RzcSd@ecZE8tGk1t|F(^s1>Gd)H6HEY zNaHF>j7aBt4@9NK_i^PLO7(5hZS>&XO(u0cc_YJ?D?Jrc(v4Tl-oX63qE!^aO@AX8 zBmM>KKXse>zjT5EE~i4sKHsWwI+~GE`MJcM*%%{!7Nv+h4LUy0ht5yr(@EfY)WU6I zgBi!R?D0ooPQ_+*VEqW(8j6iCTZLQuMi5h|zxXzeIfpm7z$Z@wztfd4n)p$~Zg0K! zl5X;pD_mmO`ko0gAznCqvTtubCwvB-l{u+UanBL6O-Yr7;j2~shP15d4+a<~F4zZ? z^=38E2x};_M8OOry8lI&&)f2=ovydWHH;IdOx-oAo;H@}nzT!pd%92lzi~@E>(5No t=-z+a90yT06SLO1W{6E}GS>c6_#54O_Fd*NNlE|!002ovPDHLkV1iI+a902T delta 1154 zcmV-|1bzFD3Xchp9De}sD~Znl001yhOjJex|Nj600PgPY-QC^H%*?yHyQ-?HnVFe( zc6Nw}h-GDER8&+$Lqjq$G9e)$5D*Yz=_k4X0004WQchC3DwIZ%aQz53FASEh=%}ZNE=qU|7t$&3LXl(`Is0gVbYz3RM zr1TU@`sOKyAc$N;k$?&ZsYGbOwmwwfY!T^WtUk2*;>_&M-t69Po_dSQeQ>+;`|W(c zZ~p#f4(Owg|27VfzqRvNR$}^O4&pnZ}YWiJqYLU6&`ShV!FA!ML5qide}35-x1)<hc-)l zId=txb6yZ;NQ^~XZOC#YYubTPN3>dZ+}YGhd^P2vzC~toE`OJMCkbq;K3mDFpFLAu>BDi2bJ|;8?hcU%$1}y#4)>7 zGU$9iS>vn?-o{7A{1_3s*+Tx0AoMO)%V@!!wWToX60VC#H1S*r#trr+8IKZ&k5g>>2$l1QjV2!YcL)4%yq1g zGq>m}*gXw=QBmk{HB!~WIl$D_Ww3?FZ~@vU7cq6?eWoeX)zhV#a_4F0&TWA%$88Lh zF~LriLK!I-Y({PJ9PeP5r1!IZ9;a`saDR86-qt$K{A({zYVJ3ls#CBKv(@`-_6qOn zWtMBY>D>Jk@KVRM9fcar?I-+hs(wj)4b2qJ%b3#`Grf0Icy3c<^>JQS*KR544#KotHG+q5>;6C6Z~kY*DF72K_(xMWvQoE$Uw z1L8j@;t#0eLIrrK5a z#&R6TEt!23hmSm5IbbMJoUD*o<*_(;fNt9s&ppp=2V*G^jD2iK1`~|VaP>SA`-u`6 z$WBvUMuM9`7_vWR_1X+>J2$4}%)}yny~hNFXW2nhF?f2KW)I_q7;m<%7}$)LsfIYi zM_ta(C8H5Df(c9nD3^6eje=kl^_bBpdR*hmjN+(R&)B{yK&PLD1-N>6*Ps}5-U!c> zP*#yf(1PB4U?s)&hcW6J`vvCCF4{>;i{^T0n_cp<|Ef8nTciW6BsD&%nbJhXaG5Q^ zWMSQMzMm;El`iqLa(o&|R49s>L}{^|Sc2Z*Mw&$Z66(b%707*qoM6N<$f`_je AHvj+t literal 537 zcmV+!0_OdRP)F6+fF%fB#H)okof(TDwARw_W2iFBpMeA$l--el z$Bb?;$#jE(!M^}Sf>nTlAz~whovE}|0k;u>V3JFSfq_F9!w9G>!y*R720}(K9suf* zz-0upGy~58%8X!`!oaryo8}0I$_X$r@8f5gziz@Q%h=AD4EVE#CP@FviO3$Pi%47BDtkU9mj zlEIFFp$b*rwgAb9N^B-DFz_WX3q#$@V8Y?Run3fnxX*w<0+7Y_0AU1M0Yd{eBMcQd z4+Jncg4tYQ6Bw38ph&}FBnRk9kI?W5Y=?nH9ft5>xR!yZU;@-09>E3%K~W4NEDr84 zNSwgH^ifc-fK3u;#1{sJdY)^0+!4!;B3I(_lr)(6A bf{_gXSm{p9H3k3700000NkvXXu0mjf+vn4E diff --git a/docs/html/img60.png b/docs/html/img60.png index fa89897d1759ef00946a0f8d73b81f5b1bf489b2..f6e845e6319414ddf9b108b1584f0eb247987d37 100644 GIT binary patch delta 277 zcmV+w0qXvd0;mFz9Df0nhjkbL001yhOjJex|NohpnRj=0RaI5)?(Q=)GtA7)5fKrp zs;Y>Hh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchC(jPFDAOVP}j2oCh+J6{~9)P(z3_&n?4lFhh z1K6Q7C)5^)1t6OLg9e!2pils^k6-Bkn9IUY08-Ce#UIUN^2kbjKej|7q3=C%&7}TJ=CI*JR3=A1ihXBoLgsEd$ zc!a^?VJm9^vKK;@BJ&I$A@kT5AoIB0QFv(#!vg>Sq0boCXmq3u00000NkvXXu0mjf D8?s+L diff --git a/docs/html/img61.png b/docs/html/img61.png index 22890c94fd3b155a97cbb50aa07c33e0c1895e0b..a681445d51f94e0456885c25f21bf10de8032047 100644 GIT binary patch delta 404 zcmV;F0c-w+1EvFz9De~Y?aj*o001yhOjJex|NohpnRj=0RaI5)?(Q=)GtA7)5fKrp zs;Y>Hh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchC~f{Ee52LUiwL4V)^g94CtNVvcNF-3r| z890n>V1PRj=(Il!i=eIof(;DJS|5;|&RD<{z<`hk>wm$3;YAvP0yv8iL>RDuNNyko zy7LmluL}ZDt^xzY9sUNeA`tfi10y#N7dWb44Mp}P=x|$Xt6qg)t+Hs*aQla0ESCS zN=gba*%csyML>^%so^b9`WLF+4Im<)VK%BL41i=AFEIT6z`*N(DGM@L0Vt{f;r>FE yg}4f2fGUVQfaXm#7()r!M;IW;0jJb(0RUgjG61Gle+{t!0000it~+001yhOjJex|Nj600PgPY-QC^H%*?yHyQ-?HnVFe( zc6Nw}h-GDER8&+$Lqjq$G9e)$5D*Yz=_k4X0004WQchC(#1DThAE{!Z(DF9`-gUJ8}hNBD&TnaF0s4VjW5XlPU34fRcFfBlnf<6HPV>OimYN;5ZIarNB_p(a~W5lU)iTn5K#{@XTmnVBjb~)%yWNa43s0FtQvd zU|?NHh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchCJ41|HHGi155U8%vpr-($QU-_v z8%}m0^8|d@!MyuGJTY~HPBEBQ=)l0R4{k3{0|V1nIFI=O1N#C7rUVGbp@o4(1w O002ovPDHLkU;%=dd1+k$ diff --git a/docs/html/img63.png b/docs/html/img63.png index a9a0aa75259ee9ca01b0a3964fb202c340f9c6a0..0de130c7ebbee1b4ec1ac2af90d307e307ea8c93 100644 GIT binary patch literal 309 zcmV-50m}Y~P)SU|?Y2W z_<npS{pJPo)s?mP{E{Nl6}6fZz)gDnUw;1|5@0Mw@7Ty;y8b?vGKWs zKV!)08aB3Lyz15q_S|(~WM-5v<9HvQaYX4Fuhr26zV3>Q=}dRj&hhi?5q@Cvj+du~ zm&b>*;5Co5#0{wj*I3O|4#?DRoa?y1(#hh`NuPyl;ut;R5}pM+JTeSf_@maF(I`Kf d>F@^z2HQ&tCN<|7Rs!9~;OXk;vd$@?2>>U=X-EJ7 diff --git a/docs/html/img64.png b/docs/html/img64.png index 6857598df925976259681c5e3e3ce1da87e5c13e..bd52ba03858185dc617ce0006d77af73eef2a01f 100644 GIT binary patch delta 284 zcmV+%0ptFP0Hh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchCxPEFugHjc**sp(;5A7#Pm;%xHk{ zxDPNei!-tuC;;>L8yI2=qM42xfO(E9I+74JO+>MG4~S5M@qU1a3@C?16xs2;Qb40w w3y}4OEJfxSJVNHNFF@vTyQA>Z7={S|0D(Rl%lTG)>i_@%07*qoM6N<$f?Ahk`v3p{ diff --git a/docs/html/img65.png b/docs/html/img65.png index 85a75169da2034ebbd4d9d6e3857bb96caa682af..b27f16968b64fecfb90d3e5736238783151aa24c 100644 GIT binary patch delta 600 zcmV-e0;m0>1nC5j9Df0L@(>OH001yhOjJex|NohpnRj=0RaI5)?(Q=)GtA7)5fKrp zs;Y>Hh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchCTnVH@)++}#rzzOshCg2463Y++#1#L)d zerVF+gHR1fQh(5}V_=0)@dZ%+1_l+TJP4C)SLciI06byhg2g05Y0t+D8nHa&e0w_|zx)>ONDU63^vh0$egrP=C364sa&Z1XL-8Pp^Rl|7Kl| z1*qa(2qw28njW@pV8Rf3z`$yRDjuu=k$&nhL4)risvHxK0)q#)0K-4FSV*d3(gJ4T zApQrb_rZFAIUNHe0#kN^9+H59C_@heqHq?&)WV>^wzq|0BZ&12m>iW9C$MZ|h-YYl zNh{Bn!BNn{CcyBDf%5^7#n{KdPyn=mZ43VvHoT=f0yJ=6V90tdK%8O-xWT|PffHmC m@!-!{2GPJQaONBZ0|5XP4PWQvesL`T0000mYX zR~SS%1frRagMXzRm?pq{2-m}s(8J)uaRFg3yRi`K2ZjT1z9$0);8X}?DBx{C2rzSO z;Ml+b7hpjTGa%q#2vk>4OaR#pROi`Q$-rB{Gl2=N(v5))%Hlo)0tsL}j3o?-3ZRfW zz`)YLu#|yOfzg3o0cOo{rNtQbgfZ|hVCV(0$}TW)1%Ch?#mHc&zyXuiU>C%2oW5Dy)iMf3!N39ldBj-C Ug{CHh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchC_=kz?#Tn)(jG0 zbPV8s0MGok3@~MJ(A>_{yBzP;`@Z14|RK zGLGX=hHGd5M41H#gV6)_1q=s}mGR7I0Mj{bFl8Lv3~URy5|}m^fh8;_FeI@yFtQvd z0CIr3VU~JoF>n;4=d(WIXa{z3bg#|=}o3j*5^A_+-U@CwrYlU0N z5rGtrK)|TL=)kT3<#-{&ZNny1WekQ2954=70bH4fjsmhWj@Fe+5h1<80qn0+ea#%* rmr;yU0YW%n={a+NVHAvlVFUmj6hI5njrrdI0000`VbGK-D~(+F!h1}RJZ{`1p%=F zL%_2O3`_zLp$!3Gdc%ef*!6>)_a2$Y8-UDX5?glx!Sn8z0M_tj18)J-0VOsgunU+c sFe$JIz|{O^;AY^2>)<>jWCV2^03K-;;ZyW4VoB#j- delta 224 zcmV<603ZK>0`CEk7k?B40{{R3idl<}0000jP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBOYl5R4oFw*UYD0d!JMQvg8b*k%9#0B}h}K~xx( zV_={VSTrE>I8b;z0mwW?=2RqJj9WDlucrW6<;e~(#XOUNO<5s=LBNL{#N*_3V036? z-Jnwp;uRYz#4+%|G#GRifK apiBVUQV~%rIw36p0000`~0{{R4{JhI}0000mP)t-s|NsA)nVENYcU4tY?(Xh0Gc(N0 z%n=b0s;a7ph=^upW&i*HL_|d0-Q6N0BD=f09~~i;00001bW%=J06^y0W&i*Ht4Tyb zR2Y?GU_b&~3oXbAK^IS-C*$FrnZBkcv5Q z9GhAsaE4PrS>X$W$#XzJzyZR%8Q7>l(W&zd=j`={pdn|y6vcEbH^&1aALjsc+R4voT l32^g1Ak58jb{Igh3IGG!C86B07asrs002ovPDHLkV1jkOap3>} delta 285 zcmV+&0pk9x0;>X$7k?830{{R3|F1a?0000mP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001bW%=J06^y0W&i*HsYygZ zR2Y?GV4xguzCC~XgaJdES}}@n1P?>o5_a7Q(F`n2Aifby)PI75S&yNLf#Cp%9}E-a z;AY5TSjND#0jQ4204D0G#n8_5U;^9JY6b?g15iHh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchC6)+a+Eb522(`U2E4t!-gn&ke-swvpyH|``XLgIe+})C%7+Um)f4@<#{vc5I*g? z!y_1P$BLhy)oUGc<3d~>oH%J*9g0UcfUnaxW0QZ9t09a_rSa&9_Xv(o$9iv~BBeDm zEO^GY-08Kri%MWo(iW`Lb#5|r-pmEyB7WJ9pw|`FPQzZ=_Lt7@Nz37bN?i<7&5fwPmBLIQWa+Xed_Up|-QUIP5T8X<40L;|33IU)ft+Fbr70FrV@S=7xZ%%Vl;jA^(5hfUch`t(}6M4#sV;j7=BOQpBVj+0m?0kmIrgIMDrJN z!j=l7fClA?BY!!UYO>l%FX*P(>HNp_9`Mw+>-s`^b4=$-S{K17LU2g$B0r zH!3j?d}4wX$Ue>W1XXg)`-{mgc7_?CQ>qp?*)d6-%n iHh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchC)2Q39ScpEBd{e_cH%ylUAtW{=&?>_x=Coz4yI0 z0cM3xmqXW4rv=nM*$aF|y{mM+%~6L79D(3C7@3X<)|tU}BS|R15;TT4)_@^B31-&@ zH@|c&qQA%jxqr=H=+?f0%FOBba3(E2X|YAdV?yKLaemnD`C)jdfzl0y2Da36U~bY| zFx{Ykp~i0JX7ay6 z#(?(tG>XY_HvUWyYQba9dPO;@sG+Q&Z=@|Q8NAhU`}kE68hqlU>90RWe>x)H;Efj5 z7g1vNgyB34f7000I1#9Z8cgJy$hZ~uTdugfdFTBZV`4bx#((6Pr>N$nL>EGF=)Msqx8MdbIOYp*$26{i7JJ$Of-wdi;$%cRC8SI$ts!2#tnR`GP%lx6pcyH@W-S}Q=R)`!kl`L zpMN|TYJJv~nXpl*)5TBP6=0b(#IG;egeu2B3{`!jNv9|3E_ShtdxJy8Tb)Al;^#A& zH49exSEFKGzmlMa< zTkV5n*7&H{w2$Va?PD;W>z$%%e{gxQYJZz4ks8m+qZ9^yjJB8Du_x^_{1h&NwU@sA zT^CwxgHpMkG`dYm{6Ma7!1Err6lMRoF&1A-2JKB3QpTC*ZTY!3ulOb(!RfV)-dT+6 z^of(i0XHKL{Tx@#XV#%#sOHT|(*6#o7tRhUmI25Arm2%bT$6lHU=v~!rn#;BJbyow z6kk^P{36SN;VQ*zS?mdpvyp6>zRzInS4~^l8E;Lc9YPc1@m7-hy%>+l#Og}Qx#;^T zXS(=?uEy)M1UCxepfGD0i$k+Yu59kZle22mQhYT{eGCX+cvn(hh)U$=fl?1;D?bk4 zK{T(YsT@qk#|r=E%G56X*22nrNq_30o6tVAWyhaaD}us9iC|vM)3qos0mBth{Kav9 z;%}Xk(W)U%w(F@#PC&%R=!7Yb*W3P**XUp_j;P`izV=#~+Qw5UYY9x&c}%T%oo9mY z015yANkvXX Hu0mjfTn&}o delta 1046 zcmV+x1nK*n3Zn>+9De}GJLI?k001yhOjJex|Nj600PgPY-QC^H%*?yHyQ-?HnVFe( zc6Nw}h-GDER8&+$Lqjq$G9e)$5D*Yz=_k4X0004WQchCf{1PmnBvb97mnH=Vv>aS+8nW#bf}tY)suC=E9EO$NVn_$FjN z1DuVKIT~ef|E4jgnZhwN%WLq2UE@-KCUKKyotk4kJ1Z%(>xHVGgfDsw-9u>N#guOs zdNS-LbIgkX<2dHwaJbXJxT6A^v*B=9G?`~v&2pN_%uTkXK$>Bqq}DqaqU2Cm6>}A! z_M!q+g@0I+cjQzLxCOZmQ?3*`O;s>b6*CHJ(CCoW9FHb)%!%?Eb&tE3OhK}&X1UCK zXnO{C`=$17(~i`4gn%EPrm!lQhZUgqq5)R}!G__BaiMS6os1iDsCb=5ST*LrI3tn_ zg8MzKgTm%n(lOB-)nX&6&zper@ zFu$^rl!*bm9C?;h+?lz*s4vJ}S2>nnn)zeBnqEbp4x=U#z3~lC??n@X;HUQRTUr{x z$bS$>*|Gc4A+=skt+ogfJSM+9S!oh{VpQKskPJpEwMVO!r4fP%{xv%mJt5y%FQ-<0 z7vhlA@7XX0e)%S^f-fvmPX+5d~b=E3%*mJfZ8 Q;{X5v07*qoM6N<$f-3au)&Kwi diff --git a/docs/html/img70.png b/docs/html/img70.png index 838139b8bd15d89f8fbd7cab4914c0e0bc58fbf7..991ff18cedb6d7848ae273bdc8c99608d8d822b6 100644 GIT binary patch delta 640 zcmV-`0)PG81d#=h9Df0@p8D7T001yhOjJex|NohpnRj=0RaI5)?(Q=)GtA7)5fKrp zs;Y>Hh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchCNO^LeP-Pa(|m(p@Cp4$W|h$HjpM* z7#p>`|G+IRw@fAZ=I8EhE{Ud)6nU^S-#2gG%$wbB?f{280RBBs*V3y(?xa zYy%I+egZ7+^blc4LrgR2-^gcS-mR?BtH=&&WuF!B@<}3M#jN1DfcFNJb2a}fZWi&4Cq`AEGeyWt*?icDogtK?Hxj^ z!I#XMSZ(jUs`r*y7+&uzHwI7IiD*J!ccDp{riUH6HVO_Z%HxV#I{K)(pC%>QT_jc{ ztDc&Xcp%^>NsUT=+xa|J%!h?L_)O89vr=Mkzws4tvw!3STD^ff%qFG;Ib*V}6`b1!3C4_qhC`AgmHwa>lRocq5N`YmQ7xrhkItz@)4bNHyE2~yS8=w(!F z!VZ@)RP@aGc+>xdIVORR?FlpooC6jxI}5`ikcSAzoIBaciLZs)ms z2`qS{z;G}C8zjpB=4V#&#^h{=m>CTmgX~cMjZ*&KkIp*%lyN*=b zUZeZ+Rj1B2;Wa;E`PAh1CsV0;VUAhvE*>tolBa2R>$Jr*pUR50 delta 588 zcmV-S0<-;*1>FRY9De}EnaWN8001yhOjJex|Nj600PgPY-QC^H%*?yHyQ-?HnVFe( zc6Nw}h-GDER8&+$Lqjq$G9e)$5D*Yz=_k4X0004WQchCg$s(BPOU_+ zKSB@$ivvyMAVp%6KEEV0v$uP1XSET_{ffuD@0)Mldou&%cnY-eG38A_660a|QF9;J zWqy5-#t+F;@OjjMVih=#StZdqouD*LGhjx<1-4&X!$j81=@|O$=T^%6O~gOI%G)N4 zql}r;$q0Apu7CA29{X!m?DPKbVTNJ2L(GDXM>q~r<`-g!@r5cn{3>@dl{@hbpW2>M zX#3RsQpD}Dhf>7^mV0LH1ctp7(Y)pG%KxO^Ic)i!;~iVfir#%C&|8y@Zpxl&YZv_k zuHtS*G(!R7alypAB2I-8$nBz0wpUT?<%J{25awoh*ni5HojvTaV-w5)s+TpZ0gCNN zA!htV2V)qG3w!X4sK4u93_sbT!n?L%{f1Dch26kU|G zAp~)v2DK5sF$K%T{A*V`cvTh336a9((Hh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchCosGKc^J;3aS? zSxsSvWRO_GxPK&bY}1xeQO5;-ucK8bj=jXlfuTb!q<@CtLAst`U%g;Gc1A#L+nA;H zS>sH34r-!PNiLvv>j*R+GVhP7-4U2;6Uzy68ZYSXrV8+Uu5uZXyLo(r!riDl$Z;5V zZVI6sIE}(FUW^kQ5k^$kryAo%=TQTRC3PRJsY7fH+Q|qk)aLzXqWch+8c5Fhxl``M zv|8~9w}0_Exq4lH$vioLeLV5&B=gH!((AmPi!iM!z4zbL-k!mou=uNABboTnP^dL& zF#g;XF@7hVZg7RAlg7KM@eM6*PBPZCwR`_uLx4eDRhP(oQRvO23Whq3_|ygy5|z(; z@!_^E9>Ul6fB01YpHclk7@u=V9G-(l>w?HigBw(al%3e5XrIusJ)%x z5rZ}}#0mTp7<4wU9!cMTp{b_;)tkDPz*I3%`(?IG1)1RxEshQh90DB2v1mHkfocGY z6qIq8;Q{MPg@2v^hzlkHJ^q1bMgyuQ&P8kt0zT}hCQM8~<{el9@%0`C2EzhImIDPS znmW3tvu@BS2C`T~LBIec$o(1FfDO|j2K-=PJ?Uyw8bfhQKV41p6c#W)49YGNtCR0@m-h*eAp5PvQkh~Pc|BGq7;)Syb;AhI9@ zp!9bJqGbtGV*{9Cp9muP!JG`3rVOY9jw>z3bN~mMvlu~yBRuUQYtmpB#NvkvC>@Su zfW^h-K$5ips)-eQ$GtNjDNApv(p+w~HM}urV=U2MRq542%sx^*#&%4nU${0#tnWZnyzh z0E@r|wptL)G=V_@B*4wU0k)peasraF-4Fl(RN)hSUVCoi00000NkvXXu0mjfd7??V delta 165 zcmcb@xP@_oc)b7%GXn#|m0iJ{KuSHpC&cyt|NlVdyLa#I-o1O~%$eQ0cduHtYUa$D zWo2a@9UZBusUaaDMn*FVdQ&MBb@0QE0C-2eap diff --git a/docs/html/img73.png b/docs/html/img73.png index a848d51605e6f069d3ace08b7d962b9a8a34b3c9..7143bb00baddd5f4762374bdf5bf2f9cb1ce17bf 100644 GIT binary patch delta 213 zcmV;`04o2>0ptOY7k?520{{R4IM5jJ0000jP)t-s|NsA)nVENYcU4tY?(Xh0Gc(N0 z%n=b0s;a7ph=^upW&i*HL_|d0-QBypyS_Xe%K!iX0d!JMQvg8b*k%9#0A)!;K~xBt zV_*P--5Vejm}Gm#00pdv7+4$_cJGGqwK$o8q#GX#0}i0T5Kh3rB+vk4Z3qC88#X+E zn!g)i2rj_)WCL#j(*Yohg?R##0*e4h@HGQB11DIT^N^5H1B!;-P_O|2Q=A%;0}M@MREYDh?kv$M02k&%FaK#vULcA#p;k|4ie28U-i(tsQvPZ!4!j+w~`3-}V| zojkBifHA4?la+y$NmInpHm*V*8-;0(=FaBK>=6%3P1`2(yh@lR(9Gd1I79V-&XEfY nX{9b_y8;+C&yblR(;&idSCUKnWQB(w&|n5nS3j3^P6@No(+Cw7uf8 zE>wj{%_E{f^zfk;=3@yHMI1yE5(L5=#1aDe94;=}$FQuA*_|Q#97_}D6zf?c3=C!a WgifS*ZF&rJ2!p4qpUXO@geCz0Ax`iB delta 181 zcmV;m080Pz0m%W79De|Gc+$TB001FSOjJex|Nj600PgPY-QC^0ySu8Ys+pOYc6N4D zR8&JlLozZljaKfZ00001bW%=J06^y0W&i*HR!KxbR49>SV4yN!g-{s|P`-O3gl4J; zfQmRmX{O2qQ~?Ht%p^1chRgyqfh<%3rpyFXL#t2?Wv+lZ1THF&3F9Lh3I^sA+YKHh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchCB9?{ z_<+O$ApQVy9IpY;Az)Xs9Dp)h85sO|fb?aMVl|5FBHmF-%TV|%Wem&;AO`Q^4-f?# zKnNnIDu61$z%mD@mLDh(zyQ(H0H(DVu3rGt7ij8s;s5|snH6nXr0NU+0000m5={s4w92*0`s;*JJ}r(j0SB&b10IT}DTdjZTO f)?lK&JzM|)1bh|YOxyn900000NkvXXu0mjfr36={ diff --git a/docs/html/img76.png b/docs/html/img76.png index 947f4e734ff9e3dec2b83bcb1b459c27c4aef8e2..323290a9d8ee4f3001eddcf637af130541352839 100644 GIT binary patch literal 469 zcmV;`0V@89P)5v zlS}OEOzb811)I~@P(U=XvY@u|6UfTSPmf)Ap8frQ92rjwvM4h&jjv6gG zzAA;`GL2mVj=%q#4W6*YuZs}&5FKw2~Id8 zoqoWIx`x{XPe7v6YrLUjV5&BSKFqrtGr;z)aDE#4eq}H&fsy)|9`V_{g);2JdjR&h z&g}rFM#HdmPuAf?k>2~7iUWZOH9ORJKI&{h(=f<7hW~)}C)UOnuTXxk6R}FY00000 LNkvXXu0mjfMkmhq literal 442 zcmV;r0Y(0aP)LH1Q4j>++zlv_ssRiP<)|_TfS9F#foWO-nCHX5 zaESpS1EqKy7;F`)K)eYy3~UXU3g$L2EN9>;0J2!OFmNkiC}7EHU=U^C0Nbg{5W#?< zfP<%jRfK`#0Rzx@UWZK#5e}6TP!vo8DiC1c5MW?nZk@&2z?Aw@p%YmFO9EVh0;>VH z0=xPnh7M!}oD4t(LLdboTcQ}4xf&R*BP*!r=sRHwbmRqw5^)BG#S9F53CzOC3QR)- zmnwW^;8?)Gu!eydNE#||9tc1Q2gU}56%2epvA_T>0|tg#V30bLgFz<%%oz$e7@|Ns9pXU;4yFAoh3 zefRF2v9a-)GiL+^1y`+F)zQ(BmX-!o=;GpX_wHRKC8gcFcgxEvP6Y}vmIV0)GdMiE z0g{jOba4#fn3sC}fFVUpgQ1i2 z_5z{Z~WI> PTEgJz>gTe~DWM4fd?ra6 literal 192 zcmeAS@N?(olHy`uVBq!ia0vp^d_XL~!VDy@>gTe~DWM4f9L7SD diff --git a/docs/html/img78.png b/docs/html/img78.png index 367c2cd60b01f24764bc019e43974c19e0ea430a..5bf75696f66ec90cc498fa32fded0f95904189a2 100644 GIT binary patch delta 211 zcmX@k_?&TqOg$rW{Uc2V1_qS?pAgso|NqaNIkUXHJTx@)-Me?IR;}vj=txUT1IoL& zxZJ&aclYkyrggQGfqcf2AirP+hi5lHl7*fwjv*QolM{d-=>Q*>goMOKubhMg4hBIc z1t$FqOoDe3mI<^RLK$Y}j)O@)45GGIgFM{I=9 zMsSfp2<5#PO@P5`F`58_)mAhC28*p|0t{LQPz6|58K4NT?kq4s(Zaq%0mV@ElTg0J hL5Rw7bT5q{000j~4zFF2ixmI>002ovPDHLkV1h69NI(Dp diff --git a/docs/html/img79.png b/docs/html/img79.png index 226f53362d9da72bc2f98cd900fce36b112f54ff..d44da06edfa39b7540d1b8f102bd9aa1b54a22e8 100644 GIT binary patch delta 373 zcmV-*0gC>$0)qpP7k?-O0{{R4BWGl10000mP)t-s|NsA)nVENYcU4tY?(Xh0Gc(N0 z%n=b0s;a7ph=^upW&i*HL_|d0-Q6N0BD=f09~~i;00001bW%=J06^y0W&i*I0ZBwb zR5*=eU_b(#4CsIdM6hBA0|Ao)1H*4H1Dh-^0MZ2l-0WcL0Dprw7ubXYq!~jHurY!u z{tZwsNHZ{l1(Y^0T+&mzz`(2rQMZb>2&{tX0ILGE?B0zEHjt>DLrD=;fS(5(HasxC z0s|YEz62Ba&oBW@-~RwLfr+sQL^CNVFeoW0F))16fhjeBP!5pb=ikCq3uatT(EdQ8 zGwBN`3{w&S^KOOP@Q`IYfF{ZEfZ+mz5d#a9+XQt7Tv_IRpr!&CkCT5dsyw5^MxX@~ zV1@~>?MIcLz)*x_Sq1~cCKP#328J^TY0e99E<~P9fPq09tDn%lF$xHR-S`0jlekwK Twgnp`00000NkvXXu0mjfwa$$V delta 295 zcmV+?0oeY71GNH>7k?)N0{{R3r8edy0000mP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001bW%=J06^y0W&i*Hvq?lj zR5*=eU>K@^b81FdD;{|ZhS>~hP&O;NBv7D$VJAZflpBaH4}TOeVEDqI0Oejpmj?;3 ze1JQpFaS(*pa^hofN?bg(d5Ab+!J8jCc^|&d9VP#1I)1nj14IAU;&QCHYk^a0Zkq* z00Gq<{UE38IdksJnPW%-P{7o{z;gguKSBT^s=&Z~0a+d)00!Ye5dma*ga8P5$v80g tNdzF|kp$2H2Ot(PWPlNkqhJ)^2LS!lCTFM2s9pd7002ovPDHLkV1h~_Z&?5U diff --git a/docs/html/img8.png b/docs/html/img8.png index f2dfeb5d19c046d891c38b3fc7ba07cb5fce7d40..f31f1db8a57ca7836040dfa3c4680c506d9cb7b9 100644 GIT binary patch literal 274 zcmeAS@N?(olHy`uVBq!ia0vp^N_!2^=r{y*8J{17k?rI0{{R3_~i%C0000mP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001bW%=J06^y0W&i*Hzez+v zR49>SU>H!qe;k>|aRx<_hk-#e4a!acb5SIjFR?EGu~@qW5Py=cp#fk?t^x*#(X0r` zoHnQ=V*o=pnk2+15HHYyp$|<`8*XPH14AR4sW3=nP=!MU(V` zOY#RWbfHNCeFv4~YG8QEkYj-2&lL_(Nv5M54Gf7B7?^vcn_-eHJx~WRum%I^3Gkps z30p8=cEBUa$t-|Pk~bJkDM9UuL6Kw)M&_}EFpL5k0syC?BI&e5b`Agl002ovPDHLk FV1h~*cbfnJ diff --git a/docs/html/img81.png b/docs/html/img81.png index 50e53c27794a7fbf0a6b26c125ef3959a320fcb8..9f6148ed3adeda084d4732b39c49a246f4775dbd 100644 GIT binary patch delta 208 zcmV;>05AX10p9_T7k>`~0{{R4x(aC00000jP)t-s|NsA)nVENYcU4tY?(Xi)%*+uH z5vr=Hh=_=0W@Z2Y07OJY-QC?HA|kuHyQY*5oB#j-0d!JMQvg8b*k%9#0ANW(K~xBt zV_;xlVqjp{0K^Pj2_TZwfPo3jg#Z^WAhAFPNJugu0oDQrhDi%RY;=Kv@4*5FR`vr7 z4AYSnFmNabfG9=ED7=pW^j0RBMrz2@^oL zzDo u9b?42g|az3?x~DNq|^;GIoOz9m@ueR@;==yE~WxBp25@A&t;ucLK6UD4@Niu diff --git a/docs/html/img82.png b/docs/html/img82.png index 9e70e6eb114eabcc114cfbfb9c7760b5d8eb75dc..02046ff389550de6739c2d1009a989805af52671 100644 GIT binary patch delta 198 zcmV;%06G880onnO9Df11+-gYx001yhOjJex|NohpnRj=0RaI5)?(Q=)GtA7)5fKrp zs;Y>Hh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchC;TzyX-JfrK$mX;i@b!-avxAfJI@!#@EAhD8qO7LfpE^=k29cC!ZzCxJ9G#{z~IAbH*bW-$=0Xu$aZL^CHc=mmi2?$)hf{nuH* o6q7K-I15n-Z5paTx!Z680LttQiHh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchC^1`NQ-z`#?$0c0qEcubfIPyja&a{!4CK!5s`0y~2i0rj{57nJq| zI!n!kfnfmy1Mh=;28IJbu>hc(6M(dmLjZ$5$k}uPfnaiRh88H4c$E(+04Yu`1%~|~ zVRnd`+YX!sAX*c`UB@8Gz%+q@VFM?~!Ms~QVhS+xL|+04#tXD|HUK5*6bp}6r_TTY O002ovPDHLkU;%03wU?7}{o-*VB4g1Qe0OWG)hz?*#1RB;^0#d_U05TEC zWdTVtD1t0yc7QsKxe;UlC(NbHp+P`WiJTA^C;$MHSQu={&-BFr0000SU_b?o zTu=rR1A`L-!vh8`GzAPi3@jjNpg1Q;5domiz`)J00Lb7F0Dc;^04i!pP#-QZ0f>1) z*0LCY-1q<_W&mU;0BLUq2;(r2&CTZk(ZH%iwp}Cv)=3bHcqTu92q-hKra)LM(gGlA z5g0*$umZ9Gi*f;&-o(JL97Jm#fGTr4z^Q=MHtpR&uz`B6Ck6ljo)i>fm{jDq00000 LNkvXXu0mjf(;Q+d delta 234 zcmVbr099O51Y;yvMHo09z|5;@015~& za0tKzYEcE4YCwjt3c&=JdclUW0u8+YVla0@9rBfdV*%Jen8Q{u@WGf6pcBx6=9y3f kFl8DF1juSJ1cnU&043WOP7|6t761SM07*qoM6N<$g7rpMnE(I) diff --git a/docs/html/img85.png b/docs/html/img85.png index e0aa874c12cf6be93fa4138e36697d74390f99c8..9758b0d8309ea8150ca245cf3e823a03ee703a4a 100644 GIT binary patch literal 207 zcmeAS@N?(olHy`uVBq!ia0vp^+(0bE!py+H$PvSN0m#t`@CkAK|NsBYnKR4F%R@s$ z-@SWx=FAyELBUn4R&{iAq@|?+Ro%UNS4l}}_wL=t67Pfq`HUq&e!&b5&u)MugFRgw zLpWw8ConXHI@B~KGIpF~Rg$PUpu!!%rgP%Jg389mgAI(LA_fKqYK$+L9quq3@ez0! zYG9i%fmdy&T7%{~UV+03LGG0YV^l?3UWF=bU|{$mDBykjnZSCW@eH1>elF{r5}E)P C>_w{p literal 166 zcmeAS@N?(olHy`uVBq!ia0vp^AhrMtGmyL+__-KJ$p!d?xc>kD|J}QHXU?42y?gh} znKR4E$~rnaLPA0m6%_>p1Xh-AF9E7#ED7=pW^j0RBMrzg^K@|x;h346aDX#{*Fj}D zQ^yq+!DXU~3afZ@tT|l_d>JO@uqsTlb(C0gM?r9jDeD^ViH(d5+g7oLCr_St4QK*` Mr>mdKI;Vst0LWf6@c;k- diff --git a/docs/html/img86.png b/docs/html/img86.png index f1553febeae5bf1177dce30ccb5e0aa5f2c4fbe1..b08434897ffde58e8b8a62952f011bbb263a1751 100644 GIT binary patch delta 596 zcmV-a0;~PL1mFaa7k?)N0{{R4y?~0J0000mP)t-s|NsA)nVENYcU4tY?(Xh0Gc(N0 z%n=b0s;a7ph=^upW&i*HL_|d0-Q6N0BD=f09~~i;00001bW%=J06^y0W&i*I-bqA3 zR7i>KRliHaP!Rr_U;UBR7abKOeK@J0)WtzCxQOV`!ATIhyMMR}4#m+agQ(zA6r2R3 zh>L?#aB!>QAWr@X9b8lp@8#ubs?v5474d`I^>Y2*eRsL0Kn%v1OV)xxb{{REg|-5Z z2(2Ivw9*X2S4>n98@(4zae9xSo5vjVAt;IU{9=IqB zHWXcrre^WXBY#N?Oc_>?Unj>hG7R)&+J;riM&aw!BQVhXe+N#QAo%KHy`SDKX@{Jg zjoQZ?&3D+=xGVR9;4Z^-N2B7#{#q5q+QGdZFt^8p$TcV%V_5q1fLr9A< z)gF<#WHx|l|CNc(wwNozECEl>8&h-M@`e-Of;<-(5*laGee+zN^yVo@AM(9=q)?jS}K zHPKO)KTW>G_IX2l6MPr?4)?GMbS?A#(RfnySsgF9VV_H?cnk}|gtL8z_GbJ3d7|y- i`Hvq%vlm9wf20?gM4aO7k$)%v0000L4|ja-fF6Ny*rj>=_ZU|2+)M&<MBA`y$Q;&A17?#utDb{-xn76d)Se8-W(u z0vYaXR}&3D0)NIr48q7d^AuPGit`wFrXB!t932?q5|G>jvUdX818{sXb8cXLfb7_p z46H&1T?~A!Af59W7&tzm=``S20O9Z!z*u0wDhdjg>kNjeAf3B`Iz`ZQ0(C$+3Opdz zo-;sj45(9pfwzH4m|-3ZNGC8lc`qR8)CUoY2CPtH41W!fHh-PMH0000)L`2=)-6A3)ySuv|9U+wf0004WQchCg;$dJA5NP0L z;AbcZxX-{~#ZV*wk`W-&M0`L=*`di`(lQWJhk<{Kz+Q&mKqmiQ1}+081qNe~_*;fW p4Bi6F3NS6J5V|kz`angu004*^6@}(WgLMD^002ovPDHLkV1lQ-TOR-b delta 228 zcmV%oz$e7@|Ns9pXU;4yFAoh3 zefRF2v9a-)GiL+^1y`+F)zQ(BmX-!o=;GpX_wHRKC8gcFcgxEvP6Y}vmIV0)GdMiE z0g{jKba4#fn34fO`DO^jZfhq z`w^Kte*!+<-Cdr4U?D5ltsjSX9pquxV_k6}mwiK7pR<#j#<#a^4ZIBB4hahj_9ycI P?O^b9^>bP0l+XkKfJaX@ literal 188 zcmeAS@N?(olHy`uVBq!ia0vp^d_XL~!VDy@>?A+G=b{|7SPy?b}}?%gwI z&g|a3d)2B{GiS~$D=X{h=txaXb#`_(GBQ$BR1^>pn7v^e4^TB@NswPKgTu2MX+Vyx zr;B3<$IRpe1?dfELT2+Vx_h%vO^V?qXO8$C#~S87RsmKUR)MIC4Wb^KY&B9iSTEjA jTdLmB(knSfLV}@JmuvDo^WLdIgBUzr{an^LB{Ts5hu}WS diff --git a/docs/html/img89.png b/docs/html/img89.png index 39f857d5cd44721405568c69f4e06a8449dd86bb..69a3e66c3c684afb91e749159334418f209e0a57 100644 GIT binary patch delta 198 zcmcb}c#Cm@Og-byJ6WC#3=FyfJ|V9E|Noykb7pyYd1z?pyLa!5jg8NoIU^`2xN6m^ zj*gDBv^1c?yLay@DJkvVy*tT3P7BCqED7=pW^j0R10)&k>Eal|F*7-Vfk{o^;D?4p zW@fVku?G$mFs$YgC@5m&T*tj*Ng$&sGHb50R6_`;y6 y*2iGB;qDs#8LSQ_*3CL0M{NZT3NLYNd&n@kmfQP(tx6Bj9tKZWKbLh*2~7aAKuDAT delta 189 zcmV;u07C!T0nq`F9De}L+gjfM001yhOjJex|Nj600PgPY-QC^H%*?yHyQ-?HnVFe( zc6Nw}h-GDER8&+$Lqjq$G9e)$5D*Yz=_k4X0004WQchC@#KW_`VnrXxm00000NkvXXu0mjfNoz^T diff --git a/docs/html/img9.png b/docs/html/img9.png index 2e5452b92f974975d13b2a3be764f55b0ca9f06d..e411ffb394eec9ee56f049a1a5a8c8037577aabd 100644 GIT binary patch delta 262 zcmV+h0r~#@0hI!f7k?520{{R4D+gEw0000mP)t-s|NsA)nVENYcU4tY?(Xh0Gc(N0 z%n=b0s;a7ph=^upW&i*HL_|d0-Q6N0BD=f09~~i;00001bW%=J06^y0W&i*HlSxED zR0x@4U;u&-3=p8rz@QIhGIBG(fB^$9!vY{?VBp|qKmbl<27fjXy@BDt0T9i@Ai#hX zGypNPCPM&7Ew92eAa#IYL$&}&=LC@a1tt*5_K^#Rejs2fK;cb*(5@y7J|PU=oa?~6 zQXmdzP-=q6#Q||BLjjitn8!1LfxiT%ox?$wfeYc--J2M=cV7TA0kV4+IIfXVRR910 M07*qoM6N<$f^VZ@hX4Qo delta 238 zcmV|ow~AfA}IL8lnZD|BFB*ax?lr-6a#E1bvtfPsAhoa4~Kz@?A? o<1Wo);0lGi@}L9*qaehU0QK@2A}n3HVE_OC07*qoM6N<$fKRXs~1K^T6V-OZXE;sk%eFp&r<7!a&eTS%}!2naS7dVh9y_F4oE6tP*3;gSBIZ)sr7zE1e5r`22 zezCv*s0_&iYla4T^idh8*dW<^a6x`?Po*b9@$;vgvFEGp;w9<=Oo{bGxI3J=yb2Yz zQL>6(iwh%>@_*GQM|$|0F{AadZluWf90~{2O4vZum5Yg%yy4FK@9`}g!!0&xQ_@*O zRLRm;`J(C=w>`y{96M|1Ay=nFaN1qTJR%{qJ*a#sGr9h|I^Hq%1}mEQ8XKj`5^H^D zm(~L#uvViegB)<%ZaB~is;mHhWiq>W{pQIbgf~a`?D>^76X;Or+npU2>ILsyn!s z#J?0vRWq6CSzu8~LSa@(&YhTRCCm~Zk!#+b;6UG_J*kiX+~8^*?vbTo5j-Anw}}t! z*2ltx^-NiH+4{(LJLB>c$Bj5ty%$QyVrC*~w0jq4Vrm{~eAeAOr1Ytk&%#1VleO>v h@s`o&Z`kK!^&2epqK>q>Wb^<4002ovPDHLkV1jkXAL{@B delta 493 zcmV;1RKH*=`6gY(-F%2qJ%6(8?lby;ZTGk!2mt^)Tqw!r_J2O3?{2ci5x&UqyYXAM zmVJ2N-C*OfBg0HsfZ`M+*^`a;v)*?%*gNJ6xx_`Rw{PyD+Z6+MUaXSz6b;5H8D4cc z!h{IFYBBe0>{q<+PK%y`dRrmPOh z*`&uU$EAYd+JBrSB>{KrfjfG`Zi)TnA*67H%FYFYrPWj2Av18ZNW~n;DHoRM%1#BN zMm4wY0ej$1>~O`wJ4X4Ely`Hm)A{tA-J7687oG3b~n(o|+bvyZd z?$<^wDhayN$Q>aH5JEG802J|Lix6&svoH>}>rAYY?PkF?cIOSIQ9|X;uc$`DGHbKr zn5NFX63cx&^pV>RJ|>UZ78sTre6(@#;Yai*o904&mTtAzN$Nq&GxkLfD*2|^UH0E= jvL}18CwsCd`>nnKP8#b{&}v5p00000NkvXXu0mjf88Pe# diff --git a/docs/html/img91.png b/docs/html/img91.png index 4a631dd625fa84ac25f8e8d6fd51b1d9f8629d14..18a953e24cef184e13703c06ad864a93b79fe88b 100644 GIT binary patch literal 638 zcmV-^0)hRBP)KRY6PKKotIV5;u&aCiEAC*`C^>0l`Br=CT)iSxSFE z*n<}@i%`Ma;t!CeJ@mSWdMG_eEj_eY_Rw1?i2VWGKTs;3L_zu{nc2<6)eThJgMN_A zoA=)L=Doa^1Q=j?FI!!@ScnoJC&gi2cf7BP$YSik4DA}@6?8V^0gYl%7+ zaOgSa(Lvvc&Gtr@V^$ZcBe3^!WDc-%_*eLRJ@#(-cs85@Q@(3^3}%#}nmDNxXbne; z?hyuC2TQ4BW-051azZ0uQ!a#5TuCG9OLg+9>IM6r1`XN*6d}t;=m;&-clc;Ee!5uJ z?KKfP!|p%DYQX*HHRN;nA;0E|2?ldCtfGi3p2Ho&f1b&|!D;_m^BjJ=T}z|35B6nk zTkom3qXOyVrF^uIImf(**fQ4X;xyskAPI-*FQH-cs~>^K$C=qnv{KgMjp)@b7D@Ix zSb8x$A7?h-iNM#i{93P1;C~1XaGv_V0WOjpL0ELGB)DkXD*phJ5&e|rQ~o-=gZZWw z`11v`!Y^#$S>S{!e^vfYoHN?_tMVKkv&MmKp2K!lcs5!)&~5cV~V?UQA$CG&VubwL2#&B z-7?xP{!s{YFpHo#*wL{R1jVJJf`dPUE<$k--8yt~G8e18+|^JAo$^BNxbL|qU+w|~ z`KuIt>EUv6g<0Hn8lG{86)ONprgt-zLpZ8|5 zY@)PKHWFlU0c;w5-~A>kH1781ihdyMzu|t4EZz&1onCz-X+k82l?o(j23yIZJBOc< zmuK6!T6GqoaY!$8L(SuJ*vY7k{8XflSK=!jU{7cKemLwTpL1>{ZiG6L23wc8 lif_2Xioeo>1PSuL`2a@}WBQ+CYB2x+002ovPDHLkV1gJN_<;Zb diff --git a/docs/html/img92.png b/docs/html/img92.png index ed89fe01e72248263b00f4fff6d1778eb7934a68..b58a4533a11894432d3bb88efc80e34427eb22ca 100644 GIT binary patch literal 339 zcmV-Z0j&OsP)0000jP)t-s|NsAY zcXw4)RqpQYGcz;H%*+uH5vr=Hh=_=0W@Z2Y07OJY-QC?HA|kuHyDISx_5c6?0d!JM zQvg8b*k%9#0MtoDK~yM_V_*ORu7?bmK!AaP6N_*h7BLLK4k8#23a~IRu!7kPT+9p% zd=N=yVoZPnzCo#Z1_v;k3CUFCu$Vx)`$+{P_!mC_`bQMT&VU6DSeOUm zVFr!_28O)|VTKL}lWn7*qXC4;C?&_hU<+Zl0l61Y&4(JziySOq)jUEA1*L_NUDJWp ljWCy>0a2`?gAJ_03INx!Ex(SV4wj=z$#iPfL%3EcoCEtvAd(I2_dWnQ}UC6;VeR! zZ32YJBErDX$WYPI(P01*X1D|q=KR3Gun(b{p&i2H-oU{A1xYvx!sK5XzCr=QtdJ;R zV6cU-9UU0rkiEeOq2@C%aD2iP-VGEM!4w8MoA&~eus+<`>m87UV?YFRuS7>r6Ot&y yOa`prFji6K1z3f-6|f4IU^m(TyYMI=2><{eh8{?-?2L2(0000u1cC*S7k?-O0{{R4z1?HS0000mP)t-s|NsA)nVENYcU4tY?(Xh0Gc(N0 z%n=b0s;a7ph=^upW&i*HL_|d0-Q6N0BD=f09~~i;00001bW%=J06^y0W&i*J07*na zR7i>KRljT7KotHgDVF6+s%z#B;+&}o!4T-srCz+aiwRk}iGL1Vx)?(P-Aw*~AhKjN zA;}OjgtTNxahsuAm*D;Z$=Ib3I++$s-<>4;&J~HE`7tCPobKIw_kP`{lYkLs4&vFN zVFkzm+9Z7}x0`RXRl^Sa03yH~>=1Z_(>!_dqa3Pf3amhr3!DRm{qy$)O_%P#2T|Eh*3?{o!s*vL@$^|N zF4DL#jCC3wU4w5Bgj4lPXqx`TBVhhQnZHoNno^2NZLPYoix(uj5gIGw{P=D9+f{h0 zvG@ddtZ#$`_#b%>f7Jd>U>Ir+%=CX7V%RZNeh=j;{pOaG|9iT{I;j)>OA}^^pV-1n zZU?e{+5S#VGn)0w_6>82J^83-7)~;D|Dt~^nUMTV8gjWm;Qr!@58PGw3thahJp~Y? QIRF3v07*qoM6N<$f(S<}ZU6uP delta 546 zcmV+-0^R+B1+D~;7k?)N0{{R3JB;Ck0000mP)t-s|Ns90008dp?%mzp%*@QYySu8Y zs+pOYc6N4%h=^rnWmHsDLqkI{GBP0{ArKG{V(BNk00001bW%=J06^y0W&i*ItVu*c zR7i>Kl08VnKp2K!lg9Md2K>P>#l=awD5W4o!AX&J=pZ=Mt$%J=1lz?w3V{v=QE;=P zqZ9F16(DQbQNPp)cH#yXSlF`@XvXef^d4{&>QM$ISGl+p9Yl5g>~97X^^VChs6ytG90au5w{WTR7L7v7m~VI z9u^ByXtFs2L4QrPENjp4$Aku4tPm=5EKI980U}K|e^9s*7gN95uB2$9Fkdv{ba4r6 z8Lr={i4lWefdl8Gq#sL1A9$Fhi?3X1_a}C9+=NV~Qg@cs zVEYT%Y^VpfbCB^EAP3nZ0isFoUKdHu&s_I{bWe7qM(Mob1-0J%(>a~YgNC@TdUkx} kX;$tQ)f-n|ef<-C1Il4!QfX%VEdT%j07*qoM6N<$f=^cavH$=8 diff --git a/docs/html/node13.html b/docs/html/node13.html index 7cfb275b..26b49b23 100644 --- a/docs/html/node13.html +++ b/docs/html/node13.html @@ -80,25 +80,25 @@ where $A=(a_{ij}) \in \mathbb{R}^{n \times n}$ is a nonsingular sparse matrix; for ease of presentation we assume $A$ has a symmetric sparsity pattern.

      Let us consider as finest index space the set of row (column) indices of $A$, i.e., $\Omega = \{1, 2, \ldots, n\}$. Any algebraic multilevel preconditioners implemented in MLD2P4 generates @@ -122,39 +122,39 @@ a hierarchy of index spaces and a corresponding hierarchy of matrices,

      by using the information contained in $A$, without assuming any knowledge of the geometry of the problem from which $A$ originates. A vector space $\mathbb{R}^{n_{k}}$ is associated with $\Omega^k$, where $n_k$ is the size of $\Omega^k$. For all $k < nlev$, a restriction operator and a prolongation one are built, which connect two levels $k$ and $k+1$: @@ -168,7 +168,7 @@ P^k \in \mathbb{R}^{n_k \times n_{k+1}}, \quad --> \begin{displaymath}
 P^k \in \mathbb{R}^{n_k \times n_{k+1}}, \quad
@@ -178,7 +178,7 @@ R^k \in \mathbb{R}^{n_{k+1}\times n_k};
 <BR CLEAR=

      the matrix $A^{k+1}$ is computed by using the previous operators according to the Galerkin approach, i.e., @@ -192,7 +192,7 @@ A^{k+1}=R^kA^kP^k. --> \begin{displaymath}
 A^{k+1}=R^kA^kP^k.
@@ -205,22 +205,22 @@ In the current implementation of MLD2P4 we have <SPAN CLASS=$R^k=(P^k)^T$ A smoother with iteration matrix $M^k$ is set up at each level $k < nlev$, and a solver is set up at the coarsest level, so that they are ready for application (for example, setting up a solver based on the $LU$ factorization means computing and storing the $L$ and $U$ factors). The construction of the hierarchy of AMG components described so far corresponds to the so-called build phase of the preconditioner. @@ -262,8 +262,8 @@ end \begin{tabbing} \quad \=\quad \=\quad... ...[1mm] -\>endif [1mm] -\>return $u^k$ [1mm] +\>endif \\ [1mm] +\>return $u^k$\ \\ [1mm] end \end{tabbing}\end{minipage}}"> @@ -276,7 +276,7 @@ end to obtain different multilevel preconditioners; this is done in the application phase, i.e., in the computation of a vector of type $w=B^{-1}v$, where

      In order to define the prolongator $P^k$, used to compute the coarse-level matrix $A^{k+1}$, MLD2P4 uses the smoothed aggregation algorithm described in [26]. The basic idea of this algorithm is to build a coarse set of indices $\Omega^{k+1}$ by suitably grouping the indices of $\Omega^k$ into disjoint subsets (aggregates), and to define the coarse-to-fine space transfer operator $P^k$ by applying a suitable smoother to a simple piecewise constant prolongation operator, with the aim of improving the quality of the coarse-space correction. @@ -84,26 +84,26 @@ prolongation operator, with the aim of improving the quality of the coarse-space

      1. aggregation of the indices of $\Omega^k$ to obtain $\Omega^{k+1}$;
      2. construction of the prolongator $P^k$;
      3. application of $P^k$ and $R^k=(P^k)^T$ to build $A^{k+1}$.
      4. @@ -116,13 +116,13 @@ each index $j \in \Omega^{k+1}$ corresponds to an aggregate $\Omega^k_j$ of $\Omega^k$, consisting of a suitably chosen index $\theta \in [0,1]$ (see [26] for the details). @@ -175,7 +175,7 @@ distribution. This version is embarrassingly parallel, since it does not require communication. On the other hand, it may produce some nonuniform aggregates and is strongly dependent on the number of processors and on the initial partitioning of the matrix $A$. Nevertheless, this parallel algorithm has been chosen for MLD2P4, since it has been shown to produce good results in practice @@ -186,7 +186,7 @@ MLD2P4, since it has been shown to produce good results in practice

        The prolongator $P^k$ is built starting from a tentative prolongator $j \in \Omega^{k+1}$. $P^k$ is obtained by applying to $\bar{P}^k$ a smoother \begin{displaymath}
 P^k = S^k \bar{P}^k,
@@ -277,7 +277,7 @@ method [<A
  HREF=2,24]. A simple choice for $S^k$ is the damped Jacobi smoother: @@ -290,7 +290,7 @@ S^k = I - \omega^k (D^k)^{-1} A^k_F , --> \begin{displaymath}
 S^k = I - \omega^k (D^k)^{-1} A^k_F ,
@@ -299,17 +299,17 @@ S^k = I - \omega^k (D^k)^{-1} A^k_F ,
 <BR CLEAR=

        where $D^k$ is the diagonal matrix with the same diagonal entries as $A^k$, $A^k_F = (\bar{a}_{ij}^k)$ is the filtered matrix defined as @@ -344,7 +344,7 @@ a_{ij}^k & \m...

      and $\omega^k$ is an approximation of $\rho^k$. Note that for systems coming from uniformly elliptic problems, filtering the matrix $A^k$ has little or no effect, and $A^k$ can be used instead of $A^k_F$. The latter choice is the default in MLD2P4. diff --git a/docs/html/node15.html b/docs/html/node15.html index db064fff..f45480f8 100644 --- a/docs/html/node15.html +++ b/docs/html/node15.html @@ -68,7 +68,7 @@ the beginning of the current iteration.

      In the AS methods, the index space $\Omega^k$ is divided into $\Omega^k_i$ of size $n_{k,i}$, possibly overlapping. For each $i$ we consider the restriction operator $\mathbb{R}^{n_{k,i}}$, i.e. $\lfloor 40 \sqrt[3]{n} \rfloor$, where $n$ is the dimension of the matrix at the finest level

      Any real

      number $\in [0, 1]$

      0.01 The threshold $\theta$ in the aggregation algorithm, see (3) in Section 4.2. @@ -643,7 +643,7 @@ number $\ge 0$ 0 Drop tolerance $t$ in the ILU( 0 Drop tolerance $t$ in the ILU( $y = op(B^{-1})\, x$, where The local part of the vector $x$. Note that type and kind_parameter must be chosen according @@ -137,28 +137,28 @@ and hence it is completely transparent to the user. $op(B^{-1}) = B^{-1}$ --> $op(B^{-1}) = B^{-1}$; if trans = 'T','t' then $op(B^{-1}) = B^{-T}$ (transpose of $B^{-1})$; if trans = 'C','c' then $op(B^{-1}) = B^{-C}$ (conjugate transpose of $B^{-1})$.

      where $A$ is a square, real or complex, sparse matrix. The name of the package comes from its original implementation, containing diff --git a/docs/mld2p4-2.2-guide.pdf b/docs/mld2p4-2.2-guide.pdf index 664a13a8..29db2a71 100644 --- a/docs/mld2p4-2.2-guide.pdf +++ b/docs/mld2p4-2.2-guide.pdf @@ -10166,8 +10166,8 @@ endobj 737 0 obj << /Title (MultiLevel Domain Decomposition Parallel Preconditioners Package based on PSBLAS, V. 2.2) /Subject (MultiLevel Domain Decomposition Parallel Preconditioners Package) /Keywords (Parallel Numerical Software, Algebraic Multilevel Preconditioners, Sparse Iterative Solvers, PSBLAS, MPI) /Creator (pdfLaTeX) /Producer ($Id: userguide.tex 2008-04-08 Pasqua D'Ambra, Daniela di Serafino, Salvatore Filippone$) /Author()/Title()/Subject()/Creator(LaTeX with hyperref package)/Producer(pdfTeX-1.40.17)/Keywords() -/CreationDate (D:20180514140750+01'00') -/ModDate (D:20180514140750+01'00') +/CreationDate (D:20180514143546+01'00') +/ModDate (D:20180514143546+01'00') /Trapped /False /PTEX.Fullbanner (This is pdfTeX, Version 3.14159265-2.6-1.40.17 (TeX Live 2016) kpathsea version 6.2.2) >> @@ -10580,7 +10580,7 @@ endobj /W [1 3 1] /Root 736 0 R /Info 737 0 R -/ID [<3899C85B41B440C76C6602BE660690F2> <3899C85B41B440C76C6602BE660690F2>] +/ID [<8C81DAEA73A339289C5AFD04D6D5A2A7> <8C81DAEA73A339289C5AFD04D6D5A2A7>] /Length 3695 >> stream