From 462f1d098cac86391058885cd116487661c866d0 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Sun, 15 Apr 2018 16:56:58 +0100 Subject: [PATCH 1/7] Modified internals to have tmp_ovrlap in local numbering. Also simplified crea_index taking out isglob argument. Fixed bldext, cdall & friends accordingly. --- base/internals/Makefile | 2 +- base/internals/psi_crea_index.f90 | 9 +--- base/internals/psi_crea_ovr_elem.f90 | 4 -- base/internals/psi_desc_impl.f90 | 8 +-- base/internals/psi_desc_index.F90 | 43 ++++++---------- base/internals/psi_exist_ovr_elem.f90 | 73 --------------------------- base/modules/desc/psb_desc_mod.F90 | 32 ++++-------- base/modules/psi_i_mod.f90 | 6 +-- base/tools/psb_ccdbldext.F90 | 29 +++-------- base/tools/psb_cd_inloc.f90 | 16 ++++++ base/tools/psb_cd_reinit.f90 | 6 +-- base/tools/psb_cdals.f90 | 16 +++++- base/tools/psb_dcdbldext.F90 | 29 +++-------- base/tools/psb_scdbldext.F90 | 29 +++-------- base/tools/psb_zcdbldext.F90 | 29 +++-------- test/pargen/runs/ppde.inp | 4 +- 16 files changed, 94 insertions(+), 241 deletions(-) delete mode 100644 base/internals/psi_exist_ovr_elem.f90 diff --git a/base/internals/Makefile b/base/internals/Makefile index de55e4b1..471fc383 100644 --- a/base/internals/Makefile +++ b/base/internals/Makefile @@ -3,7 +3,7 @@ include ../../Make.inc FOBJS = psi_compute_size.o psi_crea_bnd_elem.o psi_crea_index.o \ psi_crea_ovr_elem.o psi_bld_tmpovrl.o psi_dl_check.o \ psi_bld_tmphalo.o psi_sort_dl.o \ - psi_desc_impl.o psi_exist_ovr_elem.o psi_list_search.o psi_srtlist.o + psi_desc_impl.o psi_list_search.o psi_srtlist.o MPFOBJS = psi_desc_index.o psi_extrct_dl.o \ psi_fnd_owner.o psb_indx_map_fnd_owner.o diff --git a/base/internals/psi_crea_index.f90 b/base/internals/psi_crea_index.f90 index 7025413f..6c88ae2d 100644 --- a/base/internals/psi_crea_index.f90 +++ b/base/internals/psi_crea_index.f90 @@ -44,16 +44,12 @@ ! mapping parts are used. ! index_in(:) - integer The index list, build format ! index_out(:) - integer(psb_ipk_), allocatable The index list, assembled format -! glob_idx - logical Whether the input indices are in local or global -! numbering; the global numbering is used when -! converting the overlap exchange lists. ! nxch - integer The number of data exchanges on the calling process ! nsnd - integer Total send buffer size on the calling process ! nrcv - integer Total receive buffer size on the calling process ! ! -subroutine psi_crea_index(desc_a,index_in,index_out,glob_idx,nxch,nsnd,nrcv,info) - +subroutine psi_crea_index(desc_a,index_in,index_out,nxch,nsnd,nrcv,info) use psb_realloc_mod use psb_desc_mod use psb_error_mod @@ -65,7 +61,6 @@ subroutine psi_crea_index(desc_a,index_in,index_out,glob_idx,nxch,nsnd,nrcv,info integer(psb_ipk_), intent(out) :: info,nxch,nsnd,nrcv integer(psb_ipk_), intent(in) :: index_in(:) integer(psb_ipk_), allocatable, intent(inout) :: index_out(:) - logical :: glob_idx ! ....local scalars... integer(psb_ipk_) :: ictxt, me, np, mode, err_act, dl_lda @@ -135,7 +130,7 @@ subroutine psi_crea_index(desc_a,index_in,index_out,glob_idx,nxch,nsnd,nrcv,info & write(debug_unit,*) me,' ',trim(name),': calling psi_desc_index' ! Do the actual format conversion. call psi_desc_index(desc_a,index_in,dep_list(1:,me),& - & length_dl(me),nsnd,nrcv, index_out,glob_idx,info) + & length_dl(me),nsnd,nrcv, index_out,info) if(debug_level >= psb_debug_inner_) & & write(debug_unit,*) me,' ',trim(name),': out of psi_desc_index',& & size(index_out) diff --git a/base/internals/psi_crea_ovr_elem.f90 b/base/internals/psi_crea_ovr_elem.f90 index 13bf8af1..9fd69247 100644 --- a/base/internals/psi_crea_ovr_elem.f90 +++ b/base/internals/psi_crea_ovr_elem.f90 @@ -61,10 +61,6 @@ subroutine psi_crea_ovr_elem(me,desc_overlap,ovr_elem,info) integer(psb_ipk_) :: dim_ovr_elem integer(psb_ipk_) :: pairtree(2) - ! ...external function... - integer(psb_ipk_) :: psi_exist_ovr_elem - external :: psi_exist_ovr_elem - integer(psb_ipk_) :: nel, ip, ix, iel, insize, err_act, iproc integer(psb_ipk_), allocatable :: telem(:,:) diff --git a/base/internals/psi_desc_impl.f90 b/base/internals/psi_desc_impl.f90 index 8ab3bd0f..977af721 100644 --- a/base/internals/psi_desc_impl.f90 +++ b/base/internals/psi_desc_impl.f90 @@ -102,7 +102,7 @@ subroutine psi_cnv_dsc(halo_in,ovrlap_in,ext_in,cdesc, info, mold) ! first the halo index if (debug_level>0) write(debug_unit,*) me,'Calling crea_index on halo',& & size(halo_in) - call psi_crea_index(cdesc,halo_in, idx_out,.false.,nxch,nsnd,nrcv,info) + call psi_crea_index(cdesc,halo_in, idx_out,nxch,nsnd,nrcv,info) if (info /= psb_success_) then call psb_errpush(psb_err_from_subroutine_,name,a_err='psi_crea_index') goto 9999 @@ -115,7 +115,7 @@ subroutine psi_cnv_dsc(halo_in,ovrlap_in,ext_in,cdesc, info, mold) ! then ext index if (debug_level>0) write(debug_unit,*) me,'Calling crea_index on ext' - call psi_crea_index(cdesc,ext_in, idx_out,.false.,nxch,nsnd,nrcv,info) + call psi_crea_index(cdesc,ext_in, idx_out,nxch,nsnd,nrcv,info) if (info /= psb_success_) then call psb_errpush(psb_err_from_subroutine_,name,a_err='psi_crea_index') goto 9999 @@ -126,7 +126,7 @@ subroutine psi_cnv_dsc(halo_in,ovrlap_in,ext_in,cdesc, info, mold) if (debug_level>0) write(debug_unit,*) me,'Calling crea_index on ovrlap' ! then the overlap index - call psi_crea_index(cdesc,ovrlap_in, idx_out,.true.,nxch,nsnd,nrcv,info) + call psi_crea_index(cdesc,ovrlap_in, idx_out,nxch,nsnd,nrcv,info) if (info /= psb_success_) then call psb_errpush(psb_err_from_subroutine_,name,a_err='psi_crea_index') goto 9999 @@ -150,7 +150,7 @@ subroutine psi_cnv_dsc(halo_in,ovrlap_in,ext_in,cdesc, info, mold) if (debug_level>0) write(debug_unit,*) me,'Calling bld_ovr_mst' call psi_bld_ovr_mst(me,cdesc%ovrlap_elem,tmp_mst_idx,info) if (info == psb_success_) call psi_crea_index(cdesc,& - & tmp_mst_idx,idx_out,.false.,nxch,nsnd,nrcv,info) + & tmp_mst_idx,idx_out,nxch,nsnd,nrcv,info) if (debug_level>0) write(debug_unit,*) me,'Done crea_indx' if (info /= psb_success_) then call psb_errpush(psb_err_from_subroutine_,name,a_err='psi_bld_ovr_mst') diff --git a/base/internals/psi_desc_index.F90 b/base/internals/psi_desc_index.F90 index 386b89af..e5a890f4 100644 --- a/base/internals/psi_desc_index.F90 +++ b/base/internals/psi_desc_index.F90 @@ -38,16 +38,13 @@ ! See below for a description of the formats. ! ! Arguments: -! desc_a - type(psb_desc_type) The descriptor; in this context only the index -! mapping parts are used. -! index_in(:) - integer The index list, build format +! desc_a - type(psb_desc_type) The descriptor; in this context only the index +! mapping parts are used. +! index_in(:) - integer The index list, build format ! index_out(:) - integer(psb_ipk_), allocatable The index list, assembled format -! glob_idx - logical Whether the input indices are in local or global -! numbering; the global numbering is used when -! converting the overlap exchange lists. -! nxch - integer The number of data exchanges on the calling process -! nsnd - integer Total send buffer size on the calling process -! nrcv - integer Total receive buffer size on the calling process +! nxch - integer The number of data exchanges on the calling process +! nsnd - integer Total send buffer size on the calling process +! nrcv - integer Total receive buffer size on the calling process ! ! The format of the index lists. Copied from base/modules/psb_desc_type ! @@ -99,7 +96,7 @@ ! ! subroutine psi_desc_index(desc,index_in,dep_list,& - & length_dl,nsnd,nrcv,desc_index,isglob_in,info) + & length_dl,nsnd,nrcv,desc_index,info) use psb_desc_mod use psb_realloc_mod use psb_error_mod @@ -119,7 +116,6 @@ subroutine psi_desc_index(desc,index_in,dep_list,& integer(psb_ipk_) :: index_in(:),dep_list(:) integer(psb_ipk_),allocatable :: desc_index(:) integer(psb_ipk_) :: length_dl,nsnd,nrcv,info - logical :: isglob_in ! ....local scalars... integer(psb_ipk_) :: j,me,np,i,proc ! ...parameters... @@ -255,22 +251,15 @@ subroutine psi_desc_index(desc,index_in,dep_list,& ! ! note that here bsdinx is zero-based, hence the following loop ! - if (isglob_in) then - do j=1, nerv - sndbuf(bsdindx(proc+1)+j) = (index_in(i+j)) - end do - else - - call desc%indxmap%l2g(index_in(i+1:i+nerv),& - & sndbuf(bsdindx(proc+1)+1:bsdindx(proc+1)+nerv),& - & info) - - if (info /= psb_success_) then - call psb_errpush(psb_err_from_subroutine_,name,a_err='l2g') - goto 9999 - end if - - endif + call desc%indxmap%l2g(index_in(i+1:i+nerv),& + & sndbuf(bsdindx(proc+1)+1:bsdindx(proc+1)+nerv),& + & info) + + if (info /= psb_success_) then + call psb_errpush(psb_err_from_subroutine_,name,a_err='l2g') + goto 9999 + end if + bsdindx(proc+1) = bsdindx(proc+1) + nerv i = i + nerv + 1 end do diff --git a/base/internals/psi_exist_ovr_elem.f90 b/base/internals/psi_exist_ovr_elem.f90 deleted file mode 100644 index cd7d4712..00000000 --- a/base/internals/psi_exist_ovr_elem.f90 +++ /dev/null @@ -1,73 +0,0 @@ -! -! Parallel Sparse BLAS version 3.5 -! (C) Copyright 2006, 2010, 2015, 2017 -! Salvatore Filippone -! Alfredo Buttari CNRS-IRIT, Toulouse -! -! Redistribution and use in source and binary forms, with or without -! modification, are permitted provided that the following conditions -! are met: -! 1. Redistributions of source code must retain the above copyright -! notice, this list of conditions and the following disclaimer. -! 2. Redistributions in binary form must reproduce the above copyright -! notice, this list of conditions, and the following disclaimer in the -! documentation and/or other materials provided with the distribution. -! 3. The name of the PSBLAS group or the names of its contributors may -! not be used to endorse or promote products derived from this -! software without specific written permission. -! -! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR -! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE PSBLAS GROUP OR ITS CONTRIBUTORS -! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -! POSSIBILITY OF SUCH DAMAGE. -! -! -integer function psi_exist_ovr_elem(ovr_elem, dim_list,elem_searched) - use psb_const_mod - ! PURPOSE: - ! == = ==== - ! - ! If ELEM_SEARCHED exist in the list OVR_ELEM returns its position in - ! the list, else returns -1 - ! - ! - ! INPUT - ! == = === - ! OVRLAP_ELEMENT_D.: Contains for all overlap points belonging to - ! the current process: - ! 1. overlap point index - ! 2. Number of domains sharing that overlap point - ! the end is marked by a -1............................... - ! - ! DIM_LIST..........: Dimension of list OVRLAP_ELEMENT_D - ! - ! ELEM_SEARCHED.....:point's Local index identifier to be searched. - - implicit none - - ! ....Scalars parameters.... - integer(psb_ipk_) :: dim_list,elem_searched - ! ...array parameters.... - integer(psb_ipk_) :: ovr_elem(dim_list,*) - - ! ...local scalars.... - integer(psb_ipk_) :: i - - i=1 - do while ((i.le.dim_list).and.(ovr_elem(i,1).ne.elem_searched)) - i=i+1 - enddo - if ((i.le.dim_list).and.(ovr_elem(i,1).eq.elem_searched)) then - psi_exist_ovr_elem=i - else - psi_exist_ovr_elem=-1 - endif -end function psi_exist_ovr_elem - diff --git a/base/modules/desc/psb_desc_mod.F90 b/base/modules/desc/psb_desc_mod.F90 index 5d5b22a7..724b9114 100644 --- a/base/modules/desc/psb_desc_mod.F90 +++ b/base/modules/desc/psb_desc_mod.F90 @@ -1,4 +1,4 @@ -! + ! Parallel Sparse BLAS version 3.5 ! (C) Copyright 2006-2018 ! Salvatore Filippone @@ -142,9 +142,9 @@ module psb_desc_mod ! psb_ovrl subroutine. ! ! 8. When the descriptor is in the BLD state the INDEX vectors contains only - ! the indices to be received, organized as a sequence - ! of entries of the form (proc,N,(lx1,lx2,...,lxn)) with owning process, - ! number of indices (most often but not necessarily N=1), list of local indices. + ! the indices to be received, organized as a sequence of entries of + ! the form (proc,N,(lx1,lx2,...,lxn)) with owning process, number of indices + ! (most often but not necessarily N=1), list of local indices. ! This is because we only know the list of halo indices to be received ! as we go about building the sparse matrix pattern, and we want the build ! phase to be loosely synchronized. Thus we record the indices we have to ask @@ -1072,7 +1072,7 @@ contains end subroutine psb_cd_clone - Subroutine psb_cd_get_recv_idx(tmp,desc,data,info,toglob) + Subroutine psb_cd_get_recv_idx(tmp,desc,data,info) use psb_error_mod use psb_penv_mod @@ -1082,7 +1082,6 @@ contains integer(psb_ipk_), intent(in) :: data Type(psb_desc_type), Intent(in), target :: desc integer(psb_ipk_), intent(out) :: info - logical, intent(in) :: toglob ! .. Local Scalars .. integer(psb_ipk_) :: incnt, outcnt, j, np, me, ictxt, l_tmp,& @@ -1141,23 +1140,10 @@ contains call psb_errpush(info,name,a_err='psb_ensure_size') goto 9999 end if - if (toglob) then - call desc%indxmap%l2g(idx,gidx,info) - If (gidx < 0) then - info=-3 - call psb_errpush(info,name) - goto 9999 - endif - tmp(outcnt) = proc - tmp(outcnt+1) = 1 - tmp(outcnt+2) = gidx - tmp(outcnt+3) = -1 - else - tmp(outcnt) = proc - tmp(outcnt+1) = 1 - tmp(outcnt+2) = idx - tmp(outcnt+3) = -1 - end if + tmp(outcnt) = proc + tmp(outcnt+1) = 1 + tmp(outcnt+2) = idx + tmp(outcnt+3) = -1 outcnt = outcnt+3 end Do incnt = incnt+n_elem_recv+n_elem_send+3 diff --git a/base/modules/psi_i_mod.f90 b/base/modules/psi_i_mod.f90 index 76d73726..c6e65f26 100644 --- a/base/modules/psi_i_mod.f90 +++ b/base/modules/psi_i_mod.f90 @@ -53,13 +53,12 @@ module psi_i_mod end interface interface - subroutine psi_crea_index(desc_a,index_in,index_out,glob_idx,nxch,nsnd,nrcv,info) + subroutine psi_crea_index(desc_a,index_in,index_out,nxch,nsnd,nrcv,info) import type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info,nxch,nsnd,nrcv integer(psb_ipk_), intent(in) :: index_in(:) integer(psb_ipk_), allocatable, intent(inout) :: index_out(:) - logical :: glob_idx end subroutine psi_crea_index end interface @@ -74,13 +73,12 @@ module psi_i_mod interface subroutine psi_desc_index(desc,index_in,dep_list,& - & length_dl,nsnd,nrcv,desc_index,isglob_in,info) + & length_dl,nsnd,nrcv,desc_index,info) import type(psb_desc_type) :: desc integer(psb_ipk_) :: index_in(:),dep_list(:) integer(psb_ipk_),allocatable :: desc_index(:) integer(psb_ipk_) :: length_dl,nsnd,nrcv,info - logical :: isglob_in end subroutine psi_desc_index end interface diff --git a/base/tools/psb_ccdbldext.F90 b/base/tools/psb_ccdbldext.F90 index 0792222e..705e82af 100644 --- a/base/tools/psb_ccdbldext.F90 +++ b/base/tools/psb_ccdbldext.F90 @@ -84,7 +84,8 @@ Subroutine psb_ccdbldext(a,desc_a,novr,desc_ov,info, extype) integer(psb_ipk_) :: i, j, err_act,m,& & lovr, lworks,lworkr, n_row,n_col, n_col_prev, & & index_dim,elem_dim, l_tmp_ovr_idx,l_tmp_halo, nztot,nhalo - integer(psb_ipk_) :: counter,counter_h, counter_o, counter_e,idx,gidx,proc,n_elem_recv,& + integer(psb_ipk_) :: counter,counter_h, counter_o, counter_e,& + & idx,proc,n_elem_recv,& & n_elem_send,tot_recv,tot_elem,cntov_o,& & counter_t,n_elem,i_ovr,jj,proc_id,isz, & & idxr, idxs, iszr, iszs, nxch, nsnd, nrcv,lidx, extype_ @@ -255,12 +256,6 @@ Subroutine psb_ccdbldext(a,desc_a,novr,desc_ov,info, extype) Do j=0,n_elem_recv-1 idx = ovrlap(counter+psb_elem_recv_+j) - call desc_ov%indxmap%l2g(idx,gidx,info) - If (gidx < 0) then - info=-3 - call psb_errpush(info,name) - goto 9999 - endif call psb_ensure_size((cntov_o+3),orig_ovr,info,pad=-ione) if (info /= psb_success_) then info=psb_err_from_subroutine_ @@ -269,7 +264,7 @@ Subroutine psb_ccdbldext(a,desc_a,novr,desc_ov,info, extype) end if orig_ovr(cntov_o)=proc orig_ovr(cntov_o+1)=1 - orig_ovr(cntov_o+2)=gidx + orig_ovr(cntov_o+2)=idx orig_ovr(cntov_o+3)=-1 cntov_o=cntov_o+3 end Do @@ -356,12 +351,6 @@ Subroutine psb_ccdbldext(a,desc_a,novr,desc_ov,info, extype) end If idx = halo(counter+psb_elem_recv_+j) - call desc_ov%l2g(idx,gidx,info) - If (gidx < 0) then - info=-3 - call psb_errpush(info,name) - goto 9999 - endif call psb_ensure_size((counter_o+3),tmp_ovr_idx,info,pad=-ione) if (info /= psb_success_) then info=psb_err_from_subroutine_ @@ -371,7 +360,7 @@ Subroutine psb_ccdbldext(a,desc_a,novr,desc_ov,info, extype) tmp_ovr_idx(counter_o) = proc tmp_ovr_idx(counter_o+1) = 1 - tmp_ovr_idx(counter_o+2) = gidx + tmp_ovr_idx(counter_o+2) = idx tmp_ovr_idx(counter_o+3) = -1 counter_o=counter_o+3 call psb_ensure_size((counter_h+3),tmp_halo,info,pad=-ione) @@ -400,12 +389,6 @@ Subroutine psb_ccdbldext(a,desc_a,novr,desc_ov,info, extype) Do j=0,n_elem_send-1 idx = halo(counter+psb_elem_send_+j) - call desc_ov%l2g(idx,gidx,info) - If (gidx < 0) then - info=-3 - call psb_errpush(info,name) - goto 9999 - endif call psb_ensure_size((counter_o+3),tmp_ovr_idx,info,pad=-ione) if (info /= psb_success_) then info=psb_err_from_subroutine_ @@ -415,7 +398,7 @@ Subroutine psb_ccdbldext(a,desc_a,novr,desc_ov,info, extype) tmp_ovr_idx(counter_o) = proc tmp_ovr_idx(counter_o+1) = 1 - tmp_ovr_idx(counter_o+2) = gidx + tmp_ovr_idx(counter_o+2) = idx tmp_ovr_idx(counter_o+3) = -1 counter_o=counter_o+3 @@ -599,7 +582,7 @@ Subroutine psb_ccdbldext(a,desc_a,novr,desc_ov,info, extype) write(debug_unit,*) me,' ',trim(name),':Calling Crea_index' end if - call psi_crea_index(desc_ov,t_halo_in,t_halo_out,.false.,& + call psi_crea_index(desc_ov,t_halo_in,t_halo_out,& & nxch,nsnd,nrcv,info) if (debug_level >= psb_debug_outer_) then diff --git a/base/tools/psb_cd_inloc.f90 b/base/tools/psb_cd_inloc.f90 index 0310a7d9..1b31fe2e 100644 --- a/base/tools/psb_cd_inloc.f90 +++ b/base/tools/psb_cd_inloc.f90 @@ -369,6 +369,22 @@ subroutine psb_cd_inloc(v, ictxt, desc, info, globalcheck,idx) call aa%init(iictxt,vl(1:nlu),info) end select + + ! + ! Now that we have initialized indxmap we can convert the + ! indices to local numbering. + ! + block + integer(psb_ipk_) :: i,nprocs + i = 1 + do while (temp_ovrlap(i) /= -1) + call desc%indxmap%g2lip(temp_ovrlap(i),info) + i = i + 1 + nprocs = temp_ovrlap(i) + i = i + 1 + i = i + nprocs + enddo + end block call psi_bld_tmpovrl(temp_ovrlap,desc,info) if (info == psb_success_) deallocate(temp_ovrlap,vl,ix,stat=info) diff --git a/base/tools/psb_cd_reinit.f90 b/base/tools/psb_cd_reinit.f90 index f790218a..d579ba95 100644 --- a/base/tools/psb_cd_reinit.f90 +++ b/base/tools/psb_cd_reinit.f90 @@ -61,9 +61,9 @@ Subroutine psb_cd_reinit(desc,info) if (debug_level >= psb_debug_outer_) & & write(debug_unit,*) me,' ',trim(name),': start' if (desc%is_asb()) then - call psb_cd_get_recv_idx(tmp_ovr,desc,psb_comm_ovr_,info,toglob=.true.) - call psb_cd_get_recv_idx(tmp_halo,desc,psb_comm_halo_,info,toglob=.false.) - call psb_cd_get_recv_idx(tmp_ext,desc,psb_comm_ext_,info,toglob=.false.) + call psb_cd_get_recv_idx(tmp_ovr,desc,psb_comm_ovr_,info) + call psb_cd_get_recv_idx(tmp_halo,desc,psb_comm_halo_,info) + call psb_cd_get_recv_idx(tmp_ext,desc,psb_comm_ext_,info) call psb_move_alloc(tmp_ovr,desc%ovrlap_index,info) call psb_move_alloc(tmp_halo,desc%halo_index,info) diff --git a/base/tools/psb_cdals.f90 b/base/tools/psb_cdals.f90 index 4c7131c7..e141a427 100644 --- a/base/tools/psb_cdals.f90 +++ b/base/tools/psb_cdals.f90 @@ -267,7 +267,21 @@ subroutine psb_cdals(m, n, parts, ictxt, desc, info) if (debug_level >= psb_debug_ext_) & & write(debug_unit,*) me,' ',trim(name),': error check:' ,err - + ! + ! Now that we have initialized indxmap we can convert the + ! indices to local numbering. + ! + block + integer(psb_ipk_) :: i,nprocs + i = 1 + do while (temp_ovrlap(i) /= -1) + call desc%indxmap%g2lip(temp_ovrlap(i),info) + i = i + 1 + nprocs = temp_ovrlap(i) + i = i + 1 + i = i + nprocs + enddo + end block call psi_bld_tmpovrl(temp_ovrlap,desc,info) if (info == psb_success_) deallocate(prc_v,temp_ovrlap,stat=info) diff --git a/base/tools/psb_dcdbldext.F90 b/base/tools/psb_dcdbldext.F90 index 14aa6976..99610cc3 100644 --- a/base/tools/psb_dcdbldext.F90 +++ b/base/tools/psb_dcdbldext.F90 @@ -84,7 +84,8 @@ Subroutine psb_dcdbldext(a,desc_a,novr,desc_ov,info, extype) integer(psb_ipk_) :: i, j, err_act,m,& & lovr, lworks,lworkr, n_row,n_col, n_col_prev, & & index_dim,elem_dim, l_tmp_ovr_idx,l_tmp_halo, nztot,nhalo - integer(psb_ipk_) :: counter,counter_h, counter_o, counter_e,idx,gidx,proc,n_elem_recv,& + integer(psb_ipk_) :: counter,counter_h, counter_o, counter_e,& + & idx,proc,n_elem_recv,& & n_elem_send,tot_recv,tot_elem,cntov_o,& & counter_t,n_elem,i_ovr,jj,proc_id,isz, & & idxr, idxs, iszr, iszs, nxch, nsnd, nrcv,lidx, extype_ @@ -255,12 +256,6 @@ Subroutine psb_dcdbldext(a,desc_a,novr,desc_ov,info, extype) Do j=0,n_elem_recv-1 idx = ovrlap(counter+psb_elem_recv_+j) - call desc_ov%indxmap%l2g(idx,gidx,info) - If (gidx < 0) then - info=-3 - call psb_errpush(info,name) - goto 9999 - endif call psb_ensure_size((cntov_o+3),orig_ovr,info,pad=-ione) if (info /= psb_success_) then info=psb_err_from_subroutine_ @@ -269,7 +264,7 @@ Subroutine psb_dcdbldext(a,desc_a,novr,desc_ov,info, extype) end if orig_ovr(cntov_o)=proc orig_ovr(cntov_o+1)=1 - orig_ovr(cntov_o+2)=gidx + orig_ovr(cntov_o+2)=idx orig_ovr(cntov_o+3)=-1 cntov_o=cntov_o+3 end Do @@ -356,12 +351,6 @@ Subroutine psb_dcdbldext(a,desc_a,novr,desc_ov,info, extype) end If idx = halo(counter+psb_elem_recv_+j) - call desc_ov%l2g(idx,gidx,info) - If (gidx < 0) then - info=-3 - call psb_errpush(info,name) - goto 9999 - endif call psb_ensure_size((counter_o+3),tmp_ovr_idx,info,pad=-ione) if (info /= psb_success_) then info=psb_err_from_subroutine_ @@ -371,7 +360,7 @@ Subroutine psb_dcdbldext(a,desc_a,novr,desc_ov,info, extype) tmp_ovr_idx(counter_o) = proc tmp_ovr_idx(counter_o+1) = 1 - tmp_ovr_idx(counter_o+2) = gidx + tmp_ovr_idx(counter_o+2) = idx tmp_ovr_idx(counter_o+3) = -1 counter_o=counter_o+3 call psb_ensure_size((counter_h+3),tmp_halo,info,pad=-ione) @@ -400,12 +389,6 @@ Subroutine psb_dcdbldext(a,desc_a,novr,desc_ov,info, extype) Do j=0,n_elem_send-1 idx = halo(counter+psb_elem_send_+j) - call desc_ov%l2g(idx,gidx,info) - If (gidx < 0) then - info=-3 - call psb_errpush(info,name) - goto 9999 - endif call psb_ensure_size((counter_o+3),tmp_ovr_idx,info,pad=-ione) if (info /= psb_success_) then info=psb_err_from_subroutine_ @@ -415,7 +398,7 @@ Subroutine psb_dcdbldext(a,desc_a,novr,desc_ov,info, extype) tmp_ovr_idx(counter_o) = proc tmp_ovr_idx(counter_o+1) = 1 - tmp_ovr_idx(counter_o+2) = gidx + tmp_ovr_idx(counter_o+2) = idx tmp_ovr_idx(counter_o+3) = -1 counter_o=counter_o+3 @@ -599,7 +582,7 @@ Subroutine psb_dcdbldext(a,desc_a,novr,desc_ov,info, extype) write(debug_unit,*) me,' ',trim(name),':Calling Crea_index' end if - call psi_crea_index(desc_ov,t_halo_in,t_halo_out,.false.,& + call psi_crea_index(desc_ov,t_halo_in,t_halo_out,& & nxch,nsnd,nrcv,info) if (debug_level >= psb_debug_outer_) then diff --git a/base/tools/psb_scdbldext.F90 b/base/tools/psb_scdbldext.F90 index 20fda8dc..d4dd77c2 100644 --- a/base/tools/psb_scdbldext.F90 +++ b/base/tools/psb_scdbldext.F90 @@ -84,7 +84,8 @@ Subroutine psb_scdbldext(a,desc_a,novr,desc_ov,info, extype) integer(psb_ipk_) :: i, j, err_act,m,& & lovr, lworks,lworkr, n_row,n_col, n_col_prev, & & index_dim,elem_dim, l_tmp_ovr_idx,l_tmp_halo, nztot,nhalo - integer(psb_ipk_) :: counter,counter_h, counter_o, counter_e,idx,gidx,proc,n_elem_recv,& + integer(psb_ipk_) :: counter,counter_h, counter_o, counter_e,& + & idx,proc,n_elem_recv,& & n_elem_send,tot_recv,tot_elem,cntov_o,& & counter_t,n_elem,i_ovr,jj,proc_id,isz, & & idxr, idxs, iszr, iszs, nxch, nsnd, nrcv,lidx, extype_ @@ -255,12 +256,6 @@ Subroutine psb_scdbldext(a,desc_a,novr,desc_ov,info, extype) Do j=0,n_elem_recv-1 idx = ovrlap(counter+psb_elem_recv_+j) - call desc_ov%indxmap%l2g(idx,gidx,info) - If (gidx < 0) then - info=-3 - call psb_errpush(info,name) - goto 9999 - endif call psb_ensure_size((cntov_o+3),orig_ovr,info,pad=-ione) if (info /= psb_success_) then info=psb_err_from_subroutine_ @@ -269,7 +264,7 @@ Subroutine psb_scdbldext(a,desc_a,novr,desc_ov,info, extype) end if orig_ovr(cntov_o)=proc orig_ovr(cntov_o+1)=1 - orig_ovr(cntov_o+2)=gidx + orig_ovr(cntov_o+2)=idx orig_ovr(cntov_o+3)=-1 cntov_o=cntov_o+3 end Do @@ -356,12 +351,6 @@ Subroutine psb_scdbldext(a,desc_a,novr,desc_ov,info, extype) end If idx = halo(counter+psb_elem_recv_+j) - call desc_ov%l2g(idx,gidx,info) - If (gidx < 0) then - info=-3 - call psb_errpush(info,name) - goto 9999 - endif call psb_ensure_size((counter_o+3),tmp_ovr_idx,info,pad=-ione) if (info /= psb_success_) then info=psb_err_from_subroutine_ @@ -371,7 +360,7 @@ Subroutine psb_scdbldext(a,desc_a,novr,desc_ov,info, extype) tmp_ovr_idx(counter_o) = proc tmp_ovr_idx(counter_o+1) = 1 - tmp_ovr_idx(counter_o+2) = gidx + tmp_ovr_idx(counter_o+2) = idx tmp_ovr_idx(counter_o+3) = -1 counter_o=counter_o+3 call psb_ensure_size((counter_h+3),tmp_halo,info,pad=-ione) @@ -400,12 +389,6 @@ Subroutine psb_scdbldext(a,desc_a,novr,desc_ov,info, extype) Do j=0,n_elem_send-1 idx = halo(counter+psb_elem_send_+j) - call desc_ov%l2g(idx,gidx,info) - If (gidx < 0) then - info=-3 - call psb_errpush(info,name) - goto 9999 - endif call psb_ensure_size((counter_o+3),tmp_ovr_idx,info,pad=-ione) if (info /= psb_success_) then info=psb_err_from_subroutine_ @@ -415,7 +398,7 @@ Subroutine psb_scdbldext(a,desc_a,novr,desc_ov,info, extype) tmp_ovr_idx(counter_o) = proc tmp_ovr_idx(counter_o+1) = 1 - tmp_ovr_idx(counter_o+2) = gidx + tmp_ovr_idx(counter_o+2) = idx tmp_ovr_idx(counter_o+3) = -1 counter_o=counter_o+3 @@ -599,7 +582,7 @@ Subroutine psb_scdbldext(a,desc_a,novr,desc_ov,info, extype) write(debug_unit,*) me,' ',trim(name),':Calling Crea_index' end if - call psi_crea_index(desc_ov,t_halo_in,t_halo_out,.false.,& + call psi_crea_index(desc_ov,t_halo_in,t_halo_out,& & nxch,nsnd,nrcv,info) if (debug_level >= psb_debug_outer_) then diff --git a/base/tools/psb_zcdbldext.F90 b/base/tools/psb_zcdbldext.F90 index 355d540c..e967190d 100644 --- a/base/tools/psb_zcdbldext.F90 +++ b/base/tools/psb_zcdbldext.F90 @@ -84,7 +84,8 @@ Subroutine psb_zcdbldext(a,desc_a,novr,desc_ov,info, extype) integer(psb_ipk_) :: i, j, err_act,m,& & lovr, lworks,lworkr, n_row,n_col, n_col_prev, & & index_dim,elem_dim, l_tmp_ovr_idx,l_tmp_halo, nztot,nhalo - integer(psb_ipk_) :: counter,counter_h, counter_o, counter_e,idx,gidx,proc,n_elem_recv,& + integer(psb_ipk_) :: counter,counter_h, counter_o, counter_e,& + & idx,proc,n_elem_recv,& & n_elem_send,tot_recv,tot_elem,cntov_o,& & counter_t,n_elem,i_ovr,jj,proc_id,isz, & & idxr, idxs, iszr, iszs, nxch, nsnd, nrcv,lidx, extype_ @@ -255,12 +256,6 @@ Subroutine psb_zcdbldext(a,desc_a,novr,desc_ov,info, extype) Do j=0,n_elem_recv-1 idx = ovrlap(counter+psb_elem_recv_+j) - call desc_ov%indxmap%l2g(idx,gidx,info) - If (gidx < 0) then - info=-3 - call psb_errpush(info,name) - goto 9999 - endif call psb_ensure_size((cntov_o+3),orig_ovr,info,pad=-ione) if (info /= psb_success_) then info=psb_err_from_subroutine_ @@ -269,7 +264,7 @@ Subroutine psb_zcdbldext(a,desc_a,novr,desc_ov,info, extype) end if orig_ovr(cntov_o)=proc orig_ovr(cntov_o+1)=1 - orig_ovr(cntov_o+2)=gidx + orig_ovr(cntov_o+2)=idx orig_ovr(cntov_o+3)=-1 cntov_o=cntov_o+3 end Do @@ -356,12 +351,6 @@ Subroutine psb_zcdbldext(a,desc_a,novr,desc_ov,info, extype) end If idx = halo(counter+psb_elem_recv_+j) - call desc_ov%l2g(idx,gidx,info) - If (gidx < 0) then - info=-3 - call psb_errpush(info,name) - goto 9999 - endif call psb_ensure_size((counter_o+3),tmp_ovr_idx,info,pad=-ione) if (info /= psb_success_) then info=psb_err_from_subroutine_ @@ -371,7 +360,7 @@ Subroutine psb_zcdbldext(a,desc_a,novr,desc_ov,info, extype) tmp_ovr_idx(counter_o) = proc tmp_ovr_idx(counter_o+1) = 1 - tmp_ovr_idx(counter_o+2) = gidx + tmp_ovr_idx(counter_o+2) = idx tmp_ovr_idx(counter_o+3) = -1 counter_o=counter_o+3 call psb_ensure_size((counter_h+3),tmp_halo,info,pad=-ione) @@ -400,12 +389,6 @@ Subroutine psb_zcdbldext(a,desc_a,novr,desc_ov,info, extype) Do j=0,n_elem_send-1 idx = halo(counter+psb_elem_send_+j) - call desc_ov%l2g(idx,gidx,info) - If (gidx < 0) then - info=-3 - call psb_errpush(info,name) - goto 9999 - endif call psb_ensure_size((counter_o+3),tmp_ovr_idx,info,pad=-ione) if (info /= psb_success_) then info=psb_err_from_subroutine_ @@ -415,7 +398,7 @@ Subroutine psb_zcdbldext(a,desc_a,novr,desc_ov,info, extype) tmp_ovr_idx(counter_o) = proc tmp_ovr_idx(counter_o+1) = 1 - tmp_ovr_idx(counter_o+2) = gidx + tmp_ovr_idx(counter_o+2) = idx tmp_ovr_idx(counter_o+3) = -1 counter_o=counter_o+3 @@ -599,7 +582,7 @@ Subroutine psb_zcdbldext(a,desc_a,novr,desc_ov,info, extype) write(debug_unit,*) me,' ',trim(name),':Calling Crea_index' end if - call psi_crea_index(desc_ov,t_halo_in,t_halo_out,.false.,& + call psi_crea_index(desc_ov,t_halo_in,t_halo_out,& & nxch,nsnd,nrcv,info) if (debug_level >= psb_debug_outer_) then diff --git a/test/pargen/runs/ppde.inp b/test/pargen/runs/ppde.inp index 5ae8f8db..4a1e7ab3 100644 --- a/test/pargen/runs/ppde.inp +++ b/test/pargen/runs/ppde.inp @@ -4,8 +4,8 @@ BJAC Preconditioner NONE DIAG BJAC CSR Storage format for matrix A: CSR COO 040 Domain size (acutal system is this**3 (pde3d) or **2 (pde2d) ) 2 Stopping criterion 1 2 -1000 MAXIT --1 ITRACE +0100 MAXIT +01 ITRACE 002 IRST restart for RGMRES and BiCGSTABL From eaaa701c2edb3f0aae929101ebed6500a7ba996e Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 20 Apr 2018 15:13:36 +0100 Subject: [PATCH 2/7] New interface for methods with global reductions. --- base/modules/psblas/psb_c_psblas_mod.F90 | 115 ++++++++++++++--------- base/modules/psblas/psb_d_psblas_mod.F90 | 115 ++++++++++++++--------- base/modules/psblas/psb_s_psblas_mod.F90 | 115 ++++++++++++++--------- base/modules/psblas/psb_z_psblas_mod.F90 | 115 ++++++++++++++--------- base/psblas/psb_camax.f90 | 61 +++++++++--- base/psblas/psb_casum.f90 | 58 ++++++++++-- base/psblas/psb_cdot.f90 | 72 +++++++++++--- base/psblas/psb_cnrm2.f90 | 72 +++++++++----- base/psblas/psb_cnrmi.f90 | 12 ++- base/psblas/psb_cspnrm1.f90 | 12 ++- base/psblas/psb_damax.f90 | 61 +++++++++--- base/psblas/psb_dasum.f90 | 58 ++++++++++-- base/psblas/psb_ddot.f90 | 72 +++++++++++--- base/psblas/psb_dnrm2.f90 | 72 +++++++++----- base/psblas/psb_dnrmi.f90 | 12 ++- base/psblas/psb_dspnrm1.f90 | 12 ++- base/psblas/psb_samax.f90 | 61 +++++++++--- base/psblas/psb_sasum.f90 | 58 ++++++++++-- base/psblas/psb_sdot.f90 | 72 +++++++++++--- base/psblas/psb_snrm2.f90 | 72 +++++++++----- base/psblas/psb_snrmi.f90 | 12 ++- base/psblas/psb_sspnrm1.f90 | 12 ++- base/psblas/psb_zamax.f90 | 61 +++++++++--- base/psblas/psb_zasum.f90 | 58 ++++++++++-- base/psblas/psb_zdot.f90 | 72 +++++++++++--- base/psblas/psb_znrm2.f90 | 72 +++++++++----- base/psblas/psb_znrmi.f90 | 12 ++- base/psblas/psb_zspnrm1.f90 | 12 ++- 28 files changed, 1172 insertions(+), 436 deletions(-) diff --git a/base/modules/psblas/psb_c_psblas_mod.F90 b/base/modules/psblas/psb_c_psblas_mod.F90 index 22a1d82e..53271ea9 100644 --- a/base/modules/psblas/psb_c_psblas_mod.F90 +++ b/base/modules/psblas/psb_c_psblas_mod.F90 @@ -35,50 +35,55 @@ module psb_c_psblas_mod use psb_c_mat_mod, only : psb_cspmat_type interface psb_gedot - function psb_cdot_vect(x, y, desc_a,info) result(res) + function psb_cdot_vect(x, y, desc_a,info,global) result(res) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type complex(psb_spk_) :: res type(psb_c_vect_type), intent(inout) :: x, y type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_cdot_vect - function psb_cdotv(x, y, desc_a,info) + function psb_cdotv(x, y, desc_a,info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type complex(psb_spk_) :: psb_cdotv complex(psb_spk_), intent(in) :: x(:), y(:) type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_cdotv - function psb_cdot(x, y, desc_a, info, jx, jy) + function psb_cdot(x, y, desc_a, info, jx, jy,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type complex(psb_spk_) :: psb_cdot complex(psb_spk_), intent(in) :: x(:,:), y(:,:) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), optional, intent(in) :: jx, jy - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_cdot end interface interface psb_gedots - subroutine psb_cdotvs(res,x, y, desc_a, info) + subroutine psb_cdotvs(res,x, y, desc_a, info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type complex(psb_spk_), intent(out) :: res complex(psb_spk_), intent(in) :: x(:), y(:) type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_cdotvs - subroutine psb_cmdots(res,x, y, desc_a,info) + subroutine psb_cmdots(res,x, y, desc_a,info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type complex(psb_spk_), intent(out) :: res(:) complex(psb_spk_), intent(in) :: x(:,:), y(:,:) type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_cmdots end interface @@ -91,7 +96,7 @@ module psb_c_psblas_mod type(psb_c_vect_type), intent (inout) :: y complex(psb_spk_), intent (in) :: alpha, beta type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info end subroutine psb_caxpby_vect subroutine psb_caxpbyv(alpha, x, beta, y,& & desc_a, info) @@ -112,35 +117,38 @@ module psb_c_psblas_mod complex(psb_spk_), intent (in) :: alpha, beta type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), optional, intent(in) :: n, jx, jy - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info end subroutine psb_caxpby end interface interface psb_geamax - function psb_camax(x, desc_a, info, jx) + function psb_camax(x, desc_a, info, jx,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type real(psb_spk_) psb_camax complex(psb_spk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), optional, intent (in) :: jx - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_camax - function psb_camaxv(x, desc_a,info) + function psb_camaxv(x, desc_a,info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type real(psb_spk_) psb_camaxv complex(psb_spk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_camaxv - function psb_camax_vect(x, desc_a, info) result(res) + function psb_camax_vect(x, desc_a, info,global) result(res) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type real(psb_spk_) :: res type(psb_c_vect_type), intent (inout) :: x - type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + type(psb_desc_type), intent (in) :: desc_a + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_camax_vect end interface @@ -154,69 +162,76 @@ module psb_c_psblas_mod #endif interface psb_geamaxs - subroutine psb_camaxvs(res,x,desc_a,info) + subroutine psb_camaxvs(res,x,desc_a,info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type real(psb_spk_), intent (out) :: res complex(psb_spk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_camaxvs - subroutine psb_cmamaxs(res,x,desc_a,info,jx) + subroutine psb_cmamaxs(res,x,desc_a,info,jx,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type real(psb_spk_), intent (out) :: res(:) complex(psb_spk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), optional, intent(in) :: jx + logical, intent(in), optional :: global end subroutine psb_cmamaxs end interface interface psb_geasum - function psb_casum_vect(x, desc_a, info) result(res) + function psb_casum_vect(x, desc_a, info,global) result(res) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type real(psb_spk_) :: res type(psb_c_vect_type), intent (inout) :: x - type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + type(psb_desc_type), intent (in) :: desc_a + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_casum_vect - function psb_casum(x, desc_a, info, jx) + function psb_casum(x, desc_a, info, jx,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type real(psb_spk_) psb_casum complex(psb_spk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), optional, intent (in) :: jx - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_casum - function psb_casumv(x, desc_a, info) + function psb_casumv(x, desc_a, info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type real(psb_spk_) psb_casumv complex(psb_spk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_casumv end interface interface psb_geasums - subroutine psb_casumvs(res,x,desc_a,info) + subroutine psb_casumvs(res,x,desc_a,info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type real(psb_spk_), intent (out) :: res complex(psb_spk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_casumvs - subroutine psb_cmasum(res,x,desc_a,info) + subroutine psb_cmasum(res,x,desc_a,info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type real(psb_spk_), intent (out) :: res(:) complex(psb_spk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_cmasum end interface @@ -230,30 +245,33 @@ module psb_c_psblas_mod #endif interface psb_genrm2 - function psb_cnrm2(x, desc_a, info, jx) + function psb_cnrm2(x, desc_a, info, jx,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type real(psb_spk_) psb_cnrm2 complex(psb_spk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), optional, intent (in) :: jx - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_cnrm2 - function psb_cnrm2v(x, desc_a, info) + function psb_cnrm2v(x, desc_a, info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type real(psb_spk_) psb_cnrm2v complex(psb_spk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_cnrm2v - function psb_cnrm2_vect(x, desc_a, info) result(res) + function psb_cnrm2_vect(x, desc_a, info,global) result(res) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type real(psb_spk_) :: res type(psb_c_vect_type), intent (inout) :: x type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_cnrm2_vect end interface @@ -264,25 +282,27 @@ module psb_c_psblas_mod #endif interface psb_genrm2s - subroutine psb_cnrm2vs(res,x,desc_a,info) + subroutine psb_cnrm2vs(res,x,desc_a,info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type real(psb_spk_), intent (out) :: res complex(psb_spk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_cnrm2vs end interface interface psb_spnrmi - function psb_cnrmi(a, desc_a,info) + function psb_cnrmi(a, desc_a,info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type real(psb_spk_) :: psb_cnrmi type(psb_cspmat_type), intent (in) :: a type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_cnrmi end interface @@ -293,13 +313,14 @@ module psb_c_psblas_mod #endif interface psb_spnrm1 - function psb_cspnrm1(a, desc_a,info) + function psb_cspnrm1(a, desc_a,info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_c_vect_type, psb_cspmat_type - real(psb_spk_) :: psb_cspnrm1 + real(psb_spk_) :: psb_cspnrm1 type(psb_cspmat_type), intent (in) :: a - type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + type(psb_desc_type), intent (in) :: desc_a + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_cspnrm1 end interface diff --git a/base/modules/psblas/psb_d_psblas_mod.F90 b/base/modules/psblas/psb_d_psblas_mod.F90 index ece28141..56386f92 100644 --- a/base/modules/psblas/psb_d_psblas_mod.F90 +++ b/base/modules/psblas/psb_d_psblas_mod.F90 @@ -35,50 +35,55 @@ module psb_d_psblas_mod use psb_d_mat_mod, only : psb_dspmat_type interface psb_gedot - function psb_ddot_vect(x, y, desc_a,info) result(res) + function psb_ddot_vect(x, y, desc_a,info,global) result(res) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_) :: res type(psb_d_vect_type), intent(inout) :: x, y type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_ddot_vect - function psb_ddotv(x, y, desc_a,info) + function psb_ddotv(x, y, desc_a,info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_) :: psb_ddotv real(psb_dpk_), intent(in) :: x(:), y(:) type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_ddotv - function psb_ddot(x, y, desc_a, info, jx, jy) + function psb_ddot(x, y, desc_a, info, jx, jy,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_) :: psb_ddot real(psb_dpk_), intent(in) :: x(:,:), y(:,:) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), optional, intent(in) :: jx, jy - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_ddot end interface interface psb_gedots - subroutine psb_ddotvs(res,x, y, desc_a, info) + subroutine psb_ddotvs(res,x, y, desc_a, info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_), intent(out) :: res real(psb_dpk_), intent(in) :: x(:), y(:) type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_ddotvs - subroutine psb_dmdots(res,x, y, desc_a,info) + subroutine psb_dmdots(res,x, y, desc_a,info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_), intent(out) :: res(:) real(psb_dpk_), intent(in) :: x(:,:), y(:,:) type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_dmdots end interface @@ -91,7 +96,7 @@ module psb_d_psblas_mod type(psb_d_vect_type), intent (inout) :: y real(psb_dpk_), intent (in) :: alpha, beta type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info end subroutine psb_daxpby_vect subroutine psb_daxpbyv(alpha, x, beta, y,& & desc_a, info) @@ -112,35 +117,38 @@ module psb_d_psblas_mod real(psb_dpk_), intent (in) :: alpha, beta type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), optional, intent(in) :: n, jx, jy - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info end subroutine psb_daxpby end interface interface psb_geamax - function psb_damax(x, desc_a, info, jx) + function psb_damax(x, desc_a, info, jx,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_) psb_damax real(psb_dpk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), optional, intent (in) :: jx - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_damax - function psb_damaxv(x, desc_a,info) + function psb_damaxv(x, desc_a,info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_) psb_damaxv real(psb_dpk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_damaxv - function psb_damax_vect(x, desc_a, info) result(res) + function psb_damax_vect(x, desc_a, info,global) result(res) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_) :: res type(psb_d_vect_type), intent (inout) :: x - type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + type(psb_desc_type), intent (in) :: desc_a + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_damax_vect end interface @@ -154,69 +162,76 @@ module psb_d_psblas_mod #endif interface psb_geamaxs - subroutine psb_damaxvs(res,x,desc_a,info) + subroutine psb_damaxvs(res,x,desc_a,info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_), intent (out) :: res real(psb_dpk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_damaxvs - subroutine psb_dmamaxs(res,x,desc_a,info,jx) + subroutine psb_dmamaxs(res,x,desc_a,info,jx,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_), intent (out) :: res(:) real(psb_dpk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), optional, intent(in) :: jx + logical, intent(in), optional :: global end subroutine psb_dmamaxs end interface interface psb_geasum - function psb_dasum_vect(x, desc_a, info) result(res) + function psb_dasum_vect(x, desc_a, info,global) result(res) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_) :: res type(psb_d_vect_type), intent (inout) :: x - type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + type(psb_desc_type), intent (in) :: desc_a + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_dasum_vect - function psb_dasum(x, desc_a, info, jx) + function psb_dasum(x, desc_a, info, jx,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_) psb_dasum real(psb_dpk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), optional, intent (in) :: jx - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_dasum - function psb_dasumv(x, desc_a, info) + function psb_dasumv(x, desc_a, info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_) psb_dasumv real(psb_dpk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_dasumv end interface interface psb_geasums - subroutine psb_dasumvs(res,x,desc_a,info) + subroutine psb_dasumvs(res,x,desc_a,info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_), intent (out) :: res real(psb_dpk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_dasumvs - subroutine psb_dmasum(res,x,desc_a,info) + subroutine psb_dmasum(res,x,desc_a,info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_), intent (out) :: res(:) real(psb_dpk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_dmasum end interface @@ -230,30 +245,33 @@ module psb_d_psblas_mod #endif interface psb_genrm2 - function psb_dnrm2(x, desc_a, info, jx) + function psb_dnrm2(x, desc_a, info, jx,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_) psb_dnrm2 real(psb_dpk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), optional, intent (in) :: jx - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_dnrm2 - function psb_dnrm2v(x, desc_a, info) + function psb_dnrm2v(x, desc_a, info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_) psb_dnrm2v real(psb_dpk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_dnrm2v - function psb_dnrm2_vect(x, desc_a, info) result(res) + function psb_dnrm2_vect(x, desc_a, info,global) result(res) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_) :: res type(psb_d_vect_type), intent (inout) :: x type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_dnrm2_vect end interface @@ -264,25 +282,27 @@ module psb_d_psblas_mod #endif interface psb_genrm2s - subroutine psb_dnrm2vs(res,x,desc_a,info) + subroutine psb_dnrm2vs(res,x,desc_a,info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_), intent (out) :: res real(psb_dpk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_dnrm2vs end interface interface psb_spnrmi - function psb_dnrmi(a, desc_a,info) + function psb_dnrmi(a, desc_a,info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type real(psb_dpk_) :: psb_dnrmi type(psb_dspmat_type), intent (in) :: a type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_dnrmi end interface @@ -293,13 +313,14 @@ module psb_d_psblas_mod #endif interface psb_spnrm1 - function psb_dspnrm1(a, desc_a,info) + function psb_dspnrm1(a, desc_a,info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_d_vect_type, psb_dspmat_type - real(psb_dpk_) :: psb_dspnrm1 + real(psb_dpk_) :: psb_dspnrm1 type(psb_dspmat_type), intent (in) :: a - type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + type(psb_desc_type), intent (in) :: desc_a + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_dspnrm1 end interface diff --git a/base/modules/psblas/psb_s_psblas_mod.F90 b/base/modules/psblas/psb_s_psblas_mod.F90 index fae7aaf0..a764bb40 100644 --- a/base/modules/psblas/psb_s_psblas_mod.F90 +++ b/base/modules/psblas/psb_s_psblas_mod.F90 @@ -35,50 +35,55 @@ module psb_s_psblas_mod use psb_s_mat_mod, only : psb_sspmat_type interface psb_gedot - function psb_sdot_vect(x, y, desc_a,info) result(res) + function psb_sdot_vect(x, y, desc_a,info,global) result(res) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_) :: res type(psb_s_vect_type), intent(inout) :: x, y type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_sdot_vect - function psb_sdotv(x, y, desc_a,info) + function psb_sdotv(x, y, desc_a,info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_) :: psb_sdotv real(psb_spk_), intent(in) :: x(:), y(:) type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_sdotv - function psb_sdot(x, y, desc_a, info, jx, jy) + function psb_sdot(x, y, desc_a, info, jx, jy,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_) :: psb_sdot real(psb_spk_), intent(in) :: x(:,:), y(:,:) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), optional, intent(in) :: jx, jy - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_sdot end interface interface psb_gedots - subroutine psb_sdotvs(res,x, y, desc_a, info) + subroutine psb_sdotvs(res,x, y, desc_a, info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_), intent(out) :: res real(psb_spk_), intent(in) :: x(:), y(:) type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_sdotvs - subroutine psb_smdots(res,x, y, desc_a,info) + subroutine psb_smdots(res,x, y, desc_a,info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_), intent(out) :: res(:) real(psb_spk_), intent(in) :: x(:,:), y(:,:) type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_smdots end interface @@ -91,7 +96,7 @@ module psb_s_psblas_mod type(psb_s_vect_type), intent (inout) :: y real(psb_spk_), intent (in) :: alpha, beta type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info end subroutine psb_saxpby_vect subroutine psb_saxpbyv(alpha, x, beta, y,& & desc_a, info) @@ -112,35 +117,38 @@ module psb_s_psblas_mod real(psb_spk_), intent (in) :: alpha, beta type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), optional, intent(in) :: n, jx, jy - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info end subroutine psb_saxpby end interface interface psb_geamax - function psb_samax(x, desc_a, info, jx) + function psb_samax(x, desc_a, info, jx,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_) psb_samax real(psb_spk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), optional, intent (in) :: jx - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_samax - function psb_samaxv(x, desc_a,info) + function psb_samaxv(x, desc_a,info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_) psb_samaxv real(psb_spk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_samaxv - function psb_samax_vect(x, desc_a, info) result(res) + function psb_samax_vect(x, desc_a, info,global) result(res) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_) :: res type(psb_s_vect_type), intent (inout) :: x - type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + type(psb_desc_type), intent (in) :: desc_a + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_samax_vect end interface @@ -154,69 +162,76 @@ module psb_s_psblas_mod #endif interface psb_geamaxs - subroutine psb_samaxvs(res,x,desc_a,info) + subroutine psb_samaxvs(res,x,desc_a,info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_), intent (out) :: res real(psb_spk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_samaxvs - subroutine psb_smamaxs(res,x,desc_a,info,jx) + subroutine psb_smamaxs(res,x,desc_a,info,jx,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_), intent (out) :: res(:) real(psb_spk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), optional, intent(in) :: jx + logical, intent(in), optional :: global end subroutine psb_smamaxs end interface interface psb_geasum - function psb_sasum_vect(x, desc_a, info) result(res) + function psb_sasum_vect(x, desc_a, info,global) result(res) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_) :: res type(psb_s_vect_type), intent (inout) :: x - type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + type(psb_desc_type), intent (in) :: desc_a + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_sasum_vect - function psb_sasum(x, desc_a, info, jx) + function psb_sasum(x, desc_a, info, jx,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_) psb_sasum real(psb_spk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), optional, intent (in) :: jx - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_sasum - function psb_sasumv(x, desc_a, info) + function psb_sasumv(x, desc_a, info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_) psb_sasumv real(psb_spk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_sasumv end interface interface psb_geasums - subroutine psb_sasumvs(res,x,desc_a,info) + subroutine psb_sasumvs(res,x,desc_a,info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_), intent (out) :: res real(psb_spk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_sasumvs - subroutine psb_smasum(res,x,desc_a,info) + subroutine psb_smasum(res,x,desc_a,info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_), intent (out) :: res(:) real(psb_spk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_smasum end interface @@ -230,30 +245,33 @@ module psb_s_psblas_mod #endif interface psb_genrm2 - function psb_snrm2(x, desc_a, info, jx) + function psb_snrm2(x, desc_a, info, jx,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_) psb_snrm2 real(psb_spk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), optional, intent (in) :: jx - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_snrm2 - function psb_snrm2v(x, desc_a, info) + function psb_snrm2v(x, desc_a, info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_) psb_snrm2v real(psb_spk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_snrm2v - function psb_snrm2_vect(x, desc_a, info) result(res) + function psb_snrm2_vect(x, desc_a, info,global) result(res) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_) :: res type(psb_s_vect_type), intent (inout) :: x type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_snrm2_vect end interface @@ -264,25 +282,27 @@ module psb_s_psblas_mod #endif interface psb_genrm2s - subroutine psb_snrm2vs(res,x,desc_a,info) + subroutine psb_snrm2vs(res,x,desc_a,info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_), intent (out) :: res real(psb_spk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_snrm2vs end interface interface psb_spnrmi - function psb_snrmi(a, desc_a,info) + function psb_snrmi(a, desc_a,info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type real(psb_spk_) :: psb_snrmi type(psb_sspmat_type), intent (in) :: a type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_snrmi end interface @@ -293,13 +313,14 @@ module psb_s_psblas_mod #endif interface psb_spnrm1 - function psb_sspnrm1(a, desc_a,info) + function psb_sspnrm1(a, desc_a,info,global) import :: psb_desc_type, psb_spk_, psb_ipk_, & & psb_s_vect_type, psb_sspmat_type - real(psb_spk_) :: psb_sspnrm1 + real(psb_spk_) :: psb_sspnrm1 type(psb_sspmat_type), intent (in) :: a - type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + type(psb_desc_type), intent (in) :: desc_a + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_sspnrm1 end interface diff --git a/base/modules/psblas/psb_z_psblas_mod.F90 b/base/modules/psblas/psb_z_psblas_mod.F90 index b218ce5b..08ee92a7 100644 --- a/base/modules/psblas/psb_z_psblas_mod.F90 +++ b/base/modules/psblas/psb_z_psblas_mod.F90 @@ -35,50 +35,55 @@ module psb_z_psblas_mod use psb_z_mat_mod, only : psb_zspmat_type interface psb_gedot - function psb_zdot_vect(x, y, desc_a,info) result(res) + function psb_zdot_vect(x, y, desc_a,info,global) result(res) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type complex(psb_dpk_) :: res type(psb_z_vect_type), intent(inout) :: x, y type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_zdot_vect - function psb_zdotv(x, y, desc_a,info) + function psb_zdotv(x, y, desc_a,info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type complex(psb_dpk_) :: psb_zdotv complex(psb_dpk_), intent(in) :: x(:), y(:) type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_zdotv - function psb_zdot(x, y, desc_a, info, jx, jy) + function psb_zdot(x, y, desc_a, info, jx, jy,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type complex(psb_dpk_) :: psb_zdot complex(psb_dpk_), intent(in) :: x(:,:), y(:,:) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), optional, intent(in) :: jx, jy - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_zdot end interface interface psb_gedots - subroutine psb_zdotvs(res,x, y, desc_a, info) + subroutine psb_zdotvs(res,x, y, desc_a, info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type complex(psb_dpk_), intent(out) :: res complex(psb_dpk_), intent(in) :: x(:), y(:) type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_zdotvs - subroutine psb_zmdots(res,x, y, desc_a,info) + subroutine psb_zmdots(res,x, y, desc_a,info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type complex(psb_dpk_), intent(out) :: res(:) complex(psb_dpk_), intent(in) :: x(:,:), y(:,:) type(psb_desc_type), intent(in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_zmdots end interface @@ -91,7 +96,7 @@ module psb_z_psblas_mod type(psb_z_vect_type), intent (inout) :: y complex(psb_dpk_), intent (in) :: alpha, beta type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info end subroutine psb_zaxpby_vect subroutine psb_zaxpbyv(alpha, x, beta, y,& & desc_a, info) @@ -112,35 +117,38 @@ module psb_z_psblas_mod complex(psb_dpk_), intent (in) :: alpha, beta type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), optional, intent(in) :: n, jx, jy - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info end subroutine psb_zaxpby end interface interface psb_geamax - function psb_zamax(x, desc_a, info, jx) + function psb_zamax(x, desc_a, info, jx,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type real(psb_dpk_) psb_zamax complex(psb_dpk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), optional, intent (in) :: jx - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_zamax - function psb_zamaxv(x, desc_a,info) + function psb_zamaxv(x, desc_a,info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type real(psb_dpk_) psb_zamaxv complex(psb_dpk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_zamaxv - function psb_zamax_vect(x, desc_a, info) result(res) + function psb_zamax_vect(x, desc_a, info,global) result(res) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type real(psb_dpk_) :: res type(psb_z_vect_type), intent (inout) :: x - type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + type(psb_desc_type), intent (in) :: desc_a + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_zamax_vect end interface @@ -154,69 +162,76 @@ module psb_z_psblas_mod #endif interface psb_geamaxs - subroutine psb_zamaxvs(res,x,desc_a,info) + subroutine psb_zamaxvs(res,x,desc_a,info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type real(psb_dpk_), intent (out) :: res complex(psb_dpk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_zamaxvs - subroutine psb_zmamaxs(res,x,desc_a,info,jx) + subroutine psb_zmamaxs(res,x,desc_a,info,jx,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type real(psb_dpk_), intent (out) :: res(:) complex(psb_dpk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), optional, intent(in) :: jx + logical, intent(in), optional :: global end subroutine psb_zmamaxs end interface interface psb_geasum - function psb_zasum_vect(x, desc_a, info) result(res) + function psb_zasum_vect(x, desc_a, info,global) result(res) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type real(psb_dpk_) :: res type(psb_z_vect_type), intent (inout) :: x - type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + type(psb_desc_type), intent (in) :: desc_a + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_zasum_vect - function psb_zasum(x, desc_a, info, jx) + function psb_zasum(x, desc_a, info, jx,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type real(psb_dpk_) psb_zasum complex(psb_dpk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), optional, intent (in) :: jx - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_zasum - function psb_zasumv(x, desc_a, info) + function psb_zasumv(x, desc_a, info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type real(psb_dpk_) psb_zasumv complex(psb_dpk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_zasumv end interface interface psb_geasums - subroutine psb_zasumvs(res,x,desc_a,info) + subroutine psb_zasumvs(res,x,desc_a,info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type real(psb_dpk_), intent (out) :: res complex(psb_dpk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_zasumvs - subroutine psb_zmasum(res,x,desc_a,info) + subroutine psb_zmasum(res,x,desc_a,info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type real(psb_dpk_), intent (out) :: res(:) complex(psb_dpk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_zmasum end interface @@ -230,30 +245,33 @@ module psb_z_psblas_mod #endif interface psb_genrm2 - function psb_znrm2(x, desc_a, info, jx) + function psb_znrm2(x, desc_a, info, jx,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type real(psb_dpk_) psb_znrm2 complex(psb_dpk_), intent (in) :: x(:,:) type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), optional, intent (in) :: jx - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_znrm2 - function psb_znrm2v(x, desc_a, info) + function psb_znrm2v(x, desc_a, info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type real(psb_dpk_) psb_znrm2v complex(psb_dpk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_znrm2v - function psb_znrm2_vect(x, desc_a, info) result(res) + function psb_znrm2_vect(x, desc_a, info,global) result(res) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type real(psb_dpk_) :: res type(psb_z_vect_type), intent (inout) :: x type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_znrm2_vect end interface @@ -264,25 +282,27 @@ module psb_z_psblas_mod #endif interface psb_genrm2s - subroutine psb_znrm2vs(res,x,desc_a,info) + subroutine psb_znrm2vs(res,x,desc_a,info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type real(psb_dpk_), intent (out) :: res complex(psb_dpk_), intent (in) :: x(:) type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end subroutine psb_znrm2vs end interface interface psb_spnrmi - function psb_znrmi(a, desc_a,info) + function psb_znrmi(a, desc_a,info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type real(psb_dpk_) :: psb_znrmi type(psb_zspmat_type), intent (in) :: a type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_znrmi end interface @@ -293,13 +313,14 @@ module psb_z_psblas_mod #endif interface psb_spnrm1 - function psb_zspnrm1(a, desc_a,info) + function psb_zspnrm1(a, desc_a,info,global) import :: psb_desc_type, psb_dpk_, psb_ipk_, & & psb_z_vect_type, psb_zspmat_type - real(psb_dpk_) :: psb_zspnrm1 + real(psb_dpk_) :: psb_zspnrm1 type(psb_zspmat_type), intent (in) :: a - type(psb_desc_type), intent (in) :: desc_a - integer(psb_ipk_), intent(out) :: info + type(psb_desc_type), intent (in) :: desc_a + integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global end function psb_zspnrm1 end interface diff --git a/base/psblas/psb_camax.f90 b/base/psblas/psb_camax.f90 index fea7798e..f9a11055 100644 --- a/base/psblas/psb_camax.f90 +++ b/base/psblas/psb_camax.f90 @@ -44,7 +44,7 @@ ! info - integer. Return code ! jx - integer(optional). The column offset. ! -function psb_camax(x,desc_a, info, jx) result(res) +function psb_camax(x,desc_a, info, jx,global) result(res) use psb_base_mod, psb_protect_name => psb_camax implicit none @@ -54,10 +54,12 @@ function psb_camax(x,desc_a, info, jx) result(res) integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), optional, intent(in) :: jx real(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ix, ijx, m, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_camax' @@ -82,6 +84,12 @@ function psb_camax(x,desc_a, info, jx) result(res) ijx = 1 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() ldx = size(x,1) @@ -107,7 +115,7 @@ function psb_camax(x,desc_a, info, jx) result(res) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return @@ -162,7 +170,7 @@ end function psb_camax ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_camaxv (x,desc_a, info) result(res) +function psb_camaxv (x,desc_a, info,global) result(res) use psb_base_mod, psb_protect_name => psb_camaxv implicit none @@ -171,11 +179,12 @@ function psb_camaxv (x,desc_a, info) result(res) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info real(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, jx, ix, m, ldx - + logical :: global_ character(len=20) :: name, ch_err name='psb_camaxv' @@ -193,6 +202,12 @@ function psb_camaxv (x,desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx = 1 @@ -221,7 +236,7 @@ function psb_camaxv (x,desc_a, info) result(res) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return @@ -232,7 +247,7 @@ function psb_camaxv (x,desc_a, info) result(res) end function psb_camaxv -function psb_camax_vect(x, desc_a, info) result(res) +function psb_camax_vect(x, desc_a, info,global) result(res) use psb_penv_mod use psb_serial_mod use psb_desc_mod @@ -245,10 +260,12 @@ function psb_camax_vect(x, desc_a, info) result(res) type(psb_c_vect_type), intent (inout) :: x type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, jx, ix, m + logical :: global_ character(len=20) :: name, ch_err name='psb_camaxv' @@ -271,6 +288,12 @@ function psb_camax_vect(x, desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx = 1 @@ -297,7 +320,7 @@ function psb_camax_vect(x, desc_a, info) result(res) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return @@ -355,7 +378,7 @@ end function psb_camax_vect ! info - integer. Return code ! jx - integer(optional). The column offset. ! -subroutine psb_camaxvs(res,x,desc_a, info) +subroutine psb_camaxvs(res,x,desc_a, info,global) use psb_base_mod, psb_protect_name => psb_camaxvs implicit none @@ -364,10 +387,12 @@ subroutine psb_camaxvs(res,x,desc_a, info) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info real(psb_spk_), intent(out) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ix, ijx, m, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_camaxvs' @@ -385,6 +410,12 @@ subroutine psb_camaxvs(res,x,desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 ijx=1 @@ -412,7 +443,7 @@ subroutine psb_camaxvs(res,x,desc_a, info) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return @@ -466,7 +497,7 @@ end subroutine psb_camaxvs ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -subroutine psb_cmamaxs(res,x,desc_a, info,jx) +subroutine psb_cmamaxs(res,x,desc_a, info,jx,global) use psb_base_mod, psb_protect_name => psb_cmamaxs implicit none @@ -476,10 +507,12 @@ subroutine psb_cmamaxs(res,x,desc_a, info,jx) integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), optional, intent(in) :: jx real(psb_spk_), intent(out) :: res(:) + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ix, ijx, m, ldx, i, k + logical :: global_ character(len=20) :: name, ch_err name='psb_cmamaxs' @@ -503,6 +536,12 @@ subroutine psb_cmamaxs(res,x,desc_a, info,jx) ijx = 1 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() k = min(size(x,2),size(res,1)) ldx = size(x,1) @@ -529,7 +568,7 @@ subroutine psb_cmamaxs(res,x,desc_a, info,jx) end if ! compute global max - call psb_amx(ictxt, res(1:k)) + if (global_) call psb_amx(ictxt, res(1:k)) call psb_erractionrestore(err_act) return diff --git a/base/psblas/psb_casum.f90 b/base/psblas/psb_casum.f90 index bd77453f..c9e29461 100644 --- a/base/psblas/psb_casum.f90 +++ b/base/psblas/psb_casum.f90 @@ -44,7 +44,7 @@ ! info - integer. Return code ! jx - integer(optional). The column offset. ! -function psb_casum (x,desc_a, info, jx) result(res) +function psb_casum (x,desc_a, info, jx,global) result(res) use psb_base_mod, psb_protect_name => psb_casum implicit none @@ -54,10 +54,12 @@ function psb_casum (x,desc_a, info, jx) result(res) integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), optional, intent(in) :: jx real(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, & & err_act, iix, jjx, ix, ijx, m, i, idx, ndm, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_casum' @@ -82,6 +84,12 @@ function psb_casum (x,desc_a, info, jx) result(res) ijx = 1 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() ldx = size(x,1) ! check vector correctness @@ -114,7 +122,7 @@ function psb_casum (x,desc_a, info, jx) result(res) res = szero end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -125,7 +133,7 @@ function psb_casum (x,desc_a, info, jx) result(res) end function psb_casum -function psb_casum_vect(x, desc_a, info) result(res) +function psb_casum_vect(x, desc_a, info,global) result(res) use psb_base_mod, psb_protect_name => psb_casum_vect implicit none @@ -133,10 +141,12 @@ function psb_casum_vect(x, desc_a, info) result(res) type(psb_c_vect_type), intent (inout) :: x type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& - & err_act, iix, jjx, jx, ix, m, imax + & err_act, iix, jjx, jx, ix, m, imax, i, idx, ndm + logical :: global_ character(len=20) :: name, ch_err name='psb_casumv' @@ -160,6 +170,11 @@ function psb_casum_vect(x, desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = 1 jx = 1 @@ -182,12 +197,21 @@ function psb_casum_vect(x, desc_a, info) result(res) ! compute local max if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then res = x%asum(desc_a%get_local_rows()) + if (size(desc_a%ovrlap_elem,1)>0) then + if (x%is_dev()) call x%sync() + ! adjust res because overlapped elements are computed more than once + do i=1,size(desc_a%ovrlap_elem,1) + idx = desc_a%ovrlap_elem(i,1) + ndm = desc_a%ovrlap_elem(i,2) + res = res - (real(ndm-1)/real(ndm))*abs(x%v%v(idx)) + end do + end if else res = szero end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -242,7 +266,7 @@ end function psb_casum_vect ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_casumv(x,desc_a, info) result(res) +function psb_casumv(x,desc_a, info,global) result(res) use psb_base_mod, psb_protect_name => psb_casumv implicit none @@ -251,10 +275,12 @@ function psb_casumv(x,desc_a, info) result(res) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info real(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, jx, ix, m, i, idx, ndm, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_casumv' @@ -271,6 +297,12 @@ function psb_casumv(x,desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx=1 @@ -307,7 +339,7 @@ function psb_casumv(x,desc_a, info) result(res) end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -362,7 +394,7 @@ end function psb_casumv ! info - integer. Return code ! jx - integer(optional). The column offset. ! -subroutine psb_casumvs(res,x,desc_a, info) +subroutine psb_casumvs(res,x,desc_a, info,global) use psb_base_mod, psb_protect_name => psb_casumvs implicit none @@ -371,10 +403,12 @@ subroutine psb_casumvs(res,x,desc_a, info) real(psb_spk_), intent(out) :: res type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ix, jx, m, i, idx, ndm, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_casumvs' @@ -391,6 +425,12 @@ subroutine psb_casumvs(res,x,desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx = 1 @@ -427,7 +467,7 @@ subroutine psb_casumvs(res,x,desc_a, info) end if ! compute global sum - call psb_sum(ictxt,res) + if (global_) call psb_sum(ictxt,res) call psb_erractionrestore(err_act) return diff --git a/base/psblas/psb_cdot.f90 b/base/psblas/psb_cdot.f90 index cf7d5f01..c6d545c6 100644 --- a/base/psblas/psb_cdot.f90 +++ b/base/psblas/psb_cdot.f90 @@ -48,7 +48,7 @@ ! jx - integer(optional). The column offset for sub( X ). ! jy - integer(optional). The column offset for sub( Y ). ! -function psb_cdot_vect(x, y, desc_a,info) result(res) +function psb_cdot_vect(x, y, desc_a,info,global) result(res) use psb_desc_mod use psb_c_base_mat_mod use psb_check_mod @@ -61,10 +61,12 @@ function psb_cdot_vect(x, y, desc_a,info) result(res) type(psb_c_vect_type), intent(inout) :: x, y type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, ijx, iy, ijy, iiy, jjy, i, m, nr + logical :: global_ character(len=20) :: name, ch_err name='psb_cdot_vect' @@ -91,6 +93,11 @@ function psb_cdot_vect(x, y, desc_a,info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = ione ijx = ione @@ -122,17 +129,21 @@ function psb_cdot_vect(x, y, desc_a,info) result(res) res = x%dot(nr,y) ! FIXME ! adjust dot_local because overlapped elements are computed more than once -!!$ do i=1,size(desc_a%ovrlap_elem,1) -!!$ idx = desc_a%ovrlap_elem(i,1) -!!$ ndm = desc_a%ovrlap_elem(i,2) -!!$ dot_local = dot_local - (real(ndm-1)/real(ndm))*(x(idx)*y(idx)) -!!$ end do + if (size(desc_a%ovrlap_elem,1)>0) then + if (x%is_dev()) call x%sync() + if (y%is_dev()) call y%sync() + do i=1,size(desc_a%ovrlap_elem,1) + idx = desc_a%ovrlap_elem(i,1) + ndm = desc_a%ovrlap_elem(i,2) + res = res - (real(ndm-1)/real(ndm))*(x%v%v(idx)*y%v%v(idx)) + end do + end if else res = czero end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -143,7 +154,7 @@ function psb_cdot_vect(x, y, desc_a,info) result(res) end function psb_cdot_vect -function psb_cdot(x, y,desc_a, info, jx, jy) result(res) +function psb_cdot(x, y,desc_a, info, jx, jy,global) result(res) use psb_base_mod, psb_protect_name => psb_cdot implicit none @@ -152,12 +163,14 @@ function psb_cdot(x, y,desc_a, info, jx, jy) result(res) integer(psb_ipk_), intent(in), optional :: jx, jy integer(psb_ipk_), intent(out) :: info complex(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, ijx, iy, ijy, iiy, jjy, i, m, nr, & & lldx, lldy complex(psb_spk_) :: cdotc + logical :: global_ character(len=20) :: name, ch_err name='psb_cdot' @@ -193,6 +206,12 @@ function psb_cdot(x, y,desc_a, info, jx, jy) result(res) goto 9999 end if + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() lldx = size(x,1) lldy = size(y,1) @@ -228,7 +247,7 @@ function psb_cdot(x, y,desc_a, info, jx, jy) result(res) end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -284,7 +303,7 @@ end function psb_cdot ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_cdotv(x, y,desc_a, info) result(res) +function psb_cdotv(x, y,desc_a, info,global) result(res) use psb_base_mod, psb_protect_name => psb_cdotv implicit none @@ -292,11 +311,13 @@ function psb_cdotv(x, y,desc_a, info) result(res) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info complex(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, jx, iy, jy, iiy, jjy, i, m, nr, & & lldx, lldy + logical :: global_ complex(psb_spk_) :: cdotc character(len=20) :: name, ch_err @@ -314,6 +335,12 @@ function psb_cdotv(x, y,desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = ione iy = ione jx = ione @@ -352,7 +379,7 @@ function psb_cdotv(x, y,desc_a, info) result(res) end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) @@ -409,7 +436,7 @@ end function psb_cdotv ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -subroutine psb_cdotvs(res, x, y,desc_a, info) +subroutine psb_cdotvs(res, x, y,desc_a, info,global) use psb_base_mod, psb_protect_name => psb_cdotvs implicit none @@ -417,11 +444,13 @@ subroutine psb_cdotvs(res, x, y,desc_a, info) complex(psb_spk_), intent(out) :: res type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, iy, iiy, jjy, i, m,nr, & & lldx, lldy + logical :: global_ complex(psb_spk_) :: cdotc character(len=20) :: name, ch_err @@ -439,6 +468,12 @@ subroutine psb_cdotvs(res, x, y,desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = ione iy = ione m = desc_a%get_global_rows() @@ -475,7 +510,7 @@ subroutine psb_cdotvs(res, x, y,desc_a, info) end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -532,7 +567,7 @@ end subroutine psb_cdotvs ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -subroutine psb_cmdots(res, x, y, desc_a, info) +subroutine psb_cmdots(res, x, y, desc_a, info,global) use psb_base_mod, psb_protect_name => psb_cmdots implicit none @@ -540,11 +575,13 @@ subroutine psb_cmdots(res, x, y, desc_a, info) complex(psb_spk_), intent(out) :: res(:) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, iy, iiy, jjy, i, m, j, k, nr, & & lldx, lldy + logical :: global_ complex(psb_spk_) :: cdotc character(len=20) :: name, ch_err @@ -562,6 +599,11 @@ subroutine psb_cmdots(res, x, y, desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = ione iy = ione @@ -611,7 +653,7 @@ subroutine psb_cmdots(res, x, y, desc_a, info) ! compute global sum - call psb_sum(ictxt, res(1:k)) + if (global_) call psb_sum(ictxt, res(1:k)) call psb_erractionrestore(err_act) return diff --git a/base/psblas/psb_cnrm2.f90 b/base/psblas/psb_cnrm2.f90 index 893e3843..f54db995 100644 --- a/base/psblas/psb_cnrm2.f90 +++ b/base/psblas/psb_cnrm2.f90 @@ -44,7 +44,7 @@ ! info - integer. Return code ! jx - integer(optional). The column offset for sub( X ). ! -function psb_cnrm2(x, desc_a, info, jx) result(res) +function psb_cnrm2(x, desc_a, info, jx,global) result(res) use psb_desc_mod use psb_check_mod use psb_error_mod @@ -56,10 +56,12 @@ function psb_cnrm2(x, desc_a, info, jx) result(res) integer(psb_ipk_), intent(in), optional :: jx integer(psb_ipk_), intent(out) :: info real(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ndim, ix, ijx, i, m, id, idx, ndm, ldx + logical :: global_ real(psb_spk_) :: scnrm2, dd character(len=20) :: name, ch_err @@ -84,6 +86,12 @@ function psb_cnrm2(x, desc_a, info, jx) result(res) ijx = 1 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() ldx = size(x,1) call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx) @@ -114,7 +122,7 @@ function psb_cnrm2(x, desc_a, info, jx) result(res) res = szero end if - call psb_nrm2(ictxt,res) + if (global_) call psb_nrm2(ictxt,res) call psb_erractionrestore(err_act) return @@ -168,7 +176,7 @@ end function psb_cnrm2 ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_cnrm2v(x, desc_a, info) result(res) +function psb_cnrm2v(x, desc_a, info,global) result(res) use psb_desc_mod use psb_check_mod use psb_error_mod @@ -179,13 +187,13 @@ function psb_cnrm2v(x, desc_a, info) result(res) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info real(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ndim, ix, jx, i, m, id, idx, ndm, ldx + logical :: global_ real(psb_spk_) :: scnrm2, dd - -!!$ external scombnrm2 character(len=20) :: name, ch_err name='psb_cnrm2v' @@ -202,6 +210,11 @@ function psb_cnrm2v(x, desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = 1 jx=1 m = desc_a%get_global_rows() @@ -233,8 +246,7 @@ function psb_cnrm2v(x, desc_a, info) result(res) res = szero end if - call psb_nrm2(ictxt,res) - + if (global_) call psb_nrm2(ictxt,res) call psb_erractionrestore(err_act) return @@ -246,7 +258,7 @@ end function psb_cnrm2v -function psb_cnrm2_vect(x, desc_a, info) result(res) +function psb_cnrm2_vect(x, desc_a, info,global) result(res) use psb_desc_mod use psb_check_mod use psb_error_mod @@ -258,12 +270,13 @@ function psb_cnrm2_vect(x, desc_a, info) result(res) type(psb_c_vect_type), intent (inout) :: x type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ndim, ix, jx, i, m, id, idx, ndm, ldx + logical :: global_ real(psb_spk_) :: snrm2, dd -!!$ external dcombnrm2 character(len=20) :: name, ch_err name='psb_cnrm2v' @@ -286,6 +299,11 @@ function psb_cnrm2_vect(x, desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = 1 jx=1 @@ -307,18 +325,21 @@ function psb_cnrm2_vect(x, desc_a, info) result(res) if (desc_a%get_local_rows() > 0) then ndim = desc_a%get_local_rows() res = x%nrm2(ndim) -!!$ ! adjust because overlapped elements are computed more than once -!!$ do i=1,size(desc_a%ovrlap_elem,1) -!!$ idx = desc_a%ovrlap_elem(i,1) -!!$ ndm = desc_a%ovrlap_elem(i,2) -!!$ dd = dble(ndm-1)/dble(ndm) -!!$ nrm2 = nrm2 * sqrt(done - dd*(abs(x(idx))/nrm2)**2) -!!$ end do - else + ! adjust because overlapped elements are computed more than once + if (size(desc_a%ovrlap_elem,1)>0) then + if (x%is_dev()) call x%sync() + do i=1,size(desc_a%ovrlap_elem,1) + idx = desc_a%ovrlap_elem(i,1) + ndm = desc_a%ovrlap_elem(i,2) + dd = dble(ndm-1)/dble(ndm) + res = res - sqrt(cone - dd*(abs(x%v%v(idx))/res)**2) + end do + end if + else res = szero end if - call psb_nrm2(ictxt,res) + if (global_) call psb_nrm2(ictxt,res) call psb_erractionrestore(err_act) return @@ -329,7 +350,6 @@ function psb_cnrm2_vect(x, desc_a, info) result(res) end function psb_cnrm2_vect - !!$ !!$ Parallel Sparse BLAS version 3.5 !!$ (C) Copyright 2006-2018 @@ -373,7 +393,7 @@ end function psb_cnrm2_vect ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -subroutine psb_cnrm2vs(res, x, desc_a, info) +subroutine psb_cnrm2vs(res, x, desc_a, info,global) use psb_desc_mod use psb_check_mod use psb_error_mod @@ -384,13 +404,13 @@ subroutine psb_cnrm2vs(res, x, desc_a, info) real(psb_spk_), intent(out) :: res type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ndim, ix, jx, i, m, id, idx, ndm, ldx + logical :: global_ real(psb_spk_) :: nrm2, scnrm2, dd - -!!$ external scombnrm2 character(len=20) :: name, ch_err name='psb_cnrm2' @@ -407,6 +427,12 @@ subroutine psb_cnrm2vs(res, x, desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx = 1 m = desc_a%get_global_rows() @@ -439,7 +465,7 @@ subroutine psb_cnrm2vs(res, x, desc_a, info) res = szero end if - call psb_nrm2(ictxt,res) + if (global_) call psb_nrm2(ictxt,res) call psb_erractionrestore(err_act) diff --git a/base/psblas/psb_cnrmi.f90 b/base/psblas/psb_cnrmi.f90 index fced0cbd..9a89a02a 100644 --- a/base/psblas/psb_cnrmi.f90 +++ b/base/psblas/psb_cnrmi.f90 @@ -41,7 +41,7 @@ ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_cnrmi(a,desc_a,info) result(res) +function psb_cnrmi(a,desc_a,info,global) result(res) use psb_base_mod, psb_protect_name => psb_cnrmi implicit none @@ -49,10 +49,12 @@ function psb_cnrmi(a,desc_a,info) result(res) integer(psb_ipk_), intent(out) :: info type(psb_desc_type), intent(in) :: desc_a real(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, n, iia, jja, ia, ja, mdim, ndim, m + logical :: global_ character(len=20) :: name, ch_err name='psb_cnrmi' @@ -69,6 +71,12 @@ function psb_cnrmi(a,desc_a,info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ia = 1 ja = 1 m = desc_a%get_global_rows() @@ -101,7 +109,7 @@ function psb_cnrmi(a,desc_a,info) result(res) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return diff --git a/base/psblas/psb_cspnrm1.f90 b/base/psblas/psb_cspnrm1.f90 index 02a98424..79907295 100644 --- a/base/psblas/psb_cspnrm1.f90 +++ b/base/psblas/psb_cspnrm1.f90 @@ -41,7 +41,7 @@ ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_cspnrm1(a,desc_a,info) result(res) +function psb_cspnrm1(a,desc_a,info,global) result(res) use psb_base_mod, psb_protect_name => psb_cspnrm1 implicit none @@ -49,10 +49,12 @@ function psb_cspnrm1(a,desc_a,info) result(res) integer(psb_ipk_), intent(out) :: info type(psb_desc_type), intent(in) :: desc_a real(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, nr,nc,& & err_act, n, iia, jja, ia, ja, mdim, ndim, m + logical :: global_ character(len=20) :: name, ch_err real(psb_spk_), allocatable :: v(:) @@ -70,6 +72,12 @@ function psb_cspnrm1(a,desc_a,info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ia = 1 ja = 1 m = desc_a%get_global_rows() @@ -119,7 +127,7 @@ function psb_cspnrm1(a,desc_a,info) result(res) res = szero end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return diff --git a/base/psblas/psb_damax.f90 b/base/psblas/psb_damax.f90 index b04e9646..4307ba08 100644 --- a/base/psblas/psb_damax.f90 +++ b/base/psblas/psb_damax.f90 @@ -44,7 +44,7 @@ ! info - integer. Return code ! jx - integer(optional). The column offset. ! -function psb_damax(x,desc_a, info, jx) result(res) +function psb_damax(x,desc_a, info, jx,global) result(res) use psb_base_mod, psb_protect_name => psb_damax implicit none @@ -54,10 +54,12 @@ function psb_damax(x,desc_a, info, jx) result(res) integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), optional, intent(in) :: jx real(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ix, ijx, m, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_damax' @@ -82,6 +84,12 @@ function psb_damax(x,desc_a, info, jx) result(res) ijx = 1 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() ldx = size(x,1) @@ -107,7 +115,7 @@ function psb_damax(x,desc_a, info, jx) result(res) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return @@ -162,7 +170,7 @@ end function psb_damax ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_damaxv (x,desc_a, info) result(res) +function psb_damaxv (x,desc_a, info,global) result(res) use psb_base_mod, psb_protect_name => psb_damaxv implicit none @@ -171,11 +179,12 @@ function psb_damaxv (x,desc_a, info) result(res) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info real(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, jx, ix, m, ldx - + logical :: global_ character(len=20) :: name, ch_err name='psb_damaxv' @@ -193,6 +202,12 @@ function psb_damaxv (x,desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx = 1 @@ -221,7 +236,7 @@ function psb_damaxv (x,desc_a, info) result(res) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return @@ -232,7 +247,7 @@ function psb_damaxv (x,desc_a, info) result(res) end function psb_damaxv -function psb_damax_vect(x, desc_a, info) result(res) +function psb_damax_vect(x, desc_a, info,global) result(res) use psb_penv_mod use psb_serial_mod use psb_desc_mod @@ -245,10 +260,12 @@ function psb_damax_vect(x, desc_a, info) result(res) type(psb_d_vect_type), intent (inout) :: x type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, jx, ix, m + logical :: global_ character(len=20) :: name, ch_err name='psb_damaxv' @@ -271,6 +288,12 @@ function psb_damax_vect(x, desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx = 1 @@ -297,7 +320,7 @@ function psb_damax_vect(x, desc_a, info) result(res) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return @@ -355,7 +378,7 @@ end function psb_damax_vect ! info - integer. Return code ! jx - integer(optional). The column offset. ! -subroutine psb_damaxvs(res,x,desc_a, info) +subroutine psb_damaxvs(res,x,desc_a, info,global) use psb_base_mod, psb_protect_name => psb_damaxvs implicit none @@ -364,10 +387,12 @@ subroutine psb_damaxvs(res,x,desc_a, info) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info real(psb_dpk_), intent(out) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ix, ijx, m, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_damaxvs' @@ -385,6 +410,12 @@ subroutine psb_damaxvs(res,x,desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 ijx=1 @@ -412,7 +443,7 @@ subroutine psb_damaxvs(res,x,desc_a, info) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return @@ -466,7 +497,7 @@ end subroutine psb_damaxvs ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -subroutine psb_dmamaxs(res,x,desc_a, info,jx) +subroutine psb_dmamaxs(res,x,desc_a, info,jx,global) use psb_base_mod, psb_protect_name => psb_dmamaxs implicit none @@ -476,10 +507,12 @@ subroutine psb_dmamaxs(res,x,desc_a, info,jx) integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), optional, intent(in) :: jx real(psb_dpk_), intent(out) :: res(:) + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ix, ijx, m, ldx, i, k + logical :: global_ character(len=20) :: name, ch_err name='psb_dmamaxs' @@ -503,6 +536,12 @@ subroutine psb_dmamaxs(res,x,desc_a, info,jx) ijx = 1 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() k = min(size(x,2),size(res,1)) ldx = size(x,1) @@ -529,7 +568,7 @@ subroutine psb_dmamaxs(res,x,desc_a, info,jx) end if ! compute global max - call psb_amx(ictxt, res(1:k)) + if (global_) call psb_amx(ictxt, res(1:k)) call psb_erractionrestore(err_act) return diff --git a/base/psblas/psb_dasum.f90 b/base/psblas/psb_dasum.f90 index 4871c29f..654df8ef 100644 --- a/base/psblas/psb_dasum.f90 +++ b/base/psblas/psb_dasum.f90 @@ -44,7 +44,7 @@ ! info - integer. Return code ! jx - integer(optional). The column offset. ! -function psb_dasum (x,desc_a, info, jx) result(res) +function psb_dasum (x,desc_a, info, jx,global) result(res) use psb_base_mod, psb_protect_name => psb_dasum implicit none @@ -54,10 +54,12 @@ function psb_dasum (x,desc_a, info, jx) result(res) integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), optional, intent(in) :: jx real(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, & & err_act, iix, jjx, ix, ijx, m, i, idx, ndm, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_dasum' @@ -82,6 +84,12 @@ function psb_dasum (x,desc_a, info, jx) result(res) ijx = 1 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() ldx = size(x,1) ! check vector correctness @@ -114,7 +122,7 @@ function psb_dasum (x,desc_a, info, jx) result(res) res = dzero end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -125,7 +133,7 @@ function psb_dasum (x,desc_a, info, jx) result(res) end function psb_dasum -function psb_dasum_vect(x, desc_a, info) result(res) +function psb_dasum_vect(x, desc_a, info,global) result(res) use psb_base_mod, psb_protect_name => psb_dasum_vect implicit none @@ -133,10 +141,12 @@ function psb_dasum_vect(x, desc_a, info) result(res) type(psb_d_vect_type), intent (inout) :: x type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& - & err_act, iix, jjx, jx, ix, m, imax + & err_act, iix, jjx, jx, ix, m, imax, i, idx, ndm + logical :: global_ character(len=20) :: name, ch_err name='psb_dasumv' @@ -160,6 +170,11 @@ function psb_dasum_vect(x, desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = 1 jx = 1 @@ -182,12 +197,21 @@ function psb_dasum_vect(x, desc_a, info) result(res) ! compute local max if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then res = x%asum(desc_a%get_local_rows()) + if (size(desc_a%ovrlap_elem,1)>0) then + if (x%is_dev()) call x%sync() + ! adjust res because overlapped elements are computed more than once + do i=1,size(desc_a%ovrlap_elem,1) + idx = desc_a%ovrlap_elem(i,1) + ndm = desc_a%ovrlap_elem(i,2) + res = res - (real(ndm-1)/real(ndm))*abs(x%v%v(idx)) + end do + end if else res = dzero end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -242,7 +266,7 @@ end function psb_dasum_vect ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_dasumv(x,desc_a, info) result(res) +function psb_dasumv(x,desc_a, info,global) result(res) use psb_base_mod, psb_protect_name => psb_dasumv implicit none @@ -251,10 +275,12 @@ function psb_dasumv(x,desc_a, info) result(res) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info real(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, jx, ix, m, i, idx, ndm, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_dasumv' @@ -271,6 +297,12 @@ function psb_dasumv(x,desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx=1 @@ -307,7 +339,7 @@ function psb_dasumv(x,desc_a, info) result(res) end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -362,7 +394,7 @@ end function psb_dasumv ! info - integer. Return code ! jx - integer(optional). The column offset. ! -subroutine psb_dasumvs(res,x,desc_a, info) +subroutine psb_dasumvs(res,x,desc_a, info,global) use psb_base_mod, psb_protect_name => psb_dasumvs implicit none @@ -371,10 +403,12 @@ subroutine psb_dasumvs(res,x,desc_a, info) real(psb_dpk_), intent(out) :: res type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ix, jx, m, i, idx, ndm, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_dasumvs' @@ -391,6 +425,12 @@ subroutine psb_dasumvs(res,x,desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx = 1 @@ -427,7 +467,7 @@ subroutine psb_dasumvs(res,x,desc_a, info) end if ! compute global sum - call psb_sum(ictxt,res) + if (global_) call psb_sum(ictxt,res) call psb_erractionrestore(err_act) return diff --git a/base/psblas/psb_ddot.f90 b/base/psblas/psb_ddot.f90 index 2a2b00f3..a679003f 100644 --- a/base/psblas/psb_ddot.f90 +++ b/base/psblas/psb_ddot.f90 @@ -48,7 +48,7 @@ ! jx - integer(optional). The column offset for sub( X ). ! jy - integer(optional). The column offset for sub( Y ). ! -function psb_ddot_vect(x, y, desc_a,info) result(res) +function psb_ddot_vect(x, y, desc_a,info,global) result(res) use psb_desc_mod use psb_d_base_mat_mod use psb_check_mod @@ -61,10 +61,12 @@ function psb_ddot_vect(x, y, desc_a,info) result(res) type(psb_d_vect_type), intent(inout) :: x, y type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, ijx, iy, ijy, iiy, jjy, i, m, nr + logical :: global_ character(len=20) :: name, ch_err name='psb_ddot_vect' @@ -91,6 +93,11 @@ function psb_ddot_vect(x, y, desc_a,info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = ione ijx = ione @@ -122,17 +129,21 @@ function psb_ddot_vect(x, y, desc_a,info) result(res) res = x%dot(nr,y) ! FIXME ! adjust dot_local because overlapped elements are computed more than once -!!$ do i=1,size(desc_a%ovrlap_elem,1) -!!$ idx = desc_a%ovrlap_elem(i,1) -!!$ ndm = desc_a%ovrlap_elem(i,2) -!!$ dot_local = dot_local - (real(ndm-1)/real(ndm))*(x(idx)*y(idx)) -!!$ end do + if (size(desc_a%ovrlap_elem,1)>0) then + if (x%is_dev()) call x%sync() + if (y%is_dev()) call y%sync() + do i=1,size(desc_a%ovrlap_elem,1) + idx = desc_a%ovrlap_elem(i,1) + ndm = desc_a%ovrlap_elem(i,2) + res = res - (real(ndm-1)/real(ndm))*(x%v%v(idx)*y%v%v(idx)) + end do + end if else res = dzero end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -143,7 +154,7 @@ function psb_ddot_vect(x, y, desc_a,info) result(res) end function psb_ddot_vect -function psb_ddot(x, y,desc_a, info, jx, jy) result(res) +function psb_ddot(x, y,desc_a, info, jx, jy,global) result(res) use psb_base_mod, psb_protect_name => psb_ddot implicit none @@ -152,12 +163,14 @@ function psb_ddot(x, y,desc_a, info, jx, jy) result(res) integer(psb_ipk_), intent(in), optional :: jx, jy integer(psb_ipk_), intent(out) :: info real(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, ijx, iy, ijy, iiy, jjy, i, m, nr, & & lldx, lldy real(psb_dpk_) :: ddot + logical :: global_ character(len=20) :: name, ch_err name='psb_ddot' @@ -193,6 +206,12 @@ function psb_ddot(x, y,desc_a, info, jx, jy) result(res) goto 9999 end if + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() lldx = size(x,1) lldy = size(y,1) @@ -228,7 +247,7 @@ function psb_ddot(x, y,desc_a, info, jx, jy) result(res) end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -284,7 +303,7 @@ end function psb_ddot ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_ddotv(x, y,desc_a, info) result(res) +function psb_ddotv(x, y,desc_a, info,global) result(res) use psb_base_mod, psb_protect_name => psb_ddotv implicit none @@ -292,11 +311,13 @@ function psb_ddotv(x, y,desc_a, info) result(res) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info real(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, jx, iy, jy, iiy, jjy, i, m, nr, & & lldx, lldy + logical :: global_ real(psb_dpk_) :: ddot character(len=20) :: name, ch_err @@ -314,6 +335,12 @@ function psb_ddotv(x, y,desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = ione iy = ione jx = ione @@ -352,7 +379,7 @@ function psb_ddotv(x, y,desc_a, info) result(res) end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) @@ -409,7 +436,7 @@ end function psb_ddotv ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -subroutine psb_ddotvs(res, x, y,desc_a, info) +subroutine psb_ddotvs(res, x, y,desc_a, info,global) use psb_base_mod, psb_protect_name => psb_ddotvs implicit none @@ -417,11 +444,13 @@ subroutine psb_ddotvs(res, x, y,desc_a, info) real(psb_dpk_), intent(out) :: res type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, iy, iiy, jjy, i, m,nr, & & lldx, lldy + logical :: global_ real(psb_dpk_) :: ddot character(len=20) :: name, ch_err @@ -439,6 +468,12 @@ subroutine psb_ddotvs(res, x, y,desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = ione iy = ione m = desc_a%get_global_rows() @@ -475,7 +510,7 @@ subroutine psb_ddotvs(res, x, y,desc_a, info) end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -532,7 +567,7 @@ end subroutine psb_ddotvs ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -subroutine psb_dmdots(res, x, y, desc_a, info) +subroutine psb_dmdots(res, x, y, desc_a, info,global) use psb_base_mod, psb_protect_name => psb_dmdots implicit none @@ -540,11 +575,13 @@ subroutine psb_dmdots(res, x, y, desc_a, info) real(psb_dpk_), intent(out) :: res(:) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, iy, iiy, jjy, i, m, j, k, nr, & & lldx, lldy + logical :: global_ real(psb_dpk_) :: ddot character(len=20) :: name, ch_err @@ -562,6 +599,11 @@ subroutine psb_dmdots(res, x, y, desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = ione iy = ione @@ -611,7 +653,7 @@ subroutine psb_dmdots(res, x, y, desc_a, info) ! compute global sum - call psb_sum(ictxt, res(1:k)) + if (global_) call psb_sum(ictxt, res(1:k)) call psb_erractionrestore(err_act) return diff --git a/base/psblas/psb_dnrm2.f90 b/base/psblas/psb_dnrm2.f90 index 14e83d00..66eeca93 100644 --- a/base/psblas/psb_dnrm2.f90 +++ b/base/psblas/psb_dnrm2.f90 @@ -44,7 +44,7 @@ ! info - integer. Return code ! jx - integer(optional). The column offset for sub( X ). ! -function psb_dnrm2(x, desc_a, info, jx) result(res) +function psb_dnrm2(x, desc_a, info, jx,global) result(res) use psb_desc_mod use psb_check_mod use psb_error_mod @@ -56,10 +56,12 @@ function psb_dnrm2(x, desc_a, info, jx) result(res) integer(psb_ipk_), intent(in), optional :: jx integer(psb_ipk_), intent(out) :: info real(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ndim, ix, ijx, i, m, id, idx, ndm, ldx + logical :: global_ real(psb_dpk_) :: dnrm2, dd character(len=20) :: name, ch_err @@ -84,6 +86,12 @@ function psb_dnrm2(x, desc_a, info, jx) result(res) ijx = 1 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() ldx = size(x,1) call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx) @@ -114,7 +122,7 @@ function psb_dnrm2(x, desc_a, info, jx) result(res) res = dzero end if - call psb_nrm2(ictxt,res) + if (global_) call psb_nrm2(ictxt,res) call psb_erractionrestore(err_act) return @@ -168,7 +176,7 @@ end function psb_dnrm2 ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_dnrm2v(x, desc_a, info) result(res) +function psb_dnrm2v(x, desc_a, info,global) result(res) use psb_desc_mod use psb_check_mod use psb_error_mod @@ -179,13 +187,13 @@ function psb_dnrm2v(x, desc_a, info) result(res) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info real(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ndim, ix, jx, i, m, id, idx, ndm, ldx + logical :: global_ real(psb_dpk_) :: dnrm2, dd - -!!$ external scombnrm2 character(len=20) :: name, ch_err name='psb_dnrm2v' @@ -202,6 +210,11 @@ function psb_dnrm2v(x, desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = 1 jx=1 m = desc_a%get_global_rows() @@ -233,8 +246,7 @@ function psb_dnrm2v(x, desc_a, info) result(res) res = dzero end if - call psb_nrm2(ictxt,res) - + if (global_) call psb_nrm2(ictxt,res) call psb_erractionrestore(err_act) return @@ -246,7 +258,7 @@ end function psb_dnrm2v -function psb_dnrm2_vect(x, desc_a, info) result(res) +function psb_dnrm2_vect(x, desc_a, info,global) result(res) use psb_desc_mod use psb_check_mod use psb_error_mod @@ -258,12 +270,13 @@ function psb_dnrm2_vect(x, desc_a, info) result(res) type(psb_d_vect_type), intent (inout) :: x type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ndim, ix, jx, i, m, id, idx, ndm, ldx + logical :: global_ real(psb_dpk_) :: snrm2, dd -!!$ external dcombnrm2 character(len=20) :: name, ch_err name='psb_dnrm2v' @@ -286,6 +299,11 @@ function psb_dnrm2_vect(x, desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = 1 jx=1 @@ -307,18 +325,21 @@ function psb_dnrm2_vect(x, desc_a, info) result(res) if (desc_a%get_local_rows() > 0) then ndim = desc_a%get_local_rows() res = x%nrm2(ndim) -!!$ ! adjust because overlapped elements are computed more than once -!!$ do i=1,size(desc_a%ovrlap_elem,1) -!!$ idx = desc_a%ovrlap_elem(i,1) -!!$ ndm = desc_a%ovrlap_elem(i,2) -!!$ dd = dble(ndm-1)/dble(ndm) -!!$ nrm2 = nrm2 * sqrt(done - dd*(abs(x(idx))/nrm2)**2) -!!$ end do - else + ! adjust because overlapped elements are computed more than once + if (size(desc_a%ovrlap_elem,1)>0) then + if (x%is_dev()) call x%sync() + do i=1,size(desc_a%ovrlap_elem,1) + idx = desc_a%ovrlap_elem(i,1) + ndm = desc_a%ovrlap_elem(i,2) + dd = dble(ndm-1)/dble(ndm) + res = res - sqrt(done - dd*(abs(x%v%v(idx))/res)**2) + end do + end if + else res = dzero end if - call psb_nrm2(ictxt,res) + if (global_) call psb_nrm2(ictxt,res) call psb_erractionrestore(err_act) return @@ -329,7 +350,6 @@ function psb_dnrm2_vect(x, desc_a, info) result(res) end function psb_dnrm2_vect - !!$ !!$ Parallel Sparse BLAS version 3.5 !!$ (C) Copyright 2006-2018 @@ -373,7 +393,7 @@ end function psb_dnrm2_vect ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -subroutine psb_dnrm2vs(res, x, desc_a, info) +subroutine psb_dnrm2vs(res, x, desc_a, info,global) use psb_desc_mod use psb_check_mod use psb_error_mod @@ -384,13 +404,13 @@ subroutine psb_dnrm2vs(res, x, desc_a, info) real(psb_dpk_), intent(out) :: res type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ndim, ix, jx, i, m, id, idx, ndm, ldx + logical :: global_ real(psb_dpk_) :: nrm2, dnrm2, dd - -!!$ external scombnrm2 character(len=20) :: name, ch_err name='psb_dnrm2' @@ -407,6 +427,12 @@ subroutine psb_dnrm2vs(res, x, desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx = 1 m = desc_a%get_global_rows() @@ -439,7 +465,7 @@ subroutine psb_dnrm2vs(res, x, desc_a, info) res = dzero end if - call psb_nrm2(ictxt,res) + if (global_) call psb_nrm2(ictxt,res) call psb_erractionrestore(err_act) diff --git a/base/psblas/psb_dnrmi.f90 b/base/psblas/psb_dnrmi.f90 index 1dca687d..9cb0edfe 100644 --- a/base/psblas/psb_dnrmi.f90 +++ b/base/psblas/psb_dnrmi.f90 @@ -41,7 +41,7 @@ ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_dnrmi(a,desc_a,info) result(res) +function psb_dnrmi(a,desc_a,info,global) result(res) use psb_base_mod, psb_protect_name => psb_dnrmi implicit none @@ -49,10 +49,12 @@ function psb_dnrmi(a,desc_a,info) result(res) integer(psb_ipk_), intent(out) :: info type(psb_desc_type), intent(in) :: desc_a real(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, n, iia, jja, ia, ja, mdim, ndim, m + logical :: global_ character(len=20) :: name, ch_err name='psb_dnrmi' @@ -69,6 +71,12 @@ function psb_dnrmi(a,desc_a,info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ia = 1 ja = 1 m = desc_a%get_global_rows() @@ -101,7 +109,7 @@ function psb_dnrmi(a,desc_a,info) result(res) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return diff --git a/base/psblas/psb_dspnrm1.f90 b/base/psblas/psb_dspnrm1.f90 index 9afab5e9..dff6a232 100644 --- a/base/psblas/psb_dspnrm1.f90 +++ b/base/psblas/psb_dspnrm1.f90 @@ -41,7 +41,7 @@ ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_dspnrm1(a,desc_a,info) result(res) +function psb_dspnrm1(a,desc_a,info,global) result(res) use psb_base_mod, psb_protect_name => psb_dspnrm1 implicit none @@ -49,10 +49,12 @@ function psb_dspnrm1(a,desc_a,info) result(res) integer(psb_ipk_), intent(out) :: info type(psb_desc_type), intent(in) :: desc_a real(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, nr,nc,& & err_act, n, iia, jja, ia, ja, mdim, ndim, m + logical :: global_ character(len=20) :: name, ch_err real(psb_dpk_), allocatable :: v(:) @@ -70,6 +72,12 @@ function psb_dspnrm1(a,desc_a,info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ia = 1 ja = 1 m = desc_a%get_global_rows() @@ -119,7 +127,7 @@ function psb_dspnrm1(a,desc_a,info) result(res) res = dzero end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return diff --git a/base/psblas/psb_samax.f90 b/base/psblas/psb_samax.f90 index 456be8c6..a92ceb91 100644 --- a/base/psblas/psb_samax.f90 +++ b/base/psblas/psb_samax.f90 @@ -44,7 +44,7 @@ ! info - integer. Return code ! jx - integer(optional). The column offset. ! -function psb_samax(x,desc_a, info, jx) result(res) +function psb_samax(x,desc_a, info, jx,global) result(res) use psb_base_mod, psb_protect_name => psb_samax implicit none @@ -54,10 +54,12 @@ function psb_samax(x,desc_a, info, jx) result(res) integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), optional, intent(in) :: jx real(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ix, ijx, m, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_samax' @@ -82,6 +84,12 @@ function psb_samax(x,desc_a, info, jx) result(res) ijx = 1 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() ldx = size(x,1) @@ -107,7 +115,7 @@ function psb_samax(x,desc_a, info, jx) result(res) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return @@ -162,7 +170,7 @@ end function psb_samax ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_samaxv (x,desc_a, info) result(res) +function psb_samaxv (x,desc_a, info,global) result(res) use psb_base_mod, psb_protect_name => psb_samaxv implicit none @@ -171,11 +179,12 @@ function psb_samaxv (x,desc_a, info) result(res) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info real(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, jx, ix, m, ldx - + logical :: global_ character(len=20) :: name, ch_err name='psb_samaxv' @@ -193,6 +202,12 @@ function psb_samaxv (x,desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx = 1 @@ -221,7 +236,7 @@ function psb_samaxv (x,desc_a, info) result(res) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return @@ -232,7 +247,7 @@ function psb_samaxv (x,desc_a, info) result(res) end function psb_samaxv -function psb_samax_vect(x, desc_a, info) result(res) +function psb_samax_vect(x, desc_a, info,global) result(res) use psb_penv_mod use psb_serial_mod use psb_desc_mod @@ -245,10 +260,12 @@ function psb_samax_vect(x, desc_a, info) result(res) type(psb_s_vect_type), intent (inout) :: x type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, jx, ix, m + logical :: global_ character(len=20) :: name, ch_err name='psb_samaxv' @@ -271,6 +288,12 @@ function psb_samax_vect(x, desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx = 1 @@ -297,7 +320,7 @@ function psb_samax_vect(x, desc_a, info) result(res) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return @@ -355,7 +378,7 @@ end function psb_samax_vect ! info - integer. Return code ! jx - integer(optional). The column offset. ! -subroutine psb_samaxvs(res,x,desc_a, info) +subroutine psb_samaxvs(res,x,desc_a, info,global) use psb_base_mod, psb_protect_name => psb_samaxvs implicit none @@ -364,10 +387,12 @@ subroutine psb_samaxvs(res,x,desc_a, info) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info real(psb_spk_), intent(out) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ix, ijx, m, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_samaxvs' @@ -385,6 +410,12 @@ subroutine psb_samaxvs(res,x,desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 ijx=1 @@ -412,7 +443,7 @@ subroutine psb_samaxvs(res,x,desc_a, info) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return @@ -466,7 +497,7 @@ end subroutine psb_samaxvs ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -subroutine psb_smamaxs(res,x,desc_a, info,jx) +subroutine psb_smamaxs(res,x,desc_a, info,jx,global) use psb_base_mod, psb_protect_name => psb_smamaxs implicit none @@ -476,10 +507,12 @@ subroutine psb_smamaxs(res,x,desc_a, info,jx) integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), optional, intent(in) :: jx real(psb_spk_), intent(out) :: res(:) + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ix, ijx, m, ldx, i, k + logical :: global_ character(len=20) :: name, ch_err name='psb_smamaxs' @@ -503,6 +536,12 @@ subroutine psb_smamaxs(res,x,desc_a, info,jx) ijx = 1 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() k = min(size(x,2),size(res,1)) ldx = size(x,1) @@ -529,7 +568,7 @@ subroutine psb_smamaxs(res,x,desc_a, info,jx) end if ! compute global max - call psb_amx(ictxt, res(1:k)) + if (global_) call psb_amx(ictxt, res(1:k)) call psb_erractionrestore(err_act) return diff --git a/base/psblas/psb_sasum.f90 b/base/psblas/psb_sasum.f90 index 10a1b987..e4fe548e 100644 --- a/base/psblas/psb_sasum.f90 +++ b/base/psblas/psb_sasum.f90 @@ -44,7 +44,7 @@ ! info - integer. Return code ! jx - integer(optional). The column offset. ! -function psb_sasum (x,desc_a, info, jx) result(res) +function psb_sasum (x,desc_a, info, jx,global) result(res) use psb_base_mod, psb_protect_name => psb_sasum implicit none @@ -54,10 +54,12 @@ function psb_sasum (x,desc_a, info, jx) result(res) integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), optional, intent(in) :: jx real(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, & & err_act, iix, jjx, ix, ijx, m, i, idx, ndm, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_sasum' @@ -82,6 +84,12 @@ function psb_sasum (x,desc_a, info, jx) result(res) ijx = 1 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() ldx = size(x,1) ! check vector correctness @@ -114,7 +122,7 @@ function psb_sasum (x,desc_a, info, jx) result(res) res = szero end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -125,7 +133,7 @@ function psb_sasum (x,desc_a, info, jx) result(res) end function psb_sasum -function psb_sasum_vect(x, desc_a, info) result(res) +function psb_sasum_vect(x, desc_a, info,global) result(res) use psb_base_mod, psb_protect_name => psb_sasum_vect implicit none @@ -133,10 +141,12 @@ function psb_sasum_vect(x, desc_a, info) result(res) type(psb_s_vect_type), intent (inout) :: x type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& - & err_act, iix, jjx, jx, ix, m, imax + & err_act, iix, jjx, jx, ix, m, imax, i, idx, ndm + logical :: global_ character(len=20) :: name, ch_err name='psb_sasumv' @@ -160,6 +170,11 @@ function psb_sasum_vect(x, desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = 1 jx = 1 @@ -182,12 +197,21 @@ function psb_sasum_vect(x, desc_a, info) result(res) ! compute local max if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then res = x%asum(desc_a%get_local_rows()) + if (size(desc_a%ovrlap_elem,1)>0) then + if (x%is_dev()) call x%sync() + ! adjust res because overlapped elements are computed more than once + do i=1,size(desc_a%ovrlap_elem,1) + idx = desc_a%ovrlap_elem(i,1) + ndm = desc_a%ovrlap_elem(i,2) + res = res - (real(ndm-1)/real(ndm))*abs(x%v%v(idx)) + end do + end if else res = szero end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -242,7 +266,7 @@ end function psb_sasum_vect ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_sasumv(x,desc_a, info) result(res) +function psb_sasumv(x,desc_a, info,global) result(res) use psb_base_mod, psb_protect_name => psb_sasumv implicit none @@ -251,10 +275,12 @@ function psb_sasumv(x,desc_a, info) result(res) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info real(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, jx, ix, m, i, idx, ndm, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_sasumv' @@ -271,6 +297,12 @@ function psb_sasumv(x,desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx=1 @@ -307,7 +339,7 @@ function psb_sasumv(x,desc_a, info) result(res) end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -362,7 +394,7 @@ end function psb_sasumv ! info - integer. Return code ! jx - integer(optional). The column offset. ! -subroutine psb_sasumvs(res,x,desc_a, info) +subroutine psb_sasumvs(res,x,desc_a, info,global) use psb_base_mod, psb_protect_name => psb_sasumvs implicit none @@ -371,10 +403,12 @@ subroutine psb_sasumvs(res,x,desc_a, info) real(psb_spk_), intent(out) :: res type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ix, jx, m, i, idx, ndm, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_sasumvs' @@ -391,6 +425,12 @@ subroutine psb_sasumvs(res,x,desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx = 1 @@ -427,7 +467,7 @@ subroutine psb_sasumvs(res,x,desc_a, info) end if ! compute global sum - call psb_sum(ictxt,res) + if (global_) call psb_sum(ictxt,res) call psb_erractionrestore(err_act) return diff --git a/base/psblas/psb_sdot.f90 b/base/psblas/psb_sdot.f90 index 86627f07..5afb520d 100644 --- a/base/psblas/psb_sdot.f90 +++ b/base/psblas/psb_sdot.f90 @@ -48,7 +48,7 @@ ! jx - integer(optional). The column offset for sub( X ). ! jy - integer(optional). The column offset for sub( Y ). ! -function psb_sdot_vect(x, y, desc_a,info) result(res) +function psb_sdot_vect(x, y, desc_a,info,global) result(res) use psb_desc_mod use psb_s_base_mat_mod use psb_check_mod @@ -61,10 +61,12 @@ function psb_sdot_vect(x, y, desc_a,info) result(res) type(psb_s_vect_type), intent(inout) :: x, y type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, ijx, iy, ijy, iiy, jjy, i, m, nr + logical :: global_ character(len=20) :: name, ch_err name='psb_sdot_vect' @@ -91,6 +93,11 @@ function psb_sdot_vect(x, y, desc_a,info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = ione ijx = ione @@ -122,17 +129,21 @@ function psb_sdot_vect(x, y, desc_a,info) result(res) res = x%dot(nr,y) ! FIXME ! adjust dot_local because overlapped elements are computed more than once -!!$ do i=1,size(desc_a%ovrlap_elem,1) -!!$ idx = desc_a%ovrlap_elem(i,1) -!!$ ndm = desc_a%ovrlap_elem(i,2) -!!$ dot_local = dot_local - (real(ndm-1)/real(ndm))*(x(idx)*y(idx)) -!!$ end do + if (size(desc_a%ovrlap_elem,1)>0) then + if (x%is_dev()) call x%sync() + if (y%is_dev()) call y%sync() + do i=1,size(desc_a%ovrlap_elem,1) + idx = desc_a%ovrlap_elem(i,1) + ndm = desc_a%ovrlap_elem(i,2) + res = res - (real(ndm-1)/real(ndm))*(x%v%v(idx)*y%v%v(idx)) + end do + end if else res = szero end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -143,7 +154,7 @@ function psb_sdot_vect(x, y, desc_a,info) result(res) end function psb_sdot_vect -function psb_sdot(x, y,desc_a, info, jx, jy) result(res) +function psb_sdot(x, y,desc_a, info, jx, jy,global) result(res) use psb_base_mod, psb_protect_name => psb_sdot implicit none @@ -152,12 +163,14 @@ function psb_sdot(x, y,desc_a, info, jx, jy) result(res) integer(psb_ipk_), intent(in), optional :: jx, jy integer(psb_ipk_), intent(out) :: info real(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, ijx, iy, ijy, iiy, jjy, i, m, nr, & & lldx, lldy real(psb_spk_) :: sdot + logical :: global_ character(len=20) :: name, ch_err name='psb_sdot' @@ -193,6 +206,12 @@ function psb_sdot(x, y,desc_a, info, jx, jy) result(res) goto 9999 end if + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() lldx = size(x,1) lldy = size(y,1) @@ -228,7 +247,7 @@ function psb_sdot(x, y,desc_a, info, jx, jy) result(res) end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -284,7 +303,7 @@ end function psb_sdot ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_sdotv(x, y,desc_a, info) result(res) +function psb_sdotv(x, y,desc_a, info,global) result(res) use psb_base_mod, psb_protect_name => psb_sdotv implicit none @@ -292,11 +311,13 @@ function psb_sdotv(x, y,desc_a, info) result(res) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info real(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, jx, iy, jy, iiy, jjy, i, m, nr, & & lldx, lldy + logical :: global_ real(psb_spk_) :: sdot character(len=20) :: name, ch_err @@ -314,6 +335,12 @@ function psb_sdotv(x, y,desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = ione iy = ione jx = ione @@ -352,7 +379,7 @@ function psb_sdotv(x, y,desc_a, info) result(res) end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) @@ -409,7 +436,7 @@ end function psb_sdotv ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -subroutine psb_sdotvs(res, x, y,desc_a, info) +subroutine psb_sdotvs(res, x, y,desc_a, info,global) use psb_base_mod, psb_protect_name => psb_sdotvs implicit none @@ -417,11 +444,13 @@ subroutine psb_sdotvs(res, x, y,desc_a, info) real(psb_spk_), intent(out) :: res type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, iy, iiy, jjy, i, m,nr, & & lldx, lldy + logical :: global_ real(psb_spk_) :: sdot character(len=20) :: name, ch_err @@ -439,6 +468,12 @@ subroutine psb_sdotvs(res, x, y,desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = ione iy = ione m = desc_a%get_global_rows() @@ -475,7 +510,7 @@ subroutine psb_sdotvs(res, x, y,desc_a, info) end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -532,7 +567,7 @@ end subroutine psb_sdotvs ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -subroutine psb_smdots(res, x, y, desc_a, info) +subroutine psb_smdots(res, x, y, desc_a, info,global) use psb_base_mod, psb_protect_name => psb_smdots implicit none @@ -540,11 +575,13 @@ subroutine psb_smdots(res, x, y, desc_a, info) real(psb_spk_), intent(out) :: res(:) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, iy, iiy, jjy, i, m, j, k, nr, & & lldx, lldy + logical :: global_ real(psb_spk_) :: sdot character(len=20) :: name, ch_err @@ -562,6 +599,11 @@ subroutine psb_smdots(res, x, y, desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = ione iy = ione @@ -611,7 +653,7 @@ subroutine psb_smdots(res, x, y, desc_a, info) ! compute global sum - call psb_sum(ictxt, res(1:k)) + if (global_) call psb_sum(ictxt, res(1:k)) call psb_erractionrestore(err_act) return diff --git a/base/psblas/psb_snrm2.f90 b/base/psblas/psb_snrm2.f90 index f9a35313..f5ef9cb2 100644 --- a/base/psblas/psb_snrm2.f90 +++ b/base/psblas/psb_snrm2.f90 @@ -44,7 +44,7 @@ ! info - integer. Return code ! jx - integer(optional). The column offset for sub( X ). ! -function psb_snrm2(x, desc_a, info, jx) result(res) +function psb_snrm2(x, desc_a, info, jx,global) result(res) use psb_desc_mod use psb_check_mod use psb_error_mod @@ -56,10 +56,12 @@ function psb_snrm2(x, desc_a, info, jx) result(res) integer(psb_ipk_), intent(in), optional :: jx integer(psb_ipk_), intent(out) :: info real(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ndim, ix, ijx, i, m, id, idx, ndm, ldx + logical :: global_ real(psb_spk_) :: snrm2, dd character(len=20) :: name, ch_err @@ -84,6 +86,12 @@ function psb_snrm2(x, desc_a, info, jx) result(res) ijx = 1 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() ldx = size(x,1) call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx) @@ -114,7 +122,7 @@ function psb_snrm2(x, desc_a, info, jx) result(res) res = szero end if - call psb_nrm2(ictxt,res) + if (global_) call psb_nrm2(ictxt,res) call psb_erractionrestore(err_act) return @@ -168,7 +176,7 @@ end function psb_snrm2 ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_snrm2v(x, desc_a, info) result(res) +function psb_snrm2v(x, desc_a, info,global) result(res) use psb_desc_mod use psb_check_mod use psb_error_mod @@ -179,13 +187,13 @@ function psb_snrm2v(x, desc_a, info) result(res) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info real(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ndim, ix, jx, i, m, id, idx, ndm, ldx + logical :: global_ real(psb_spk_) :: snrm2, dd - -!!$ external scombnrm2 character(len=20) :: name, ch_err name='psb_snrm2v' @@ -202,6 +210,11 @@ function psb_snrm2v(x, desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = 1 jx=1 m = desc_a%get_global_rows() @@ -233,8 +246,7 @@ function psb_snrm2v(x, desc_a, info) result(res) res = szero end if - call psb_nrm2(ictxt,res) - + if (global_) call psb_nrm2(ictxt,res) call psb_erractionrestore(err_act) return @@ -246,7 +258,7 @@ end function psb_snrm2v -function psb_snrm2_vect(x, desc_a, info) result(res) +function psb_snrm2_vect(x, desc_a, info,global) result(res) use psb_desc_mod use psb_check_mod use psb_error_mod @@ -258,12 +270,13 @@ function psb_snrm2_vect(x, desc_a, info) result(res) type(psb_s_vect_type), intent (inout) :: x type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ndim, ix, jx, i, m, id, idx, ndm, ldx + logical :: global_ real(psb_spk_) :: snrm2, dd -!!$ external dcombnrm2 character(len=20) :: name, ch_err name='psb_snrm2v' @@ -286,6 +299,11 @@ function psb_snrm2_vect(x, desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = 1 jx=1 @@ -307,18 +325,21 @@ function psb_snrm2_vect(x, desc_a, info) result(res) if (desc_a%get_local_rows() > 0) then ndim = desc_a%get_local_rows() res = x%nrm2(ndim) -!!$ ! adjust because overlapped elements are computed more than once -!!$ do i=1,size(desc_a%ovrlap_elem,1) -!!$ idx = desc_a%ovrlap_elem(i,1) -!!$ ndm = desc_a%ovrlap_elem(i,2) -!!$ dd = dble(ndm-1)/dble(ndm) -!!$ nrm2 = nrm2 * sqrt(done - dd*(abs(x(idx))/nrm2)**2) -!!$ end do - else + ! adjust because overlapped elements are computed more than once + if (size(desc_a%ovrlap_elem,1)>0) then + if (x%is_dev()) call x%sync() + do i=1,size(desc_a%ovrlap_elem,1) + idx = desc_a%ovrlap_elem(i,1) + ndm = desc_a%ovrlap_elem(i,2) + dd = dble(ndm-1)/dble(ndm) + res = res - sqrt(sone - dd*(abs(x%v%v(idx))/res)**2) + end do + end if + else res = szero end if - call psb_nrm2(ictxt,res) + if (global_) call psb_nrm2(ictxt,res) call psb_erractionrestore(err_act) return @@ -329,7 +350,6 @@ function psb_snrm2_vect(x, desc_a, info) result(res) end function psb_snrm2_vect - !!$ !!$ Parallel Sparse BLAS version 3.5 !!$ (C) Copyright 2006-2018 @@ -373,7 +393,7 @@ end function psb_snrm2_vect ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -subroutine psb_snrm2vs(res, x, desc_a, info) +subroutine psb_snrm2vs(res, x, desc_a, info,global) use psb_desc_mod use psb_check_mod use psb_error_mod @@ -384,13 +404,13 @@ subroutine psb_snrm2vs(res, x, desc_a, info) real(psb_spk_), intent(out) :: res type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ndim, ix, jx, i, m, id, idx, ndm, ldx + logical :: global_ real(psb_spk_) :: nrm2, snrm2, dd - -!!$ external scombnrm2 character(len=20) :: name, ch_err name='psb_snrm2' @@ -407,6 +427,12 @@ subroutine psb_snrm2vs(res, x, desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx = 1 m = desc_a%get_global_rows() @@ -439,7 +465,7 @@ subroutine psb_snrm2vs(res, x, desc_a, info) res = szero end if - call psb_nrm2(ictxt,res) + if (global_) call psb_nrm2(ictxt,res) call psb_erractionrestore(err_act) diff --git a/base/psblas/psb_snrmi.f90 b/base/psblas/psb_snrmi.f90 index eaeaf127..ecabd400 100644 --- a/base/psblas/psb_snrmi.f90 +++ b/base/psblas/psb_snrmi.f90 @@ -41,7 +41,7 @@ ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_snrmi(a,desc_a,info) result(res) +function psb_snrmi(a,desc_a,info,global) result(res) use psb_base_mod, psb_protect_name => psb_snrmi implicit none @@ -49,10 +49,12 @@ function psb_snrmi(a,desc_a,info) result(res) integer(psb_ipk_), intent(out) :: info type(psb_desc_type), intent(in) :: desc_a real(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, n, iia, jja, ia, ja, mdim, ndim, m + logical :: global_ character(len=20) :: name, ch_err name='psb_snrmi' @@ -69,6 +71,12 @@ function psb_snrmi(a,desc_a,info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ia = 1 ja = 1 m = desc_a%get_global_rows() @@ -101,7 +109,7 @@ function psb_snrmi(a,desc_a,info) result(res) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return diff --git a/base/psblas/psb_sspnrm1.f90 b/base/psblas/psb_sspnrm1.f90 index ea7cd618..b8f2a4b7 100644 --- a/base/psblas/psb_sspnrm1.f90 +++ b/base/psblas/psb_sspnrm1.f90 @@ -41,7 +41,7 @@ ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_sspnrm1(a,desc_a,info) result(res) +function psb_sspnrm1(a,desc_a,info,global) result(res) use psb_base_mod, psb_protect_name => psb_sspnrm1 implicit none @@ -49,10 +49,12 @@ function psb_sspnrm1(a,desc_a,info) result(res) integer(psb_ipk_), intent(out) :: info type(psb_desc_type), intent(in) :: desc_a real(psb_spk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, nr,nc,& & err_act, n, iia, jja, ia, ja, mdim, ndim, m + logical :: global_ character(len=20) :: name, ch_err real(psb_spk_), allocatable :: v(:) @@ -70,6 +72,12 @@ function psb_sspnrm1(a,desc_a,info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ia = 1 ja = 1 m = desc_a%get_global_rows() @@ -119,7 +127,7 @@ function psb_sspnrm1(a,desc_a,info) result(res) res = szero end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return diff --git a/base/psblas/psb_zamax.f90 b/base/psblas/psb_zamax.f90 index b2032264..e601725e 100644 --- a/base/psblas/psb_zamax.f90 +++ b/base/psblas/psb_zamax.f90 @@ -44,7 +44,7 @@ ! info - integer. Return code ! jx - integer(optional). The column offset. ! -function psb_zamax(x,desc_a, info, jx) result(res) +function psb_zamax(x,desc_a, info, jx,global) result(res) use psb_base_mod, psb_protect_name => psb_zamax implicit none @@ -54,10 +54,12 @@ function psb_zamax(x,desc_a, info, jx) result(res) integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), optional, intent(in) :: jx real(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ix, ijx, m, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_zamax' @@ -82,6 +84,12 @@ function psb_zamax(x,desc_a, info, jx) result(res) ijx = 1 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() ldx = size(x,1) @@ -107,7 +115,7 @@ function psb_zamax(x,desc_a, info, jx) result(res) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return @@ -162,7 +170,7 @@ end function psb_zamax ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_zamaxv (x,desc_a, info) result(res) +function psb_zamaxv (x,desc_a, info,global) result(res) use psb_base_mod, psb_protect_name => psb_zamaxv implicit none @@ -171,11 +179,12 @@ function psb_zamaxv (x,desc_a, info) result(res) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info real(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, jx, ix, m, ldx - + logical :: global_ character(len=20) :: name, ch_err name='psb_zamaxv' @@ -193,6 +202,12 @@ function psb_zamaxv (x,desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx = 1 @@ -221,7 +236,7 @@ function psb_zamaxv (x,desc_a, info) result(res) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return @@ -232,7 +247,7 @@ function psb_zamaxv (x,desc_a, info) result(res) end function psb_zamaxv -function psb_zamax_vect(x, desc_a, info) result(res) +function psb_zamax_vect(x, desc_a, info,global) result(res) use psb_penv_mod use psb_serial_mod use psb_desc_mod @@ -245,10 +260,12 @@ function psb_zamax_vect(x, desc_a, info) result(res) type(psb_z_vect_type), intent (inout) :: x type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, jx, ix, m + logical :: global_ character(len=20) :: name, ch_err name='psb_zamaxv' @@ -271,6 +288,12 @@ function psb_zamax_vect(x, desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx = 1 @@ -297,7 +320,7 @@ function psb_zamax_vect(x, desc_a, info) result(res) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return @@ -355,7 +378,7 @@ end function psb_zamax_vect ! info - integer. Return code ! jx - integer(optional). The column offset. ! -subroutine psb_zamaxvs(res,x,desc_a, info) +subroutine psb_zamaxvs(res,x,desc_a, info,global) use psb_base_mod, psb_protect_name => psb_zamaxvs implicit none @@ -364,10 +387,12 @@ subroutine psb_zamaxvs(res,x,desc_a, info) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info real(psb_dpk_), intent(out) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ix, ijx, m, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_zamaxvs' @@ -385,6 +410,12 @@ subroutine psb_zamaxvs(res,x,desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 ijx=1 @@ -412,7 +443,7 @@ subroutine psb_zamaxvs(res,x,desc_a, info) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return @@ -466,7 +497,7 @@ end subroutine psb_zamaxvs ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -subroutine psb_zmamaxs(res,x,desc_a, info,jx) +subroutine psb_zmamaxs(res,x,desc_a, info,jx,global) use psb_base_mod, psb_protect_name => psb_zmamaxs implicit none @@ -476,10 +507,12 @@ subroutine psb_zmamaxs(res,x,desc_a, info,jx) integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), optional, intent(in) :: jx real(psb_dpk_), intent(out) :: res(:) + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ix, ijx, m, ldx, i, k + logical :: global_ character(len=20) :: name, ch_err name='psb_zmamaxs' @@ -503,6 +536,12 @@ subroutine psb_zmamaxs(res,x,desc_a, info,jx) ijx = 1 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() k = min(size(x,2),size(res,1)) ldx = size(x,1) @@ -529,7 +568,7 @@ subroutine psb_zmamaxs(res,x,desc_a, info,jx) end if ! compute global max - call psb_amx(ictxt, res(1:k)) + if (global_) call psb_amx(ictxt, res(1:k)) call psb_erractionrestore(err_act) return diff --git a/base/psblas/psb_zasum.f90 b/base/psblas/psb_zasum.f90 index 3b4fadee..9d49881b 100644 --- a/base/psblas/psb_zasum.f90 +++ b/base/psblas/psb_zasum.f90 @@ -44,7 +44,7 @@ ! info - integer. Return code ! jx - integer(optional). The column offset. ! -function psb_zasum (x,desc_a, info, jx) result(res) +function psb_zasum (x,desc_a, info, jx,global) result(res) use psb_base_mod, psb_protect_name => psb_zasum implicit none @@ -54,10 +54,12 @@ function psb_zasum (x,desc_a, info, jx) result(res) integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), optional, intent(in) :: jx real(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, & & err_act, iix, jjx, ix, ijx, m, i, idx, ndm, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_zasum' @@ -82,6 +84,12 @@ function psb_zasum (x,desc_a, info, jx) result(res) ijx = 1 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() ldx = size(x,1) ! check vector correctness @@ -114,7 +122,7 @@ function psb_zasum (x,desc_a, info, jx) result(res) res = dzero end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -125,7 +133,7 @@ function psb_zasum (x,desc_a, info, jx) result(res) end function psb_zasum -function psb_zasum_vect(x, desc_a, info) result(res) +function psb_zasum_vect(x, desc_a, info,global) result(res) use psb_base_mod, psb_protect_name => psb_zasum_vect implicit none @@ -133,10 +141,12 @@ function psb_zasum_vect(x, desc_a, info) result(res) type(psb_z_vect_type), intent (inout) :: x type(psb_desc_type), intent (in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& - & err_act, iix, jjx, jx, ix, m, imax + & err_act, iix, jjx, jx, ix, m, imax, i, idx, ndm + logical :: global_ character(len=20) :: name, ch_err name='psb_zasumv' @@ -160,6 +170,11 @@ function psb_zasum_vect(x, desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = 1 jx = 1 @@ -182,12 +197,21 @@ function psb_zasum_vect(x, desc_a, info) result(res) ! compute local max if ((desc_a%get_local_rows() > 0).and.(m /= 0)) then res = x%asum(desc_a%get_local_rows()) + if (size(desc_a%ovrlap_elem,1)>0) then + if (x%is_dev()) call x%sync() + ! adjust res because overlapped elements are computed more than once + do i=1,size(desc_a%ovrlap_elem,1) + idx = desc_a%ovrlap_elem(i,1) + ndm = desc_a%ovrlap_elem(i,2) + res = res - (real(ndm-1)/real(ndm))*abs(x%v%v(idx)) + end do + end if else res = dzero end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -242,7 +266,7 @@ end function psb_zasum_vect ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_zasumv(x,desc_a, info) result(res) +function psb_zasumv(x,desc_a, info,global) result(res) use psb_base_mod, psb_protect_name => psb_zasumv implicit none @@ -251,10 +275,12 @@ function psb_zasumv(x,desc_a, info) result(res) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info real(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, jx, ix, m, i, idx, ndm, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_zasumv' @@ -271,6 +297,12 @@ function psb_zasumv(x,desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx=1 @@ -307,7 +339,7 @@ function psb_zasumv(x,desc_a, info) result(res) end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -362,7 +394,7 @@ end function psb_zasumv ! info - integer. Return code ! jx - integer(optional). The column offset. ! -subroutine psb_zasumvs(res,x,desc_a, info) +subroutine psb_zasumvs(res,x,desc_a, info,global) use psb_base_mod, psb_protect_name => psb_zasumvs implicit none @@ -371,10 +403,12 @@ subroutine psb_zasumvs(res,x,desc_a, info) real(psb_dpk_), intent(out) :: res type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ix, jx, m, i, idx, ndm, ldx + logical :: global_ character(len=20) :: name, ch_err name='psb_zasumvs' @@ -391,6 +425,12 @@ subroutine psb_zasumvs(res,x,desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx = 1 @@ -427,7 +467,7 @@ subroutine psb_zasumvs(res,x,desc_a, info) end if ! compute global sum - call psb_sum(ictxt,res) + if (global_) call psb_sum(ictxt,res) call psb_erractionrestore(err_act) return diff --git a/base/psblas/psb_zdot.f90 b/base/psblas/psb_zdot.f90 index a9cd1d98..9006a08b 100644 --- a/base/psblas/psb_zdot.f90 +++ b/base/psblas/psb_zdot.f90 @@ -48,7 +48,7 @@ ! jx - integer(optional). The column offset for sub( X ). ! jy - integer(optional). The column offset for sub( Y ). ! -function psb_zdot_vect(x, y, desc_a,info) result(res) +function psb_zdot_vect(x, y, desc_a,info,global) result(res) use psb_desc_mod use psb_z_base_mat_mod use psb_check_mod @@ -61,10 +61,12 @@ function psb_zdot_vect(x, y, desc_a,info) result(res) type(psb_z_vect_type), intent(inout) :: x, y type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, ijx, iy, ijy, iiy, jjy, i, m, nr + logical :: global_ character(len=20) :: name, ch_err name='psb_zdot_vect' @@ -91,6 +93,11 @@ function psb_zdot_vect(x, y, desc_a,info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = ione ijx = ione @@ -122,17 +129,21 @@ function psb_zdot_vect(x, y, desc_a,info) result(res) res = x%dot(nr,y) ! FIXME ! adjust dot_local because overlapped elements are computed more than once -!!$ do i=1,size(desc_a%ovrlap_elem,1) -!!$ idx = desc_a%ovrlap_elem(i,1) -!!$ ndm = desc_a%ovrlap_elem(i,2) -!!$ dot_local = dot_local - (real(ndm-1)/real(ndm))*(x(idx)*y(idx)) -!!$ end do + if (size(desc_a%ovrlap_elem,1)>0) then + if (x%is_dev()) call x%sync() + if (y%is_dev()) call y%sync() + do i=1,size(desc_a%ovrlap_elem,1) + idx = desc_a%ovrlap_elem(i,1) + ndm = desc_a%ovrlap_elem(i,2) + res = res - (real(ndm-1)/real(ndm))*(x%v%v(idx)*y%v%v(idx)) + end do + end if else res = zzero end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -143,7 +154,7 @@ function psb_zdot_vect(x, y, desc_a,info) result(res) end function psb_zdot_vect -function psb_zdot(x, y,desc_a, info, jx, jy) result(res) +function psb_zdot(x, y,desc_a, info, jx, jy,global) result(res) use psb_base_mod, psb_protect_name => psb_zdot implicit none @@ -152,12 +163,14 @@ function psb_zdot(x, y,desc_a, info, jx, jy) result(res) integer(psb_ipk_), intent(in), optional :: jx, jy integer(psb_ipk_), intent(out) :: info complex(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, ijx, iy, ijy, iiy, jjy, i, m, nr, & & lldx, lldy complex(psb_dpk_) :: zdotc + logical :: global_ character(len=20) :: name, ch_err name='psb_zdot' @@ -193,6 +206,12 @@ function psb_zdot(x, y,desc_a, info, jx, jy) result(res) goto 9999 end if + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() lldx = size(x,1) lldy = size(y,1) @@ -228,7 +247,7 @@ function psb_zdot(x, y,desc_a, info, jx, jy) result(res) end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -284,7 +303,7 @@ end function psb_zdot ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_zdotv(x, y,desc_a, info) result(res) +function psb_zdotv(x, y,desc_a, info,global) result(res) use psb_base_mod, psb_protect_name => psb_zdotv implicit none @@ -292,11 +311,13 @@ function psb_zdotv(x, y,desc_a, info) result(res) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info complex(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, jx, iy, jy, iiy, jjy, i, m, nr, & & lldx, lldy + logical :: global_ complex(psb_dpk_) :: zdotc character(len=20) :: name, ch_err @@ -314,6 +335,12 @@ function psb_zdotv(x, y,desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = ione iy = ione jx = ione @@ -352,7 +379,7 @@ function psb_zdotv(x, y,desc_a, info) result(res) end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) @@ -409,7 +436,7 @@ end function psb_zdotv ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -subroutine psb_zdotvs(res, x, y,desc_a, info) +subroutine psb_zdotvs(res, x, y,desc_a, info,global) use psb_base_mod, psb_protect_name => psb_zdotvs implicit none @@ -417,11 +444,13 @@ subroutine psb_zdotvs(res, x, y,desc_a, info) complex(psb_dpk_), intent(out) :: res type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, iy, iiy, jjy, i, m,nr, & & lldx, lldy + logical :: global_ complex(psb_dpk_) :: zdotc character(len=20) :: name, ch_err @@ -439,6 +468,12 @@ subroutine psb_zdotvs(res, x, y,desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = ione iy = ione m = desc_a%get_global_rows() @@ -475,7 +510,7 @@ subroutine psb_zdotvs(res, x, y,desc_a, info) end if ! compute global sum - call psb_sum(ictxt, res) + if (global_) call psb_sum(ictxt, res) call psb_erractionrestore(err_act) return @@ -532,7 +567,7 @@ end subroutine psb_zdotvs ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -subroutine psb_zmdots(res, x, y, desc_a, info) +subroutine psb_zmdots(res, x, y, desc_a, info,global) use psb_base_mod, psb_protect_name => psb_zmdots implicit none @@ -540,11 +575,13 @@ subroutine psb_zmdots(res, x, y, desc_a, info) complex(psb_dpk_), intent(out) :: res(:) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, idx, ndm,& & err_act, iix, jjx, ix, iy, iiy, jjy, i, m, j, k, nr, & & lldx, lldy + logical :: global_ complex(psb_dpk_) :: zdotc character(len=20) :: name, ch_err @@ -562,6 +599,11 @@ subroutine psb_zmdots(res, x, y, desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = ione iy = ione @@ -611,7 +653,7 @@ subroutine psb_zmdots(res, x, y, desc_a, info) ! compute global sum - call psb_sum(ictxt, res(1:k)) + if (global_) call psb_sum(ictxt, res(1:k)) call psb_erractionrestore(err_act) return diff --git a/base/psblas/psb_znrm2.f90 b/base/psblas/psb_znrm2.f90 index 40e2156b..b3fd48df 100644 --- a/base/psblas/psb_znrm2.f90 +++ b/base/psblas/psb_znrm2.f90 @@ -44,7 +44,7 @@ ! info - integer. Return code ! jx - integer(optional). The column offset for sub( X ). ! -function psb_znrm2(x, desc_a, info, jx) result(res) +function psb_znrm2(x, desc_a, info, jx,global) result(res) use psb_desc_mod use psb_check_mod use psb_error_mod @@ -56,10 +56,12 @@ function psb_znrm2(x, desc_a, info, jx) result(res) integer(psb_ipk_), intent(in), optional :: jx integer(psb_ipk_), intent(out) :: info real(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ndim, ix, ijx, i, m, id, idx, ndm, ldx + logical :: global_ real(psb_dpk_) :: dznrm2, dd character(len=20) :: name, ch_err @@ -84,6 +86,12 @@ function psb_znrm2(x, desc_a, info, jx) result(res) ijx = 1 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + m = desc_a%get_global_rows() ldx = size(x,1) call psb_chkvect(m,ione,ldx,ix,ijx,desc_a,info,iix,jjx) @@ -114,7 +122,7 @@ function psb_znrm2(x, desc_a, info, jx) result(res) res = dzero end if - call psb_nrm2(ictxt,res) + if (global_) call psb_nrm2(ictxt,res) call psb_erractionrestore(err_act) return @@ -168,7 +176,7 @@ end function psb_znrm2 ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_znrm2v(x, desc_a, info) result(res) +function psb_znrm2v(x, desc_a, info,global) result(res) use psb_desc_mod use psb_check_mod use psb_error_mod @@ -179,13 +187,13 @@ function psb_znrm2v(x, desc_a, info) result(res) type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info real(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ndim, ix, jx, i, m, id, idx, ndm, ldx + logical :: global_ real(psb_dpk_) :: dznrm2, dd - -!!$ external scombnrm2 character(len=20) :: name, ch_err name='psb_znrm2v' @@ -202,6 +210,11 @@ function psb_znrm2v(x, desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = 1 jx=1 m = desc_a%get_global_rows() @@ -233,8 +246,7 @@ function psb_znrm2v(x, desc_a, info) result(res) res = dzero end if - call psb_nrm2(ictxt,res) - + if (global_) call psb_nrm2(ictxt,res) call psb_erractionrestore(err_act) return @@ -246,7 +258,7 @@ end function psb_znrm2v -function psb_znrm2_vect(x, desc_a, info) result(res) +function psb_znrm2_vect(x, desc_a, info,global) result(res) use psb_desc_mod use psb_check_mod use psb_error_mod @@ -258,12 +270,13 @@ function psb_znrm2_vect(x, desc_a, info) result(res) type(psb_z_vect_type), intent (inout) :: x type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ndim, ix, jx, i, m, id, idx, ndm, ldx + logical :: global_ real(psb_dpk_) :: snrm2, dd -!!$ external dcombnrm2 character(len=20) :: name, ch_err name='psb_znrm2v' @@ -286,6 +299,11 @@ function psb_znrm2_vect(x, desc_a, info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if ix = 1 jx=1 @@ -307,18 +325,21 @@ function psb_znrm2_vect(x, desc_a, info) result(res) if (desc_a%get_local_rows() > 0) then ndim = desc_a%get_local_rows() res = x%nrm2(ndim) -!!$ ! adjust because overlapped elements are computed more than once -!!$ do i=1,size(desc_a%ovrlap_elem,1) -!!$ idx = desc_a%ovrlap_elem(i,1) -!!$ ndm = desc_a%ovrlap_elem(i,2) -!!$ dd = dble(ndm-1)/dble(ndm) -!!$ nrm2 = nrm2 * sqrt(done - dd*(abs(x(idx))/nrm2)**2) -!!$ end do - else + ! adjust because overlapped elements are computed more than once + if (size(desc_a%ovrlap_elem,1)>0) then + if (x%is_dev()) call x%sync() + do i=1,size(desc_a%ovrlap_elem,1) + idx = desc_a%ovrlap_elem(i,1) + ndm = desc_a%ovrlap_elem(i,2) + dd = dble(ndm-1)/dble(ndm) + res = res - sqrt(zone - dd*(abs(x%v%v(idx))/res)**2) + end do + end if + else res = dzero end if - call psb_nrm2(ictxt,res) + if (global_) call psb_nrm2(ictxt,res) call psb_erractionrestore(err_act) return @@ -329,7 +350,6 @@ function psb_znrm2_vect(x, desc_a, info) result(res) end function psb_znrm2_vect - !!$ !!$ Parallel Sparse BLAS version 3.5 !!$ (C) Copyright 2006-2018 @@ -373,7 +393,7 @@ end function psb_znrm2_vect ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -subroutine psb_znrm2vs(res, x, desc_a, info) +subroutine psb_znrm2vs(res, x, desc_a, info,global) use psb_desc_mod use psb_check_mod use psb_error_mod @@ -384,13 +404,13 @@ subroutine psb_znrm2vs(res, x, desc_a, info) real(psb_dpk_), intent(out) :: res type(psb_desc_type), intent(in) :: desc_a integer(psb_ipk_), intent(out) :: info + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, iix, jjx, ndim, ix, jx, i, m, id, idx, ndm, ldx + logical :: global_ real(psb_dpk_) :: nrm2, dznrm2, dd - -!!$ external scombnrm2 character(len=20) :: name, ch_err name='psb_znrm2' @@ -407,6 +427,12 @@ subroutine psb_znrm2vs(res, x, desc_a, info) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ix = 1 jx = 1 m = desc_a%get_global_rows() @@ -439,7 +465,7 @@ subroutine psb_znrm2vs(res, x, desc_a, info) res = dzero end if - call psb_nrm2(ictxt,res) + if (global_) call psb_nrm2(ictxt,res) call psb_erractionrestore(err_act) diff --git a/base/psblas/psb_znrmi.f90 b/base/psblas/psb_znrmi.f90 index c917b784..c0d169b9 100644 --- a/base/psblas/psb_znrmi.f90 +++ b/base/psblas/psb_znrmi.f90 @@ -41,7 +41,7 @@ ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_znrmi(a,desc_a,info) result(res) +function psb_znrmi(a,desc_a,info,global) result(res) use psb_base_mod, psb_protect_name => psb_znrmi implicit none @@ -49,10 +49,12 @@ function psb_znrmi(a,desc_a,info) result(res) integer(psb_ipk_), intent(out) :: info type(psb_desc_type), intent(in) :: desc_a real(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me,& & err_act, n, iia, jja, ia, ja, mdim, ndim, m + logical :: global_ character(len=20) :: name, ch_err name='psb_znrmi' @@ -69,6 +71,12 @@ function psb_znrmi(a,desc_a,info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ia = 1 ja = 1 m = desc_a%get_global_rows() @@ -101,7 +109,7 @@ function psb_znrmi(a,desc_a,info) result(res) end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return diff --git a/base/psblas/psb_zspnrm1.f90 b/base/psblas/psb_zspnrm1.f90 index 19b5164c..95796ff5 100644 --- a/base/psblas/psb_zspnrm1.f90 +++ b/base/psblas/psb_zspnrm1.f90 @@ -41,7 +41,7 @@ ! desc_a - type(psb_desc_type). The communication descriptor. ! info - integer. Return code ! -function psb_zspnrm1(a,desc_a,info) result(res) +function psb_zspnrm1(a,desc_a,info,global) result(res) use psb_base_mod, psb_protect_name => psb_zspnrm1 implicit none @@ -49,10 +49,12 @@ function psb_zspnrm1(a,desc_a,info) result(res) integer(psb_ipk_), intent(out) :: info type(psb_desc_type), intent(in) :: desc_a real(psb_dpk_) :: res + logical, intent(in), optional :: global ! locals integer(psb_ipk_) :: ictxt, np, me, nr,nc,& & err_act, n, iia, jja, ia, ja, mdim, ndim, m + logical :: global_ character(len=20) :: name, ch_err real(psb_dpk_), allocatable :: v(:) @@ -70,6 +72,12 @@ function psb_zspnrm1(a,desc_a,info) result(res) goto 9999 endif + if (present(global)) then + global_ = global + else + global_ = .true. + end if + ia = 1 ja = 1 m = desc_a%get_global_rows() @@ -119,7 +127,7 @@ function psb_zspnrm1(a,desc_a,info) result(res) res = dzero end if ! compute global max - call psb_amx(ictxt, res) + if (global_) call psb_amx(ictxt, res) call psb_erractionrestore(err_act) return From 4a6c0857f18cfbcfdec6bbaf0b0125d0f6fa71c6 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 20 Apr 2018 15:57:26 +0100 Subject: [PATCH 3/7] Updated description of DOT and friends to account for optional GLOBAL var. --- docs/html/footnode.html | 12 +- docs/html/img100.png | Bin 340 -> 175 bytes docs/html/img101.png | Bin 217 -> 336 bytes docs/html/img102.png | Bin 316 -> 486 bytes docs/html/img103.png | Bin 258 -> 310 bytes docs/html/img104.png | Bin 184 -> 340 bytes docs/html/img105.png | Bin 620 -> 217 bytes docs/html/img106.png | Bin 332 -> 316 bytes docs/html/img107.png | Bin 134 -> 258 bytes docs/html/img108.png | Bin 254 -> 184 bytes docs/html/img109.png | Bin 357 -> 620 bytes docs/html/img110.png | Bin 241 -> 332 bytes docs/html/img111.png | Bin 233 -> 134 bytes docs/html/img112.png | Bin 222 -> 254 bytes docs/html/img113.png | Bin 360 -> 357 bytes docs/html/img114.png | Bin 203 -> 241 bytes docs/html/img115.png | Bin 243 -> 233 bytes docs/html/img116.png | Bin 786 -> 222 bytes docs/html/img117.png | Bin 370 -> 360 bytes docs/html/img118.png | Bin 388 -> 203 bytes docs/html/img119.png | Bin 330 -> 243 bytes docs/html/img120.png | Bin 298 -> 786 bytes docs/html/img121.png | Bin 804 -> 370 bytes docs/html/img122.png | Bin 302 -> 388 bytes docs/html/img123.png | Bin 491 -> 330 bytes docs/html/img124.png | Bin 383 -> 298 bytes docs/html/img125.png | Bin 238 -> 804 bytes docs/html/img126.png | Bin 491 -> 302 bytes docs/html/img127.png | Bin 530 -> 491 bytes docs/html/img128.png | Bin 318 -> 383 bytes docs/html/img129.png | Bin 223 -> 238 bytes docs/html/img130.png | Bin 484 -> 491 bytes docs/html/img131.png | Bin 517 -> 530 bytes docs/html/img132.png | Bin 496 -> 318 bytes docs/html/img133.png | Bin 207 -> 223 bytes docs/html/img134.png | Bin 526 -> 484 bytes docs/html/img135.png | Bin 671 -> 517 bytes docs/html/img136.png | Bin 244 -> 496 bytes docs/html/img137.png | Bin 500 -> 0 bytes docs/html/img138.png | Bin 259 -> 244 bytes docs/html/img139.png | Bin 487 -> 0 bytes docs/html/img140.png | Bin 234 -> 207 bytes docs/html/img141.png | Bin 0 -> 526 bytes docs/html/img142.png | Bin 8199 -> 671 bytes docs/html/img143.png | Bin 0 -> 500 bytes docs/html/img144.png | Bin 980 -> 259 bytes docs/html/img145.png | Bin 707 -> 487 bytes docs/html/img146.png | Bin 807 -> 234 bytes docs/html/img147.png | Bin 848 -> 0 bytes docs/html/img148.png | Bin 1036 -> 8199 bytes docs/html/img149.png | Bin 1196 -> 0 bytes docs/html/img150.png | Bin 931 -> 980 bytes docs/html/img151.png | Bin 1001 -> 707 bytes docs/html/img152.png | Bin 1038 -> 807 bytes docs/html/img153.png | Bin 1009 -> 848 bytes docs/html/img154.png | Bin 328 -> 1036 bytes docs/html/img155.png | Bin 403 -> 1196 bytes docs/html/img156.png | Bin 262 -> 931 bytes docs/html/img157.png | Bin 793 -> 1001 bytes docs/html/img158.png | Bin 604 -> 1038 bytes docs/html/img159.png | Bin 591 -> 1009 bytes docs/html/img160.png | Bin 210 -> 328 bytes docs/html/img161.png | Bin 385 -> 403 bytes docs/html/img162.png | Bin 2021 -> 262 bytes docs/html/img163.png | Bin 436 -> 793 bytes docs/html/img164.png | Bin 444 -> 604 bytes docs/html/img165.png | Bin 393 -> 591 bytes docs/html/img166.png | Bin 335 -> 210 bytes docs/html/img167.png | Bin 353 -> 385 bytes docs/html/img168.png | Bin 291 -> 2021 bytes docs/html/img27.png | Bin 645 -> 2504 bytes docs/html/img28.png | Bin 240 -> 645 bytes docs/html/img29.png | Bin 498 -> 240 bytes docs/html/img30.png | Bin 908 -> 498 bytes docs/html/img31.png | Bin 290 -> 908 bytes docs/html/img32.png | Bin 717 -> 290 bytes docs/html/img33.png | Bin 432 -> 2257 bytes docs/html/img34.png | Bin 740 -> 717 bytes docs/html/img35.png | Bin 307 -> 432 bytes docs/html/img36.png | Bin 468 -> 740 bytes docs/html/img37.png | Bin 793 -> 307 bytes docs/html/img38.png | Bin 526 -> 2211 bytes docs/html/img39.png | Bin 540 -> 468 bytes docs/html/img40.png | Bin 316 -> 793 bytes docs/html/img41.png | Bin 574 -> 526 bytes docs/html/img42.png | Bin 405 -> 540 bytes docs/html/img43.png | Bin 440 -> 316 bytes docs/html/img44.png | Bin 485 -> 2264 bytes docs/html/img45.png | Bin 551 -> 574 bytes docs/html/img46.png | Bin 531 -> 405 bytes docs/html/img47.png | Bin 221 -> 440 bytes docs/html/img48.png | Bin 241 -> 485 bytes docs/html/img49.png | Bin 393 -> 551 bytes docs/html/img50.png | Bin 1732 -> 531 bytes docs/html/img51.png | Bin 200 -> 221 bytes docs/html/img52.png | Bin 212 -> 241 bytes docs/html/img53.png | Bin 414 -> 393 bytes docs/html/img54.png | Bin 707 -> 1732 bytes docs/html/img55.png | Bin 222 -> 200 bytes docs/html/img56.png | Bin 1294 -> 212 bytes docs/html/img57.png | Bin 2637 -> 414 bytes docs/html/img58.png | Bin 2518 -> 707 bytes docs/html/img59.png | Bin 311 -> 222 bytes docs/html/img60.png | Bin 230 -> 1294 bytes docs/html/img61.png | Bin 225 -> 2637 bytes docs/html/img62.png | Bin 243 -> 2518 bytes docs/html/img63.png | Bin 1640 -> 311 bytes docs/html/img64.png | Bin 243 -> 230 bytes docs/html/img65.png | Bin 279 -> 225 bytes docs/html/img66.png | Bin 686 -> 243 bytes docs/html/img67.png | Bin 4853 -> 1640 bytes docs/html/img68.png | Bin 4873 -> 243 bytes docs/html/img69.png | Bin 706 -> 279 bytes docs/html/img70.png | Bin 351 -> 686 bytes docs/html/img71.png | Bin 476 -> 4853 bytes docs/html/img72.png | Bin 310 -> 4873 bytes docs/html/img73.png | Bin 333 -> 706 bytes docs/html/img74.png | Bin 284 -> 351 bytes docs/html/img75.png | Bin 1264 -> 476 bytes docs/html/img76.png | Bin 278 -> 310 bytes docs/html/img77.png | Bin 430 -> 333 bytes docs/html/img78.png | Bin 160 -> 284 bytes docs/html/img79.png | Bin 740 -> 1264 bytes docs/html/img80.png | Bin 344 -> 278 bytes docs/html/img81.png | Bin 1316 -> 430 bytes docs/html/img82.png | Bin 434 -> 160 bytes docs/html/img83.png | Bin 334 -> 740 bytes docs/html/img84.png | Bin 238 -> 344 bytes docs/html/img85.png | Bin 235 -> 1316 bytes docs/html/img86.png | Bin 186 -> 434 bytes docs/html/img87.png | Bin 396 -> 334 bytes docs/html/img88.png | Bin 481 -> 238 bytes docs/html/img89.png | Bin 213 -> 235 bytes docs/html/img90.png | Bin 543 -> 186 bytes docs/html/img91.png | Bin 282 -> 396 bytes docs/html/img92.png | Bin 416 -> 481 bytes docs/html/img93.png | Bin 347 -> 213 bytes docs/html/img94.png | Bin 264 -> 543 bytes docs/html/img95.png | Bin 381 -> 282 bytes docs/html/img96.png | Bin 175 -> 416 bytes docs/html/img97.png | Bin 336 -> 347 bytes docs/html/img98.png | Bin 486 -> 264 bytes docs/html/img99.png | Bin 310 -> 381 bytes docs/html/index.html | 68 +- docs/html/node1.html | 56 +- docs/html/node10.html | 56 +- docs/html/node100.html | 36 +- docs/html/node101.html | 22 +- docs/html/node102.html | 34 +- docs/html/node103.html | 16 +- docs/html/node104.html | 22 +- docs/html/node105.html | 16 +- docs/html/node106.html | 16 +- docs/html/node107.html | 16 +- docs/html/node108.html | 18 +- docs/html/node109.html | 36 +- docs/html/node11.html | 16 +- docs/html/node110.html | 36 +- docs/html/node111.html | 36 +- docs/html/node112.html | 36 +- docs/html/node113.html | 40 +- docs/html/node114.html | 154 +- docs/html/node115.html | 111 +- docs/html/node116.html | 345 +- docs/html/node117.html | 349 +- docs/html/node118.html | 164 +- docs/html/node119.html | 123 +- docs/html/node12.html | 16 +- docs/html/node120.html | 113 +- docs/html/node121.html | 50 +- docs/html/node122.html | 70 +- docs/html/node123.html | 62 +- docs/html/node124.html | 127 +- docs/html/node125.html | 153 +- docs/html/node126.html | 185 +- docs/html/node127.html | 131 +- docs/html/node128.html | 111 +- docs/html/node129.html | 82 +- docs/html/node13.html | 16 +- docs/html/node130.html | 75 +- docs/html/node131.html | 99 +- docs/html/node132.html | 425 +- docs/html/node133.html | 511 +- docs/html/node14.html | 16 +- docs/html/node15.html | 16 +- docs/html/node16.html | 16 +- docs/html/node17.html | 16 +- docs/html/node18.html | 16 +- docs/html/node19.html | 16 +- docs/html/node2.html | 52 +- docs/html/node20.html | 16 +- docs/html/node21.html | 16 +- docs/html/node22.html | 16 +- docs/html/node23.html | 74 +- docs/html/node24.html | 16 +- docs/html/node25.html | 16 +- docs/html/node26.html | 16 +- docs/html/node27.html | 16 +- docs/html/node28.html | 16 +- docs/html/node29.html | 16 +- docs/html/node3.html | 46 +- docs/html/node30.html | 16 +- docs/html/node31.html | 16 +- docs/html/node32.html | 16 +- docs/html/node33.html | 16 +- docs/html/node34.html | 16 +- docs/html/node35.html | 16 +- docs/html/node36.html | 16 +- docs/html/node37.html | 16 +- docs/html/node38.html | 16 +- docs/html/node39.html | 16 +- docs/html/node4.html | 36 +- docs/html/node40.html | 16 +- docs/html/node41.html | 16 +- docs/html/node42.html | 16 +- docs/html/node43.html | 44 +- docs/html/node44.html | 16 +- docs/html/node45.html | 16 +- docs/html/node46.html | 16 +- docs/html/node47.html | 16 +- docs/html/node48.html | 16 +- docs/html/node49.html | 16 +- docs/html/node5.html | 32 +- docs/html/node50.html | 16 +- docs/html/node51.html | 16 +- docs/html/node52.html | 42 +- docs/html/node53.html | 34 +- docs/html/node54.html | 79 +- docs/html/node55.html | 40 +- docs/html/node56.html | 86 +- docs/html/node57.html | 38 +- docs/html/node58.html | 87 +- docs/html/node59.html | 42 +- docs/html/node6.html | 34 +- docs/html/node60.html | 86 +- docs/html/node61.html | 38 +- docs/html/node62.html | 20 +- docs/html/node63.html | 20 +- docs/html/node64.html | 46 +- docs/html/node65.html | 58 +- docs/html/node66.html | 24 +- docs/html/node67.html | 44 +- docs/html/node68.html | 62 +- docs/html/node69.html | 56 +- docs/html/node7.html | 16 +- docs/html/node70.html | 54 +- docs/html/node71.html | 70 +- docs/html/node72.html | 70 +- docs/html/node73.html | 50 +- docs/html/node74.html | 16 +- docs/html/node75.html | 16 +- docs/html/node76.html | 16 +- docs/html/node77.html | 34 +- docs/html/node78.html | 18 +- docs/html/node79.html | 46 +- docs/html/node8.html | 32 +- docs/html/node80.html | 32 +- docs/html/node81.html | 16 +- docs/html/node82.html | 16 +- docs/html/node83.html | 20 +- docs/html/node84.html | 38 +- docs/html/node85.html | 16 +- docs/html/node86.html | 16 +- docs/html/node87.html | 20 +- docs/html/node88.html | 32 +- docs/html/node89.html | 16 +- docs/html/node9.html | 116 +- docs/html/node90.html | 16 +- docs/html/node91.html | 16 +- docs/html/node92.html | 16 +- docs/html/node93.html | 16 +- docs/html/node94.html | 16 +- docs/html/node95.html | 16 +- docs/html/node96.html | 44 +- docs/html/node97.html | 16 +- docs/html/node98.html | 58 +- docs/html/node99.html | 54 +- docs/html/userhtml.html | 68 +- docs/psblas-3.5.pdf | 20407 ++++++++++++++++++++------------------ docs/src/penv.tex | 60 + docs/src/psbrout.tex | 131 +- 281 files changed, 14318 insertions(+), 13248 deletions(-) delete mode 100644 docs/html/img137.png diff --git a/docs/html/footnode.html b/docs/html/footnode.html index 408c91fe..37fb0814 100644 --- a/docs/html/footnode.html +++ b/docs/html/footnode.html @@ -14,7 +14,7 @@ - + @@ -137,8 +137,8 @@ sample scatter/gather routines. . -
... follows4
+
... follows4
The string is case-insensitive
.
@@ -173,12 +173,12 @@ sample scatter/gather routines.
 .
 
-
... method5
+
... method5
Note: the implementation is for $FCG(1)$.
.
diff --git a/docs/html/img100.png b/docs/html/img100.png
index 86b732f9a792856c95330b86ea376a99401551c3..fe961f95eb6a8204e85301c38ab9d86920f6c4cc 100644
GIT binary patch
delta 148
zcmcb@w4PDFGr-TCmrII^fq{Y7)59eQNb>+O9}6>(d^!2SeITV3;1l9{;J^VjHMNPR
zDlra4ZLff$j3q&S!3+-1ZlnP@#-1*YAsjQ46Ati2kFi=cX
zMZmzov$L}%CMJM@fRQgGe~E{4Gynhq0d!JMQvg8b*k%9#0MbcBK~yM_V_={iFa=_6
zD4SaVOtC*;V4lGG0U{O4!0_Nd14s%4eDpXEGPHxl7?#4s
z7!U9zFf5(G{DFa4VFE-i1M>yW3w#L$Ksz`J4WM=aH94Cr8vxzHzZ>Wlum_kPFmMX6
zGB9{DFic=zkOc{S4THKl1Wbbb#+um)3yKFIF4&4VxaYnih1Ey`0LSz%N)>GtiU0rr
M07*qoM6N<$g5Yv-egFUf

diff --git a/docs/html/img101.png b/docs/html/img101.png
index 757d96014b84a88cdf1d89f82ee535045cad5def..183814e16f592d47f8893e7a87d4c60d1868f772 100644
GIT binary patch
delta 270
zcmV+p0rCFX0nh>=iBL{Q4GJ0x0000DNk~Le0000y0000U1Oos70D`t)e32ncf6hrn
zK~yM_V_+CqP=Aks-D3l$IO`oS#qG<$@D-arTZr_V00u0Y85sUUq}d#>OY4EjdF%^W
z4NxVx{ffUcFdhK2H!!Yd7hrhb4>Aq}9xyPNeiC@bz1eN0RR91

delta 150
zcmcb>bdyoBGr-TCmrII^fq{Y7)59eQNQ(h69}6>(yea?j-$X^9oN!MU#}JO0$q5Uj
zZhX44ui@d;N7f3HE#oHYH$Hs)he=^}|Kf(9Ow5N%{4R^aB)zmbeCZLK?gD50lz|P^qD`H=8c&a%20~Q=}EeO
ztHK%3NLj&=;Xt}iwLNnvgUG05e@y9JuJhk&@^Fe({?0~f$
z+?=@R0;h>$&s|*D>#!2xV9I_?En-WWj~7_ONU?Z?Biw-}!ij8BlP9x*>0$(nxMDr_
zh>l1@FH1uqzOs#g(opsk)2i1#dZCt(3)7-lzyRfaYym4wF{9OpEI*(ld>Ac<+Lixq
zQul+BI6`Mm9f99td!y#ig^)wV<4*)fDAteb;zB<9#6*D*%+`S&;jjn{i7f-?@KB^Z
z$#U(=l?D@lH+{u)H)XlZSPhZI*t-l<_>c~ELa)dkjUJDO>P8(_VI%nL6?ux){O#{&qP*@0yOT;e|vGk!4uv)Kap6yOqiV6wIVM9yJg
zI0&S;{ffUcFdl%&*A@baHw+BtfRyPcfoBZN7oa-70kI84;z2vmX8sSDIvAD$ZDx9a
zWCv7&Gl5}gfD9{=t6~^f!InGlQ7LSA%Z=m@-U-YNK#HS)_40$*IwX&CUW^C;g$4tI
zAOm9na*)V9Kn*ba|3JWi1;o93_wFS&iBW(b007%AH0#O3c}@TT002ovPDHLkV1kWz
BUBdtX

diff --git a/docs/html/img103.png b/docs/html/img103.png
index 76aba14992ae4a4e84029eae81afa1aa9bcd2016..493bdcc4a555e9a62de2aaee551c84c23965cbe8 100644
GIT binary patch
delta 244
zcmV6#$Xt9~kBr
zJ21=zv-k~wB783|a4Iq^^YMRRE8uou_zz++@PV!53Ya6nQ2-PIvY~ERLtq!oaekA)dX?)k*rI8o83zQNPQF@$4ga>4@P
z8=vm%Yq-7shc)wI?W5%mcEx*?;+tNoH>UIO$UhfnVEtjiHACMfBYgwwCiUj61*{+H
z6CzH1nBUlVnL)>(w^4hFabsd8L%>0n4GVetckGn?A!1fgm-?4MC?maN>tl_Cy?-3$
sJ)OYdq0rD6*f6!xae^bm5;10mTvz#=X)6Pc10BWS>FVdQ&MBb@0F9hRB>(^b

diff --git a/docs/html/img104.png b/docs/html/img104.png
index dca7425991c402a644865b087bab004598ca20d9..86b732f9a792856c95330b86ea376a99401551c3 100644
GIT binary patch
delta 274
zcmV+t0qy>{0n`E^iBL{Q4GJ0x0000DNk~Le0000b0000W1Oos70B3!ygOMRjf6_@r
zK~yM_V_={iFa=_6D4SaVOtC*;V4lGG0U{O4!0_Nd14s%4
z^f(VPw1dPLmcqms5AY>0ESyW3w#L$Ksz`J4WM=aH94Cr8vxzH
zzZ>Wlum_kPFmMX6GB9{DFic=zkOc{S4THKl1Wbbb#+um)3yKFIF4&4VxaYnih1Ey`
Y0LSz%N)>GtiU0rr07*qoM6N<$f`X-FMgRZ+

delta 117
zcmcb@w1ZKxGr-TCmrII^fq{Y7)59eQNb>+O9}6>(d^!2S{fUY`-e#UIjv*W~lM@se
z&*+yiOq$bmhSQ;IZG-fY*~$k38J5g5EO2F7xs&JojYg5~!ik0+hh5qj*chI(yea?j-$X_4T!wH@7sn8enaK$Y
zq;7n=v#;Ud)JN6|lP%*W>Nh@o{D(}Fwvf5>@@vR2(Z!$~H+7^0r?ZbkUA*~XzLrzvkfji4@;n3+4kh!Kge0v|&K
zg2ik94b)Skiy5OCVqB=w6Enc#kY`!qC
zyEyiU8Feq-yz0VdxIfTFBsli=Ylk>9xlH{Umt!csRe{~@5i5UaQt61{@6zn913O0kaL-~E_aSZoLu{GZx8?j<&fQGg!+0NXA!>&e4;P5=M^07*qoM6N<$f@_am
Ar~m)}

delta 266
zcmV+l0rmd80?Yy-iBL{Q4GJ0x0000DNk~Le000160000T1Oos705=&8+mRtmf67Tj
zK~y-6V_+CufO!HkPn?i)CIckS>${}c^_RNJ+3N`^=k_c9&cN_W@g0!;ZZ44E{|^NJ
za49$aB=C%Z;p6-QAp608f~G%cXRrlQlfj&&gx$WB0ca*CI0Ts$fZ@(@7YOd*QqGyc
zurvT@I4FWR3X#Jdr2IVt1K$T^V2ay;PhkV+SJn?8U+zX${a))k!=DKZ{0kTueldV4
zAdjPf_3{IGmO}y{6)0%{1o$SP@mLuc1Q`S{6+!?z9v&7j4-an?i~xcS;h*KZtH#S~o&@t$3)ShD8n3%~BaFAugLZ1E|J7s@}m=)Be{$&u#
zNblJCSR-NYABTBQCop&@G&BY_Ol@?W;K;CqnIYFzK4;p>fa5^7FnGH9xvXqyv0HTn`*Lpr)o)TwKhtJzX3_IA$g%IIue=Y*OJpl&##q
dN+2(Zf#LBlwk(D35*|QB44$rjF6*2UngEzuB?SNg

diff --git a/docs/html/img108.png b/docs/html/img108.png
index 8ca3ed43ac00e7fca1a99aecb08c0c28aa40317c..dca7425991c402a644865b087bab004598ca20d9 100644
GIT binary patch
delta 117
zcmeyzxPwu#Gr-TCmrII^fq{Y7)59eQNb>+O9}6>(d^!2S{fUY`-e#UIjv*W~lM@se
z&*+yiOq$bmhSQ;IZG-fY*~$k38J5g5EO2F7xs&JojYg5~!ik0+hh5qj*chI3nXX&

delta 188
zcmdnN_>WPsGr-TCmrII^fq{Y7)59eQNJ|1SKMOOEeC$zqZK9%2eT}D!V+hC0P`j9yVrM=W&dg(LwG$>%NAaJm+ux)XQP;j5AA1Fw`?j+xw4U
mO-MsyqLMR1vj#IW!>n~eG8F=ok}m@t#Ng@b=d#Wzp$Pzcc|x)P

diff --git a/docs/html/img109.png b/docs/html/img109.png
index 596d70023febc2645174c9d03868d0cf7e66b2de..17a85bdefa6517814b144b573d69142fde9d08ac 100644
GIT binary patch
delta 603
zcmV-h0;K)r0_+4YiBL{Q4GJ0x0000DNk~Le0001d0000W1Oos703v(=0RR91Fi=cX
zMZmzov$M02EFOOV001*HGmVXnSy@?$hjTOl0004WQchC6Eo-
z=vHXm|3IOXteOH{Vu3NCq$IgJ$+3j;AH)ZG`t;Lx(&K;b9xw|ELj%?w41V6bjH&lU
zeA^~fiV|kI6J~gwZ0h;|W=MGAZOF<`4O}IjhkC+_O()FmC_snttyjYFczuLCE9_=r
zgn!6+i?UYTJi|#Qy%?gN@@_@=vf0L=D5oiJK8>I*mYA74z=#ovuL2)K1%kzE{|(er
zql+OcSaE+n{1qIy&xqliKJk+giB|$wU`K+*Ydg_=&uZhE6~Ez<>1({lH)06s8Zsks
zou)8?+h#7S+
z-n{C_K{QulaCDdna$W1JbiPMOW?F*
zoNj_YLs0vbb7>88PH*pOe8>^e)ZEDGveDuLlP5P@8ynj@<{5G&Y=SqMT3$1$956U2
iE6nDyp`Ymy1H*qwv(s1Ycr<{1X7F_Nb6Mw<&;$TOFmww5

diff --git a/docs/html/img110.png b/docs/html/img110.png
index 449a3c08420535816021c3fdf56263aa83d07887..53d08568446c39a998ba09ff800022dd5b52a726 100644
GIT binary patch
delta 266
zcmV+l0rmdz0n7p+iBL{Q4GJ0x0000DNk~Le000160000T1Oos705=&8+mRtmf67Tj
zK~y-6V_+CufO!HkPn?i)CIckS>${}c^_RNJ+3N`^=k_c9&cN_W@g0!;ZZ44E{|^NJ
za49$aB=C%Z;p6-QAp608f~G%cXRrlQlfj&&gx$WB0ca*CI0Ts$fZ@(@7YOd*QqGyc
zurvT@I4FWR3X#Jdr2IVt1K$T^V2ay;PhkV+SJn?8U+zX${a))k!=DKZ{0kTueldV4
zAdjPf_3{IGmO}y{6)0%{1o$SP@mLuc1Q`S{6+!?z9v&7j4-an?i~IYEKv
z#_Ln_#Sc_|;(5y>zu*l6n{(Sz9yS5K$3bjt=U8SKy(@Nj!|>Rb?UTiWv>J=^2M&lb
z7~49`Z~T4Uf5*%42|54%_=z8Uc<1{$@q>@k6MnQl$W2Yy&{#ZgPI|)r&;1qyv0HTn`*Lpr)o)TwKhtJzX3_IA$g%IIue=Y*OJpl&##q
dN+2(Zf#LBlwk(D35*|QB44$rjF6*2UngEzuB?SNg

literal 233
zcmeAS@N?(olHy`uVBq!ia0vp^vOp}y!VDypG&v>#Dct~{5Z40-4s71MSxrr?p`pRY
z$7k8HWs;JT#l^+;_VzPp&P+>711dB&Hty~1jf{-^`Tp}sAfK@$$S;_|;n@w4WR|Ck
zV~E7mxXn>gB%v)Cp8DJ41n_BQZB*iab1M5e*
zKj{_6!w$SX@Iih}ou>0a8OA;)Hd}#q?ABY`_w_YSQVN*|-)q$`
z_?)VfZsK={NsuYz!1|@DgPF}2$TM5mU0ZC=x>)b-q?D~K-`I}Ul{RdvpA@05T&y
Vg)f{{ms>y%_jL7hS?83{1OOjzRxtno

diff --git a/docs/html/img113.png b/docs/html/img113.png
index 7174a30adf8f00eab85ea24ab7b7e95f6b64cc00..596d70023febc2645174c9d03868d0cf7e66b2de 100644
GIT binary patch
delta 338
zcmaFC^pr`bGr-TCmrII^fq{Y7)59eQNb3W!0t+*cEQq)90#dpGJ|V6L4jh=MFIT^L
z^JZgX_K{QulaCDdna$W1JbiPMOW?F*
zoNj_YLs0vbb7>88PH*pOe8>^e)ZEDGveDuLlP5P@8ynj@<{5G&Y=SqMT3$1$956U2
iE6nDyp`Ymy1H*qwv(s1Ycr<{1X7F_Nb6Mw<&;$TGMsx)L

delta 341
zcmaFL^nyvhGr-TCmrII^fq{Y7)59eQNP7XXEDJM`{9pQ<7f2Zd_=LC~IB;O|=FJmz
zU3Iy}gl}<4?IxQ*qCT^xcNU1|1HU!MyLAs_i`)0>oKSu=KLlS&hVezpjeaRultIo
z6AWLQ516p63s5L#+I)!R9823$Mvn5vR102(%D`G?q4t}~}f
zJYzr7eB&+8#obuGr-TCmrII^fq{Y7)59eQNJ{~+2n#ciOw2Rrov7$jpYQ477$Pw>IYEKv
z#_Ln_#Sc_|;(5y>zu*l6n{(Sz9yS5K$3bjt=U8SKy(@Nj!|>Rb?UTiWv>J=^2M&lb
z7~49`Z~T4Uf5*%42|54%_=z8Uc<1{$@q>@k6MnQl$W2Yy&{#ZgPI|)r&;1(yznKkWul@_oTsOYV+hC0{|{rbmZoN8uJ;lvUtG(+7XVotkmqSjTegf+H|0c^{!vTJ0U{byQnf&JQJfomdc
lZE6OOPj)eUn^Vuj!=Utu|KsXlT_d3344$rjF6*2UngE<`E5ZN(

diff --git a/docs/html/img115.png b/docs/html/img115.png
index 1dc3fc9735bf5bdd973417a5a285c0d849c10629..0f22ca533de1e6c7795d9848dfee6d7fe02d637b 100644
GIT binary patch
delta 209
zcmey&_>xhzGr-TCmrII^fq{Y7)59eQNXr7T91Am$RMO;_1f+B)sw&l|rKJIx#>U3I
zy}glzO*H
zy>9)GZfualV*I4$;FVmqw!H$9-ySPmk~-JUq3}eq;&;H+?c59}GuW>6dfbw%P%|)Z
z$k0sh&^p&F$f&SO?3uE|P41Mc5`*Tu8VSr+@(h*NHRrkVZNCS!mci52&t;ucLK6Ub
C?L~Y5

delta 219
zcmaFK_?c0)Gr-TCmrII^fq{Y7)59eQNJ|4T9}6>()OlFt2c!%psw&m<@bILir2%=y
z#>Tz9y^)cTo$bXYKt5whkY6x^!?PP8$wE&T#}JO0$q5RASMJ|G5Ky1$bmA{(g5Gx~
zHnwAzd2|HinBAEt6eMqG(Ry}^LFJi*v#R7X76#5`B{KqVA7GPdEsSmdKI;Vst0QLJuYXATM

diff --git a/docs/html/img116.png b/docs/html/img116.png
index 303731c2db6363bf9c50e56d58e7e03810bcf007..bec89570d1194a436136910b899f52068a217fff 100644
GIT binary patch
literal 222
zcmeAS@N?(olHy`uVBq!ia0vp^@<7bT0VEhc`Omlwq?k&A{DK*7cFtMu0pv~hba4!k
zn0nRUQIN%uV|9a+1#|WSrm}bY*$fW+PBUm=WVyn?mZfk>?ABY`_w_YSQVN*|-)q$`
z_?)VfZsK={NsuYz!1|@DgPF}2$TM5mU0ZC=x>)b-q?D~K-`I}Ul{RdvpA@05T&y
Vg)f{{ms>y%_jL7hS?83{1OOjzRxtno

literal 786
zcmV+t1MU2YP)@Km#;D1C(|)7?Mdc
zn_F~RbWd6_Ya9Fd0|=D=5U`rS3}7{Z8Nm38>qvYTpljZ}DPKq#yBR8+4OU7xx#TF9?N?Cc#X3_Q$gX&a3$x`aKeS
zvY4*Oj?a=73y;kauetsk9g<|1okvd>1P)}QEJh?YXgrOnR#{07JxZy9$DQ15ce$H1
z6(Z-caiQu5Vex$ws-RKXQpvnOknOV#YSRMNk&Y%8lFgO_8%@&<)Lw+-tmMjd$aV9<
zf3BBAW#XuqNMh^R90p}o{SJ}E2bNGjxTJY&`X(4uJd<(d)-O2dobJmF+Z>?~e>u78
zv^GtM-&{z!jr2H+DzlP=bwL~aIMPk^s|E~#-N^@+w7Bm7L?xcjjFPrZBqJTAAQEO5
zhnELlB1n130GA_)ALCWmWYtmGsM(%IdZaN}r_~?I7>4SSF-8#pb)Oc4y}w;mHD2A-l6DI+Y&@v2PYG})9or~z
zXkTQQ*c!`D9Q)~2aW?X(2Ba*VmR;`K4=*ivdHNgEpPSHqCyw)Vsyf8FHgZQ}0n
zk%&Xh3OUvfyM^=~&6|P}e(@Y!XY&&PPQ#FYqv4mpUvUom<*@$*pxnFpgb=OMR0yBWs1ZDuM3CsXi6PN+4CNKk7O<)GFn!pTTHGvtxY63HW)dXhn2R$_2+UEqX
Q-2eap07*qoM6N<$g7T?p1^@s6

diff --git a/docs/html/img117.png b/docs/html/img117.png
index 05296cb17f80c7dd5b12bbd5fb384f7eeadd3ee9..7174a30adf8f00eab85ea24ab7b7e95f6b64cc00 100644
GIT binary patch
delta 294
zcmV+>0onfY0_XxEiBL{Q4GJ0x0000DNk~Le0000=0000T1Oos70RMI84Ur*Cf96R<
zK~y-6V_+Caz&wE%RZIqOCM!|Kz9&=Fmgn{b46hX5vDY(j`xSpjQU#XbTO{`Y=;nAu
zz66Gk^9$b1Wib6D@C=~}BEv5U(#XeAz8Ek<<@7`^B_bvb?!wL2j
zR{;M9Fmovg{YR*R$N=?&z%&M~d{7{B0<*#d&IE>~0SI@2WjGBu!ER)D#LfAY^#ezt
z0k;F6!UiPQ17#TI2gHNe?F_MY@+^l0_;)jK6tG@?fKUaJVf^5u2x12?FbW7T0AptY
sD98noLINbi$iRs+REdkBQ7|k407KMC4TETZYXATM07*qoM6N<$f_?aMe*gdg

delta 305
zcmV-10nYyD0`dYOiBL{Q4GJ0x0000DNk~Le0000!0000W1Oos70Jt;OoRJ|+fAC2}
zK~yM_V_+CGfH?q7fE!9%LZ~_h2F3zpdDagQS{cUU+j{}UfPcsw{s};gDldV|VPe3L
z=M?~vA^q?ZOr;
zANU#I?gQ)E!tjV2;y#Ao8+MrcZ3Ov`@6&o<0P-&YX<~@AW8ejcI41+E04D(4h-l3C43q7p-aQ!2MYLc#qTH>H~;`EIXUfR3EblV0000<2SrXqu0mjf
Dwi0^(

diff --git a/docs/html/img118.png b/docs/html/img118.png
index 54b8b872dee971463d565456cc307296c1b7ad44..47a31088b6a98e456d4ecb72a3877d250bc2bdf8 100644
GIT binary patch
delta 137
zcmZo+KFz4u8Q|y6%O%Cdz`(%k>ERLtq=kT(kA)dXUicE&GEvbxp25@8#W93qW^#f8
z!;Sw{n|}RcF-|ozsBmJ56q=##5HY7+H&N>Si07ZcAE;MfNXZQeeX}d7GOMxQ5aM;b=T=H4~()OlFtH&M~2zR=UfF@$4ga)N^3
zmHYP(1k|TGo%qX{p!c1LjqTWF9vuNWW_RWZ1<4y)w4U8!P

delta 264
zcmV+j0r&p%0m=d)iBL{Q4GJ0x0000DNk~Le0000b0000W1Oos70B3!ygOMRjf5=Hh
zK~yM_V_={eU=9Eh8=xFZ2vr9Zo)8ZeQwEc)9~c;z4EP@)YvrE+A{iTy#h4(}MKD?Z
zfpL4EZNOXx2KIUehR+}&zLyuc8Sb-9c+bG_4k*4KEXMzVlOd0R;Xebz10a46*2@*Z
zz<2;G#;_D7X2i+Beu0(29_T!UUI`Gr4DG@eEFbt8fM#(N8bIt|_`P9=x!*>RTljY~
zFkA(TaWb$9a56Bk0Np%+f$;*en^_&ezCrOD!#)rZk0Qjtj~rGb2><|FPc1a>$q_UF
O0000@Km#;D1C(|)7?Mdc
zn_F~RbWd6_Ya9Fd0|=D=5U`rS3}7{Z8Nm38>qvYTpljZ}DPKq#yBR8+4OU7xx#TF9?N?Cc#X3_Q$gX&a3$x`aKeS
zvY4*Oj?a=73y;kauetsk9g<|1okvd>1P)}QEJh?YXgrOnR#{07JxZy9$DQ15ce$H1
z6(Z-caiQu5Vex$ws-RKXQpvnOknOV#YSRMNk&Y%8lFgO_8%@&<)Lw+-tmMjd$aV9<
zf3BBAW#XuqNMh^R90p}o{SJ}E2bNGjxTJY&`X(4uJd<(d)-O2dobJmF+Z>?~e>u78
zv^GtM-&{z!jr2H+DzlP=bwL~aIMPk^s|E~#-N^@+w7Bm7L?xcjjFPrZBqJTAAQEO5
zhnELlB1n130GA_)ALCWmWYtmGsM(%IdZaN}r_~?I7>4SSF-8#pb)Oc4y}w;mHD2A-l6DI+Y&@v2PYG})9or~z
zXkTQQ*c!`D9Q)~2aW?X(2Ba*VmR;`K4=*ivdHNgEpPSHqCyw)Vsyf8FHgZQ}0n
zk%&Xh3OUvfyM^=~&6|P}e(@Y!XY&&PPQ#FYqv4mpUvUom<*@$*pxnFpgb=OMR0yBWs1ZDuM3CsXi6PN+4CNKk7O<)GFn!pTTHGvtxY63HW)dXhn2R$_2+UEqX
Q-2eap07*qoM6N<$g7T?p1^@s6

literal 298
zcmeAS@N?(olHy`uVBq!ia0vp^@<6P>!VDxO*6b?+QU(D&A+84w9N4^hvznS(Lqmg)
zkI%AY%OoWwi;Iix?d@mIoXNw(la`hSRBLQ(+}qn585!BxUTgy7GnNGT1v5B2y8)71
z;pyTSqA@W!VS!u%AA^we1eRA45;~HP1Z%GG^YEPF`NRK!>5s63N-}dy1E*6g3wQqe
z&Ac;C9|+*P@>Nphz}bTNxreIR_DvU;koeZjVj=lSLgJtChmXvmd)Tv6Y#4+R9&j~q
zZir7v-H@JO@TetgW5Uk^=NU}4#7bnn;49wWtB_sKEL$h~#)EM|)HF_q!;%vE3Ul5u
rl<6OO$@ANRWzutr9~bx9%P=r--%?fC`8>QI=w=2_S3j3^P6
zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001
zbW%=J06^y0W&i*H@JU2LR49>SU>G!jIRH(78%kS3s5%A)#sXw{)(;R`8OGz=djZ9O
zf5;sE2|$c0FM-TqV!)8+6#$Xt9~igy*#^vo$+I^Ai7n6V3mEtffGob37q}VjvrTx9
zEYBRT$d|yt4RRnK{|8QnJO+mU$ma8L6fj?4-~)SrD}aIV0Gd2dkpBZz-iVWd{Q@h4
zJ&OD^2Ch(u`3&vC7Azn58Q|^%>)OKbh#TTQhTj`@nEP!6`H%0@dSC$ZF92y`h_z$j
z1&25%1FHZh0|UzhWUm9=B)}kx650+7=l~^r8TO$|!{P@D_;JPWC>S^Z04q5;?PUqv
Q;{X5v07*qoM6N<$g10D-(*OVf

literal 804
zcmV+<1Ka$GP)<4%AUIGDmG)O`Yoc}9ewSZ~BY5~)LF^$VaOaWw)jk9OcaBuoOa5tZr+s(aW=4&{U
zf%J6?WO6ub$x?sf{({5)Y_pH43h$6AU&pvVZNZhvzTy5()z4Cb>eCGOW-s85rzN;f
z-iyR5q&K8I#O1@}8hl!6{_xnWmq}Y^rfyec~{sx32IhCvYHP}
z;mGCTgFaRw)7F^jRE|v@GlNLt~w6^CiEl`x#M3(OzTU{aB
zKVRy~S`x^9cJh~NnfFWD)-<0)|B+l@%DiVNy3agy&j6)9b
zvXd{$<5r%hdOW$d$ef-wo&-E!>IyDgVu~9dkz%e#Ol7Ue(AZlVMMsjdmr8Ioig}EU
zwZUNaT@KxUuEw6Xro6U=q>-!DdsN=@n+x%#%!$=_Jj$&KrHxQGAyO#lYc6odl9r}}
z%gurU6%HhBbiwm>8-=wP(erM|alADcM7gcO$VF$&Jt;5VT@71G)h4wHh@)}zwOq!2
z`0>w(mr@=kGIrL72Sg6rKm4~U%1u-+Ld!9@eW%_Z={NX<73hSi07ZcAE;MfNXZQeeX}d7GOMxQ5aM;b=T=H4~31ALjVAud7FnJL~u-7w4
zS3JJTFqeU$f`Q>PNa)>Mh7G(QG8x{3h4zDl9{gvRzy>t+KUm{?Fu9b0L52ZEh*@C*
zLoGu9gFRRXtdXP8xWS*{1IYOILr~-ScXKzFycPgC;uizMRj}F#41qw*zyfya1!SkP
nI$(H+VIRWVa8DuvXV?P(m~SgZ_p^Ww00000NkvXXu0mjf>6%%M

diff --git a/docs/html/img123.png b/docs/html/img123.png
index 395516d978c1c0e9453b3a376d1b0050970d8f5e..288b4a800ad6b5f7819701ea243719ffb064b30f 100644
GIT binary patch
delta 265
zcmV+k0rvju1Ihv+iBL{Q4GJ0x0000DNk~Le0000b0000W1Oos70B3!ygOMRie*nly
zL_t(2kz-(>8DI_o5*wf#O9)j56rKQIkX!h7
zGca5Qi*Yir3UD$oumIgWfr0S?vYS~Qz`jB88^b;j5sxCoz>geOBMATiTTd-C@5vD~
P00000NkvXXu0mjfO(bCI

delta 428
zcmV;d0aO0U0_y`IiBL{Q4GJ0x0000DNk~Le0000=0000W1Oos707sGYevu(de*tMp
zL_t(IjqQ@LOT$nQ#=qJ=ZJRcEE+P(6{|Gm0ii?}XL0r^S{09Q+B#Pir#3fS)!BND?
z2n8o~a1+srIEtxY>(P<885KWf$1;
zi{)Y$WqRA1#J&_Yzo>Ron#($ne*%(@X7{2(+pG)3CX0ROre@ofdzL9MbpR+ct4*dv
zLzl7Xy#i3E=oZjm>W)^tRt3i2WtpiVDN_Azo<7?gQ?tM&J6w@WxZi-ALz<~gU?t%u
zD2-ZS@~<*=OY#JwaLB3_zkuh6m1YY=t9caYUFtD(np+l!22tn0k#crQe@A)5=R8Mz
z(vuDDKBJ}_qDG`xjz~T#;6?Gf*Xrg6K$D1C;=#q+No+^Am78nw%3*O5cx=sMsYDX7
zA%MYFK^W9PCwao>*0tcx87;Ll2mkR$;s*?&
WVPo&uxQze+002ovPDHLk0$_p%>%v3;

diff --git a/docs/html/img124.png b/docs/html/img124.png
index 1cfdaf8a12105c39bf821c65ed8e1016f6a971aa..a802fa08b32be76cfd26f0852f4fcc8c68a37e0d 100644
GIT binary patch
delta 232
zcmV-4Ezt^0{jy|Bx3_yfC)lf1PgEPvkjQb
zz)%j<^%*3<&2XP>!g~h3mlqfq_JagC8S)qy{xk6L168~SYh*kC5@6s8fC;c)U}dmp
zU@+o@YO!GXz|R0Qv|Si#=niwgK8+x2e*+zU73@d>pjws*K*JdrFCd)m0Cq3J=?wco
i1d`_%_|d&T8~^|d+9f2p=U0ya0000agT=x2GW-|)4-5jJJKGsz?Z6^e
zAzptc0CMgGh5!ae0dSaJKnh4!2RIWN4p6WU&WcACX5fcM$OeW{KrR3P6e?vo!NOdg
Q!vFvP07*qoM6N<$f|u=k)Bpeg

diff --git a/docs/html/img125.png b/docs/html/img125.png
index 97bf076756306630769c6ecf031a8ddd90399030..88a40ab11ed3b0db4f4e76c082cda32addf75fa2 100644
GIT binary patch
literal 804
zcmV+<1Ka$GP)<4%AUIGDmG)O`Yoc}9ewSZ~BY5~)LF^$VaOaWw)jk9OcaBuoOa5tZr+s(aW=4&{U
zf%J6?WO6ub$x?sf{({5)Y_pH43h$6AU&pvVZNZhvzTy5()z4Cb>eCGOW-s85rzN;f
z-iyR5q&K8I#O1@}8hl!6{_xnWmq}Y^rfyec~{sx32IhCvYHP}
z;mGCTgFaRw)7F^jRE|v@GlNLt~w6^CiEl`x#M3(OzTU{aB
zKVRy~S`x^9cJh~NnfFWD)-<0)|B+l@%DiVNy3agy&j6)9b
zvXd{$<5r%hdOW$d$ef-wo&-E!>IyDgVu~9dkz%e#Ol7Ue(AZlVMMsjdmr8Ioig}EU
zwZUNaT@KxUuEw6Xro6U=q>-!DdsN=@n+x%#%!$=_Jj$&KrHxQGAyO#lYc6odl9r}}
z%gurU6%HhBbiwm>8-=wP(erM|alADcM7gcO$VF$&Jt;5VT@71G)h4wHh@)}zwOq!2
z`0>w(mr@=kGIrL72Sg6rKm4~U%1u-+Ld!9@eW%_Z={NX<73hq_!IAnU(*+|oOt$FBVpf%1#=(jd+>%c{AX`l
z$|I-n&4g`Tz&Vz-rwMy``giQq-w@BR@wQ~rTZ>uVEDmoN*xVS`U0~QDds*Px$E~6l
ij>#`+Hs)wJ!^U8HM31ALjVAud7FnJL~u-7w4
zS3JJTFqeU$f`Q>PNa)>Mh7G(QG8x{3h4zDl9{gvRzy>t+KUm{?Fu9b0L52ZEh*@C*
zLoGu9gFRRXtdXP8xWS*{1IYOILr~-ScXKzFycPgC;uizMRj}F#41qw*zyfya1!SkP
nI$(H+VIRWVa8DuvXV?P(m~SgZ_p^Ww00000NkvXXu0mjfNd#H+

delta 428
zcmV;d0aO020_y`IiBL{Q4GJ0x0000DNk~Le0001s0000T1Oos70B8t;l93@xe*tMp
zL_t(YiDO_G&VaE1h08pFES-FNFF;wW{veXc07H4m2dt(bbb3|yf=gO}qE8<08wfdogPZZX$TOeTBPV12-3-p=$_DKWj~IAgBZ&h&8f(YVTq1x|Cn}i0z$w7W5Wv6)Vj=;c
zhyYh8j-Ar2V&FR_TTf}#cLEWS3}o)`tAU=&aX006|Z
Wgk4YMmtp__002ovPDHLk0$_pzIH}wK

diff --git a/docs/html/img127.png b/docs/html/img127.png
index 85cad49a4a28a87fecd6be21f63b4bc747b9b93c..395516d978c1c0e9453b3a376d1b0050970d8f5e 100644
GIT binary patch
delta 427
zcmV;c0aX5y1nUDKiBL{Q4GJ0x0000DNk~Le0000=0000W1Oos707sGYevu(ee`!fX
zK~y-6?UJ!e!%z^$zuG=+n>KkaA`Vjj2sdkri<`tjT+~$j2LkFOir`ShB~u5%QN+mz
z1t)cI6VZw|im71h*483*5xr|tXbRm$Jb2%`-20L5a(TdSj#pY?qsO7+ZLwx$7ufQP
zM?YhTNZ}~QRl#sa&}5be|f~`JV$)e
zlMU`Zqoy39MxgESPlZaa4!NuE2Y)7}1n``pQVQ~_8Y|Ue-L=v$f
zfWcNl7}P*02N(!RggVA7GJ%1U%SPZ2`Ee1ThS%roerk5swcyPeEwwWT|M5rS2MnQM
VWAE6wjQ{`u07*qoM6N<$0fMA~!VLfb

delta 466
zcmV;@0WJRP1Cj(GiBL{Q4GJ0x0000DNk~Le0001h0000T1Oos70FdZ;WsxCFe~?K;
zK~y-6?Nc#N!ax{(wG>*=(#0KO+=*ahlA7q?q8(r`QDHI0t;)b;bTPPz3yD$U#H<6G
zA;EvZ>S7uO#08OH9P9NCLQ~r4tiIvzoRhQ7fci}Z
zh6%qOQjH=O;4h6UkVTzul0ZaKm%wluKsH$oRop0|PLhc->%j+2K`q=Pf5CU^G!Pot
zrkArR@R3p*!7V9=IhYcavMH1i%veEpegdA5WNX1BK|G9A&<=!D?hyx9Y$I#EgBn^P
z)Nwp91yp9w?BoM{@uRq?%Mm=^+ct{WS;qO&%9xS+ceEU?3p+^TE};p40?E#6;1pCd
z@IuNYaN&82A3bH#8BgqzD9*mR@PgIy(f`%i_cr*)KmItr0M6BYO5_$AMF0Q*07*qo
IM6N<$f)Cf*4gdfE

diff --git a/docs/html/img128.png b/docs/html/img128.png
index 8569567c4113363b84e9268c7d7b443ad80e7e6d..1cfdaf8a12105c39bf821c65ed8e1016f6a971aa 100644
GIT binary patch
delta 318
zcmV-E0m1&h0{;RbiBL{Q4GJ0x0000DNk~Le0000j0000Y1Oos706Ah!e32ncfBi{B
zK~yM_V_={SV5|agT=x2GW-|)4-5jJJKGsz?Z6^e
zAzptc0CMgGh5!ae0dSaJKnh4!2RIWN4p6WU&WcACX5fcM$OeW{KrR3P6e?vo!NOdg
Q!vFvP07*qoM6N<$g0RJV=l}o!

delta 252
zcmVu$mZiHV7~C6o#8J?4OamF2Zp5#9w7EK
z2Ch)f1cv2cy$p}Ixi7F^0I}N{V(mDZO9Vjd00u?@uFwFu9n%oj@wFAu#vi1EGYEjp
a1^_+WC|VB4>p1`b002ovPDHLk0$_rBRYKDM

delta 156
zcmaFIc%M#EkOVP

diff --git a/docs/html/img130.png b/docs/html/img130.png
index 5d5f10711f6e1e8f2ce311ec4b413e6664b279c5..2990ab4979e95e80665acbf17ef60d6bd91dc74b 100644
GIT binary patch
delta 427
zcmV;c0aX6v1M34JiBL{Q4GJ0x0000DNk~Le0001s0000T1Oos70B8t;l93@ye`!fX
zK~zYIV_+E0fUy9D%RGTBoqT&QKv}H*Ad<-dLwU#ttfnAzf&f31!|D=%-O>1V^Fe1-^uWEetXOY%`%LF&>m|f3`3@;^w}<
zj#VefGoRKYCu9EI49@1t2JH-w7^>Me_}~Q
zK~y-6V_+CDAiNZXYYD^=NAYVB2b0VWEE6F7kPjeI8HhO(zyhrP*fqYs3#Qlt_!J--
zUExyP4q%Ng0XXdZ3nu363
z=?q&K5OzLjXRrkkK-Kf!0Re_ihWB5=T&@7lgADCpL;gc-UCQtuM0jB6jA38}hY&Pu
zjX3!d7?y(L2@*=(#0KO+=*ahlA7q?q8(r`QDHI0t;)b;bTPPz3yD$U#H<6G
zA;EvZ>S7uO#08OH9P9NCLQ~r4tiIvzoRhQ7fci}Z
zh6%qOQjH=O;4h6UkVTzul0ZaKm%wluKsH$oRop0|PLhc->%j+2K`q=Pf5CU^G!Pot
zrkArR@R3p*!7V9=IhYcavMH1i%veEpegdA5WNX1BK|G9A&<=!D?hyx9Y$I#EgBn^P
z)Nwp91yp9w?BoM{@uRq?%Mm=^+ct{WS;qO&%9xS+ceEU?3p+^TE};p40?E#6;1pCd
z@IuNYaN&82A3bH#8BgqzD9*mR@PgIy(f`%i_cr*)KmItr0M6BYO5_$AMF0Q*07*qo
IM6N<$f>-U@sQ>@~

delta 453
zcmV;$0XqJY1cd}4iBL{Q4GJ0x0000DNk~Le0001)0000U1Oos70L{mt>5(B!e}hRx
zK~zYIV_+CTfVDh;8pbddfGHCOPyFfAKRo5p#7
zfkyz$kN=5X*#`*C`hNmp)A)d-e%l)u;;RdQxcFN?*fLfZq~P81+`fR{
zz1R`MG-jx2^S^?G{sX~31_sl=f7};16&W-^7~*oy{{aYT=6FTEgr|QQN^rUD#Ybdk
zKWJxQ;4NUd55nM3<%2j73ivn*m@fd;`~}+b4hSBgn`W{RB@~u2Fw7BPSPa7d!9MUt
zHjRNR02rD}89XpdV?DqS15ycg9LHTCxCc~|z`*c~fo~xQU*?264kpboe~p1F6sTr7
zhEEx8GFX7=_g|4>!2zU$w*Z6>azlLgA2}8n9&vMDV84KA+Fa3A2p=g@Ie-b9f8S>?
zz6T8h3E9%)s~#CK3;qV+9eC5X=b|`~a5^U|d_+t$>=wje=1y3UGrn8&m`bsB0Pk#0UHlfbL7$00000NkvXXu0mjfGoZO8

diff --git a/docs/html/img132.png b/docs/html/img132.png
index 4d735b64647acb03b20febd4d06f0ec71090ac78..8569567c4113363b84e9268c7d7b443ad80e7e6d 100644
GIT binary patch
literal 318
zcmeAS@N?(olHy`uVBq!ia0vp^oc(9q!H
zsh7zW9re>qV^?qz@eY+hB`0u*)Ii2RN;bgtT*TXJpl>Vs5_J1B*
zdT}aqACnzxTeY--$lmL}_?D>~6mV@Y+F)eBVNj67yD`v!%YczV@Uh(^HM2AGf&O6d
MboFyt=akR{0Bdw}0{{R3

literal 496
zcmeAS@N?(olHy`uVBq!ia0vp^OMzI914uAr_%?0;QcNX5e!&bkJLfF-U|?We>FMGa
z64Cm0TI|Hb3IYw`4m?*JcoZ0zB_fz54lo#h-@|0kz{sQUmgA@YgH3Zyj^8;`tMARp
z9e>h^`=dU?TGj}MY(}wySDeqj>#p)KDtMu$d*tlQc=ONUVv-iNhc>5Pc<*!f{z<*l
z4sQ>3xtF~6=_%iI+9;rU!d|JEe+kZ%daQ)p8E9f>ny{;=0YhkO*LFHK8Z{>a0*
z{g&BQ>s?8nH_CVXPnue6H8s`6H)Fa0>)ZRE`ESPE*s?JwD%kQ-_nC{EI*tcDzr&Fy
z{pe-cn)LRV)Ay!tuVyw-kw02k7w|B%o7-cb#Q(eph5i1p5WEo8z`8{&fe{*@XxtCy
bkN;p}n((8v#nkdYC@MW&{an^LB{Ts592M62

diff --git a/docs/html/img133.png b/docs/html/img133.png
index f98b00f15c78cd4a3c23f16449ac13bd1740ddda..9cf86be44703a0d124abfcefd505d220db7737a8 100644
GIT binary patch
delta 135
zcmV;20C@k;0p9_T7YYvq0{{R38>oUIks(ZST}ebiR0x@4U?2o685mf50zfQfAf5&n
z-vVc~gNX7E4D*YZ0vUWSFK{X{CxBS|AJ_`G9YC^N0doX63P3C)&SwleuoxE^gIJsl3=^>Me_}~Q
zK~y-6V_+CDAiNZXYYD^=NAYVB2b0VWEE6F7kPjeI8HhO(zyhrP*fqYs3#Qlt_!J--
zUExyP4q%Ng0XXdZ3nu363
z=?q&K5OzLjXRrkkK-Kf!0Re_ihWB5=T&@7lgADCpL;gc-UCQtuM0jB6jA38}hY&Pu
zjX3!d7?y(L2@(JNCJK0l#~(BZf&f5R*9ne}fGA4+0N>JVoXNhDP=V9g3)-|Hq)$

diff --git a/docs/html/img135.png b/docs/html/img135.png
index 9639222bc0b9adaf0bf67ce7b62d20f8cef54259..3a1efe1241f70fcdc268f6c210eeae44c4c37822 100644
GIT binary patch
delta 454
zcmV;%0XhDk1%(75iBL{Q4GJ0x0000DNk~Le0001)0000U1Oos70L{mt>5(Bze*uF@
zL_t(YiDO_GL4dV9fEvay7Jw-e22cFz5{NO3Z|?;#oyzbCDk67o_0b^4z|F
z-@Vuo!!%~7Y4g8=g#H7;KL!TVf4|%pI29Q*K^Wq4&i?@jY36uEzJ#ZL8A@=u?ZroA
zXFq6XVBjraxDUeMQ00R-5DNG>3Yaed)%*q8@(u_dpqpm05hWCsGBC^$U|0;o|G_@+
zMmCLsD*zapOBp;cOk+L35Cc*Pb{xlDAh-uqlfc06jDc?<2w&!eI}Rqze=v=KD-@_^
zIfhReZZcSa>GxleV!;8VgSP;L4{}3%_a8YH7#?wRUtqt0Y1&-TRtO&{QaOMLn}6SD
zFun&31LR0;XNa}qXf8qWJ>RGG;LO1I4ki*0mtzGHk`T-Z7yJO14`5&v;0mQmj)a0~
wR5Xi$udRTZ#*KneFbZ&k95Yk|2dHZr0K^CU5rFPX+5i9m07*qoM6N<$f>r#vGynhq

delta 609
zcmV-n0-pVa1fK;ViBL{Q4GJ0x0000DNk~Le000220000W1Oos70DWzaNRc5+e*zsz
zL_t(YiS1O+YZE~f{+6&N(>1#TQc;Rk$v?1!)F1UykRAk)9C}a?l8Y2iE_f*7$%Evi
zE-e(av<0DOTiS~UArZVvz>^2Vq9}Sv*Fs!MOXGX9n{?A8hmwm(K6o>4zM1*v&3m&8
z4DpX*q6cS$oj#X8p4Qd2m-MK)fBhjgr#aAl<>heWc(R$cSKvkzm9JX!T@^S`<9qlT
zts3j2(~rk4H^!6_yr3A1WY4I>$~Y;*vv+%M?#Ba4D&;6Wzb%_)Ig?~PW@e@j*BiGU
z21{2$KhER)HG9s7`Fh+F!COHZBACpJAeZ>_LbhZro18=>yV_v3Nubcg^TOg6XCv3(6qEV6Ti&%T!<^d1)=KGr#(qJk0|E$@`o%eX6BVWqwhYUYLbG*Zi9o@%Wp=5A6EojLlZt
zz`hG}=Z%B3`f9a$Yg3`UT?ZsYH;+4%AZR?LQ9Zn|{BQURFx#kh62uH900000NkvXXu0mjfJOLls

diff --git a/docs/html/img136.png b/docs/html/img136.png
index 15edd122ef1d55fdb95fca06f2d444025c8f3776..4d735b64647acb03b20febd4d06f0ec71090ac78 100644
GIT binary patch
literal 496
zcmeAS@N?(olHy`uVBq!ia0vp^OMzI914uAr_%?0;QcNX5e!&bkJLfF-U|?We>FMGa
z64Cm0TI|Hb3IYw`4m?*JcoZ0zB_fz54lo#h-@|0kz{sQUmgA@YgH3Zyj^8;`tMARp
z9e>h^`=dU?TGj}MY(}wySDeqj>#p)KDtMu$d*tlQc=ONUVv-iNhc>5Pc<*!f{z<*l
z4sQ>3xtF~6=_%iI+9;rU!d|JEe+kZ%daQ)p8E9f>ny{;=0YhkO*LFHK8Z{>a0*
z{g&BQ>s?8nH_CVXPnue6H8s`6H)Fa0>)ZRE`ESPE*s?JwD%kQ-_nC{EI*tcDzr&Fy
z{pe-cn)LRV)Ay!tuVyw-kw02k7w|B%o7-cb#Q(eph5i1p5WEo8z`8{&fe{*@XxtCy
bkN;p}n((8v#nkdYC@MW&{an^LB{Ts592M62

literal 244
zcmeAS@N?(olHy`uVBq!ia0vp^Qb5el!VDxi>JME7QU(D&A+84w9N4^hvznS(Lqmg)
zkI%AY%OoWwi;Iix?d@mIoXNw(la`hSRBLQ(+}qn585!BxUTgy7GnNGT1v5B2y8)6c
z@^oo@c99vm^K505syiJ(&pSfdB{2q}G*%|x4avK;FXc?(D
z7%=lsID8=Nz*~kxJpB$_&p8T28VnBC3%r+P4p-qYj(NuN>6wvDGJ9fM^Bo7d?!t+N
m9L9HUa|BsURAlIB
zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001
zbW%=J06^y0W&i*Ia!Eu%R5*?8Qol>XKotIBn>J@{a+?T(4Q}EPC|Gc5z<(faIyIY4
zlIkJ|>gIat+LEb*TR}IWQo+Hk9UO(=P|!-7QlyjBOH%to0?wij-s5}kKHm54-T}Ya
zB1TBDJa*28@R0k)-8gR+$c?fo?F)%655)9w%#Y1SKygB(6t90m_wiFudIyB#5bBf{
zB+JJiLn`V%61tc1Bj81C!9HL`F5g=@5bTG`Fi`H81ELIsiohuhuksv>E7U?(AnFsTHQ1pO
qLPcdfAp=S-gvcBG@CpCz58EdX)MW=VKWc&i0000`ogH#8Q|y6%O%Cdz`(%k>ERLtq@{qEpM@Dna?~HXI#JQ5zR1(XF@$4ga)JWu
zhHoqi#mgO6uyAZ;_4%afQ1Lcl(tqZTIq`c$I%H?;|H^G(P@rX`-eADYKjH9!umf)y
z4)OFma6RWJ5NR+tTrcomk~v(3!#L&{%co~XHp%RXZOwNaERLtq$PovpM@DnKK7`*Hc`>1zR}agF@$4ga)JWu
zhHoqi#mgH#%{214XVkDf-P(Nee?n2+#~`-KZ06rR{SJJ~m5Q01m8+Q#J8pQ!l*iuo
zXE{?1m%=?6#y%#t#m-EBUb?g~w0S7-iidD8>^>`#SZ}jA3Fs;YPgg&ebxsLQ08SM`IsgCw

diff --git a/docs/html/img139.png b/docs/html/img139.png
index 1d74314f58d69abf3dc3cfb4dd6f2144ac033f9b..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391 100644
GIT binary patch
literal 0
HcmV?d00001

literal 487
zcmV
zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001
zbW%=J06^y0W&i*IWl2OqR7iN>@wLE}gGsGd334L;=HERA>Ai@712>t;XjqDAkf4MJA5&$a#%Ymf+167)S5_rZJe}UZrm#bcUL~(Kc
zQ-KHV3=G#9LK)EIfa11%90mLr7#QZg0|E@AOg5qzWpqe@VJQRWK`;kRZYjfm2Ce{>
z1`MNE4=}_Cz^vxD3k3HV7}y2G9&jcw@FhSrgXMZbazIOg;!6XjF>n=Nc#z>Hg9Vs=
z{}mxMYXYwTw*yF*G=?0v1E0c%y$rR;4uu*uSF{zvK#C^*cbgeFfY$zgT!10RQNVin
zL5H~`l1cBizJqDTcQBE7gk&Vp=ODQWm~udIL58KF3{(O@pHmCGNT-@nqhJ(_aBzlN
d-~bhk0sv9I^2maT&#nLf002ovPDHLkV1iHlzhM9X

diff --git a/docs/html/img140.png b/docs/html/img140.png
index c1ed1d0f0e6078f6043a07c05e77ab3ce536e3d5..f98b00f15c78cd4a3c23f16449ac13bd1740ddda 100644
GIT binary patch
delta 140
zcmaFGc%D(QGr-TCmrII^fq{Y7)59eQNDBcm9}6>(yznKkWul@_lCP(WV+hC0_Geh=I02N>j>CrXThNY7G&WC1&vau=injnJ_^xVK!&d
pR%4r_2erJDcoPy*5@sA=U|8(Jgh8OFj3K`HpA1!F@$4ga>4@6
z3ERzXeA?C2__f-wwp_@LTQxmoQ4S59KW1D}KmY@dGI&rQoL
zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001
zbW%=J06^y0W&i*Ij7da6R7iF5Ng78voqO3gu#2dj_03w+kSSDbTodzZoh%tz7
z?*$OW7Qm+fHF*QF^cJuhs1$=VUZeQICe2}BI0)vl{zq|JJ6OpF2q*q05hlH1U^oXh
z$OSoI<`*wzkheDe)-M3!g}5R+_PKolzk9JGhDkOMlQ{o_4EhfO4}d&H<^+aD_68oX
zLG!2XRa`q67+805J5HGI(H^6vMy@3UP>|dhY@OQ0^H6
zS0uZD*n`WQa7S@~r0y|*k_T5PX9B}=4BzoiU~T}r`ae>L&t-VVK5GK6z(H;>_x)Go
z5NCMA&3%FW0)|PP7b74>AV(gHagj0qyUh&updLexymp3IJC5cOq|o5|v>u$u1#TQc;Rk$v?1!)F1UykRAk)9C}a?l8Y2iE_f*7$%Evi
zE-e(av<0DOTiS~UArZVvz>^2Vq9}Sv*Fs!MOXGX9n{?A8hmwm(K6o>4zM1*v&3m&8
z4DpX*q6cS$oj#X8p4Qd2m-MK)fBhjgr#aAl<>heWc(R$cSKvkzm9JX!T@^S`<9qlT
zts3j2(~rk4H^!6_yr3A1WY4I>$~Y;*vv+%M?#Ba4D&;6Wzb%_)Ig?~PW@e@j*BiGU
z21{2$KhER)HG9s7`Fh+F!COHZBACpJAeZ>_LbhZro18=>yV_v3Nubcg^TOg6XCv3(6qEV6Ti&%T!<^d1)=KGr#(qJk0|E$@`o%eX6BVWqwhYUYLbG*Zi9o@%Wp=5A6EojLlZt
zz`hG}=Z%B3`f9a$Yg3`UT?ZsYH;+4%AZR?LQ9Zn|{BQURFx#kh62uH900000NkvXXu0mjf&qE*=

literal 8199
zcmb7p2{@GR*FOm%A(aMElwE1;CfTAewiz?_y&20ema&A$Bt({E$=H{SWf;rYA|aB-
zPWH%_ea*iA)%W-PzQ5o9{a^3({;%t~p69;r=bUq&``pXa>MI0yKE~7SjdmtJc@olSm{!KE8l}05BMg$KwG200x6mP*A|(
zaOcmTMUz5r8`6$N})J2c>0q&Nd1A5{*&b86pL_<0gn)-
z&)M%KYE_1vMACyrslCNEneDCUbh{tCzIfG;7CY@x3Xh;LY85ym--o|0t%MyO{$vlM
zec5nTZSpEMJAFU<@rY4g6blM7euRUraTqZyVDULE-tr}T#RcS!>rVbdp+Xn
zaCuAOd^1b6vf{Fm(mD|(KHWC4M|J(&r*uP>>N76>gU(uV@3msBm=Q7$02lOvRbnUp
zzl)I#LL0hsdI$~r7a
zxeWQxQehg7AvhFWA-wi=)?4o5r+5Y1n)}QP>x=eXO_d9%L^t2LU(kF-8=k(oE>zeu
z`ix~9tm;hr{?;e~E^^;p64N*2cEIhrD0gYB2CQ=Cw?>qln#N~>6#>rPG;SdntpMba
zddpF(pGQKgALSK?sQz*4>^7_Nn#)`8j-Tx{RcoH>%%*xFYV)IqH%y}sCRG#iMPlti
z^;Y?81|n^7=rIq0!Cymp^!I+Xp%ZF+PY&a{N)TzE)9A-j3g2W#DB>WzMGvr&_uk|P
zceP5USqBdMUmOWsVNw6(}PK+16&S1a-aTb2f26+8ORQTgtD{#vZ@(2JTM
z$$bpx7}q;`JazM_wihm&w}ZGHy$2S3$lL@48El~U6;PZp=|bZTUHt2sq6J~nHzIh{
zpjlzJueF-8uV|%*;gKO=s|Qw;6+Q|iwZ1%RR$`xA(a8a>qOtU&E**I9t=kIJvlPU}
z3OS(|5dL@urTP@m>Y0X72xdhFs;tR8Ef|BA7bo@S-gww&I2?K3R{svMi@a-sL=72V
zi))BViJDIzMD2Xho5?-y@kK2*otqFK5yu*8c8>EXrPGejemH^qmal410iC&@QoGf>
zt!22p`l=d_KIDA0+Xh?09_44jPk;vhv
zA3)6NnEVFHm*UtN!KOvAc8vtuHag6s@I+^GUg($wUnt7^=vA{1Ev|(qj#O&l<1t=se?_Agdu9sh-5PhDT7
zJnV^P#H_t{z8n273qwT&vdkAb;h){+>Tx~)_VQr7!yqZo{=!jGel)j{IPGb#@{05h
zwJY$VgyXui4DRe>w3YdYMC)oIZ5F9V+r!^#;Ni9iSTveEPN(euc$drMp~w$Gn7qRR
zI-BO`VV#8j3{xS;hL$|_el~X0STL(b%^dKp-eOJ{|A^ex>ili~M79=8pVDh4?jc|G
z(;ks%$w`1{y#wybs`x)v11vir{oO&
zj7-Zk{IPUi<%ThC37IyT+O93e*>wN+^4ZL5Q|VS|4thd%e;~bG&z|$)k=M98s}3%5
zu9@p`IdD(m-J!
z9A;Fel|jeA%hPSH>KgU9;8W^XUA%mCcTIl6L#j)O#bP`cmtmK79yJRs;I1Nut#=hi
z@GaI^fg&DEMyOm{p15vXR@FFmLIC#c=0PcI*p8R#(q2)VO5bzE?@kcO@kKWIiP#FEg{oF6TwrFz{f_CL4Emwur}
zA3-NFJR!WsB#q2j=;5kx;6L3*EZMNCC|mU$5pxuF4-wl1VZGnogRixB+65vHLDL0*#|zYSqxOqA;41YGNiBQZ6(0uHRyOV0RWAh2`K&
z1qSJmU(3Q6g?pnp+C7Z3w8;cD-WEDW@t%6mUkCz3NJ=`7{U@|{`_u9YG%I9eve9Ge
zoPm`0Kmk)Sd?sG2wd-_d%IHB>)pBfbJg;=(VwqY>tU-iYIx9Qk?sIPmmX70aNXdKk
zzOJwBk5w2(Lo-80csrN)PNcsxl51uT>g^H8H&tE{+29Gs6=v|jz$dc%v>GO*KR4zB
z!tShGhF*n4CiRF=LRh+vF%80x1{e=!qHv9)4P9H!=x-)kM=z(uN@xOIN6n_lEAyBBc2-Fi_`D$y6wj)_?8avKjNMeACUnnAos(t^8nZG`5x*-0&aHb@anUT3|JCmC9>bVa*uHaZ|Bv5pWn$eMJ9J6J6#|74s{9p5=vB#DLJCzGH{;
zkN%kU;w7Tj+j&>XGS_6y#*gYk(#8YYNur`1QT0cr>->`|@%rd8VhW#0;*R2G>-PTc
z+@t1EC)8@WEh|nE;3fU{Y5oNnE96kgaV%9m4Loh{blW-zhT*vcsKlV%jQ;k+GAy0LbbS6718+qQnfx>%c*U1A
z=m4YiIPOdel71oMz-pI7ygxtn&^cN&a#+h|BYbOqWk`N{LBUI<;Y|~)_d_*$N>v15
z9@JK4HlfD4>gY2S(Y@XK{hV7-`#&D-L4w-@p{WDE%fjnC;4eXQHqA5llN_2}iCtsM
zjC0*+dM7X4cin2Ev%tnrYidW;aV~Lo7gI(Pn>kKt>8&;~U^VL2X
z41hg9`|4_s$h+adxrLw=MJa)c4*-Flp&JgWdU!_nEoDT@swOYlZrd#J78~%_0Z$8y
zQ`40F0k$@E{aPE}Y`%2(cRjcN!SVj%jv;w5DncG^EkjNJ4CZf79SB2WVDb?J6Fyw-
zihn44#;%a`5jjCe>WaT2nwf8F5GFPL!^@-Q1J;N}rwo{F{8s3Ve@fMBU^Gm==5Al~
z^}^V&G*#Ms@MBnK>Mju-q<`qsAvA?o*@(*sw^bM{GXI=;JepLR6^X-9S6sbowtFxJ_<-wKd7btd@1tQn)2z)Hfx2<2nPZ>#qt0Wi*gBXN|WS4
zu!c>9z7v!0-OodxOy_6JLfnsm)EzJ8+r{8vxHsD;;0J(jHJO85;luOSHX`Q_5fnanWTZ9B{y9Z*8YBnzTL9)C
z0hl;@Ylt`*jWnn?D;n6Ojg<2!W@GivFnQx;K6{5GUhZBXq{ZyRmqH^ffG4MX8l~L#)BYl6m&kA<%@Rz_=Vxn6ONd$Dd?hmp#sR_jXF7|0gEr=|uv{cIQd
zjTpuG+fR;J$1gz#apMe;jL+m7vsHT4+vz)slNr?#1Q*TuKjY+`+rU=|`TPOamHgSF
zr1_7j^BNC6j?Cq!Y8MDSi;_$UD~>vjoyT2ZwASBpw}yE?JWBiWBjYS!sdgJr@ZrJj
zUq=o}Sf~9C!%p#?g@7oYI$-S(kEzm?QWdh<;R#`
z-+iZiiNyW+BP}k;827rhWmwGEiE#>EQ~EFT*6RLtP%lsXs+v^J`wy7qgAs!7;pQ=4
zRHAydMb$G{&Q4l>a^`#wqpy@?d&aZgdoIErG+A9U(@8lmUwuyT_jwlcu$^zzd465L
zWg|SMV)Vw;)?mhvnznnWIyACJ9>AKYFI}UfW_eXY93+S&
zZe=Rae$udA&a2lV4#C->^lygV9Mwsl^Id*~(!cceci9dh
zhxZWsCG$q4(XVOfCpi$MKUG9IF#DH9_NP3@#!WA&&n0N1mqEt2
z?X%3RjuzY|ebY`|{ye(3m1{_oTB4gp^q@_BG{#K9CE4d=MJbRjt^Rh7n_?H
zk6O*S>Bu+#7Ngjp;;d|Dq!28c&7*}nh{*ou5-0b6L`g_I2{DEgIm=LkSl$K{i
zPERimPCubuNp+VOwz9iK_>bo!^P^beU4yJ
zYgg-}@;b$d-Zj*@@1ryt_YmLHH7o%1`69^$bCw!SG8y)mexcw;x8Ymo+>~2I^AtuX
z4+xiB?4=*Px++VwCk%S-+eEtjJ1;z9~
z(yX#Nf`+ps<uP675xg-gT}JyoNO~{$!_7V|54Nu#Xcs*DIt_PLs=T(lFw)cxw7dqn6Qh
z^6yi(YX6gIj-|%41Q-oy!|)DP?KSWtX33)}JF+|0Q$_NYEKxQUJ!CYS7XhpSPv!Pg
zY$d<Mh?$4O8B;>a8s;
zovhB*={Kj`fO@7c$h7ZJ)
zfwmJF1&?ja=d_nKBYd&*0R5qIQtl7LDt7Me^45BHba>53{}_tjMqH
zvms&u3#1UgJUadsAHll5RBxH7su_V`mCUay_pt?V9NyfxTE5Pc3KVvRe@%!Vsdda$
zy9`x$8qfZ8{WlAebnV*E>I>!Cyr`V2^q}2g)zWP3E`hS_igyU+plOCP=PnY2bJhrU=
zz`nl|GBV`diPuv1OF^F>0Hd>+9s)Qn%zt_4+0bilAETHa&V9jtinoUGM@dkP)Z;UV
zLzhP!+<68z_knFjYW7DZgEQ8!gFL-S@wOid__KeBf)q7BeVjlF@7cF0X%9*ycB+SV
zx*s2xH0>pqOuY7gdQ;iHTfi2Oy*1!nCC~>z*!Aoke7X3qj(K8jTc;P9V)Kj;0?$sK
zT&zz0!}Cu4)r`PYP#nO9U*sQ3>{4#W(@JERlY^eXIsmcFt;30MlzGR^t#0{SKRgNr
zDbY$<2)~$Sb$opHvtBb(NZERHqDu#mKk^c5T7>HH@k)!||7DVHC@%TgSTt=!g?~~Wo2sZ)+!^1Z9cQHy91gM^N{=M|{eOki|Rz|-I
zhIJUp*@ASe9eY!oL(8_pb3u;)?|v8UQ4Bch3$6ZjESdj1l)H^#nFEe%)WD6Z0W_{h
z&VWS7>T$G}s*jbXyn&n4TtPK$qwJu$^T^6fPKtfX4{3a8*PBl%Kb=8gznt4
zO=axFrBQ#`Z&FQV>dOmJnl(WqH29J(w6v=`fg8-qqTG^>_21CJvw~xSn@Z
zB7OSXNs{j8`7cY@;Z1SD=9EOB{z*V&L_FIV@hY5#_DVU><7x6xb`*|-2prrX`c=p!
zR9QT#0dC3$&VUR6`One`9#`6BL?G$?PZz%2%qq8^P=r4hsoxhv6
zyiTcFIVm*{r6I5v$XjuBd9fz077Oshx$41(`X>~^?wJ`n;^pr`u2pT;G4GaiD@rh0
zBg^CB;@WC`ciI*qvp860O4OvzVKq
z_CbTs55~drd$V)2e+AF#!mLL8Voo%|X}e_0H)Yy^5dF9gCf?D3+dE6wxcoT9+tJ9F
zm&UPs8qz!E)ivWB1rW7QEA1E**P!5#g<*!{FRaa`
zp~e48x6_;nOwOhNE5e5HtM(kKwY-S`h_V^8Ad
z=sPJMDmGkR7f%pA&zWm~{C#nQkkf-_sH|&(yVwzCVvqV~DF&wz=86@E!Frer+tWZ8
zd2rkh>JIRXV3WU%IGqAUq25y~wxXhWA;{ui>igy(4$14MbHn|2qT{avvkA^u(K=Mc
zY=WZ;6YYB-sDhVuPBHCpBfN(h-+jPcQpgJdNVK>AG1h{C+d}TLtO!$MKJq2Aj#On*wm{a6-tQkZ
zNz-ngJ7WrxE}xnGnkpin42Z*eKYICos)^y5UJ3X&{CQfO%MQ1AhvAv`ZVPwy#MzzR
zaKQm!pZ;%Lwl>KWg|x}Q*iEot;J?)h=%!tzn(4ZH>IGHQJ7a-!f7f~?o^?$*0u^4$
zA_Np6>d*h-nKKPOw*8yTAH@-M_m>REkF$32uMhbCU-xNE91$uXx@G>S&wmahO9#QF
z;h@lSYMzgp?0A`^{h8^*O>Vz7PO+2InEv4N*F7xA7_f8S^3aKi(s5?mBjt-or9+%i
zf%3}nE0apw#$YJ&_K);?$lvLABa&|5cQ#dk1l)>?^vUQ)QLcWHh^>y=X#?(XJrjH`
zmNHH-4Cs_z5(ZpU;3JontoDffybF3V|6JX=#*^~{gN<_$y=9TDBM)g|+H@;88l>@`
z!{pVSDGI6Pp6As?`s5x&-#>%cFRT<_IZK|tz=%=k3E7}~dJcSzssOEsVBlkah>NjY
zxN7M^C1N5rBtr&c^K2C3Bv3Iv{PwPKf=O~T_%|~zrUal}bU}zHzDdc}Gkgguar@&Dc*|0k$6f@jIrK0o)
zxjpP5hZ7Hsr4e#&nRkE6Sp4J@9endMYw2VER)TETc2%pFY%uJ8OUJ?iGNSmv*Z?t1
zrB^M`3o0n>D-rXNAzS9P7gG&0Z8utbl;pR%?%$HRn+OSkB?f48!f7`by(+Gh&tDoH
zC|2Z0OFNt;Thf#jQzcg3qhct3s3ogica~obx=^gqMHz?j#(?*>KuKHt_SDryR#@%t
z=tYZ>nRBrjkfa;5Wf0y~w%7NTW5>_)ObMjF`6SX#gZH;(z;7w_e501LuVLZU4c2f9
z=IjF2?S~hE#RVkhPs6uMNcG(;Dg$KXF&
zHkMP3c=S_>#y}Z@M%GQT7a}w4Gi-?MiyT?ovCZIU^hcdlV*cyt={TWEGUzLH1vzP*-p*5~t7<
zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001
zbW%=J06^y0W&i*Ia!Eu%R5*?8Qol>XKotIBn>J@{a+?T(4Q}EPC|Gc5z<(faIyIY4
zlIkJ|>gIat+LEb*TR}IWQo+Hk9UO(=P|!-7QlyjBOH%to0?wij-s5}kKHm54-T}Ya
zB1TBDJa*28@R0k)-8gR+$c?fo?F)%655)9w%#Y1SKygB(6t90m_wiFudIyB#5bBf{
zB+JJiLn`V%61tc1Bj81C!9HL`F5g=@5bTG`Fi`H81ELIsiohuhuksv>E7U?(AnFsTHQ1pO
qLPcdfAp=S-gvcBG@CpCz58EdX)MW=VKWc&i0000ERLtq$PovpM@DnKK7`*Hc`>Lo}tmx#W93qW^#f8
z>xOSE3dPGCJIoNbrVmFzh}nlUQ%FISJ@222WQ%mvv4FO#niJLLdMD

delta 920
zcmV;J184k$0@Mc~iBL{Q4GJ0x0000DNk~Le0004}0000G1Oos706=-I(vcxce*;oU
zL_t(YiOp9{XcIvg{Wj^gP1DZq%}^-zUJQkTAg!%8kKKz0K}3&5Y6C5J5Tqigv=AbA
z=)v|@)Qb)E;wkB+f>27K;15b!gQn4#bX9~_Y~nZH>?S*#Z7fL+elXqcm-pVhm)YIf
z0JO4#MoZ-ys<3pH-4a8t;N&rcf0zxr)e2X34K>J9E%zDQ62nu4<0ut;^qQ>ujS@@l
zljcKdiAIgIvLf!2=0gQq;i>8B(LuR4rUOfz_k=qACT)RI%9)V4kru7coiyHIGnN=P
z%lr=P+=P?GIEEU+Q&{A%g<%WX;{+vMWcs^%PP@-0IVJxo2HEYggXwo9fA1=GsyeHz
z=M?8k#t4Sj%OC{It{4Q8U4|TrU4?N74~9(0>R}<)Yjm3M^>UI%R&TR7IttHW3F9T&
z@zUEvl(GzQV9R+R7_TTimdx0Fq71+?unCxgvXFO`eT7h4(sPP)Wn%;bv^xSJ9fFB~
z=?S$3j|_Ir)KOerr`9THe-=$8MrfUbb|9Nl&>{4oBfeVUemszj?JBqi4qnPg4ECK+V?Zkf-jzBsl=2jIbUW0lKWr5|dQK5nHYVKT<=1X1G57{uMNg=HoJTX2
zS;#<#X!aV2bV6nL3b1}<6Sswk6N*15@SZv$o4Ae*5I3AR6kCI5rX7mp`PVGNsO{3L
z0EjCa6YlXr5!%MtfBI7CdC08*4M7>m-v;gHUIOx|86CPeHt-=c3~cTf4alTk;McUh
z`_?Rv9$?G*9k(Cp3qwhiF$8P_d5fduJ70-;Yi3?J$EN9F%q^sGIG#=Bclxsi}=_f*$4ZeO6TY8aqbxozb8f>%p4
znBUHKucdhd1?R0PmjNIKZQ9tlJ?vH00007ff;B!-x45L^NFvJMJtme22
z1os#i*agHMa3(PDB|tQT<$6JKKudw*O9Q4ca1~&9kl`kS1(<&S6(KcieFColw*yF*
zG=?0v1E0c%y$rR;4uu*uSF{zvK#C^*cbgeFfY$zgT!10RQNVinL5H~`l1cBizJqDT
zcQBE7gk&Vp=ODQWm~udIL58KF3{(O@pHmCGNT-@nqhJ(_aBzlN-~bhk0sv9I^2maT
R&#nLf002ovPDHLkV1m94s@4Di

delta 645
zcmV;00($-D1H%O&iBL{Q4GJ0x0000DNk~Le0002i0000G1Oos70GNE7w2>i8e*!^C
zL_t(IjjffzYZE~f#=lKX)=iq-#e)Yy5DFd?p%C!WO1QtMDG)mKwe=4!Ned3L?g#7==hIDx{uGjR$6c>ljg5|KudKe{$
zi?J~aR%Wt1@=^{TVLV=OVK=TMSr@^s*eNlzvbz*J<%P!uSG|
zm5}XfX#m_`3t?X4S3~pcKs??@hUaU@)bn0~Wv`-)!lK2|ato>&r@Z4FfA-6c9L6fH
z1K;k@_UaASF07Q?VmYR~PO?M&UOtv#xtL=ao@52s_UwDyB{};}N^jtVGD8eAKyFdF
z42CRWrQ{ZhTzOfqm}d3xM^>lYoWPprxb&V0`Gb@Wx?L|~IRT1coF%NZtXVj~h_x)M
z!-`+WS+_kC&IZYbey?H2f5j*SpyErHmFT@jvSf9shd-(Q`!<&~%yFZJ@5pzPtTVJu
zhtp1Nih8MjQL1JcySV8p*3OV6thB6Ij7iZ||+Oxdh7aqJ}W*`+B_<(Jgh8OFj3LFjv>R-#W93qW^%#;
z&I#MiZhYF+)cCd9u;coPdouNj`iE5-_bbHx3%2ZIVrzTNvru8)MMcJS3~c9`6LQ}$
zCGjsaH29#}P`O#{16NLB!ULa#32dK!+|NzRV866qUc5m?SyF79<&6D0YOhnppr|fi6^~C7sP|$rFar41`&EFN>R|F
zP`0;T^j16?^dg8`J;YOxfCn#vYtUG!*)H~?2OH}G#rq@;)sCi~`__rCe&?VAno
zpDbyJXC{KSn_|R+XNTLQ7^9kue@<_DPuUHlYEz83b^4*y4m8B67TKuwX2I6mLu$~5
z&_EWPSu=fad`Jy{fOeuG1SNW2R)=)AtV6X<$225o=exi`X9;M{tqDxpUbnGQa*;aR
z6^L@1EfwEQ^O0J#J8l4}N9NhF9#Ol!2
zM_fF`L-I1BhM9t5ORHE4>X0+`*ictD_&|}~Q2@<=soAH?c|p_h*m)E-dmba7f}$g7
zChVAo4wO3DmPDRh7p1&n>zO>dfrcm0+#qk%J{N^98n^*m@@f1iCWuHxJX9CIcul8U
z{TlEF$@iB%kK2jYrgqHve;jD|?l__PX_ZWh${_0
zJAD;D$dg1JQqUGy9cWRty*eP&NAjy$6gptw1@OqHVUWYRs$O6bWj~(Y#i%V+@eOGw
zrlAF`$?onrc`1QvwzRyN>Qr@?xrqkHlvuwh--G1h3j)V4NFtV}ZTdrLs0(O{RLL^%c@z;S+6JV<^1
z
zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001
zbW%=J06^y0W&i*J&PhZ;R7i=vRxxN3Q5gO%@r+5@cZY*YuviduD275IAgx9x$K2u|
z6tOr3DLuqZDlHw93MB=H4%V%xiw!!8NhhZafesy%dWyziYR2i=fVyD8n`w%SbJu4Z;n
z7X3&6oUAoM^jquIQYZN~eJ#_0qtWlF9xb(lb?OH?I1D;?-|;OQf;~cS2s`$tRI`mWbVC=}9dPN%Aa>(Ryb3Ket*MH$u>6#OSnK
zB@?^+KB-xCR|$1Xq%!99dFdVS+_jXHtK?w4t$&G4U6Qt#B{%M|wzJJQ?(O%hK%r2;{^dXXnHl9)&Sue9D6C;=grC&;-*ib8(i43l
z7oJOIxTf~Pa$W+0P1y3PK?=%;%5GMYj*kjNKi?2lY|0JzgB2IKv`X){MW?0<7~#V%
z?0O@IRGRu~{kwJ~<109bdYMK8ElwIN9o*|F)GJ-VY6rKa>MI0yKE~7SjdmtJc@olSm{!KE8l}05BMg$KwG200x6mP*A|(
zaOcmTMUz5r8`6$N})J2c>0q&Nd1A5{*&b86pL_<0gn)-
z&)M%KYE_1vMACyrslCNEneDCUbh{tCzIfG;7CY@x3Xh;LY85ym--o|0t%MyO{$vlM
zec5nTZSpEMJAFU<@rY4g6blM7euRUraTqZyVDULE-tr}T#RcS!>rVbdp+Xn
zaCuAOd^1b6vf{Fm(mD|(KHWC4M|J(&r*uP>>N76>gU(uV@3msBm=Q7$02lOvRbnUp
zzl)I#LL0hsdI$~r7a
zxeWQxQehg7AvhFWA-wi=)?4o5r+5Y1n)}QP>x=eXO_d9%L^t2LU(kF-8=k(oE>zeu
z`ix~9tm;hr{?;e~E^^;p64N*2cEIhrD0gYB2CQ=Cw?>qln#N~>6#>rPG;SdntpMba
zddpF(pGQKgALSK?sQz*4>^7_Nn#)`8j-Tx{RcoH>%%*xFYV)IqH%y}sCRG#iMPlti
z^;Y?81|n^7=rIq0!Cymp^!I+Xp%ZF+PY&a{N)TzE)9A-j3g2W#DB>WzMGvr&_uk|P
zceP5USqBdMUmOWsVNw6(}PK+16&S1a-aTb2f26+8ORQTgtD{#vZ@(2JTM
z$$bpx7}q;`JazM_wihm&w}ZGHy$2S3$lL@48El~U6;PZp=|bZTUHt2sq6J~nHzIh{
zpjlzJueF-8uV|%*;gKO=s|Qw;6+Q|iwZ1%RR$`xA(a8a>qOtU&E**I9t=kIJvlPU}
z3OS(|5dL@urTP@m>Y0X72xdhFs;tR8Ef|BA7bo@S-gww&I2?K3R{svMi@a-sL=72V
zi))BViJDIzMD2Xho5?-y@kK2*otqFK5yu*8c8>EXrPGejemH^qmal410iC&@QoGf>
zt!22p`l=d_KIDA0+Xh?09_44jPk;vhv
zA3)6NnEVFHm*UtN!KOvAc8vtuHag6s@I+^GUg($wUnt7^=vA{1Ev|(qj#O&l<1t=se?_Agdu9sh-5PhDT7
zJnV^P#H_t{z8n273qwT&vdkAb;h){+>Tx~)_VQr7!yqZo{=!jGel)j{IPGb#@{05h
zwJY$VgyXui4DRe>w3YdYMC)oIZ5F9V+r!^#;Ni9iSTveEPN(euc$drMp~w$Gn7qRR
zI-BO`VV#8j3{xS;hL$|_el~X0STL(b%^dKp-eOJ{|A^ex>ili~M79=8pVDh4?jc|G
z(;ks%$w`1{y#wybs`x)v11vir{oO&
zj7-Zk{IPUi<%ThC37IyT+O93e*>wN+^4ZL5Q|VS|4thd%e;~bG&z|$)k=M98s}3%5
zu9@p`IdD(m-J!
z9A;Fel|jeA%hPSH>KgU9;8W^XUA%mCcTIl6L#j)O#bP`cmtmK79yJRs;I1Nut#=hi
z@GaI^fg&DEMyOm{p15vXR@FFmLIC#c=0PcI*p8R#(q2)VO5bzE?@kcO@kKWIiP#FEg{oF6TwrFz{f_CL4Emwur}
zA3-NFJR!WsB#q2j=;5kx;6L3*EZMNCC|mU$5pxuF4-wl1VZGnogRixB+65vHLDL0*#|zYSqxOqA;41YGNiBQZ6(0uHRyOV0RWAh2`K&
z1qSJmU(3Q6g?pnp+C7Z3w8;cD-WEDW@t%6mUkCz3NJ=`7{U@|{`_u9YG%I9eve9Ge
zoPm`0Kmk)Sd?sG2wd-_d%IHB>)pBfbJg;=(VwqY>tU-iYIx9Qk?sIPmmX70aNXdKk
zzOJwBk5w2(Lo-80csrN)PNcsxl51uT>g^H8H&tE{+29Gs6=v|jz$dc%v>GO*KR4zB
z!tShGhF*n4CiRF=LRh+vF%80x1{e=!qHv9)4P9H!=x-)kM=z(uN@xOIN6n_lEAyBBc2-Fi_`D$y6wj)_?8avKjNMeACUnnAos(t^8nZG`5x*-0&aHb@anUT3|JCmC9>bVa*uHaZ|Bv5pWn$eMJ9J6J6#|74s{9p5=vB#DLJCzGH{;
zkN%kU;w7Tj+j&>XGS_6y#*gYk(#8YYNur`1QT0cr>->`|@%rd8VhW#0;*R2G>-PTc
z+@t1EC)8@WEh|nE;3fU{Y5oNnE96kgaV%9m4Loh{blW-zhT*vcsKlV%jQ;k+GAy0LbbS6718+qQnfx>%c*U1A
z=m4YiIPOdel71oMz-pI7ygxtn&^cN&a#+h|BYbOqWk`N{LBUI<;Y|~)_d_*$N>v15
z9@JK4HlfD4>gY2S(Y@XK{hV7-`#&D-L4w-@p{WDE%fjnC;4eXQHqA5llN_2}iCtsM
zjC0*+dM7X4cin2Ev%tnrYidW;aV~Lo7gI(Pn>kKt>8&;~U^VL2X
z41hg9`|4_s$h+adxrLw=MJa)c4*-Flp&JgWdU!_nEoDT@swOYlZrd#J78~%_0Z$8y
zQ`40F0k$@E{aPE}Y`%2(cRjcN!SVj%jv;w5DncG^EkjNJ4CZf79SB2WVDb?J6Fyw-
zihn44#;%a`5jjCe>WaT2nwf8F5GFPL!^@-Q1J;N}rwo{F{8s3Ve@fMBU^Gm==5Al~
z^}^V&G*#Ms@MBnK>Mju-q<`qsAvA?o*@(*sw^bM{GXI=;JepLR6^X-9S6sbowtFxJ_<-wKd7btd@1tQn)2z)Hfx2<2nPZ>#qt0Wi*gBXN|WS4
zu!c>9z7v!0-OodxOy_6JLfnsm)EzJ8+r{8vxHsD;;0J(jHJO85;luOSHX`Q_5fnanWTZ9B{y9Z*8YBnzTL9)C
z0hl;@Ylt`*jWnn?D;n6Ojg<2!W@GivFnQx;K6{5GUhZBXq{ZyRmqH^ffG4MX8l~L#)BYl6m&kA<%@Rz_=Vxn6ONd$Dd?hmp#sR_jXF7|0gEr=|uv{cIQd
zjTpuG+fR;J$1gz#apMe;jL+m7vsHT4+vz)slNr?#1Q*TuKjY+`+rU=|`TPOamHgSF
zr1_7j^BNC6j?Cq!Y8MDSi;_$UD~>vjoyT2ZwASBpw}yE?JWBiWBjYS!sdgJr@ZrJj
zUq=o}Sf~9C!%p#?g@7oYI$-S(kEzm?QWdh<;R#`
z-+iZiiNyW+BP}k;827rhWmwGEiE#>EQ~EFT*6RLtP%lsXs+v^J`wy7qgAs!7;pQ=4
zRHAydMb$G{&Q4l>a^`#wqpy@?d&aZgdoIErG+A9U(@8lmUwuyT_jwlcu$^zzd465L
zWg|SMV)Vw;)?mhvnznnWIyACJ9>AKYFI}UfW_eXY93+S&
zZe=Rae$udA&a2lV4#C->^lygV9Mwsl^Id*~(!cceci9dh
zhxZWsCG$q4(XVOfCpi$MKUG9IF#DH9_NP3@#!WA&&n0N1mqEt2
z?X%3RjuzY|ebY`|{ye(3m1{_oTB4gp^q@_BG{#K9CE4d=MJbRjt^Rh7n_?H
zk6O*S>Bu+#7Ngjp;;d|Dq!28c&7*}nh{*ou5-0b6L`g_I2{DEgIm=LkSl$K{i
zPERimPCubuNp+VOwz9iK_>bo!^P^beU4yJ
zYgg-}@;b$d-Zj*@@1ryt_YmLHH7o%1`69^$bCw!SG8y)mexcw;x8Ymo+>~2I^AtuX
z4+xiB?4=*Px++VwCk%S-+eEtjJ1;z9~
z(yX#Nf`+ps<uP675xg-gT}JyoNO~{$!_7V|54Nu#Xcs*DIt_PLs=T(lFw)cxw7dqn6Qh
z^6yi(YX6gIj-|%41Q-oy!|)DP?KSWtX33)}JF+|0Q$_NYEKxQUJ!CYS7XhpSPv!Pg
zY$d<Mh?$4O8B;>a8s;
zovhB*={Kj`fO@7c$h7ZJ)
zfwmJF1&?ja=d_nKBYd&*0R5qIQtl7LDt7Me^45BHba>53{}_tjMqH
zvms&u3#1UgJUadsAHll5RBxH7su_V`mCUay_pt?V9NyfxTE5Pc3KVvRe@%!Vsdda$
zy9`x$8qfZ8{WlAebnV*E>I>!Cyr`V2^q}2g)zWP3E`hS_igyU+plOCP=PnY2bJhrU=
zz`nl|GBV`diPuv1OF^F>0Hd>+9s)Qn%zt_4+0bilAETHa&V9jtinoUGM@dkP)Z;UV
zLzhP!+<68z_knFjYW7DZgEQ8!gFL-S@wOid__KeBf)q7BeVjlF@7cF0X%9*ycB+SV
zx*s2xH0>pqOuY7gdQ;iHTfi2Oy*1!nCC~>z*!Aoke7X3qj(K8jTc;P9V)Kj;0?$sK
zT&zz0!}Cu4)r`PYP#nO9U*sQ3>{4#W(@JERlY^eXIsmcFt;30MlzGR^t#0{SKRgNr
zDbY$<2)~$Sb$opHvtBb(NZERHqDu#mKk^c5T7>HH@k)!||7DVHC@%TgSTt=!g?~~Wo2sZ)+!^1Z9cQHy91gM^N{=M|{eOki|Rz|-I
zhIJUp*@ASe9eY!oL(8_pb3u;)?|v8UQ4Bch3$6ZjESdj1l)H^#nFEe%)WD6Z0W_{h
z&VWS7>T$G}s*jbXyn&n4TtPK$qwJu$^T^6fPKtfX4{3a8*PBl%Kb=8gznt4
zO=axFrBQ#`Z&FQV>dOmJnl(WqH29J(w6v=`fg8-qqTG^>_21CJvw~xSn@Z
zB7OSXNs{j8`7cY@;Z1SD=9EOB{z*V&L_FIV@hY5#_DVU><7x6xb`*|-2prrX`c=p!
zR9QT#0dC3$&VUR6`One`9#`6BL?G$?PZz%2%qq8^P=r4hsoxhv6
zyiTcFIVm*{r6I5v$XjuBd9fz077Oshx$41(`X>~^?wJ`n;^pr`u2pT;G4GaiD@rh0
zBg^CB;@WC`ciI*qvp860O4OvzVKq
z_CbTs55~drd$V)2e+AF#!mLL8Voo%|X}e_0H)Yy^5dF9gCf?D3+dE6wxcoT9+tJ9F
zm&UPs8qz!E)ivWB1rW7QEA1E**P!5#g<*!{FRaa`
zp~e48x6_;nOwOhNE5e5HtM(kKwY-S`h_V^8Ad
z=sPJMDmGkR7f%pA&zWm~{C#nQkkf-_sH|&(yVwzCVvqV~DF&wz=86@E!Frer+tWZ8
zd2rkh>JIRXV3WU%IGqAUq25y~wxXhWA;{ui>igy(4$14MbHn|2qT{avvkA^u(K=Mc
zY=WZ;6YYB-sDhVuPBHCpBfN(h-+jPcQpgJdNVK>AG1h{C+d}TLtO!$MKJq2Aj#On*wm{a6-tQkZ
zNz-ngJ7WrxE}xnGnkpin42Z*eKYICos)^y5UJ3X&{CQfO%MQ1AhvAv`ZVPwy#MzzR
zaKQm!pZ;%Lwl>KWg|x}Q*iEot;J?)h=%!tzn(4ZH>IGHQJ7a-!f7f~?o^?$*0u^4$
zA_Np6>d*h-nKKPOw*8yTAH@-M_m>REkF$32uMhbCU-xNE91$uXx@G>S&wmahO9#QF
z;h@lSYMzgp?0A`^{h8^*O>Vz7PO+2InEv4N*F7xA7_f8S^3aKi(s5?mBjt-or9+%i
zf%3}nE0apw#$YJ&_K);?$lvLABa&|5cQ#dk1l)>?^vUQ)QLcWHh^>y=X#?(XJrjH`
zmNHH-4Cs_z5(ZpU;3JontoDffybF3V|6JX=#*^~{gN<_$y=9TDBM)g|+H@;88l>@`
z!{pVSDGI6Pp6As?`s5x&-#>%cFRT<_IZK|tz=%=k3E7}~dJcSzssOEsVBlkah>NjY
zxN7M^C1N5rBtr&c^K2C3Bv3Iv{PwPKf=O~T_%|~zrUal}bU}zHzDdc}Gkgguar@&Dc*|0k$6f@jIrK0o)
zxjpP5hZ7Hsr4e#&nRkE6Sp4J@9endMYw2VER)TETc2%pFY%uJ8OUJ?iGNSmv*Z?t1
zrB^M`3o0n>D-rXNAzS9P7gG&0Z8utbl;pR%?%$HRn+OSkB?f48!f7`by(+Gh&tDoH
zC|2Z0OFNt;Thf#jQzcg3qhct3s3ogica~obx=^gqMHz?j#(?*>KuKHt_SDryR#@%t
z=tYZ>nRBrjkfa;5Wf0y~w%7NTW5>_)ObMjF`6SX#gZH;(z;7w_e501LuVLZU4c2f9
z=IjF2?S~hE#RVkhPs6uMNcG(;Dg$KXF&
zHkMP3c=S_>#y}Z@M%GQT7a}w4Gi-?MiyT?ovCZIU^hcdlV*cyt={TWEGUzLH1vzP*-p*5~t7<iBL{Q4GJ0x0000DNk~Le0005b0000G1Oos70BwtcXptdHe*=n1
zL_t(YiM3ZjNEA^R{%5Cc9nG1gizG%t&?OSVQz+S`f-ddFpi6e?;6YqU=u#ncC@f?T
z9=sG?1iR$YrAw?{Is_sUQV@YmOPOW64uw?EX7B&syxI3=W@lEjA7^;~oA3Yr@0&Mo
zb_CdQ=((NOM#h0%=Br0hPF8JxfA|ULBhh8)`wlzb3eD?1F}-?YGKx&iWdy#0glMEq
z(qa0LA^ECl^TSU7Dh-JCIn1mZnr<1Fl1$*@-B6ZS0T=WhMqoDSvyrxprz0;zEJs3Y
z)2CI4*I^|p4cw@T)VPUgpiQ)OWr#K|A-3r=wKE-Rzi`37`m9Lgb;v8wf9?!q!7QB(
z`dl7hccgrMo-%!8%r$Pa@%jh$JREvjf7ABVEC~(Ys?{7!
z{pkkF_I+X+_GxujKgRg9lYCM=!Gtb!z*!aelG;1UC#goC{RrwTw7-w`sY&a}-dm4h
zC96Lop95YR_Q~!%mY7c1XG-x|jrK|P1QWWv^$fr@Wj%#Y)8RB#Up3%!yVue3@D*CC
zQ9jF%v4w`toR&8if8dFuU7`KS-b0k~ohtieJE=qXH2pnPLAtK6&kYIS@6Qen6S~j=
zXRQ-*ZF27@pQsw}J!C91=)uzbJy@FqIw;oWtXT)vOJiABTwE|GHrbo2543mdKZ`Kc
z`}{QhuJ9Co7yKeXBuw|R+5LSuWxW(SCR}Jgd2^C8W2POUf6p;dZJygi0#tzY1oL!R
zv!C9$oV89!+T`9Gg>4xJl4BE8&EhrtuEFQ`B1DHFJ(dVe6YZeEPJ0R>HA7zvgLvYz
zpOyKvLJrZ@UOfbL4XT8sEnHoY$vt~ovp>oakv=6x!7n@|@^Kdvs}l*Et5&}Iwi_ie
zco+jR5
zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001
zbW%=J06^y0W&i*LDoI2^R9J<*S50WtP!OK9uG?+hm*7Pyih`&Iu@njgsZu?O2QeUm
zf=E4z=q_3hB5FaQQb8jKdeK`!FLo&&1hIM&1ksg(KL{G7w$++#P{bd!_05}P^Inoo
z*59GseQ)NQZ)U#aWp@Go%o@!k{bj=Xtwq_feE{QSX#>z%4ySMd+U4D`lz7NG
zQlZCRau8Lo!{QqBZ9E|+H&exBTqW#q70S{^-Uimx2T=4kAqGEQwQMMOsy3BJ*wcX^
zCt5ew;u@?cCK|(LiZX6Sfz&4lT2%x+<<{1d!!i|_SMi_A;Wy^WxP=O&ZaD&XLqf$W
zOOk~v{4Y7202AQy259}=2C$Kh5SF83mTy-cp{tiYHF0*=Nwf3G7IvbV_;x=Sg%&Hx(#-rNwfIl3N-lvjmtWZRdL;T~T-8?)sR>alUgU>*)
zDkE?27rx#z?4{(#4j3kDGn2NA=XEcvvqWQ92g~EkVi?fdp}}r0LPM$949PKW&9#8-
z2Cw=J*a#(HgHs4Wlr{)w0H%3}l9h|{ZdVCf%_ci?m8nFVPhXC`I~@EI{A>^G0ayit
zxGDfwP_WAIC5G@d_Nd2>cOa5m+H*1<>$5&py#_LLf&4
z1?ARVO^(PhELfPVlyq1EIV$mT2!1h9z_aaif(It;<6{oLBrsqG&jmA7LVLM4Q#-L$sxbafcuR<
z%5F|M=C;SZP0+`<=e0~s1!05zN
zo9KNiDSK?l$2wXN
zjbRZik28y5AkR-i22aBdsA1>)g#pqdDTgoH`2QTsPiB!XWP+HyN-$%}r#}}3c($#Y
zpk_z$=p#>rN2BDo5q3*1?-g4dZQ|D~v)*5Yzm6-G7_1ABhX0&R3Z426Oqt*tkY-HQi7M2|&k11)$Eq#~%a5F&W!
z!S+_viw*VSDe0wxP)ecT4@y~srqP&mRfJY-;y2&yCOeyLEJ+T2Fx~E#_ujmh+1=Ry
zw6cOmOXV7>uymH)5<{-w4D4nymYc5=-ur
z=0j31aWe=2sWI;*Vb
z6z59D2!_|oAOy^=7zC1Ch8&7rg>eWEhD^xnVIkIQbeiz>a*{??Z?iZ$3eRB)<0abh
z(%VCnvJ7!x%XuIeuP8j0%-DUR48St537CSikav}Rg-~14bBc3iV*~@VI|3mcf{B3X
z3AF`}40g@bQCwZ8)+%Tge@!JuXq|(0Ae&OqA@ralzFOgaJdlj-D!2v@Br|rOC}%J-
zyMii*LcSJ8ZMR;fI9E0%+%pT+_yUe+YD0CKaQ0<_qc^GbqgXUtp|DG#f*&UMsS`?z
z7C%cSH1BO%a1Ka$Sc(djLm^)aqqc7-&XtW-LXGfaZ=&a8O{hyoe+Ou@h*q4HssCaK
z$Uui^_8N$ELS^_0uzqC|w}prkia#juo;o3$xQ-1FH=H*VTZ3n&9g5`n*DS-R?b53N
zh$|Zt?(snp+Q!-Xe^Tjr$gKbkK^e&32JPow0`jRD9lAF*@F6n{Z0;8g$fRE2*R;L+
z)+~=6V9WX)w;$;XLrIh|1Z)F&i=*V@kG+ZUKFSeAd7s};=2o;PyRR)SkB(kB2Ieec
zQ@f()0uZ+Xp-(vsAL;l<<^NpttUZRtyIWDYk&tfpRM$0MZJ@4d7@$|VZRGocS4%XQ
z-_ESMnnM0d4aD<4SpihJGNjLE9#KBKuvETVvU;u#qocl{Q?aH2r6WJdP1Pl`yS}e^
tsXCOUf0?1ejj>5UOJ6{FY5&JhkH2$2g*iEr_S^sf002ovPDHLkV1g(#swMyc

delta 870
zcmV-s1DX8P2crieiBL{Q4GJ0x0000DNk~Le0004t0000G1Oos702LTcjFBNse<4Xk
zK~zYItyW8G6HydClbAM>l9}K_rBEmcZp2au2%1O*7cM)Sf^MW+7a>6fS3aN%rG+vJ
z!ESUH(2WiLfYgN>p_D+u2SOZ6ZL4wOAP7EF?>TqwyfT>?YY&;s+&ka-&iCEN%mD0X
zq_use1CaCtpb=kdtHqDK#f3HYe|NL5J3SeZQ;db)ddEOYCAxIR^0t%~KjLFJtaB~M
zN0Gf9k$1NbS_=rAEh5N_(bMxblG{+jI++bMW(kDm`64h5wwyQ{M}j%YY=qJ>8>zkI
z1to;Er+3jz9HoBv0dyr`Dz-Le@Yf~HftdL
zy3TAoz)YlaW1|J>$~B9CcAhKp1a8Lc8dW3cm8yR_HmfxRF&pySiVdRzwi=>kvpfkY
zBUgh|Bd7UiV@n^hR7;$&=4GhDE=TgwQR*G34vTOc>WoEVHomZ40{F-C)1?Lh`$pBI
z`x8`6$IGzUFzGj{WepDFe_FX3P75OzltC^)T2C1P8<02DmN+5fEVSVdN1CF>$T;IV
z#e|e;QQ=?{pic+^2iR!yYSA{H0uCy|xK^%)(}H5LYZmhKM!<&2^_#AZ79|qWv7t_M
zKft}-1hUvR2+${lfP-zAu{OSTyBdcHt*D06qKz`bNA>*sWHtzCe=3GE8z4P~cHuPH
zm=aWBvw@_F*P&-oxi-23XTuidXtiepgDt8dL#n}N$aRz1Af#i1tF5alx
zCsA6M^Tmryv@djap%KSG#AYdLAeF07p
zfc5Ry29-gmbhLptob1hIjom|>JXhkPgjQ0+X(7)ZDj9sRT!f@SNcS~2!w9gI(b)e1
zT>zB67vYSX_tD#*(Yy~f8N#z|nXUpK?O0;07*qoM6N<$f}y93$N&HU

diff --git a/docs/html/img151.png b/docs/html/img151.png
index aef24ec9eff613bcfd484d48e4fec80e6c6175ff..7e4038a875d48da6c953bb0fedcd1faeb1698154 100644
GIT binary patch
delta 645
zcmV;00($-F2g3y+iBL{Q4GJ0x0000DNk~Le0002i0000G1Oos70GNE7w2>i8e*!^C
zL_t(IjjffzYZE~f#=lKX)=iq-#e)Yy5DFd?p%C!WO1QtMDG)mKwe=4!Ned3L?g#7==hIDx{uGjR$6c>ljg5|KudKe{$
zi?J~aR%Wt1@=^{TVLV=OVK=TMSr@^s*eNlzvbz*J<%P!uSG|
zm5}XfX#m_`3t?X4S3~pcKs??@hUaU@)bn0~Wv`-)!lK2|ato>&r@Z4FfA-6c9L6fH
z1K;k@_UaASF07Q?VmYR~PO?M&UOtv#xtL=ao@52s_UwDyB{};}N^jtVGD8eAKyFdF
z42CRWrQ{ZhTzOfqm}d3xM^>lYoWPprxb&V0`Gb@Wx?L|~IRT1coF%NZtXVj~h_x)M
z!-`+WS+_kC&IZYbey?H2f5j*SpyErHmFT@jvSf9shd-(Q`!<&~%yFZJ@5pzPtTVJu
zhtp1Nih8MjQL1JcySV8p*3OV6thB6Ij7iZ||+Oxdh7aqJ}W*`+B_<0000G1Oos706Sf89+4qSe*Lt*2yVns2o$81b|boxX48cm>BfbNkf4Qb{6QB=
zl`=xXZY*vJx-r3x8%ewALI@>L@Pkmt65DD_90WndHokk`Of#QkCenDx{O&vVoO|ZY
z3@-rxC&H-?6G~beps3@Dr2#fefBROJ@9TVj6T)d{K0M%4lnjL4`oKXf?HzDv8;;8=
zH?@C5a8MV_RcE^Uw(TO~s=4cdW}N_eB8eaurzdtDR~Dc-m}+s`Tqkb?X8~dh7~hpbml-xZ*G~Xh7^k@)j^joJUHXD07VYPxm<%t|BUh&;5k^h030}5i
z(gHL1IS*xQ!)>T4oKzcz=5`x~s31COSYm3T_KA`l+b{&H-j)d2f7(zr(9ri)T*kzFGB1*I$(LuvXS-6EeeX{l15VR2E-!>Une_a79<&6D0YOhnppr|fi6^~C7sP|$rFar41`&EFN>R|F
zP`0;T^j16?^dg8`J;YOxfCn#vYtUG!*)H~?2OH}G#rq@;)sCi~`__rCe&?VAno
zpDbyJXC{KSn_|R+XNTLQ7^9kue@<_DPuUHlYEz83b^4*y4m8B67TKuwX2I6mLu$~5
z&_EWPSu=fad`Jy{fOeuG1SNW2R)=)AtV6X<$225o=exi`X9;M{tqDxpUbnGQa*;aR
z6^L@1EfwEQ^O0J#J8l4}N9NhF9#Ol!2
zM_fF`L-I1BhM9t5ORHE4>X0+`*ictD_&|}~Q2@<=soAH?c|p_h*m)E-dmba7f}$g7
zChVAo4wO3DmPDRh7p1&n>zO>dfrcm0+#qk%J{N^98n^*m@@f1iCWuHxJX9CIcul8U
z{TlEF$@iB%kK2jYrgqHve;jD|?l__PX_ZWh${_0
zJAD;D$dg1JQqUGy9cWRty*eP&NAjy$6gptw1@OqHVUWYRs$O6bWj~(Y#i%V+@eOGw
zrlAF`$?onrc`1QvwzRyN>Qr@?xrqkHlvuwh--G1h3j)V4NFtV}ZTdrLs0(O{RLL^%c@z;S+6JV<^1
zc<@lNsE1yvg&tZe
zlsyP~(OW?;HuMi@^(ch0P!L6^YpHFuW?h7WKU-(so7wEIBpX}sYc{j<=6m0~ZzkDH
z0gfE$($Q-sfMO;f`k_e|pf@x!aUl#CL7Hg-Co_e2;MNJqyR_`jK`0Jv|577T8&3)Na#3U0A*&R0NV1UkmIeje~}-z-^zw7
zju#Ieo;P84(|}uLT;PfMiM^eR>G3=6hJ~?5!z})ojc}5$7?H{;T0eB2Il#)0?E@3x
zS{O%;U!tEsW4cyR3wxpl51VC!hncQAy+SmyB`wf&`XHq2ZUa)4?o!aPb`#2QARAl*
zv%}S0I13Asm7B^K?BVzMe|m)l*h^V}d4R8Mgp+&_shC!idra)mE-@{Nhxe+6;{&K=
zie4m}w0lZjHqpoySrF6ZTsQ}60n%p54mlo!b@(G2EF1E+Zov?nRQ
zzBqh+ILYsrQiG0(9j%$-@s8I?tGVMPV5^HXvPBlebecG+%Dl!zv6aSLKPjqfo-kD33F%(3ze
z)(e{DU})0#RjE66*fKJVu)_c+#W{AUD$S-nj;)#EoD+3C;CJjaaJ(d^^lXVe=3t-d
z4qGwc3v@fl9BVJ&f4MDZJLO(6e2&>yZB8RqtQ8jn3HR`AyeNdUjaFSAHR3cH8n!`L9Zf6n3}T#Mq2!|Qtmo&>0z2u+CmFrx;#4qXZbPs8YD%QPodJi!u~w)*eJU)rXYb9
zK8uJn5b;rnWl@}>p8`{t{3mv`LAG#&2-rf|-YEUh$X<|l;ge!KnzF*j+4izyu-}@}
zK9=RplSK4pDJ<1KOm+;K9QqFd{r~*8msgWT|e*(@)
zL_t(YiM>`aXcJKw{x0#1N!oXZgG#Vi5OgSpLLnfnMkmMI;vf{UI0Y#^#7!zK9h3?s
z1&0pSt*DC)I*LgrrwoA(9h7>C#$arEScEz>^}YYyU6M;`LMZ-l;r;*rec$`;y?1v3
z{#yi%E+DzZBW_C~({YU?ttTjUPTkF+Q
zC;2vgEz^Oc(eJ4qEwzJn>IXVF64UeO*P%R2>R`EReoKjsybYyRw!qHccW(MjbpheI
zJaBi)sVt4!2u|L!#U)ipPxRRZzF9jwDXk|3dRgEFo3M$ElvJpEH6jnGc$SFWWa&vQ4oUJXjnR5$`aic?8aG1FX2j^UTqP5`{648!byo>>
zOQbU9^?B(X@Z7bOl&j=my{&(VOKm3^)#UHnMMOGP8uv7-0LaSD_y~A2e-;ohvTFkxo$umzl4VxT9n1Gk#W~LW)8&ZU{}kOtEV#(s(scBQ@p7)P`m}`zO5Vxt>(|)LYi{aG{cm|
z8Sob1&*elkW(rG?ru&nS^T$zZN=|og-8!sbb-Dlh#g}4TDI}karh3M4+TfWV%(xrl3We0HR#UL=-tK-60?MAR9dt7d)oKq*L10f&V
zK&ePNc|E~Mh$&Xk;wu7bYX*T_Ys#@xtI7^N!FrEk3|q89ppR#BbREPTf+NQL5t|BS
zVxV=6+O(xwRNymjlZ@Gge{qVrGNd_V-8)6K0hM!(*1d0xCC#WO7#CuS6|^Xz578uo
z3hU)Cg}9n1LLR{iHfe=Gn&^!lbOPt2DrLftLd6)&9Q&OIqoB`1L-?^tNu{Y;tlD~1q5te|D4`Z&5xiNEnRMIb}CbPp>@v=15J$;{7O)s(Ex(`rA>
zrTRO?2bDUe0yU;8PJp#j5HKM`Gk1!jfE}uo!6&p?WY%-#FHu|;zuU4#HsR`fv~DitaE`pf5YnuMnX)nf)>x%Q_gS0
zGiV^}pfD$r4K_&Zry7dUG{n>F7_tGaIK@+9_@QP!Y@Z2)yIRy&g;*0#D{bq$b|d1Q
z4-c3lPoVQ{$rU~{&ZvD&`q$XF>;uS~gF7CesILaE>N+v(5Ag`Pv%DhF?0-EPiX8p`
YPdTShBxln}3;+NC07*qoM6N<$f-e8QrvLx|

diff --git a/docs/html/img154.png b/docs/html/img154.png
index 8388c21d2bc754730388fcf9809f0ce6e7747de6..4092180aefa4c4534a45820493b99f42cacd96ff 100644
GIT binary patch
delta 977
zcmV;?11|i?0*nYDiBL{Q4GJ0x0000DNk~Le0005b0000G1Oos70BwtcXptdHe*=n1
zL_t(YiM3ZjNEA^R{%5Cc9nG1gizG%t&?OSVQz+S`f-ddFpi6e?;6YqU=u#ncC@f?T
z9=sG?1iR$YrAw?{Is_sUQV@YmOPOW64uw?EX7B&syxI3=W@lEjA7^;~oA3Yr@0&Mo
zb_CdQ=((NOM#h0%=Br0hPF8JxfA|ULBhh8)`wlzb3eD?1F}-?YGKx&iWdy#0glMEq
z(qa0LA^ECl^TSU7Dh-JCIn1mZnr<1Fl1$*@-B6ZS0T=WhMqoDSvyrxprz0;zEJs3Y
z)2CI4*I^|p4cw@T)VPUgpiQ)OWr#K|A-3r=wKE-Rzi`37`m9Lgb;v8wf9?!q!7QB(
z`dl7hccgrMo-%!8%r$Pa@%jh$JREvjf7ABVEC~(Ys?{7!
z{pkkF_I+X+_GxujKgRg9lYCM=!Gtb!z*!aelG;1UC#goC{RrwTw7-w`sY&a}-dm4h
zC96Lop95YR_Q~!%mY7c1XG-x|jrK|P1QWWv^$fr@Wj%#Y)8RB#Up3%!yVue3@D*CC
zQ9jF%v4w`toR&8if8dFuU7`KS-b0k~ohtieJE=qXH2pnPLAtK6&kYIS@6Qen6S~j=
zXRQ-*ZF27@pQsw}J!C91=)uzbJy@FqIw;oWtXT)vOJiABTwE|GHrbo2543mdKZ`Kc
z`}{QhuJ9Co7yKeXBuw|R+5LSuWxW(SCR}Jgd2^C8W2POUf6p;dZJygi0#tzY1oL!R
zv!C9$oV89!+T`9Gg>4xJl4BE8&EhrtuEFQ`B1DHFJ(dVe6YZeEPJ0R>HA7zvgLvYz
zpOyKvLJrZ@UOfbL4XT8sEnHoY$vt~ovp>oakv=6x!7n@|@^Kdvs}l*Et5&}Iwi_ie
zco+jR5um2*?5DPY4Y`UtD&e{=zU_hLu;jF0T~4D&%uhWXVKfTBL7`GX
zBM5rYTR|^&DINr|dJ+WDm4ZJA8l|??nr%?TAGGz&n`HA|l18muQK8pCFa
zGHynJ)F%g8RRlfd*4C55G8LIu@t@1#H|EN?g$kr@IRbY>Ld7ael7%b$e=j+l02AQy
z259}=2C$Kh5SF83mTy-cp{tiYHF0*=Nwf3G7IvbV_
z;x=Sg%&Hx(#-rNwfIl3N-lvjmtWZRdL;T~T-8?)sR>alUgU>*)DkE?27rx#z?4{(#
z4j3kDGn2NA=XEcvvqWQ9e+SFs%wibO+o8d3En@?Yky*nKI6Z~us>;YH>gSaXHS5UCZ@Fj-u
zHTI~-j&~rETiSCn9_zZgOLvD;y*p?aXmMdJ3M0C>!5e
zmST5!@hLex5DWt^8!yL;fWD?2f}iyub`950tbTZ`68xF#`Sz=0VCJgV)u|
zVL50RU@n&6x8Ro7VL2SH-+5G}=}_lZOO``#tGppOC^;g>hf2k)Er*jPhu|md`I$Ca
z{qR^N_}<-~@46mee`wuZOZCUeLBpUNYZ26Hs`A
zSeUGobXWp8D)Dj%eld}D6Zepu$(S`pqu
zb0t=erErwC+QZCBMGk)47SN-VlBdIRw3?jQlVdty<(%4se~296Y=`*8MC=Y+vwb-P
zYk+6ve2IK>9z_aaif(It;<6{oLBrsqG&jmA7LVLM4Q#-L$sxbafcuR<%5F|M=C;SZP0+`<=e0~s1!05zNo9KNiDSK?l
z>LIzL64ya-0{DlG1BPoY3+xY(+%TH#JFJyw4yh<=*%BMdU1$eftnxJM!@#rH@
zgh!*~w-I(rF7Fjv9Bty)EVJHUg};s~mKdxHkcR)9NKND^*6^z~lMYF-5r1(x36&VE
z3y_BYd^m|m{SdBYF+ae5)%3sp1OGQIXQX4&jQ_y@37sDJuDL@In*aa+07*qoM6N<$
Eg1ea){r~^~

delta 339
zcmV-Z0j&P436ldMiBL{Q4GJ0x0000DNk~Le0000u0000W1Oos70JSZq+mRtle*qCm
zL_t(2k?oPMPs30UfWNXnx-!zvpbf195SV}j$NqpV!67hJ2n5t1
zFk}eC6a|B01riJ)<9cs`AG0I~F8!|Q`_jwZJ@^|@ii(`rkDc2@c*1*sqjmt>n2m_K
zm6byaTi|7woEnRSnaXn0!V-k?f3#TR9;c~tBC!yw9K%nUta7cgEe*6=V6I>pIs_s!
zUR0h4r-GNlCiE$(JXg6Z>laiU>LZwhB2yVnu2nd=;1s5(mn}TknTNfcg1y??x3#ElJ
z3&C!57toCj{(#hl8=;gy!3RPdOKq!h;vfh%kyDI?-g?JCN+r5<#`3n57C+)+IIMFm
z$VZXA9g%mp4_XTdoGl{AjM3BcHj>*=!#bG_HD(Ef=J_Hp4z`>)8%KgU$!vtuG8?JA
zB=>WfOeiM@&s>5=g=#{E}IyS2{1Th=(+=>mO0=62WWwSg9
zDI-^dR3oSPXJbnrvQ$f)u;yi`!Y)Vh(NXFhsSb;99O{fkVm7|8UIO^X^V6jU0sBVP
zr27+8O~=cy*)Zuhs$~rhf8$!Y8cqu%7L-9QKw3{30UMAv)Rs6Q<1Dn{4@a7!#>hD1
zI>m&PX;I-|6QEBB0SDM<^J>vHo&pXk!njthhSP##v1=Cc^hUsj$@QDAjTR*m(y^gV
zbU(no-UPDPHVDusgn)x>n6Wm#cDovf39YDx)1r+s!bkP|`(!o2o#%N<469YDa*|ay9Oo9omsD{(x7MIsq(pYn40d|&w4$7amelFgq
z+9z0DUENt$A8o(1e+YT7#CtSYDmJ9Io$n3#TLR$PUCJ+6qTMcs_e4vAhoERLtqz!>sj)fUWmV3NDGf~mIo}tCl#W6%0000G1Oos706Sf89+4qSe*Lt*2yVns2o$81b|boxX48cm>BfbNkf4Qb{6QB=
zl`=xXZY*vJx-r3x8%ewALI@>L@Pkmt65DD_90WndHokk`Of#QkCenDx{O&vVoO|ZY
z3@-rxC&H-?6G~beps3@Dr2#fefBROJ@9TVj6T)d{K0M%4lnjL4`oKXf?HzDv8;;8=
zH?@C5a8MV_RcE^Uw(TO~s=4cdW}N_eB8eaurzdtDR~Dc-m}+s`Tqkb?X8~dh7~hpbml-xZ*G~Xh7^k@)j^joJUHXD07VYPxm<%t|BUh&;5k^h030}5i
z(gHL1IS*xQ!)>T4oKzcz=5`x~s31COSYm3T_KA`l+b{&H-j)d2f7(zr(9ri)T*kzFGB1*I$(LuvXS-6EeeX{l15VR2E-!>Une_aHq)$

delta 732
zcmV<20wewD2bl&TiBL{Q4GJ0x0000DNk~Le0002Z0000i1Oos705pmreUTwce*%|D
zL_t(oh3%G4Xwy&}$A586(-_tS4}vI851vGve?|vWs0>jL)*R+Rm~=-^T5z{rB7)we
zB8Z64Q}Nm%GEZCaEG~lH{F8$PLCqqghY8($f0HgvTaq?G#=f+?^9AYakZy=szm&B7790YhMzSP7sC%2%
z$N&**Q!<~IM>UX^b0kafcbg{o?nbBk9B;4V+w8CoT&(dLnQ+AV{=BBzuh7{6AXy^%
zFp|YqrBJ2o(|c$87AfkGe{RuY(JhiAWWDz~y389rZoSBzmG@maI_JPOT2w8+&C?zT
zq7Cl+q$?-uxSZRxC>TDM>;wOB_;rLkJFERUVx1K~^t*h&WRp2d`bn1~EIm4}2XUn1
zleD-VmV-SAXAC~N90k6m%YxO(Nf~O16j#D>RL)tqPq-Wzk3*Jmf3o(^g598;w3Tv5
zaV;uGUbe4#<0I5bX9s5%_SB+rMi>Wu{(2nA6k$d0d~UyCR*&}F_&j(GaL(mSrW|!-
zUjXMOY(<<0Y+ip~1?lr9=e)@k7U5aId{d_!TKp86bESR7Fpj9n0Mn&_b^4gCQ!_MY
zCV)dUJsyxd&@FfRGD@+!a3CN@d9euL)ok0{;3MzMx7lGGnfCX>j@Lgg;6koA7v13i
O0000c<@lNsE1yvg&tZe
zlsyP~(OW?;HuMi@^(ch0P!L6^YpHFuW?h7WKU-(so7wEIBpX}sYc{j<=6m0~ZzkDH
z0gfE$($Q-sfMO;f`k_e|pf@x!aUl#CL7Hg-Co_e2;MNJqyR_`jK`0Jv|577T8&3)Na#3U0A*&R0NV1UkmIeje~}-z-^zw7
zju#Ieo;P84(|}uLT;PfMiM^eR>G3=6hJ~?5!z})ojc}5$7?H{;T0eB2Il#)0?E@3x
zS{O%;U!tEsW4cyR3wxpl51VC!hncQAy+SmyB`wf&`XHq2ZUa)4?o!aPb`#2QARAl*
zv%}S0I13Asm7B^K?BVzMe|m)l*h^V}d4R8Mgp+&_shC!idra)mE-@{Nhxe+6;{&K=
zie4m}w0lZjHqpoySrF6ZTsQ}60n%p54mlo!b@(G2EF1E+Zov?nRQ
zzBqh+ILYsrQiG0(9j%$-@s8I?tGVMPV5^HXvPBlebecG+%Dl!zv6aSLKPjqfo-kD33F%(3ze
z)(e{DU})0#RjE66*fKJVu)_c+#W{AUD$S-nj;)#EoD+3C;CJjaaJ(d^^lXVe=3t-d
z4qGwc3v@fl9BVJ&f4MDZJLO(6e2&>yZB8RqtQ8jn3HR`AyeNdUjaFSAHR3cH8n!`L9Zf6n3}T#Mq2!|Qtmo&>0z2u+CmFrx;#4qXZbPs8YD%QPodJi!u~w)*eJU)rXYb9
zK8uJn5b;rnWl@}>p8`{t{3mv`LAG#&2-rf|-YEUh$X<|l;ge!KnzF*j+4izyu-}@}
zK9=RplSK4pDJ<1KOm+;K9QqFd{r~*8mref{2sUBv)!%`)8Jkuf
zQot#uF>^!);@I?R
zkZ*m=k-X(=obaxopxTGN{S
f44Za~(Z8TC4@n1Gk#W~LW)8&ZU{}kOtEV#(s(scBQ@p7)P`m}`zO5Vxt>(|)LYi{aG{cm|
z8Sob1&*elkW(rG?ru&nS^T$zZN=|og-8!sbb-Dlh#g}4TDI}karh3M4+TfWV%(xrl3We0HR#UL=-tK-60?MAR9dt7d)oKq*L10f&V
zK&ePNc|E~Mh$&Xk;wu7bYX*T_Ys#@xtI7^N!FrEk3|q89ppR#BbREPTf+NQL5t|BS
zVxV=6+O(xwRNymjlZ@Gge{qVrGNd_V-8)6K0hM!(*1d0xCC#WO7#CuS6|^Xz578uo
z3hU)Cg}9n1LLR{iHfe=Gn&^!lbOPt2DrLftLd6)&9Q&OIqoB`1L-?^tNu{Y;tlD~1q5te|D4`Z&5xiNEnRMIb}CbPp>@v=15J$;{7O)s(Ex(`rA>
zrTRO?2bDUe0yU;8PJp#j5HKM`Gk1!jfE}uo!6&p?WY%-#FHu|;zuU4#HsR`fv~DitaE`pf5YnuMnX)nf)>x%Q_gS0
zGiV^}pfD$r4K_&Zry7dUG{n>F7_tGaIK@+9_@QP!Y@Z2)yIRy&g;*0#D{bq$b|d1Q
z4-c3lPoVQ{$rU~{&ZvD&`q$XF>;uS~gF7CesILaE>N+v(5Ag`Pv%DhF?0-EPiX8p`
YPdTShBxln}3;+NC07*qoM6N<$f+OF)qyPW_

delta 528
zcmV+r0`L9t2hRi{iBL{Q4GJ0x0000DNk~Le0001i0000i1Oos70I&?kQ;{J{e*w)&
zL_t(YiDO_G1q6TtKa9n~@PRB7F2GIT9qA@;`)zNa%mmZF+!rV_;Xyl)mZK;fmICQ_
zl$gMo0A^7Vk`4?E++Qg%fun$d!BCYF6Ig*1X9J}vip88_6O2(!VBA2o2@UX6&4FYB
z>;DPp3g=f(043fnuPcZ#menNyf2xV!z1WdK-r9hHQ<32VF!5fFzpxi5^B)8r;5LBs
zKiB|}rl)@yN*Eg18yMIM<_7>1FCQr42m-!-0Wb~K^p_$3sQ|;AcMrgcmn#5SDbE>9
z02F5ShL`}=g$Pf8
zi~t7&Sknde3$rHh3NWzmGY2Q$b~L4kk{X!_jSR4+<`Mz^cbkDik__O)8-Qj4qKrdk
zf{ge8(Zm%B)Dnruxj0RLfoXU&6J-Kl8=>eY=mvrSQBqT20;r^BHw7~ptI
zbt6jvh$+peM~(@=bjx{xX72-t`H0~MIVJ$pE&B()3y|XOKRG4<6FWcD1W_FrQ=tpd~fy1?CN44;iqNV*&_#4iNw`qt2Wr*96uFWTz-ZNsY`LqyPX8O0xf&
SZTz9y^)cTo$bXYKt5whkY6x^!?PP8$zz@_jv*QolM@zbCLGrK#j*NDeFT1#=(j&u2Q^{GVsKqtCXc
zpNtC1(~K%UFfR>mlxnCyWBFdLfyGi-V%ldZp9ekpy;l
zWjxG}*%oNH7k4te&t^PUoyw-5_S>#_Le#o|1uumqA}p7(9Pshnz5Gr-TCmrII^fq{Y7)59eQNDBe691Am$ysQ)~52SP_sw&l|rKJIx#>U3I
zy}gl%ba4!kn3|lhfG;8DUbZkpTA|^bKdjd%6cqiJ+jFKFQR&QDJNtMx
eNV5s(Fle_)>H5z!oXP_f195SV}j$NqpV!67hJ2n5t1
zFk}eC6a|B01riJ)<9cs`AG0I~F8!|Q`_jwZJ@^|@ii(`rkDc2@c*1*sqjmt>n2m_K
zm6byaTi|7woEnRSnaXn0!V-k?f3#TR9;c~tBC!yw9K%nUta7cgEe*6=V6I>pIs_s!
zUR0h4r-GNlCiE$(JXg6Z>FxZUS(h~R7E!Z0zXnva0f6jA7F0qXZQeB)D8?ERLtqz!>sj)fUWmV3NDGf~mIo}tCl#W6%N{m+}3s1b;gq>Y2x5
z-+8|0{X5?|-#O#G{Hy48u;)U5{54ec(P
z*8QwI>-eVs(E4{fcFb4wCyDaO@Ey07IsNxK9_i)3+WvHk^!}#;9e11_f3QfK8aGK_
zvddD=&+iv^+72tW#w=P~T=ZHx73<*xit{FLDt&YN8H(>4plw}(&^`?YwS4-Ts&8^M
zD+iISyQUF~jx4ui4YH=419A{sYp#)LnE^Vgk%owz2iSt`zxkt!I0dnfi2O9#l|>D(
zg;~1w49zfSXK6-$cE;baf4-5{QKBtw@@PPH+#)pP+b(BDoo6pyL7^&FEXq6pz+t0G;7t__~{AfA(Uqo9GpB@T`Cg
z?sx;8rCW4T93UelO=d&}oon!MQJu6R#fLaVqE(zD)S%$#kQ~MP)MEtvJN
z@^k`XLV`0s?ZIHqunY>GOu>iwJ8jmQ&F+(Z*ZD;!Rfd;qh;-mnW1gMeSAd_2I)f+
zw>*vTLKShB&X+X+AE8(QR5G;15(0zis76AYK}NEf5uM`ezLu#lY7ayc12v(pI>~E<_r%Hj&~)0ApHPuD5HXKz!JMg_PneC_+A~xg$_%EX8VMmH=K=QaN{fbvhh=nlb05f0f1@WdvPuEZJe%J3`bXjs!pTS7Ytd>>-X_&mYC`8=F(_L86llaEmT3=rYCQtQWc>$Z
zgH%VUVe>pad({6%^6(4%RAco7EP)Rq+iIV+f7>{xjZ=+q&fM{WhLd{A>crevg_QRPBADY9w{#wRrZ5A9Y5?`
ze?>)GLb1eGKja}tkik;$ER-4j_@oW9AOn4fe|{=h&}Uez0nu))AT_0rsn@s0V#p9r
zL%@L`rHu6=fRK2kyp#yFb+uedMVxPUTS5_Ew2+4!LB?qV%8ci-V?hQ*`wMrzz*(Px
zSOcP`W9E<9H+9?kebM>679B$#as(Nt4Jb37
zjv>g@=$Q2xh&3PvI*$CZIq1j`PeZ`bT@?v>5kOU6=#KS4t&Qx
zWy?E;JOn{To=VjQlo{1A<1EN{I`&er&d_IAtO1d{N)10x7uX%!jtsFg1RMxbYLfLL
zfLx!Fm%{B_Yk&P?$s}%M{eWdlIJ>(b4@p4=@(W8pVpb|M<0o+D8D~L;H65uD`KZj2
z`V5OTOk{JE8o{4ld6Q`Fa<3ypf9wna2ZEHH=+qT}QsR;FQZm#Fa(sgH^X`#5;gN?X
zytAEtJnGNtqmr%9xO$IIsYxM6&g%$B2|ZGf@+NYVK@3_{x4W=b?X9l@9#*NT=;-Vh
zRicJ_%WS}^$uAY~&`M23M_Z7p5;f$P#Q)gpeJ%bCyBv0fEjTUR000002uVdwM6N<$
Ef|x70{r~^~

diff --git a/docs/html/img163.png b/docs/html/img163.png
index 6a11e6613921afda2a6559cbb13b87e804b9b431..bbd4a64a0ee5b9cbbb1d7bb43651f1e37c756725 100644
GIT binary patch
delta 732
zcmV<20wevj1DOUPiBL{Q4GJ0x0000DNk~Le0002Z0000i1Oos705pmreUTwce*%|D
zL_t(oh3%G4Xwy&}$A586(-_tS4}vI851vGve?|vWs0>jL)*R+Rm~=-^T5z{rB7)we
zB8Z64Q}Nm%GEZCaEG~lH{F8$PLCqqghY8($f0HgvTaq?G#=f+?^9AYakZy=szm&B7790YhMzSP7sC%2%
z$N&**Q!<~IM>UX^b0kafcbg{o?nbBk9B;4V+w8CoT&(dLnQ+AV{=BBzuh7{6AXy^%
zFp|YqrBJ2o(|c$87AfkGe{RuY(JhiAWWDz~y389rZoSBzmG@maI_JPOT2w8+&C?zT
zq7Cl+q$?-uxSZRxC>TDM>;wOB_;rLkJFERUVx1K~^t*h&WRp2d`bn1~EIm4}2XUn1
zleD-VmV-SAXAC~N90k6m%YxO(Nf~O16j#D>RL)tqPq-Wzk3*Jmf3o(^g598;w3Tv5
zaV;uGUbe4#<0I5bX9s5%_SB+rMi>Wu{(2nA6k$d0d~UyCR*&}F_&j(GaL(mSrW|!-
zUjXMOY(<<0Y+ip~1?lr9=e)@k7U5aId{d_!TKp86bESR7Fpj9n0Mn&_b^4gCQ!_MY
zCV)dUJsyxd&@FfRGD@+!a3CN@d9euL)ok0{;3MzMx7lGGnfCX>j@Lgg;6koA7v13i
O0000{;E

delta 372
zcmV-)0gL{b2DAeqiBL{Q4GJ0x0000DNk~Le0000!0000W1Oos70Jt;OoRJ|*e*rQ{
zL_t(2kz-&OJm4vV0FdMhU}Ru01@XC|;`R6c|7c)f{bKy}0s}+5vwbWB`vV5X0tVI(
z5P9wd2F3=4q5uZA1_pLj28IlVcm}?`K(+rM@*EBf3>(-J85sCCFq8qU_|5PW$Og(w
zK;*d!SQ#e77y!j4upS2Te=;aQf8==u!18kf_!$`7fDBd!mINRbz1Kb25iBL{Q4GJ0x0000DNk~Le0001a0000i1Oos70JE10K9M0zf7(ez
zK~zYI?UcPs12GuJpW2?+tM+m@D5Cf=IJx*SROq50C^&eFgHS&uK`G86{Re~t>7FQ2!>Y3EYnMx0jNL7+!?f9D<@ND0%CTqHtY0xj>tbO;z85T+AJ=4RV*iPDHW|*ngxdv-9lF)j0jaGR|bJ-9k6L2I@%W%4$-1;*L1FS`u>N*z{_U
zZ+*;>yya`0@UEbs+K0aV6m;)yY9w_*2c2M!gkD4^2;|k`2PUzB!-Qv!E}yTkO-f_7
z-1Cf7OOnxRWoUJ;+VxUea*B(U2Ah@##~Pqr1_?5{<4S~Xwp?jSJ7R5?03AS6j1}fS
zVhGT$2AN93^RRS~|b4wHTJ5>m`{C
en|6!Qzo0JSpy

delta 379
zcmV->0fheC1iS+wiBL{Q4GJ0x0000DNk~Le0001E0000H1Oos706YH=Y>^>Me>zD-
zK~yM_V_={YV4i?qp0R*|A-oiUfq=pOqz%W!)0iP}W7Z}(A_!M9m
zD)@nbmN^Uz2Voc}!d}n(tzTfvbNkB84Gf&$O&A!r_t^%ZYI(!Ja1MrnBJbuh@CY!+
zEAk~X++&y|V8+1BaGwq6;{PD~jmNNWjVBiYi|G=5Rd61zU7^(*dXkk{EaG8@~8ZfN+Kg>&DSUQ1${Q@gcy!S2;
zKphstzq6WUqXQe%LjfmTX-ihH^4ARWH-aTQH?3J#E=
Z1pr=%!lVCcZn*#e002ovPDHLkV1l(!nA!jU

diff --git a/docs/html/img165.png b/docs/html/img165.png
index 93e93d68029081eece3cfb6235660083dd42f3ba..cc511c986e317e2f1de0b6e475399eee89edc128 100644
GIT binary patch
delta 527
zcmV+q0`UEb1J48@iBL{Q4GJ0x0000DNk~Le0001i0000i1Oos70I&?kQ;{J|f6Ylm
zK~zYIV_+Bs1b_oSjK#w6fh-d)z)j#C=_YXdZEv8=1k=CV7br8~K|7F^qbMAf0_k^@
zn829;W>FH74h#(3Unwzxqkw_IP?ZuBSb-F01End7#hhXjj8RQs+(5Jm4e(UWfn);f
z{|V>{=T}bvCEhKsD~K_c)g=I`e~I6{*pWfr+JJ#mk>LX{@m`L*27&-lQd3|8sHA2$1v43|(L<_%yE8L*RM0tkE#5dblx&YULK1l9*+rzk{8jm#XR000h3vj3WI
Rl`;ST002ovPDHLkV1m#>&awai

delta 328
zcmV-O0k{6o1c?J7iBL{Q4GJ0x0000DNk~Le0000?0000T1Oos70P<^>N|7NCU7PI
z!{tBcGX}0m2KEcASbW+p%pQL*~r64A0mtSU&J0hZ|Jc?+v`Kfp!5Mcy9xX
zagp&3bH9zq;qqSVJBZ?BV3@!Fv_=5Ln#d5qD!_>~7_kH9|3L78pfc8X9zZaG1an8h
a&;kIh7ED>C78=U{00005Gr-TCmrII^fq{Y7)59eQNDBe691Am$ysQ)~52SP_sw&l|rKJIx#>U3I
zy}gl%ba4!kn3|lhfG;8DUbZkpTA|^bKdjd%6cqiJ+jFKFQR&QDJNtMx
eNV5s(Fle_)>H5z!oXP_Tz9y^)cTo$bXYKt5whkY6x^!?PP8$+Mm=jv*3LlM@sq4g3%2ol7||p&_=-pK-Uv
ze|DXwH($@(|HZm(&$@&MfAS6;__cRNVx8%UW97w?6)ZCz>%U2zp_0IMq~20g(&3l<
zpY)0&2aX3GI56SdhSrDmR?ZsH2mdfkaP*e^XKYZwYEU4TlEI$TX8B&OVeWc^heqm$
zO%|*cl9+amdDjo#BXNCB&CPclge5HWKd6SN8F-vFFvw%DEHXd5x0mOw!?eviHywO`
zob}D`GY6&A3<``48gd?qB%~&=SOp5jub6v~i|>IDJ41O|*k7%gt0fp1fC1#`>gTe~
HDWM4fG&*-W

diff --git a/docs/html/img167.png b/docs/html/img167.png
index d894ba945f738815f88a786d3a2ca327f9bac169..007f4bd15bea6ed1e0c0366901fa29a284ea1e58 100644
GIT binary patch
delta 320
zcmV-G0l)s?0)Yb|iBL{Q4GJ0x0000DNk~Le000160000U1Oos70I`jKb&(-VfB#8D
zK~y-6V_+C!fEB-VSpzCxDgdu?mJg`>JrD3IXG4|dw85`D29?XtgJRp3*A=MpMVlLt
zxur}W7^Ev6Uxo0P<1g%GkOP_W9|-;d86FJZkyJB&;B{cw!22N+tcZb+qkw_o9kOwG
z4E_uZ^WFgg*e!OCE-*|0`3Itie+w;~SPw90BPpN#?#TrP1{t{YGzJFluRxmPE)d)U
zT6cl0ugWneH=MK=8cKT=R|2QV-nU~ced_yASZ4h&k9p!mEW
z!RGV%z)*Ysb#uvU0jMIN(^<@sm2(O(po2h$2}p`qj4>2o0-_X+f>A&j761T_9!i8|
S7DY+`0000R~$qDojyMWk(%bXC|ib5a}!@vr5
zTDvf}0|UdX3A_Raxe-<~@J?WE0MWlUZ~*!I?=~~s+X!;_76Y&%&WjP?5a48B1yPY8
l7AROAKph|lV~m0!1OVi5IORe|ea8R*002ovPDHLkV1nbN{m+}3s1b;gq>Y2x5
z-+8|0{X5?|-#O#G{Hy48u;)U5{54ec(P
z*8QwI>-eVs(E4{fcFb4wCyDaO@Ey07IsNxK9_i)3+WvHk^!}#;9e11_f3QfK8aGK_
zvddD=&+iv^+72tW#w=P~T=ZHx73<*xit{FLDt&YN8H(>4plw}(&^`?YwS4-Ts&8^M
zD+iISyQUF~jx4ui4YH=419A{sYp#)LnE^Vgk%owz2iSt`zxkt!I0dnfi2O9#l|>D(
zg;~1w49zfSXK6-$cE;baf4-5{QKBtw@@PPH+#)pP+b(BDoo6pyL7^&FEXq6pz+t0G;7t__~{AfA(Uqo9GpB@T`Cg
z?sx;8rCW4T93UelO=d&}oon!MQJu6R#fLaVqE(zD)S%$#kQ~MP)MEtvJN
z@^k`XLV`0s?ZIHqunY>GOu>iwJ8jmQ&F+(Z*ZD;!Rfd;qh;-mnW1gMeSAd_2I)f+
zw>*vTLKShB&X+X+AE8(QR5G;15(0zis76AYK}NEf5uM`ezLu#lY7ayc12v(pI>~E<_r%Hj&~)0ApHPuD5HXKz!JMg_PneC_+A~xg$_%EX8VMmH=K=QaN{fbvhh=nlb05f0f1@WdvPuEZJe%J3`bXjs!pTS7Ytd>>-X_&mYC`8=F(_L86llaEmT3=rYCQtQWc>$Z
zgH%VUVe>pad({6%^6(4%RAco7EP)Rq+iIV+f7>{xjZ=+q&fM{WhLd{A>crevg_QRPBADY9w{#wRrZ5A9Y5?`
ze?>)GLb1eGKja}tkik;$ER-4j_@oW9AOn4fe|{=h&}Uez0nu))AT_0rsn@s0V#p9r
zL%@L`rHu6=fRK2kyp#yFb+uedMVxPUTS5_Ew2+4!LB?qV%8ci-V?hQ*`wMrzz*(Px
zSOcP`W9E<9H+9?kebM>679B$#as(Nt4Jb37
zjv>g@=$Q2xh&3PvI*$CZIq1j`PeZ`bT@?v>5kOU6=#KS4t&Qx
zWy?E;JOn{To=VjQlo{1A<1EN{I`&er&d_IAtO1d{N)10x7uX%!jtsFg1RMxbYLfLL
zfLx!Fm%{B_Yk&P?$s}%M{eWdlIJ>(b4@p4=@(W8pVpb|M<0o+D8D~L;H65uD`KZj2
z`V5OTOk{JE8o{4ld6Q`Fa<3ypf9wna2ZEHH=+qT}QsR;FQZm#Fa(sgH^X`#5;gN?X
zytAEtJnGNtqmr%9xO$IIsYxM6&g%$B2|ZGf@+NYVK@3_{x4W=b?X9l@9#*NT=;-Vh
zRicJ_%WS}^$uAY~&`M23M_Z7p5;f$P#Q)gpeJ%bCyBv0fEjTUR000002uVdwM6N<$
Ef_G%P8vpNf*>
zA_D{e1|XO9Fp&7k5Mu!3PXIDm5`aVigBwT+q@3pi*wFJZ%ib7(tpw_N_bvd$e*ol7
z;5)~_@cKB&elCzf3=E5b7B2v)IOGR9;v)mYUj_zVu=NZ--dO|H@n3%Yc>|cw2sVa6
c?j?u>0MfH1tBsxC^#A|>07*qoM6N<$f(;~7Bme*a

diff --git a/docs/html/img27.png b/docs/html/img27.png
index febfe5af7ff526a5e79f2265e020f57be09ecbb6..632b6b74a9752af1ca1a965b592b170bad11874f 100644
GIT binary patch
delta 2456
zcmV;J31{|&1;`U2iBL{Q4GJ0x0000DNk~Le0005>0000<1Oos706E*qrja2_e+foO
zL_t(|ob8)`j1=V=$Dd(uZW))G+4u)uDCjjLnwUr~IVG`F!88r+A1&JwtQy0Q8l$8U
zHdPCTwvw8tsV#03LX6SI{y}IH<6T=5G~j_zOtkA|iP|5r9wVg(4c^`YUJxo=pC9l0
z&g{+X-r){+le*u)?mO?i&+|Udf4uL!^Uf!?0CBoWzH+fAr>{(*MF)YbQo>dP@zq%$
zt%?A4t%=*Em1v#)D?fbra~(mkuGLjR@s6P;J)rt@;n5?JbM6h1NKDlvtE16a*Tr{;
z)$VK5`eKu)+?dp1o-f~7`p{QSd>NhmD0DDI>QAa~dwpN@5Osvnf+ICt}R4?Xey8fC{%OKfP$arwclD4q=Y2
zy&S3A`PNd0!?1OSdjyvLZ56;X%W7~;P8p{izS@`c6UiT5JT*f8)gej{mJ%korT^S&+K*-z`IIXuLTbA1?wg}$``zOOo($+`q|{lW*u}BZCTBgLoS(OQR3sn5Zs|7&mNMpQDp1Uv
zqY|2IvU~Ydt_LPyWYEG$P3mrRi5~^$5H~}cyE(*p{ycy`p;hJ}ma`S;?3L7MN^Jx7Wxjv;iemHf!Le!Z!RvLnXeDY@i_ozs2#%mWd;klX$
z6f@_jgah+wPEL7Cs{e+}KQ~U9I`&J=&_?d;j^ZroV1M>Y7-RSQyw(-2PmWm^AC
z>KDitS;8%El}saN)zNV3qbhZAth6#y;gjg$h>B$A#n{xjf0_yuGv^qje)m^Ek2*jR
zKEpuFI*i?{cAGn
z^eptYNu=Z=Y^oa
z_qtW|e0DMUx6(5muZ?@UA1`rNbSHXr@Rd9_e{=U8zYXS<%LjAicWSs!FT=^z
zxBr{y23=f^C(STuOx
zDUkN=FKhVk{0=yV0kUJ|XMee$PGYyqOA?9o;mOYis7lFu0mzE0F+Y&hC`W+v)ZhdB
zZ=T(2f3SQf6~3)&7DY0LQ75mP$*P3&+Ij*XGjx^KIN}C?b~7FIJLvyV>ZXcIcA>`o?4tVZMF6Pp)WU}
z8XHdzP>qd;Yu$<9ilh-xdH%D-qyUxpGP>yO2@X;Ss21gECzuSN5?@-@VcAHEQV6J?
ze;aULPYO_pFD>UU@JZk{g@DT8{eLomN_>$RP?gN6rxZ}}%W*=0%DiZEXY`6KN-3aX
z#*z@A3aAhRDo=Y&DWJ+08>N2ffGTSicm`Bk^ifIy)fPfb2>~kh#UenJExPI`oq)>u
zZnc&apb}pOQ0=UaL7D;8UFC8mDL^H@e>9-7Uo5{1Z9vrqRPky9s<`?#plU^JK-E@T
z@MQ;7|9Uk!Kt;X+xyyop(g~>MCkUwK*8wW)zThB*fU0wQS0yPxCBBUAhtOY-r4UeM
zN?j|G0#xG5=w^67I7lI&0@zhZ>@TR;7fJqt%DGoLODUjQw-^!wRP2i{9Cc=&f7TZ?
zt$?aazhl?y3jr#FR~S%%UaeCKsK7gv7@%TbECy8Yxf<1U0;=bFb3;i1D)GfyxEh={
zV82Q&oq%drDW1cB5kMurG@x=eG9^hbpz~7ZlpOBmn$#~?nc;56oOwKX|%}!zx8gU-CJnXm(uJf_GK89
zVjntn0axTcHyi7ma3Mo?e@x^AqKF%54yDSN`g;7hpjZypumhg(&prZmsdxIT<>F`t
zr2$az^F}(Px91ofbonJ*$k3fo>M%sy$Z#kr4+DRMQkP$H(TCRqb*XzR2IP!pP?6Lb
zT+LeQ%!LBF6H47aMBGSoC{I9;Q8)*(DWoyW!?G2bC&5;I72QiqVuB#b4y5g<(*kWo}GEuvuK@hzl9I
z6A&H(QN)dy{*=pQW=QWH|GR&p-~0XXzt-eAMdXJaEFOTL^vvlm2$~X#1UG`PFT&vBTeCj6CFq*ZO*8c%o
WIV3wtg+!YG0000HOe*yzZ
zL_t(YiS1M|OB_KMee1fnw^?rIz$S?XPi#}Hf{2Z=O_Q8pXF!`2X~GFXg`gf-TsuF&
zXLge6zqk?$HCd
z>nlf<9(fI;2GJw0G3+3`Ey*qef4*^KqRSfe^A^o|7VE&2W2)Yb)M|WzqCaESGmti;
zXdAq`iG3lX>G_IT&wz0m9~!*QFR4`p9+b^`27PfX6lKg`87XD>H~1IlX8pxp74`Sr
zI{SnVz={Biujojn46gn<^qO$vW!(+nEYXS9HGSfr-}FWx^2Jr0A~VH~iw*)N5J<1(>6QdBo{PZL-9{bIii&>M^&McV6~TTw
zLSFJzH7^X|(o1HiUU-eKnl9V!H~m?%-r^ZB?j?JqlTcVg*;aGx5?6cl7K4(e%eEVW
zwZBXEK%1@&XlHL%UqX;Ge^pBb<(EQr_Cb^Bx@7FRy_HwIW7HK6kUYw3@MYr1n5ri@JTHv80=w~>^QX(y9k<2$Y1Z!^{sUop
VuU2ixs^S0u002ovPDHLkV1mb%6I%cP

diff --git a/docs/html/img28.png b/docs/html/img28.png
index f4843d98f8b8a2f9528f4ec8ea0ec8f5ea439e16..febfe5af7ff526a5e79f2265e020f57be09ecbb6 100644
GIT binary patch
delta 583
zcmV-N0=WI~0fhx2iBL{Q4GJ0x0000DNk~Le0001%0000S1Oos70C5CcZ;>HOe*yzZ
zL_t(YiS1M|OB_KMee1fnw^?rIz$S?XPi#}Hf{2Z=O_Q8pXF!`2X~GFXg`gf-TsuF&
zXLge6zqk?$HCd
z>nlf<9(fI;2GJw0G3+3`Ey*qef4*^KqRSfe^A^o|7VE&2W2)Yb)M|WzqCaESGmti;
zXdAq`iG3lX>G_IT&wz0m9~!*QFR4`p9+b^`27PfX6lKg`87XD>H~1IlX8pxp74`Sr
zI{SnVz={Biujojn46gn<^qO$vW!(+nEYXS9HGSfr-}FWx^2Jr0A~VH~iw*)N5J<1(>6QdBo{PZL-9{bIii&>M^&McV6~TTw
zLSFJzH7^X|(o1HiUU-eKnl9V!H~m?%-r^ZB?j?JqlTcVg*;aGx5?6cl7K4(e%eEVW
zwZBXEK%1@&XlHL%UqX;Ge^pBb<(EQr_Cb^Bx@7FRy_HwIW7HK6kUYw3@MYr1n5ri@JTHv80=w~>^QX(y9k<2$Y1Z!^{sUop
VuU2ixs^S0u002ovPDHLkV1oI=6LA0l

delta 175
zcmV;g08syh1@HkOiBL{Q4GJ0x0000DNk~Le0000Q0000E1Oos70K+2@aFHQPe*kVt
zL_t&tnPXs}1>pAE-oP-wdIIC;%|M>%U+xQ>iVPn(1S){M2ki_DYz6ZJ*!~5AlrCjp
znDg!d1GA1Iki(h4!0-l07c%C7OmSdfkYQllxsu@`kjGKLz`(xGoZ;VV10atTq*oG1
dPhemG0BhbEDFkA#=>Px#07*qo1w^hwV1k+DLHGaw

diff --git a/docs/html/img29.png b/docs/html/img29.png
index 4b6d5f615c1cbe5e091efbf34e86f3400bca2030..f4843d98f8b8a2f9528f4ec8ea0ec8f5ea439e16 100644
GIT binary patch
literal 240
zcmeAS@N?(olHy`uVBq!ia0vp^Qb5ed!VDx2D+?9?DT4r?5Z40-4s71MSxrr?p`pRY
z$7k8HWs;JT#l^+;_VzPp&g9|YNlQxusx>w??(OZ3jEwATFE#=48B2ovf*Bm1-2h4E
zdAc};aLi0jSit(=+wFS?4E9$sJ$`=HVcyI5cieNjc;qcuv>NuXzvbb{Vg1Z};~#6&
z6us1h8K2)VGH>ovns9jLfde1dJj9KjHTo1LBuq$5xU+N8L!}AF1A&g)cYe;p``OG2
j{h~|4g*^Nd5*Qe=?@4O1B&~l5w3)%v)z4*}Q$iB}W;9o^

literal 498
zcmV~`z0amAeY2&V{hz@y|MoXn~%yFSU4&-_GQFRVJj3&dd-OnLa7~`z0amAeY2&V{hz@y|MoXn~%yFSU4&-_GQFRVJj3&dd-OnLa7>v;v0WlB*F~ILvF%Sb7zyJm?fB+1{00u_d4WEI8WcTiJ
zWUF3R-7U+6o^C!SEa3kFcv?U=z|#V{0iG7n4e+#pZh)r+bOSsspc~+60o?#k3+M)T
zT0l2Imn>>U6lZ}NqWU=CtiM53Fu6atmUs`Orhoh_P-6|xwVuxX%Dh8WFu5kYqx6>u
zDI40?mLIP7PnV13`zQ4lRl!6}ct`3l!A;KC3hZF#-P5`pdAimOs)C7{@LFh%`MU#X
z2{31D1@>STzwfk3RWLCNh=xnG(5YRtR9qUNyqVZ*g`Blwc>`&=W78v3igP0sbJMDY
zUL?weXz(i@Uf4B5DwS63D%H&cU5v%{0qkODoqp?L^_Ekk6~
zg;SS?R*$e|r+(Z{ZkwuL(i{xX{CWkn6n=yu>02+l4SwmAl}^pV_2geF`Q&7$A%!Ck
zgJYn|@Y-o&DdnC})lU7A466wvT>Yj|Cijv%R@C`;<|?|ahJTdHMmbRIbJ
zVb+pSS+Y!M!RLP?5lur}r2LkN#}uW|O2)vJ!Nh9kYv+YiF5Km=mfNN(nAl3wYph>!
zugY8Ur6l#*_&wopQQcuZzQUJubI4<@*#bGkqC#C@cZx&fXR&<$Ta!)-e?T

diff --git a/docs/html/img31.png b/docs/html/img31.png
index dc5293d02a7fd57ebb160e1277a04151b1650f02..c0a7d73da2d3e6987a071649b35f7eff896d293f 100644
GIT binary patch
literal 908
zcmV;719SX|P)>v;v0WlB*F~ILvF%Sb7zyJm?fB+1{00u_d4WEI8WcTiJ
zWUF3R-7U+6o^C!SEa3kFcv?U=z|#V{0iG7n4e+#pZh)r+bOSsspc~+60o?#k3+M)T
zT0l2Imn>>U6lZ}NqWU=CtiM53Fu6atmUs`Orhoh_P-6|xwVuxX%Dh8WFu5kYqx6>u
zDI40?mLIP7PnV13`zQ4lRl!6}ct`3l!A;KC3hZF#-P5`pdAimOs)C7{@LFh%`MU#X
z2{31D1@>STzwfk3RWLCNh=xnG(5YRtR9qUNyqVZ*g`Blwc>`&=W78v3igP0sbJMDY
zUL?weXz(i@Uf4B5DwS63D%H&cU5v%{0qkODoqp?L^_Ekk6~
zg;SS?R*$e|r+(Z{ZkwuL(i{xX{CWkn6n=yu>02+l4SwmAl}^pV_2geF`Q&7$A%!Ck
zgJYn|@Y-o&DdnC})lU7A466wvT>Yj|Cijv%R@C`;<|?|ahJTdHMmbRIbJ
zVb+pSS+Y!M!RLP?5lur}r2LkN#}uW|O2)vJ!Nh9kYv+YiF5Km=mfNN(nAl3wYph>!
zugY8Ur6l#*_&wopQQcuZzQUJubI4<@*#bGkqC#C@cZx&fXR&<$Ta!)-e?T

literal 290
zcmeAS@N?(olHy`uVBq!ia0vp^IzY_F!VDyroqNm=qznRlLR=3VIIwy1W;HdnhK2?o
zAD?B*mPtxV78e)W+uP5aIg^KnCoL@vsMgrnxVN`AGBUEWz1RfEXDkWw3ubV5b^|22
zz|+MsL}F@kf`m)M=iQu#r#=5Rb++^YpJQ)pw=p_A^khmq^RcVuB+qvTAGW-<-#Nk!
zhhFkT|FGbiAu3_y=)>mMX0t((UGkRX4yGUW1!@g5d3x9#4%Kk-c&qy)Cm22WZ@_;f
zC1L*ouAtgR{e=nK%{>ga&&*U<#(J8)ZbDIdacXl}n>){*^#{+$KC6>H*v7rVh{eFb
j$iRoeIFi*uQi36?TJx{KmF;;zw=#IT`njxgN@xNA>jP%Z

diff --git a/docs/html/img32.png b/docs/html/img32.png
index 3f29355a015544ee631785caa9ae5c6a051dd11a..dc5293d02a7fd57ebb160e1277a04151b1650f02 100644
GIT binary patch
delta 225
zcmV<703QF%1)>5WiBL{Q4GJ0x0000DNk~Le0000i0000E1Oos70H)6450N2De*mCK
zL_t&-m1AHSM1b?V3B#7>_LZ9(z)Z&NeYOEW;Yk8!%<+nR$qe^EOa^X-`)m_{!s!fK
z_&5rf6&Nx>Oa@MdJg^xD8QK}R0{B00CV-g?j0Zr%d>iBL{Q4GJ0x0000DNk~Le0001#0000a1Oos70G-$ll93@xe*#NM
zL_t(YiS3n5XcIvc$Nyupo2Ssv~#S9c_bN>3|5}``t^%`bxx@`3+?gQ6JxGL8^MH=(s!S>xT
z7mW{2;Y4tpmIbR%kJ+T!nLd#;eQ)_N_LLWX5UWmy*@{IDTyGF4y|@I6-DWfx`MqFwTRJ2Fv~6Ps`OzhZc*cpI0CB8
zvN4m|q_fo0USi@tuUf3AK5&_bqU++$etS8Q2{l82$Vf6wLE=Aoz#
zWP$O7XEBah!rr4e7nwhbpSw-PLea){{VX(|Tnw;tP9A3D+5w_jRiNQIsTxmq@hJV_
zO?*vk-*~7w`au`yoeM!<-7xssyfpcdXUwPal#4xE@r;A-nAU9CmL@)6y?fA=J>rQxC&wV?}WrXs}{Ma`&~1&Q*c2}PlmAX4w`1#K_1
z!*}q72+1qOF?pd6qM4L#6%5iS;c%KY(UmYYImwK7Oin^ix+-tvf&7~EfXqdnt@sQ~
zGp*Ssn3GxQDcI{+GrbjBspOhOxK6cKnLDUcTLsSp^dw?(CRA*fe~3}kj1CFH@?;8B
zv?g3nA+b84rKeL9wONXF*R4&A+?~Wx!dafgmgCS32SiLLJ;8(?h?^pk{OG>4%*CEk
z9O@QlwKdyZi1Hdf4zrw!SBe9JC2t0JMYUI()zlfuLRG!!3?Ji}+-Eg4qeFrYa2X&K
zU5W8&Va&??38CLwe}`0DZQ>|$uw`K=3zu@aWOVU)Q_Mk%$%jiIbFrt&GBDDb?WW4S
z{Z@hEtW+%e&#Lx`sd>~XGQ{)Pd7Ni*E9L@FIts$_9Ez9U2WpK0QgBU-a-G$moEB!v
zVwNXylyIg|nnRls;vkAsCmlbh6qB!A$;({i*=xLq*O+IUe=A$Hui=ckV4aGO0KBH8
z#14K-oiVY-DbcANxw#KlIlE$Ye5bII~~e4Clb~&aSQcNBJA=o7a*bc^PI7P%iQ~q4AT*vAyB&6V`0e
z6QamWrdvDJd#yus{+q^f#ECTfy)LzF0@
zs999Qg0MW1Vh>0~*3Ey3@Ry;pNVQBa7Ay|uHZ^J+HHg!;HU(jkXqjV}?Jp__hrel}
zsAIOUJgVU|PmnH}QTAhClX#X{r2^mbmO)8V&0K2OS~<5OGWBLy;+@R(swGa7NJr^3
zg}K;Lf2Bv+7V&7uz{>!ehKe7;Jl-;6CV!TA@4m3Ms6pGZ8$XqFyj+ltc7
z6j;0d#fwA5mp9M7(Exu8YqzN7$_ch|`C|8N_`?JFU6yzJ`uIVL8U$$!1R~;P(oVcU{asxv$?#l
z)Q1xWnEJew$z*+{KAf;ZeV{^pD%7VSutI%CZWZcNvAf9bO6v3b4?a^LOeig&)ThR8
zf9g{cZ0b|h7SH-heK?`CAX1-DI^OIn_2Golf=GP;b|n4%t`8+73n=wz5nDZ9sShP2
z3o7-A=Y6I=ahWWr)CY`X{!$-GNT0!^KD+B<$9<(foRHQynAB%Sx-_pIHTB_y0j562
z`ku6})Q1xWnfk22t*D>WhZ0t(kJ~ELf5#bEp*|zG3iYX2#fofHJjWG;H~Kqtc_Acm
zff5H>DYl5|;4{ND3=(f!Yy^Vv@l_5ljivQLiA{7V48ew_T71TO&U!sh9YMXP*=G=B
zm{1lkjirrH@pb1P)*>0@=b#|DUt$oXwLw|DG?q3(#dQwfeiic`ZwE=m5(NDMe`WEK
z|5p3vMTuOTiY>ZBYz4pxb!?tP+!PbMu{ICu&P@CiA`hvrdqCtvvoB9T38{;A>w>9(
z5-Q$^4uK%??pR`zHik9}_DSU8RBX{5Vk;myiiA2g&%w3D1hn03HIfBu+=!<*0wts_
zvHGZ~5Q9?8APA3WY#eW0p>Es+e-UyiP^{<Ly8sn!9Fk>+#FjeaC(GIo7fB4ig+GLPY
zEJ4tCpVhENybv&QDNwBF4zU%G97QU&c@FBK1lgQ;LQN6(pFZ6LwPx=pcmz@x!^Fps
zedp>|WNG~GT%XU+10ffLB>2mU72P4WlF4*CppMORh__IJ2Rq=cx(WM}Fa-e%LmGGt
z7$_liF)sHb-N2y!nO6zVbub8mU!fFU8cRch5-w&fHrk(`hccDD
hQSlsC(0K0_{{w!_|12`uE&Kog002ovPDHLkV1oVo7$g7y

delta 368
zcmV-$0gwLC5wHUxiBL{Q4GJ0x0000DNk~Le000170000S1Oos703Mme2azF5e*rE@
zL_t(IjbmUK1tSo!FnoZs9ry_<=S5O}VSto#;8H%n*nvUb+JL>DA)aB&bNkB84Ir84
z$jYTF9$$qj=Tu})U}$7-csG~fKXbeyUoyizpaf$BvhoeQA2J!_z{=SQxE&bsp9(zq
z&v2QKqkvg~Arq*m%|kL

diff --git a/docs/html/img34.png b/docs/html/img34.png
index f0d956927086351ddf7054f2011819d493f08245..3f29355a015544ee631785caa9ae5c6a051dd11a 100644
GIT binary patch
delta 654
zcmV;90&)H119ADbZ%I75u=&H#@s&c5B%PxtVvEurvSvZ{EDOvjGM%
zi2pNkHVs~e$m`N}&6Sd>TfivJe`cUWtmTiQnb5-%B8^nT;6X1asU3-CLQfLKT{*H^
zFDTNo#m*dglBg}}XGspl3>0Z|{`%w+p-SWR8fI_0Z1pMb1J_BoD%Uq%w^i?MdFknU0ra2f4!K)4)>eP
zs)TpC+oZ(a-`OoUQyz|B3ecTdTW?LE4UzHET%9}1!=Ks
zROPKaRI54Q-b#Snz9G51)lQ?nDAY`g`t?=SO4ggS2iB~Rr92$QIp8xrUuIPtrDa1M
z(CCy@q1Zg$T5L^(sDiIae{GxB!j>x!mAyilf<2$7CQvD-wx`M-q0B`*4mcZ@sKa@|
zrMAk2XNuUvQFMU9LK&^be%at(bOl~XLO$-`ZSiw@@)CQ~_+Gz&Jydt`tUUfiY9E-#
zZ2mI#aA;D$lips+HSdCQW#QSh)Z3)Fo%c$!j8JQ10$4`mNnMk07*qoM6N<$g2YrfegFUf

delta 677
zcmV;W0$Tme1>^-GiBL{Q4GJ0x0000DNk~Le0002Z0000S1Oos705I?-(2*fbe_}~Q
zK~zYI?UlQ4(@+$~Ki6?=Cph-R!YdX3fYqv^5-MauVu>=abV?-#)P)9$c!;54%2t^U
zkqT5y?5!G!B7}JS0muxj#VTqd6vbGSs$xLlTsv`Y9hZb|NI8mgu8+R&{%-Coz$ivB
zict(133$DiDgS$&o}3=hMGB$ve~|w#p>aCd@l%l=JIY}N(dt)f$KVu$q&tT=g^)95
z_A8IW`4uFg%yTkc$U%&907r@AWIOrOKu%8?`kyc6aPFdc&yzgV8kZkzmRYsIb85}|
zP!C?IHiVbUGX?C$bL1tY^NR;hr@<+^9Ccir!y|e5o2`3daXfP!+nuQie>q~&euEW5
zrykSzlCm4O@T
zzV1QAO{#qlhX0#U+-Bb04LD94P6ZQ4TAY$`mTcgeLA^|TFj9pR22usxQ|F=_DntF~
zg4__^g&edZ9K2wkHmbamfB7@SsUtNj8z-GAb|g}anYu@(fF_t*pDOi7E|J`_EulMa
zt;oEIS&IgF9&MFVb~$UP%TFxLXyK=f8crL@RjY3w_@g^T@acp{fW3H*a?4ETg!h_BTWTY~3QC_nsKqTRZ6A-@59j_2sFd!dvvS!}O!$}R_w
z=|Im?wj_gE0yUUT;yLWZ3sk-e$xx|j$8*R@HiNbRrwlm*fDA)aB&bNkB84Ir84
z$jYTF9$$qj=Tu})U}$7-csG~fKXbeyUoyizpaf$BvhoeQA2J!_z{=SQxE&bsp9(zq
z&v2QKqkvg~Arq*m%A|<w9%RUz2~zHCu59q{wE=_d^Bo&G3iuQl
s?ri`&P=J+z6=cf1i6Vq}`~k=eti>v7A{50~l&WGt;aod$ZXK6|Zb&(bbFPoR@BVJ?E5Im5
zF^W+P83}m3mnr{yot~T?(M1ZOfAWz3FQIWd+3{169y`im1<~qPYRBLdgQPo$IE9ci
zX7($O!}%2?q0DnKUdTa=asWq(<77Me(?Cv78Ty|u=5X$!dC!wP)Ebu`Y?fKI!E#2nwzKRJj=P4bA4c8O98T$TXx);fbPfxb~wl#Z9Vx4~GAnQQT(U-3>TS8%_liNLrkdah7c0nL)iwd@xdl69!TR-BahH94bTo
z=z`o3-h~{rA{@M6pEjzzf0Fq##Hk}SD;p=BDt07NjG4Mer+_AyTc0ZRM=p`vvMr%I
zZ>`9@iCK#Vc^++*Q+7FPsLM|*&1m7Lj2ccG$yKXwANZp?Meyl_M}WO}j&jRP=Y;o|
zU*(itPGa)*r0#CwOk-;U73@H3GFyV@R470ETB6;$bs@h2e2(Yne6OLDGFfb|bIL9U
zkLf_qQnn<6S^_ngP2xH1#0ylu3dvBZX~%QONj8JF0H+K&1A;%N*Mii!cjPPk{%h~v
zL5!05?<^GliIaBxbmTpX80E0{o5JgYAHe<>%27_F5Gs`+IsaMw0VnwUN(m=hSO5S3
M07*qoM6N<$f;oUXlmGw#

delta 404
zcmV;F0c-x`1=Ir}iBL{Q4GJ0x0000DNk~Le000190000S1Oos702*u+I*}nue*scS
zL_t(IjqTFCO2beT2k?K)hq;D)fQ#Y>6mfH?iWC>k6KMJdt}aqRv>-~rp=%yM>Ez&6
za1fV1Lmb=#4kDF!L7c>BP7+GerqIDn&v3b%`%5_I-UIx{-wDwHw1J!i-rw71@$4Mf
zlzB0y=e%F^M3)ea?M;u?nX&yue+n#G)e&CXxpUDz^@R6ZTmdH>W|fYf^M0=R^qBdL
zFU@BaaMfz!4aSQPjs7RNdEe3bJ{A)nv;d{ic9f`&Zx|+rLH>9vq{zId1VEV9e+^uQ
z0mPL`>@nq(dCd3gXM4bFygd{SunnxSv>xUc`aOfAeWd-`^tEt*g9qxjYBgQbujuZA
zuP!HEZ2*(q8lqm6?(?$)-61CBymoQavzVKBnR2u7+s1Dtd0@ao!sL8Cb$F0!!}DO%
yI$|EA^&yWg(jhAI+5Hs4ESYCD=iLGS`|$%>)@%QP%CbKI0000A|<w9%RUz2~zHCu59q{wE=_d^Bo&G3iuQl
s?ri`&P=J+z6=cfm?U5l%e*%|D
zL_t(YiS3oYYui8+$G?jFOA(edrX&S>@8Bh*ONrMmt^(a%$WXGR4rFi%Z3G>%711G3
zsL7O}n@bF7DNXwq6lKWTiiXlbMG+WNI@IaA(+{6z+1-o3pp)73Hey;!HLXf7P0F0!0_HolnKff{_eN&GBd`hd{C&&z|y;)tYqj
z0t+<^r-Pc|O?StlW&)yYBm|~mHt07Wm!^Y410+j~YC!@@q(^^kDH~J?D;sRIvOtyS
ze*Q1eLY!YpeMiu<%0_W!k(2W>wq7
z7hF+mmV+%;D|WgEz(Zw#!f-YbDNOe<+`Q>daeJszb935Ef0mq6srdpAwLk22u7RtwwpkKv+Qn
zVor)`EO$rRmIKHYJKVaCxOF%Le$r2wEy2kn+Byyrw~n$8sm1lcUZ=nl>U(trQtNDy
z%gSq<)3Yw^)H0iatxxKb;dU;dmG`qjl-`LSoYdAu&8!J}6?MtQs&FLP29pV}Ol-
zV5+f^M2sk|2_b}_!4CxeVk?@U0ZRE$6V0YsLwp4(18Tw4ZkI;`HA21ToIBImd2Am{
z%NX_~WpD4D|GDSC_s;8=0^k<&fA}NjIylCdcPrw%eO7rnis%4J3Lu>K&N@Fky4f)o
z1tydceouEEXo*mrA->_P;JlnTwBFHWQ>hO+#9odX#nHzx%T4d9)KNNaG>$)R5me|!
zHRUa`vC{PJGI5_*EvBju9O2<;Q2c0^rOLai(K;S98rtX`o8eOOC>-}We;UK#;iv{=
zf$@ZAF_u}v-bZmR3V$3wb&HOLqiws?voQbXgof{d`|4%cC>-Cy?>-g-;*uxf}T_LgPVTkT#+aA$MP1(vyQy3o3kl9>iG*pxeRe$
z3Vj~bN3TKnO1=4oMwjmVe~Roi&b=g#+Im8mZC`44j4J9z$82c(31d(=3atf^`d}|8
z2Voa{2_Fkd-f$d~C;AYEPR*W#mXFm%b#)zZnhnvltUV0}NiXK_2DJ$`!jQ~WnI5pN
zaW~A+&Do~t)7UA>hu2K#o2cZK)o2LH62qf
z;Y2I})~X%wxsH0ZM(Hvgb1r4JWz#4x@_Ed&mFfIwLUQrhZ*yFo2(Obun3~{097ez3rP5Fth!{PU@2J
zk0@QJs9SwE&xWGg7hsA5ARU<({}rOW3LDFeo|z8A&?hc5N*IgykbW22wkkzh>?D0S
zY5Ag-70UmjiK3R-!t!9sDe6tzCY0kStQYq(vsBX<^8u5rTBlu9Z7xq
z2YjYJ{lk~AKvEw~-kRqVe2g~)9`cOjJCIO{Bk(8I?aZ;a%vBW{8K3hTem-drx!vJCn)izI}zQ&XGR++5>Hzk1cLDPRSYjpWb}c{OSCuZz*0>rrlK$}WvyQh8tk^7B5_khSddS9M^5>gk`8$byi
zZ^H(GAo1+z_L4SnQ45D8aw%A2JKdqSgXiGdVgh>IY|@eiYdjyfI07Z4E~qyUgW;G#
z5T=h!;-xFpfiFRXTnZf9>5gpMe|V1Qp#-$6_q_%Mj?46C_&Y)Bf_ejqnB0Rv5WNvk
zqGSGVNQ7K$j%{>@+cuuV2u7aAS`8F9)*9M)gs6+qI~)@Tnrz2ni45dob6iMwWZTAb
zc#ZK>1(>y*bh?oue6r10W7bQN;aGy8$==nlK|ByJaw%|Zr#sxX^BnX;e+jZVafg~N
zu0MUM4#t|jmEa?gx}e^AKj>X1Bqs
zHB(xXFns}iKL}~yAz+|{)P?jc>YsCs@C<_>_z_(3(gX$)l(3z(IOq|EM+jjuInG?a!kPn2*sIz!!3*#8Gd01vOj>(+zvQ&ah_&)BYG$7&h>J$mIU>6KD&=eYOb<584@QK?EO10kZ-_
zCNOR`fP9kt4g^5{;lIERw08m<)Nh;&c_3;j!+#I~w4VP1D3Hn-P<64Mf8zy-$iTzv
z03*dc0XAWFcYYaT%91-`i&K>>SvX
zc`>KwykGQ0mk^EZO^?=@vHe5}e=J(n5nkK5bJ0Hag!fxq0Vf=0m5!eCey;iSnE8z_
z&1V&G)oS7m#)}V){wKJ3-_iL#784(|0Hx7(l&Fqx7$%27{&*{-$h@ZnK$zBl4P1r+
z#Fa|yG3Atb%=hbOd%$bFJroYG4Xm-W9_APNJ%gitr2X3TwQzrf2kN&qX*_#c3&`Tcw@1te&bfa?Ch(2hd|-~Rwi!G92n
z*MMOu4sHK9mtzVxKqwx&=Ly(#FDmU|`tHz`z1!
z{%7ETg$TD_@pmAxy<}6qi
z5kb5_N$%#7*8&jk4s*YaGC-#@FbIMOpc@#0K8GttBr%XALm*s=Re+O$TmS&SetZis
Sj!_Z-0000m?U5l%e*%|D
zL_t(YiS3oYYui8+$G?jFOA(edrX&S>@8Bh*ONrMmt^(a%$WXGR4rFi%Z3G>%711G3
zsL7O}n@bF7DNXwq6lKWTiiXlbMG+WNI@IaA(+{6z+1-o3pp)73Hey;!HLXf7P0F0!0_HolnKff{_eN&GBd`hd{C&&z|y;)tYqj
z0t+<^r-Pc|O?StlW&)yYBm|~mHt07Wm!^Y410+j~YC!@@q(^^kDH~J?D;sRIvOtyS
ze*Q1eLY!YpeMiu<%0_W!k(2W>wq7
z7hF+mmV+%;D|WgEz(Zw#!f-YbDNOe<+`Q>daeJszb935Ef0mq6srdpAwLk22u7RtwwpkKv+Qn
zVor)`EO$rRmIKHYJKVaCxOF%Le$r2wEy2kn+Byyrw~n$8sm1lcUZ=nl>U(trQtNDy
z%gSq<)3Yw^)H0iatxxKb;dU;dmG`qjl-mTQGOu+^S#hHM^EsPf#eqji*KY-BO4mfmio@RI>fMh%a!)68s7ATVg
z9v0kw#ovL%_J%Fb?JGAoFie2hf5it=!2FGYp`3w1y5jLw1}>nN8MpV@1~8a@5_ra7
z`j`81ydqyR!#$w7bdX{Rxb0E}3>O#}Ht>GPfK*RoU^3wUFoC^*4X9K#f4oUV
zK~y-6?Nd!l0#Ot_<84s7Vd{yL>M~YCi<}Mou~M;aa{`!a!1d(=X&3r`+yNf_%HCA6v_i+N|#j^noLVL
z1eUQmKvwmhD(YB4N1}URdKS9vf9+@0h0j3S)2~|`m4dflr~(t7exGpXwwQmG{fXRDjny3g4j)l3M%TairB&4=oJc%}CSosD;I{t|
zlvs{B+oTGAg9>R5(@NfiT?9gzk{N2J@r{^H|4)h7TWK&lek){yQ~{g5f5cpWLYW87
zfs=*}|6GzY#!N3irqJ`VL--%@26YQ~B{Hk*U=>(UMgMBGZ+-_bS#{x`u{!++siv0V
z>dN&6jhzlw9QT-?zpxI6)h72A$r|1H(cmH(nrLMS?YhBl=!3Sm#;$_fj-kNtr}s-2&Om=-CtHa2C=^z
z_jmoN6%Ir1536UQl=uCC?sb0)x~#g;Wcp9>10WTUfM(=_-v9sr07*qoM6N<$f{Hio
AmjD0&

diff --git a/docs/html/img42.png b/docs/html/img42.png
index 6a1cb856a7a9029bfe698ad41a1583c1d064af2c..b693f7e5e50578e25db557341dc8377f70f16966 100644
GIT binary patch
delta 476
zcmV<20VDpE1DpgQiBL{Q4GJ0x0000DNk~Le0001N0000O1Oos70PXt)DUl&ef0{`|
zK~y-6V_+BsbOkbJPyvzJzLI4bV*^>*_#c3&`Tcw@1te&bfa?Ch(2hd|-~Rwi!G92n
z*MMOu4sHK9mtzVxKqwx&=Ly(#FDmU|`tHz`z1!
z{%7ETg$TD_@pmAxy<}6qi
z5kb5_N$%#7*8&jk4s*YaGC-#@FbIMOpc@#0K8GttBr%XALm*s=Re+O$TmS&SetZis
Sj!_Z-0000C!zv@_U(2oN@6V4DEZ!JhmMe*_-DbbNlN3udwZ1#*@${09*b#xw@3Iym>e^M$b9
z0yzl`O9Oxeh@s5zpA+h;xhSpzqF-3DLUf&I=um=0D320;)3!U7DOaK{9o#s`e`Di(Vrq5u>f
m>~3F4)Ik(z;KyXq8UO%$%x%&E@Cw)f000020^lrcfO!H6_X1cY<5Cz4D_}CfqKEq&UOi|4qH;13dN|PZ
zd^nG+hug3CJCNAk0AkFxU|_EYi9Scw!ycfItjF||z%vHZzuXr<3ab
z$TM6)*7Km9!4^b-un_~>ga`kDe}ZLp??3>q=kq&V6#pz`_zxl=jA;-injX%5?|hN<
za3(M;4FD1#hBCu{PG$vQ{BT}CaT^f*0<$=MJ304%WZ-t-Q`o@m01ONV#)Ax*GdT(k
zFv4If1A`5i#m?}oo`IWzqk#4D1C9b<@D}hXFx=a~zZ;~I1zFFN^9<~FPX2*daSZGW
zfwr#yxxGL|b!UHEP;Idx6=B(Eb-n1`j@nU4-SvBUp1IkbncX`b)(Q8A
z*2>iLR4yJ}Y9cFhwaFz~}`?I^j_ll^Q0ljL`oN
zsVxeqEcujO*D=wd3;EYy!9kTcvBuX_<7Hmta}HC~jeCDcQAWe7G8-zk?B_j4O#&*L
zVb}GX)~8l(aRvA&UN{dMV1R@TwXso|Ch7V4S?#v?i|Df3<*;C!o0O
zTN$?yMeU#p%;rLi@n*R$aE})X=0^Zi^ky`QuRBS_sA%IB^9NY;%?g0+iyfFdyaga#
z(gj++lPa-h(-;_|zuM*no8){=FMslF@-^2i7{l&$yz<_(e{yJVrvv5{e?szDr+e5r70K&fa0K_-Fo0tFm)9yLFNubV
zsZ>ZmGN3zAQQ~&M&^r%-u@knyTksOPI9hQ=U4&y~Hm?rlEGN^Ew#`)_VcP6%;yaXY
z%fs(03$)@`IU24|sW7{1nyo^RqI;4Z?2>7RF&OGM(AiaN`fqJzNDrEK
z+c|W(jh{O+>>0`zvNmU<6?Pv}OL|w{qd2h#ecWu9LR!Y~5}5B*d^;W(inbZxPTfwa
zs54c9whrt}4niV7f5i?ut2r93P^s{yNCKtkkBpoa*8Jh0A@N;LL&fj~EcrN(E^;+a
z?Oh_iWv#fZ6sLNXVmJyO#TI$G+5Xjmw~kgRE-A&>|ATI)RMdkJvW`@eUU4u`F-M~n
zEESFp59>(*DZ1@!&|?hH3xDAt_|EF5zelrGxa438tUh!(e}}_l-g!fOeTp{#x^!ZL
z@rUCb;~g@_lI>E}YP<^j^#$uy{2{<akhb*z#%-~Z(@m{Bb5$rL|z
z$k%+rIljewVgz_)^IEvISS<0=DRl>2I3fY9Pw0$WfAGQOZnpGZEV5WE8v73YRlv@F
z@>CA~vtF^yt4HuY+sRLKYUfngiOyK&q5gF_nA1P-BsVELj-{g)N5evZO2rt9N$d_#
zirkz3jktabtz4yB=J*6d8E-U3l8Sg%8anX-!@j{bHD9&)8z)M8vL)3~P0EgD_5N-@
zwM!~he=5i=@0Q@SDw--a>5g20BC>A15-=z8J=Ko^Yzht|sjF{(y&=1~ma5a#>LbV|Lh2)1F{VC(Y$BvSvelwK(4syq>QmL;qCS(i7WHY_X=JA*_4)C=
ze~76M1ymMO>N7KH>N7Lm)Tga4TZ)wWNI+$Aq&|s!c3Gs*bRmuV
zunl{tDs#Ue15JZ0Tb3rqCsD(r5QHsz9R~fcoqBTjtg~$_ICb#-?spH8e;}Tc>OcGxp%Dt
z>-JB522$tizxjaF<9690H%2eaU_9SpY@}V71|3sNGi*NWQjnx-jD2)RLmjgR*2;VS
zYV`(&e#~z8owJALSe`LnM5j2he;`6H%wRlUkdb1cK?7=Of+hCQOAtenD#bp!qoEG-
z7$O&hN-U+A*$to7&p!ZFirefPWSh_nGZ@eJRBTLxDr#whNoIy5HHvHKj(*|icXd*{
z0mc4;u7i
zc4N#d!2Ru0c6Y%UL|Fv!e89yh9o-ncFoW@YL3Ui@CHP7$O)(-U8j_5gkM0DU{<9$F
zDrvV_!ZG48V0;$|IR3XpWK4sMk}Rjv8cZUz)twB7As)ZeDVk+^%};lNO#`AJ3q?GB
or&IJMaY8oIc$Wz{HSulnKf1#vLjTqQ1ONa407*qoM6N<$f@}mXf&c&j

delta 421
zcmV;W0b2gp5#<9RiBL{Q4GJ0x0000DNk~Le0001H0000R1Oos70DMj7PLUx?e*t4j
zL_t(IjqQ@ZO2beThkxn+5Stsxg6)&NuZf98;}sE^P=UMBfE&iL~!1hSn=7{FGFVPe~Rh&j#r
zp2YoAba}6h&^a_x2Nfu+I1gH68!?BXXbRlz;y!q5d%RN$+27l|RJYVt$iQ!5Ggt{;>i0#}~?sPsDjAKs5IHD`MXRVXuL
P00000NkvXXu0mjf#go2_

diff --git a/docs/html/img45.png b/docs/html/img45.png
index 8117051133fa01e259dbbee38856fe85a3a2509d..3803414367ba867d7b4f8c79d6e287023f9da694 100644
GIT binary patch
delta 510
zcmVX9K#f4oUV
zK~y-6?Nd!l0#Ot_<84s7Vd{yL>M~YCi<}Mou~M;aa{`!a!1d(=X&3r`+yNf_%HCA6v_i+N|#j^noLVL
z1eUQmKvwmhD(YB4N1}URdKS9vf9+@0h0j3S)2~|`m4dflr~(t7exGpXwwQmG{fXRDjny3g4j)l3M%TairB&4=oJc%}CSosD;I{t|
zlvs{B+oTGAg9>R5(@NfiT?9gzk{N2J@r{^H|4)h7TWK&lek){yQ~{g5f5cpWLYW87
zfs=*}|6GzY#!N3irqJ`VL--%@26YQ~B{Hk*U=>(UMgMBGZ+-_bS#{x`u{!++siv0V
z>dN&6jhzlw9QT-?zpxI6)h72A$r|1H(cmH(nrLMS?YhBl=!3Sm#;$_fj-kNtr}s-2&Om=-CtHa2C=^z
z_jmoN6%Ir1536UQl=uCC?sb0)x~#g;Wcp9>10WTUfM(=_-v9sr07*qoM6N<$g1iOo
AumAu6

delta 487
zcmV0yPJBy+&cucr-zBe@3Xs56t00
z1mz2mBCu^dltJ{P7VOj=s#}2^^bWIlr`m%c2tz2ye%Xmy7h!Ex&cUIkaL;1CU!gg2
z5M2~56}EFTw#BDFzd%v66CHzk2(z|TfFZt<)W}3X&TIqaG?`b~YwZd5%
dR9a`M`UJ~Ng?zEV5IFz<002ovPDHLkV1lKu*D3%2

diff --git a/docs/html/img46.png b/docs/html/img46.png
index a2b5d2b9ef74fb1f5c60f81268bcbb2b65db10f3..6a1cb856a7a9029bfe698ad41a1583c1d064af2c 100644
GIT binary patch
delta 340
zcmV-a0jvI#1eF6JiBL{Q4GJ0x0000DNk~Le0001D0000S1Oos70BECkjFBNse-lYW
zK~y-6V_+BsqW~Q^@PnxUI12+X7NGJkfYmWBg|RRI-`)$@ba0=;se^$ZtB%Qpbu^&r
z_;4PsgWIq8JCNAk0AkFxfa%~XK+(Y-pbyt!`bpp!gXv%H3m}F8?*pg~2~=0fGhBhN
zm>C!zv@_U(2oN@6V4DEZ!JhmMe*_-DbbNlN3udwZ1#*@${09*b#xw@3Iym>e^M$b9
z0yzl`O9Oxeh@s5zpA+h;xhSpzqF-3DLUf&I=um=0D320;)3!U7DOaK{9o#s`e`Di(Vrq5u>f
m>~3F4)Ik(z;KyXq8UO%$%x%&E@Cw)f0000s$nf00Q<
zK~y-6?b0zz!$1@V@PFE-ZLH13wFdCSY6x$
z4laTgKR_$uD$!OP3h}_9f=pkb&me{O#2!F6XfC%8g52ga(ENp;z0t)v6SS9097z-<4GQgsT`y5_9XaJ&eG7)+>
z(DZybkF1B=ulPHV*xmqQ%(h@)uLp@fN7cg~ppUG_^pn6d27lAP+!sI$1KtPk<^ly7
z8&LJgGh9K|^Pru<7DRxs5d+(V2mgVBWp?jC0IuirJ6#n2EM@o)A|Q-u5GI-)&VBEE
zk@avUFf0uK5+H^$!+%a@1z`MeUO;gh5d8wPIDI=g_kU#IcHmRk!0iAG3Es2SKv#39w^}P!xcwXY)^PeNWQ#5D6OiFN){Iv+uPgEoH;WsEe)v3*x0zYw>L5}GRl1MTp*vZB*-tA!Qt5rkYu8#i(`ny
z)Z~N(%oBX0ow(ZNr)nF4ttUX6E%w%!gG4X0JRj?IF`-2Igj^j^mM2
zYJwORUYNMBvC+A~b%CJXA-l%A3xsa2VM*a*?^@b(q^hMYK~yNB;S@8&vsLm|>uy}W
Q4z!HH)78&qol`;+02yFS5C8xG

diff --git a/docs/html/img48.png b/docs/html/img48.png
index 4694a8cc13ff70345a6625de205dd12e8c2b4006..c4c081885da98090dfa189c98680841102a0b915 100644
GIT binary patch
delta 421
zcmV;W0b2g?0p$ZBiBL{Q4GJ0x0000DNk~Le0001H0000R1Oos70DMj7PLUx?e*t4j
zL_t(IjqQ@ZO2beThkxn+5Stsxg6)&NuZf98;}sE^P=UMBfE&iL~!1hSn=7{FGFVPe~Rh&j#r
zp2YoAba}6h&^a_x2Nfu+I1gH68!?BXXbRlz;y!q5d%RN$+27l|RJYVt$iQ!5Ggt{;>i0#}~?sPsDjAKs5IHD`MXRVXuL
P00000NkvXXu0mjf)NsC)

delta 176
zcmaFL{E<H#cCaPw3uz&=-+t1q4A+{$KmqE|IC{in41+l4p*!{
z!?3PrYOq&Bu)>5yr4C`^hxW|J+r--P1l;X@F`vllFgn(*P$ai$G0Tcarkf5(vRE`6
cVq{q0sQ&csj)>hrH!yg*viZ5Jb4q9e0CY}3eE0yPJBy+&cucr-zBe@3Xs56t00
z1mz2mBCu^dltJ{P7VOj=s#}2^^bWIlr`m%c2tz2ye%Xmy7h!Ex&cUIkaL;1CU!gg2
z5M2~56}EFTw#BDFzd%v66CHzk2(z|TfFZt<)W}3X&TIqaG?`b~YwZd5%
dR9a`M`UJ~Ng?zEV5IFz<002ovPDHLkV1hpO*7N`X

delta 328
zcmV-O0k{6A1c?J7iBL{Q4GJ0x0000DNk~Le0000_0000F1Oos709Qhf*^wbke+NlK
zK~yM_V_+D>p#B~MyT=AFGXbwcZeIq5uV5CR0)B;W0vI3$@_)dukj(+2kojA`z?Rn)
z4D*W}7`8mOFJO?jHb7Q5k9{F4M1V(tIsU?4PDSPf=6FTE1cpZT2B0s$me*uw6
zL_t(IjqTDgOT$1E2k?K|rfsav#kC5$xk*2O6bHdYG|q}-ad7LPMTgRYLf0sWgIHbM
z0}d{N7C%5M;wsTr918Kkp@Kq9?i!o6(%No<50V`3?#I2m7vMksSV-@*GB+5lBb*#e
z-eE}XUy1f}W2JtWIp`r{D^f3|btuuQwlOA~}5=gIKG1p~KTp)_qG8pl~PBlE2y
z3bdA$;WkNzsrX4xik%W6J_u!S;(TA+1!C<23b5&OPcynzzW2y{W|t%D*zTHLeb$xx
zif=CofktN<2_s6^J<>o_Wyq}CT?0}H%L#il3G$|ZB%VqQsRvERS=9yWf0;>QaI}Vk
zS4stt8gOJ)T!}HX%7DR;q{$P`Rl4hB4a6Q(kW*Ktc|Ulyl8KnReE}FaxI~!HSBhOzAjzlTO@}esR9V76@
z5_EW^V3*F&ieASrgPk_-D!dpPU+(e$wuRxm7!n@)f;O5sD>r86TAZ0000<
KMNUMnLSTY9o6dFs

delta 1678
zcmV;9266e51jG#?iBL{Q4GJ0x0000DNk~Le0001>0002*1Oos70Eh3wr;#B`e+EKH
zL_t(|ob8%VY}-^E$A6(sQrF9$3*yg!Z5Jej1l?&|7!jJ_fEeLSrB)gocA*g(>m;Cw
z#H8J5I4}^}T5&)Vw@ge735gC(9JtV;smIZ>ja6tO^AOVt>tyUaC;q+n?7aM*O-0N5
z9+Kwy`P;;?^YQm<0~i_o%Nk1Ae=mP8WkdLV6AY~?)x@6tbH!bbGqh%&qZ*EshnJv|
zcU`xJ4YTZNClty=!#T(~P?O%_P4;vaa(&ls$U|c=z8VYwH!5b}T2H&^`@r@5O_>pS1^`cmUvKJk}~We}_Xu8(_Kk
z+foS`uDWok_ihiheXVw1-&X^7FTfNwZ07vM?e@8LyV^0lTP!(+F*M^1_%6=yR2jUl
zHv1#@wjTlB@FmDqcc5?Dnk??_y*SN((Z8|ZKXRiS8h*3?
zF2JK}htNt{>tVD3gah*-$cV?mtI&kduywz`(ubd+3FA!{bksTYtX2Q7AMjoSyIyl5
zR~SgP|B$)8fX6bw==%kFjQaCnv=ua_oW6D
ztun)N-F5G9hFW+&?$M=%@Qe*rcy2@uo&hKuJqeJj@OZXiCD#lMF`m_29`Ve^$9Ozj@TUJ1iDxC3N4@RvJP3HsTo4RY7|&`hKklyI^1g5m&tLC5corFAJX5*M
zlr39;3^AT{x!iU3A2>WG;&LDk&na*@kiqjdk;%(Q1TKqtxxV7M(lJ5dvY3}W#N_w%
zmTGWW%*#Gvp6o5v;If#PeZ*WA4M|+)^RkZ^xSWW~d|vhue*>>4;xeC?{WG2H#Y9{d
z^0IfPGrT(ymw6!jXF8uY6LFaXvcDS^4=3X?2juJ@Q|@fpaM^I#sE_h9(`z;Lw86Ct
zPC)X#7HKbho^qPECL;zvBAQ?>+ZB2F$5)A40dsi-eD2e`R~)FWC_C{6{8pxr^k$aISuw_aJk*i{!wt1%)c-LFO_;a_P9byGUjq*~3Y$%6U+^+(R-mv}>@ydl0!CM&-cp%bP9UgUsbF
zk^{p`Rq)W~a_67VNgfHg+>$)f;BtCwH~PSC
z?k=Wt83UQ+Nw_S;TgGX_Wy58oP1O8s@j$9z_746Nf9hET6~?%n7l_z9V=nL5zcwjNp!Uv~
z%U9ahD&Z2%-WhY*#ZC4=y>mkz!d$+Do9vk0nZo6XMQg)R_0Aex?%zApxvc7)$y`?S
z&U7v-dS^P96}>Z=%c|a)&SgdKoPf*Gy>n77OTBX{Ff~NpezMk`YcHni=9Sj~!oR>-N}jfmyr9jtk71J$8JNt=VJ82WH*892=Mu=VcMk>EvaE
z=QNRO@VqUwRpV^}MaJ8%2IVr&%Pig|WGu4rZCb%eO|l{z-=-Cu)DVj7hCGDwGK;s0
zBAa}hma536=Ve8aP0!1!BAcF<`xn_7dAWa)P0!1UBAcF<6-Bn;av~Wn8yOiH8U4TX
Y4|+xZLoI)W&Hw-a07*qoM6N<$f=bOzEC2ui

diff --git a/docs/html/img51.png b/docs/html/img51.png
index 7553b4a8d1eba7301913dc3b148b70b15308d5c7..a5da47f0af7d8c5dbae05d5770e129208795be08 100644
GIT binary patch
literal 221
zcmeAS@N?(olHy`uVBq!ia0vp^l0YoS!VDy}53P6sq_hHjLR=3VIIwy1=7xp_A0MA(
z%a%z>N){Iv+uPgEoH;WsEe)v3*x0zYw>L5}GRl1MTp*vZB*-tA!Qt5rkYu8#i(`ny
z)Z~N(%oBX0ow(ZNr)nF4ttUX6E%w%!gG4X0JRj?IF`-2Igj^j^mM2
zYJwORUYNMBvC+A~b%CJXA-l%A3xsa2VM*a*?^@b(q^hMYK~yNB;S@8&vsLm|>uy}W
Q4z!HH)78&qol`;+02yFS5C8xG

delta 189
zcmcc1c!JTWGr-TCmrII^fq{Y7)59eQNDBZl9}6>(yu#SH6G#~Z_=LC~IB;O|=FMtq
zY7_NE>v?#1($dm^QpU!{y}iAWk&&J4#U?;LV@Z%-FoVOh8z4zHPZ!4!j+w~`2iVL0
zeE<93oZ&=9%7@eh#!GYfB|b^sXyi#_yH=dQ#?1ViaYfcN?f|yi>>A3?7^eg>8($Q6
i+W0U2i>wDDgIy}$q#A>XvwobuGr-TCmrII^fq{Y7)59eQNQ(op91Am$H07QVJyFr8KHt;DF+^f&a>4?|
zg!Sn&_@D2Yefop^xyldo9~wEuY8`g8m~GtX-*~^F@u6|Y;qu1+%$pgQn-x0_SFAt7
zu&!rnuvbH{!h}Sn4q@Ym_RPoI#M<%%-0glbpUCPkI@YdGB)4fX%Zf*)n+`~_STr1B
bWLV&+{`BsSh}}RZFnGH9vAV2tN@xNAU|2wE

delta 145
zcmey!c!g21Gr-TCmrII^fq{Y7)59eQNDBfn9}6>(v_AZ*eWIdIdXT4!V+hC0p#B~MyT=AFGXbwcZeIq5uV5CR0)B;W0vI3$@_)dukj(+2kojA`z?Rn)
z4D*W}7`8mOFJO?jHb7Q5k9{F4M1V(tIsU?4PDSPf=6FTE1cpZT2B0k52(ea62H0_%bl?
zV_3`o0Z4EZAc^F|l$C#A{lM*4{GEZlp7~q90OxnB0E8;ma|{g8V0&I(;QwIyN#Gg7
zySWTJ0t}M`%z&c*K>+9`_5%zIf0bZm{2zD?9<(#qGCcUt@Q8sSonZ@-oh%m^7(Rem
zTme8cmNNWj027=C8QPJQv3-Cko5t{n6&MCf1DF*iT;}8hvVg(Ydlv|RmhwDc;Ddz6
zTZS*}+zxyS8#oFL4svr|;7dUADbUyQ5SHxo9UD0cST8@|-_3AuBZITKGqM3f8K?5|
v4^ZX=RsmK92000000NkvXXu0mjf0g#9w

diff --git a/docs/html/img54.png b/docs/html/img54.png
index 31995149ce6bcc0dfacd1813a31efb496587aae6..14fd3ea0009953134916c5b9ade197510ef8abfd 100644
GIT binary patch
delta 1678
zcmV;9266er1;h;@iBL{Q4GJ0x0000DNk~Le0001>0002*1Oos70Eh3wr;#B`e+EKH
zL_t(|ob8%VY}-^E$A6(sQrF9$3*yg!Z5Jej1l?&|7!jJ_fEeLSrB)gocA*g(>m;Cw
z#H8J5I4}^}T5&)Vw@ge735gC(9JtV;smIZ>ja6tO^AOVt>tyUaC;q+n?7aM*O-0N5
z9+Kwy`P;;?^YQm<0~i_o%Nk1Ae=mP8WkdLV6AY~?)x@6tbH!bbGqh%&qZ*EshnJv|
zcU`xJ4YTZNClty=!#T(~P?O%_P4;vaa(&ls$U|c=z8VYwH!5b}T2H&^`@r@5O_>pS1^`cmUvKJk}~We}_Xu8(_Kk
z+foS`uDWok_ihiheXVw1-&X^7FTfNwZ07vM?e@8LyV^0lTP!(+F*M^1_%6=yR2jUl
zHv1#@wjTlB@FmDqcc5?Dnk??_y*SN((Z8|ZKXRiS8h*3?
zF2JK}htNt{>tVD3gah*-$cV?mtI&kduywz`(ubd+3FA!{bksTYtX2Q7AMjoSyIyl5
zR~SgP|B$)8fX6bw==%kFjQaCnv=ua_oW6D
ztun)N-F5G9hFW+&?$M=%@Qe*rcy2@uo&hKuJqeJj@OZXiCD#lMF`m_29`Ve^$9Ozj@TUJ1iDxC3N4@RvJP3HsTo4RY7|&`hKklyI^1g5m&tLC5corFAJX5*M
zlr39;3^AT{x!iU3A2>WG;&LDk&na*@kiqjdk;%(Q1TKqtxxV7M(lJ5dvY3}W#N_w%
zmTGWW%*#Gvp6o5v;If#PeZ*WA4M|+)^RkZ^xSWW~d|vhue*>>4;xeC?{WG2H#Y9{d
z^0IfPGrT(ymw6!jXF8uY6LFaXvcDS^4=3X?2juJ@Q|@fpaM^I#sE_h9(`z;Lw86Ct
zPC)X#7HKbho^qPECL;zvBAQ?>+ZB2F$5)A40dsi-eD2e`R~)FWC_C{6{8pxr^k$aISuw_aJk*i{!wt1%)c-LFO_;a_P9byGUjq*~3Y$%6U+^+(R-mv}>@ydl0!CM&-cp%bP9UgUsbF
zk^{p`Rq)W~a_67VNgfHg+>$)f;BtCwH~PSC
z?k=Wt83UQ+Nw_S;TgGX_Wy58oP1O8s@j$9z_746Nf9hET6~?%n7l_z9V=nL5zcwjNp!Uv~
z%U9ahD&Z2%-WhY*#ZC4=y>mkz!d$+Do9vk0nZo6XMQg)R_0Aex?%zApxvc7)$y`?S
z&U7v-dS^P96}>Z=%c|a)&SgdKoPf*Gy>n77OTBX{Ff~NpezMk`YcHni=9Sj~!oR>-N}jfmyr9jtk71J$8JNt=VJ82WH*892=Mu=VcMk>EvaE
z=QNRO@VqUwRpV^}MaJ8%2IVr&%Pig|WGu4rZCb%eO|l{z-=-Cu)DVj7hCGDwGK;s0
zBAa}hma536=Ve8aP0!1!BAcF<`xn_7dAWa)P0!1UBAcF<6-Bn;av~Wn8yOiH8U4TX
Y4|+xZLoI)W&Hw-a07*qoM6N<$f{Y1GT>t<8

delta 645
zcmV;00($+#4Z{T?iBL{Q4GJ0x0000DNk~Le0001_0000W1Oos70B*X@ypbVGe*!^C
zL_t(YiS3lXYZGA@$G_L}n!6miI}!Xr6%!mp5jiYH9Mr5`A-7!+wlX5L{mrD^x
zUoKdoigf*CCq$@y+kPcHoaGHGk!e`HuC)Pg#kr!(4B!XP{QaWu
z_7t7`{48=epW_3?k1+GoMr9uz!!I_|3fnV!ZPa}wi&429@LBnNvVmNXNOV?T2r^7z
zEJf~{H8fXzY(yu#SH6G#~Z_=LC~IB;O|=FMtq
zY7_NE>v?#1($dm^QpU!{y}iAWk&&J4#U?;LV@Z%-FoVOh8z4zHPZ!4!j+w~`2iVL0
zeE<93oZ&=9%7@eh#!GYfB|b^sXyi#_yH=dQ#?1ViaYfcN?f|yi>>A3?7^eg>8($Q6
i+W0U2i>wDDgIy}$q#A>Xvw-

literal 222
zcmeAS@N?(olHy`uVBq!ia0vp^+CVJ9!VDxQ&XxQCq_hHjLR=3VIIwy1=7xp_A0MA(
z%a%z>N){Iv+uPgEoH;WsEe)v3*x0zYw>L5}GRl1MTp*vZB*-tA!Qt5rkYtjli(`n!
z#N-4C)+glz%u;7`ZJ3;>pUpf$oiCVO@IgWcW8saaa}5U=*=8_2W(rB1
zaez%s;41HSUY!N!Y8t0A-t_7?P+~f}GhrQLh=kGsr2~u)tsGh(GDR>jY-^T!`>mx8
PWE+F0tDnm{r-UW|8zf0O

diff --git a/docs/html/img56.png b/docs/html/img56.png
index 3a198f8554b389cb8d10373f961ef9966d984d76..4f54c6e9322e42222763ddd95a3d42401972c37b 100644
GIT binary patch
delta 146
zcmeCERLtqy>SPkA)dXS|5JZK2gy-gCWS%#W93qW^#f8
z!;Sy{{{I&|bm!QC02PL`tp)}LxeS}985?|vV=%PnKNN9?lZPjVPeF`*LXRQC#vNP|
w5_1knJ!3H_Sl1%?J%_17aQ(Oc>?gPw_>Ty4Zm;WE0knp})78&qol`;+0D1o}vH$=8

delta 1237
zcmV;`1S#nJ^)!O{{~3`nbavR_cLs4WzVZ4@7Zl{^ccbsc97
zw$mSde8U?YXrRUhj1oqiR-R
zO8*MdqJb-wk*x=6QU-osL0Z_9FS<>T(d{7_U6W%jl=7^NsSn4z39od!e?V!vz-1iB
z-2rrZy0+Wi;Yz>_-+g4`#1SB>K)`AS&jAw0S2!ptYlY-8Sr%A>pnz7m~
zHV`aeEQXA&&`qSQHajGve~54MmaTJuh2TFPb;Fm69$u^pS2`jYMd^r
zbQX)48C3+G8BYt#K!(pMSitQVG9I#n-ZNDzgD&w`f40~H`qg()8OO_9hEYVu6*BOT
z%rjV`v3c$$QrG$fof%IH$#6Uwf)!83R(4otW&W&@u|KcD=w}P)e{w~Javs;&9ZDBL
zmrIJxuH2QkM(VV<8$bc~1f8A3)0U7SSn(EByR8)PH#+7*GP3ka8a90hPO+OF$ROjm
zU^8iFu-D{U9ES3ow@Y}z?}@$fG|E^j=q#6~Nf%s}Az1OYxPFDA*N={Uh1p^7pO|K2
z=@S_9w=I-LKQOU+e`12hjB~bfwRCTUeCgsuj=eLo^hxy&URr?hiw``W`|))e9l_#j
z_XT}oVw|VZ;D7!$q7zZdgF#FW=RFqwh#>=No*wpvy`*@IURjmRs#mQB)h}cZJM0Yn
zw}R0gT|~`&KE0Ag1Y~X@6?H
zu^LWB#9H)e*pw|Se@dg)q7U^a_QW0!i{HdP6Pu8(`u9kiSij|i_Rx(wPnv&8yjn$g
zq)qIAKiFI8%IljGcKGPB{<5RFkaN_1Xx;NLQSmW^XT9x@U9%&Z|IiA=1)E0QyO#ZQGV!e|Bgb7nh4JC3suh;Ui>+3;18B2y_Yh@D~
ziHJ-rD=!&Ipoxt{L?u>#8a8DuY+{=>`l0?mR#}g_6Hz7;00000NkvXXu0mjfn*>oR

diff --git a/docs/html/img57.png b/docs/html/img57.png
index a166a3f67c4a8249fc9b8060918415352cc37387..3016a54aa5a51e29fb8f5c4b859e0e9c66a24650 100644
GIT binary patch
delta 350
zcmV-k0ipiQ6rKYiiBL{Q4GJ0x0000DNk~Le0000?0000F1Oos70K9cH+L0kke*qjx
zL_t(2kz-&OXuv!HOhp_;2(kbD&0x}xs*K5iApuBnCLoE`0F^#KH;+#NNN_tKiTE-w
z@MBoZ{{cvF6d;M@!<3bOVEw@DSNxrUy`K47zX0cVs{n*5)^iLD(O`RCUf};=`bpp!
z!@Ic*JOT`p1k8Y<|3LugCiVjie+-piW&9s_4IZ>J*fKo$&+v$WA)R3hlASCU7#Kc)
zSzG}?GnO*^X8;qN2N~Ltl(Bt)DVxUdh!q$HO9Pk{CS2y^1G0d@*LxQTfR^$+VBmv<
z$6JOk?A#7~3L7{I4Gwa1Uf@eW@+r{Q@(`Bn^Bo&G3Ro{c;NQ(~ZzF@VG`X??LK&y>
w^AAww1Xcl71_nVOgMkw$0pcJ9_(Kp0019qUQ(rlMGXMYp07*qoM6N<$f_@)}b^rhX

literal 2637
zcmbVOeLNHD9^aZ)v{mO~d99t}Vv#d8d6!`;Wf+wu@)D+be~lb6oC*se)9POILO5x{
zk{G6lO;+Y4AxqeijLghS=I)$(Kc9R4xc7YSxqm#L=kxrY=l6Vm&+qsBexF}9!Sx7K
zNka($06>pAVLboT>|^2wNhKY{D$=xAtY(9_eSP$+mjzOu4XU0ppc
zF3!%*j!vgTAP^Es?g&7m(Yd*~US3|=SK>_NYhb*G>u~^P`mKCZk$V(te18NhFfbCVXXIhy&uDi>L`*U!|<+qSID_KQqY=3muCy_d3@Y;Avbk>HteCNkSi
zF3ACUFS@bJka`kv6Xz)%qlVVKmlDR~L^vJbs*JJGDKTA^Cwk?HCyb
z528xjiwGrSM5$i=Gsi^R+Sb-+~L6qB?vt{y5Fp1>%q6l1kQ3hOqm*1QtFbQ8?x)yQ`^Xlf^hd9GufHioz}UDXN@-C
z&35^IEqcLGx+l_RM-AKcN9kdrh5&>0iE|p$eN6Gpm6XBS?u-4;+a7CbKrZ)p?%7)I
zz)>aWJxxEx0%q=0y)U`jo@x+BpuJP!U#_+{;F|hxcYV7ul478|>OoKRfMq>+M`4f8
zXtpFV@qYB?yQySN=G9qXu~)Tu`S$t>WV?qhKd9fd{05nds$^hK7}4A6J*QD8!|aG{
z&yqn(8{SQcFTe>8zn*GZSAT$xEdPLZ+GBNg>;9kimZ6~trI|v@$^1>cTe7|9C#Xe+
z@!pYpA>O-!Gc>-Lr~&q%porF1pBO>xR?c6i*q8F&Q?{^l%C!jeV)@nF2PMFqPSk8L
zl{TScWiN&nsiTz}UN{qxUH6^c3?&qXk**goWrnt_&|&a{~hb`c?e=D
zYV5r>uQ7P)#ZxkA<4J*KikVgt8XAk;m7SeTiq+Raz*N?W-rSD=PTE@{L;Y(puYmECMCPy?l)hl3`G1&;QT?rU2w(+Cp
zp%~}C7k3W_2vJd1A#@{jIqZ<^wPf#xtE}{F9{Ttx5(`35p?M)eDwl%aZ~?dgx&(!B
z|1aiv6R{1icee`A#U;BmTIB2r^Y?I$=)hD0Uf0%n3f0h%-;y$1)a(;40F_@D$DH=$
zW?VmL?7vVEf$fr{_oC254h6UsT0~dxT`FdxMt)03s5Z}@vpkU`ns{P@{3ym2SRQhV
zpHci?z&`<~zvm4=kp)@y%e^h<#4WaadzQdjXIf#*|F^EcM*+qVoStmVz3UfNHN!G%
zL>+%G?fW^*DpZRUWMB(~Z42_Ts%BgF}uI^hE!h>s?N3F!Xw#Hl^1MdM2p8j3j
zJfoyLjFCxe`@HWG5alv$kXdw=ELDf?e6PV^xjqXb9Y&>2O%}`6<<^m3$}}0QL;QX|
z>+vO{NBFe}$Ys#akySJ~<^$_G(P;u&jI(Sf@e&zs=srSxJ|IGWwtJc!d*ADXZ`cE_
zmT&0E$n1(SWrg7Z=g`Ibp@Im1jLDk{VHupuiYKqEi$Xzpp7YGP{`p^8E*ORWVJW|r
z%btlWN$K7K?ne06>x$@Z7jx@0EOOl=p@1LywfL7$o;rHhePv}U(8Nq_%|9lR+D)4w
zM~s&Co#D5h=#iC}K-@J+!2PJt8A0}(8euFN>T#gm
zdSxch?BO<}%_CUG4>|`Nv
z91ALj2AyZrlGV7Qbrr$j|Ai(0nLH-((R-_@;ska=q;DhjHw>NbmQXkk1~my3`CD~E
z6@zZ}(ZMR{Ih(O2&P$)l&^aL|@l+J%byr}fRg>gHjV=|D2WQ$pef5o@le${ji1w^T
z>G6T0t`*+o=&33w;%2IwUPX8PpuOBjBrTvk*qGNzSUf$5@+SQr^#4@EX$$e>YF&sd
zvSDg$ocB@qtnCx=ba=BSeRK7LciO!!T1(;TTintOSOWJJ4C&I;33Ko83(^?t|xj(LGV
zV83^VjXox0f<51$dPZJjX1R=Wauk`$(^Web7WRVTu=!>tU)XZ3`3SA
z>u03DVDVq-H`hFxy+s=fIQQPXheof52SXuhDP&Fe7+bmQHG9A)SApj)kY2V|n#;e&
zIbUyUunIFT1U^Fj*i8M{-FlT*RoLkqA-b^pi9!J*9e4!D(C|}4UV9P3l(>nGpH
zJBKF*X#;Ga=fbuflSnR$S*KeyQ?nU!Bccv8W!)HcclhGr9g}6WmH-^-*Bd`{EM#5p
zC9#lGZX%10bPBA;PqokNRMAEFjV`8h#%yn2rr)^zhwX=y71>)>rML65MtS^`n>tHP
llllSe;pZ0&_qXJ30=`Xb2=q{5K;=Ci;3&=&`_REZ;~!VX|BV0u

diff --git a/docs/html/img58.png b/docs/html/img58.png
index 34a1d28977dbcb547609cfba150ac532205da7eb..31995149ce6bcc0dfacd1813a31efb496587aae6 100644
GIT binary patch
delta 645
zcmV;00($+{6T<}|iBL{Q4GJ0x0000DNk~Le0001_0000W1Oos70B*X@ypbVGe*!^C
zL_t(YiS3lXYZGA@$G_L}n!6miI}!Xr6%!mp5jiYH9Mr5`A-7!+wlX5L{mrD^x
zUoKdoigf*CCq$@y+kPcHoaGHGk!e`HuC)Pg#kr!(4B!XP{QaWu
z_7t7`{48=epW_3?k1+GoMr9uz!!I_|3fnV!ZPa}wi&429@LBnNvVmNXNOV?T2r^7z
zEJf~{H8fXzY-CUg^U?s4a
zm>9(6E?VNpnZ;xm)bVGYO(rC1%rY0B+mYkf7Mx!e$D-{(LV`5@#
zZEXPnkdl(Z<3)vH2m~T4D+`0cq^HH0h}NK3cUKQFJ3dErDCy~P;<)Ffg2h61xH9hW
zz*LmSyFAlL1J$D`Pg+-f_I{h9T3-FerST6nb)lp@>XBoLe=oJ%ts%$3YSqWEq>sF)
zulg)gqw5-_MeALcgLFh`g+WWTK(h^qzY<&&KSjsiu$szCO))(;5-cDNWG1?~H8>ZNCwyb3bE6H@H5Mk#l;d5czqhzHocq9DLf;&%$IaEQ+Ya
z`Do=#^7BpnZoJG{H<(3WH*eraau@jUK>s9&Q5-P~_T=SKiQA(_
zJ(|kH5&P2qb*gSKjD7uN!lK`=L@U6F>BsZ(`9S{#uq*8!`VK_woT)&PG=VCGr!8)S
zB#`~u;+@;OpvKupdYk;3$lX|QH$2iWIdXZ{fE-kiYT+Jx{LU#aOkb3g12VgiCLcsK
z^az~}PWbsi^z~xTzK{F&ju#e}-$d_9)J@E5yi5gy?2dVa4zXr}bY>-sTJB50@Hxz=`6C+vpldQQ3$9q>25T$Il7c;2*xFi
zxTn#2spr}8agx%fXf!?cA!iGdPd|z*o1{4S{ko(6izIYreE-kGn-^(aw+NgFnUeQO6FBV2J;kv
zL*k@U&f?E8;7xil>Y2t(?s#C)(AfJ^LFVd&LQ7xDaPC~kUTQh0igS}~WKZo%3JMvF
z$)tUOlBK#19)IB=gG?iO!gShvwVHx4EWmPN9Cm?zO~zPY5-__=(IV`*1ew3+7p_@D
zH{KZlCMQV9Q6nN76dB&lF9t$h&-30;ZjWRX7Nx{4Win
z^wOJcXzW_aitqvZ+*z}A;XDMp!Y;Svt(2?;KDr8^65(8&|3l@K{w(}#zGc5|lkp*-
znYw{qeYLdNCaI0bS1^sK#(TPT5nm^u#bJ<;u8;54Qz2R3>UiaZyKEW|tkU75FpWCt
zx4%Yl8qMHOC3`$p-b9UKl{tX~ag&`Yb;NoEjh=n*_l1(IK8?4n6Uh<
zX7KDq7b>Yw{03w7C)!bOI-HsW!v!@@zYHh#nFKh-N+-tPxG6y0GTMVLaGfHE_
z7*A7%Wsp+jkSgthVu4N0>jdc$1Mb{fagVh(n$ruJadvr!!s-U6YZf+=Zg=Djlrid<
zbrcNVgKu{j_dh|_Tw`{lu)?|AP^uQ0y!s=x3z;?m>vstKNu;Yzh#S;0bBUM%3DacC
za?Qri+FPj1G>J6rW)h(8tDBr@{&Olr$G)#sOT<1iBQ1*I%<
zzSDhI!hme!Svww<{S5b8gcr{VmA$`t6!U&lsz(*M%Pc2mhamS&CgCQK{*#VFfW3adx)y$Qwc^u##1+qp;M;Wf;E*i%J@Hb6-&n`A$<4REe
z(kHvv;(K#Vf3iwQmYG#sB_i$}cu$}+=HG|K@v5+OOp!N<;!oNOHX-<9^;ldL@H-r~}_174TmRFHC+JYsL3E
z@dQl&UX|8btv2!Q{D-OJm)T#imjA!h8prw;ZJD#J?T!x~^xNy3Ni5wEd-SgToPPWn
z-qC;b?UfD)Hq!irj|cMvwybtR&y~PAFx*_4uaG3fhwOu!%kyJudqG~+fN4a5PxB_M
zqyqmjKix}!x~e_UZM9arQ%}na!rCmiFUtBv@6OFpH!`=jQQJn72N4@`Z+*FUi-5fU
zcme_AgNw+yMS>%)Vdn3CgvNhFjjFR3elscvl11j&x4r1`*RZ^-+YMui(mbOa#r=}z
zd^749@pIB~Ep+cE0Vzxyh)=7Pwj>YaFK*F0#yy{n-i=zHnvjl2c%2rnnP7i_>tp_*
z8U3(f3&TnFVmmKZCL1`3!nrc_WvQv5Px0Hd?Oslj+88}bDgAsjJ+2Y9aNl)vdOrSD?0dzo3k)Tz11w6&BHZ%S$*Su}`Lu6Xvta1O
zgT|JGCRo~V6-YnLk~gD|F|_Ht-vIieEOsQE*qTo+B~7C}$+*wA5pAt<0#$fy0t+!F
zIkn>tP_phgER0gr%xw2<=yh+kE{QL+&ly_xw*-#4!<0TPcgo`ThYg3_IaT3aE!`?~
zk_o)JJ#Qpj@75CjObd9q`wO0{ySgqBVR(i#mMrHFDfUtC^zWHE*4B}3KM=JQsxlz&
zt2@f+z2NZHvF^rS^C8=5GmeD4qu*@pGkkt2-QH4Eq`CNmY=&XX^kaQljVG*

diff --git a/docs/html/img59.png b/docs/html/img59.png
index bb04ee281a7684cf7ebd35e56a712a4a1e858717..691856369d760220874d6cd13a612d47c764387e 100644
GIT binary patch
literal 222
zcmeAS@N?(olHy`uVBq!ia0vp^+CVJ9!VDxQ&XxQCq_hHjLR=3VIIwy1=7xp_A0MA(
z%a%z>N){Iv+uPgEoH;WsEe)v3*x0zYw>L5}GRl1MTp*vZB*-tA!Qt5rkYtjli(`n!
z#N-4C)+glz%u;7`ZJ3;>pUpf$oiCVO@IgWcW8saaa}5U=*=8_2W(rB1
zaez%s;41HSUY!N!Y8t0A-t_7?P+~f}GhrQLh=kGsr2~u)tsGh(GDR>jY-^T!`>mx8
PWE+F0tDnm{r-UW|8zf0O

delta 300
zcmcb|xSh$UGr-TCmrII^fq{Y7)59eQNSgz(Gz&A3)SAs@0i+B9d_r6g95}Ff^JXf-rnBG$jHw2ViO>ru_VYZn8D%M4UptkPZ!4!jfu$#609i<
z`xx#NeSWQ__Fz(SdCG&B4)0AK4UG@YRtd289IWE=xYN2pa{Kq2O>gS?CZ_~4csjN0
zlzg|Dacz1|gXgCj2BFuAhvx89Dl9bGU9P}Tn6kGL=$=YGtuqx2!IPdch0OTNq&?xu
z9tQJojdKpH;S@;Zp2q)&=LFxQa*Y*dTDaaDe80_6rgA4Z-sdkXi^8EbOmhU@A5@LJ
tANz#6fit;D+P=V}p`lkv&T|n1L#?WLdvTZC2A~fZJYD@<);T3K0RY8cZP5S#

diff --git a/docs/html/img60.png b/docs/html/img60.png
index 1450f40c7be19eb30541573d24159a93f21a8ad0..3a198f8554b389cb8d10373f961ef9966d984d76 100644
GIT binary patch
delta 1237
zcmV;`1S#nJ^)!O{{~3`nbavR_cLs4WzVZ4@7Zl{^ccbsc97
zw$mSde8U?YXrRUhj1oqiR-R
zO8*MdqJb-wk*x=6QU-osL0Z_9FS<>T(d{7_U6W%jl=7^NsSn4z39od!e?V!vz-1iB
z-2rrZy0+Wi;Yz>_-+g4`#1SB>K)`AS&jAw0S2!ptYlY-8Sr%A>pnz7m~
zHV`aeEQXA&&`qSQHajGve~54MmaTJuh2TFPb;Fm69$u^pS2`jYMd^r
zbQX)48C3+G8BYt#K!(pMSitQVG9I#n-ZNDzgD&w`f40~H`qg()8OO_9hEYVu6*BOT
z%rjV`v3c$$QrG$fof%IH$#6Uwf)!83R(4otW&W&@u|KcD=w}P)e{w~Javs;&9ZDBL
zmrIJxuH2QkM(VV<8$bc~1f8A3)0U7SSn(EByR8)PH#+7*GP3ka8a90hPO+OF$ROjm
zU^8iFu-D{U9ES3ow@Y}z?}@$fG|E^j=q#6~Nf%s}Az1OYxPFDA*N={Uh1p^7pO|K2
z=@S_9w=I-LKQOU+e`12hjB~bfwRCTUeCgsuj=eLo^hxy&URr?hiw``W`|))e9l_#j
z_XT}oVw|VZ;D7!$q7zZdgF#FW=RFqwh#>=No*wpvy`*@IURjmRs#mQB)h}cZJM0Yn
zw}R0gT|~`&KE0Ag1Y~X@6?H
zu^LWB#9H)e*pw|Se@dg)q7U^a_QW0!i{HdP6Pu8(`u9kiSij|i_Rx(wPnv&8yjn$g
zq)qIAKiFI8%IljGcKGPB{<5RFkaN_1Xx;NLQSmW^XT9x@U9%&Z|IiA=1)E0QyO#ZQGV!e|Bgb7nh4JC3suh;Ui>+3;18B2y_Yh@D~
ziHJ-rD=!&Ipoxt{L?u>#8a8DuY+{=>`l0?mR#}g_6Hz7;00000NkvXXu0mjf@%~Xf

delta 164
zcmeCERLtqy>Ojj)fUWUccU~G*QvJiXp|*#W6%;YI4E>
z{vS*VU;gas;#8P*cVc6)Vn?9Lfdd879-HSe3zav{aAiF8;3tF1HRg}A*?D;8JYT>w
zjay+QdlA!Shi4zGMMBb=c>g86(pO+e+OTgo$L2T3_*c9&>tdPXp31=B7cXJwD=_;7
P&|(HpS3j3^P6pAVLboT>|^2wNhKY{D$=xAtY(9_eSP$+mjzOu4XU0ppc
zF3!%*j!vgTAP^Es?g&7m(Yd*~US3|=SK>_NYhb*G>u~^P`mKCZk$V(te18NhFfbCVXXIhy&uDi>L`*U!|<+qSID_KQqY=3muCy_d3@Y;Avbk>HteCNkSi
zF3ACUFS@bJka`kv6Xz)%qlVVKmlDR~L^vJbs*JJGDKTA^Cwk?HCyb
z528xjiwGrSM5$i=Gsi^R+Sb-+~L6qB?vt{y5Fp1>%q6l1kQ3hOqm*1QtFbQ8?x)yQ`^Xlf^hd9GufHioz}UDXN@-C
z&35^IEqcLGx+l_RM-AKcN9kdrh5&>0iE|p$eN6Gpm6XBS?u-4;+a7CbKrZ)p?%7)I
zz)>aWJxxEx0%q=0y)U`jo@x+BpuJP!U#_+{;F|hxcYV7ul478|>OoKRfMq>+M`4f8
zXtpFV@qYB?yQySN=G9qXu~)Tu`S$t>WV?qhKd9fd{05nds$^hK7}4A6J*QD8!|aG{
z&yqn(8{SQcFTe>8zn*GZSAT$xEdPLZ+GBNg>;9kimZ6~trI|v@$^1>cTe7|9C#Xe+
z@!pYpA>O-!Gc>-Lr~&q%porF1pBO>xR?c6i*q8F&Q?{^l%C!jeV)@nF2PMFqPSk8L
zl{TScWiN&nsiTz}UN{qxUH6^c3?&qXk**goWrnt_&|&a{~hb`c?e=D
zYV5r>uQ7P)#ZxkA<4J*KikVgt8XAk;m7SeTiq+Raz*N?W-rSD=PTE@{L;Y(puYmECMCPy?l)hl3`G1&;QT?rU2w(+Cp
zp%~}C7k3W_2vJd1A#@{jIqZ<^wPf#xtE}{F9{Ttx5(`35p?M)eDwl%aZ~?dgx&(!B
z|1aiv6R{1icee`A#U;BmTIB2r^Y?I$=)hD0Uf0%n3f0h%-;y$1)a(;40F_@D$DH=$
zW?VmL?7vVEf$fr{_oC254h6UsT0~dxT`FdxMt)03s5Z}@vpkU`ns{P@{3ym2SRQhV
zpHci?z&`<~zvm4=kp)@y%e^h<#4WaadzQdjXIf#*|F^EcM*+qVoStmVz3UfNHN!G%
zL>+%G?fW^*DpZRUWMB(~Z42_Ts%BgF}uI^hE!h>s?N3F!Xw#Hl^1MdM2p8j3j
zJfoyLjFCxe`@HWG5alv$kXdw=ELDf?e6PV^xjqXb9Y&>2O%}`6<<^m3$}}0QL;QX|
z>+vO{NBFe}$Ys#akySJ~<^$_G(P;u&jI(Sf@e&zs=srSxJ|IGWwtJc!d*ADXZ`cE_
zmT&0E$n1(SWrg7Z=g`Ibp@Im1jLDk{VHupuiYKqEi$Xzpp7YGP{`p^8E*ORWVJW|r
z%btlWN$K7K?ne06>x$@Z7jx@0EOOl=p@1LywfL7$o;rHhePv}U(8Nq_%|9lR+D)4w
zM~s&Co#D5h=#iC}K-@J+!2PJt8A0}(8euFN>T#gm
zdSxch?BO<}%_CUG4>|`Nv
z91ALj2AyZrlGV7Qbrr$j|Ai(0nLH-((R-_@;ska=q;DhjHw>NbmQXkk1~my3`CD~E
z6@zZ}(ZMR{Ih(O2&P$)l&^aL|@l+J%byr}fRg>gHjV=|D2WQ$pef5o@le${ji1w^T
z>G6T0t`*+o=&33w;%2IwUPX8PpuOBjBrTvk*qGNzSUf$5@+SQr^#4@EX$$e>YF&sd
zvSDg$ocB@qtnCx=ba=BSeRK7LciO!!T1(;TTintOSOWJJ4C&I;33Ko83(^?t|xj(LGV
zV83^VjXox0f<51$dPZJjX1R=Wauk`$(^Web7WRVTu=!>tU)XZ3`3SA
z>u03DVDVq-H`hFxy+s=fIQQPXheof52SXuhDP&Fe7+bmQHG9A)SApj)kY2V|n#;e&
zIbUyUunIFT1U^Fj*i8M{-FlT*RoLkqA-b^pi9!J*9e4!D(C|}4UV9P3l(>nGpH
zJBKF*X#;Ga=fbuflSnR$S*KeyQ?nU!Bccv8W!)HcclhGr9g}6WmH-^-*Bd`{EM#5p
zC9#lGZX%10bPBA;PqokNRMAEFjV`8h#%yn2rr)^zhwX=y71>)>rML65MtS^`n>tHP
llllSe;pZ0&_qXJ30=`Xb2=q{5K;=Ci;3&=&`_REZ;~!VX|BV0u

delta 199
zcmX>r@{rM}Gr-TCmrII^fq{Y7)59eQNQ(in91Am$ymj((Dv;6*@Ck7}aNxk^&70NK
z)Fzs$)Ze+dniD9&SQ6wH%;50sMjDWlFVdQ&MBb@0IhdO(*OVf

diff --git a/docs/html/img62.png b/docs/html/img62.png
index 0cb6f7f2055971aa47cdacbca58e6308d4f4b050..34a1d28977dbcb547609cfba150ac532205da7eb 100644
GIT binary patch
literal 2518
zcmai0c{JPE9+xqrm5NqtDX|toMF%mlFQup^Rkf6iQbEFyP|F)tQQA^fOOdqoYwWeu
zQl*BDQN%70NjtP6q1qzoRCVkcV$%2im~-a!y!XdF_uPBW_nz-(xu0{>-CUg^U?s4a
zm>9(6E?VNpnZ;xm)bVGYO(rC1%rY0B+mYkf7Mx!e$D-{(LV`5@#
zZEXPnkdl(Z<3)vH2m~T4D+`0cq^HH0h}NK3cUKQFJ3dErDCy~P;<)Ffg2h61xH9hW
zz*LmSyFAlL1J$D`Pg+-f_I{h9T3-FerST6nb)lp@>XBoLe=oJ%ts%$3YSqWEq>sF)
zulg)gqw5-_MeALcgLFh`g+WWTK(h^qzY<&&KSjsiu$szCO))(;5-cDNWG1?~H8>ZNCwyb3bE6H@H5Mk#l;d5czqhzHocq9DLf;&%$IaEQ+Ya
z`Do=#^7BpnZoJG{H<(3WH*eraau@jUK>s9&Q5-P~_T=SKiQA(_
zJ(|kH5&P2qb*gSKjD7uN!lK`=L@U6F>BsZ(`9S{#uq*8!`VK_woT)&PG=VCGr!8)S
zB#`~u;+@;OpvKupdYk;3$lX|QH$2iWIdXZ{fE-kiYT+Jx{LU#aOkb3g12VgiCLcsK
z^az~}PWbsi^z~xTzK{F&ju#e}-$d_9)J@E5yi5gy?2dVa4zXr}bY>-sTJB50@Hxz=`6C+vpldQQ3$9q>25T$Il7c;2*xFi
zxTn#2spr}8agx%fXf!?cA!iGdPd|z*o1{4S{ko(6izIYreE-kGn-^(aw+NgFnUeQO6FBV2J;kv
zL*k@U&f?E8;7xil>Y2t(?s#C)(AfJ^LFVd&LQ7xDaPC~kUTQh0igS}~WKZo%3JMvF
z$)tUOlBK#19)IB=gG?iO!gShvwVHx4EWmPN9Cm?zO~zPY5-__=(IV`*1ew3+7p_@D
zH{KZlCMQV9Q6nN76dB&lF9t$h&-30;ZjWRX7Nx{4Win
z^wOJcXzW_aitqvZ+*z}A;XDMp!Y;Svt(2?;KDr8^65(8&|3l@K{w(}#zGc5|lkp*-
znYw{qeYLdNCaI0bS1^sK#(TPT5nm^u#bJ<;u8;54Qz2R3>UiaZyKEW|tkU75FpWCt
zx4%Yl8qMHOC3`$p-b9UKl{tX~ag&`Yb;NoEjh=n*_l1(IK8?4n6Uh<
zX7KDq7b>Yw{03w7C)!bOI-HsW!v!@@zYHh#nFKh-N+-tPxG6y0GTMVLaGfHE_
z7*A7%Wsp+jkSgthVu4N0>jdc$1Mb{fagVh(n$ruJadvr!!s-U6YZf+=Zg=Djlrid<
zbrcNVgKu{j_dh|_Tw`{lu)?|AP^uQ0y!s=x3z;?m>vstKNu;Yzh#S;0bBUM%3DacC
za?Qri+FPj1G>J6rW)h(8tDBr@{&Olr$G)#sOT<1iBQ1*I%<
zzSDhI!hme!Svww<{S5b8gcr{VmA$`t6!U&lsz(*M%Pc2mhamS&CgCQK{*#VFfW3adx)y$Qwc^u##1+qp;M;Wf;E*i%J@Hb6-&n`A$<4REe
z(kHvv;(K#Vf3iwQmYG#sB_i$}cu$}+=HG|K@v5+OOp!N<;!oNOHX-<9^;ldL@H-r~}_174TmRFHC+JYsL3E
z@dQl&UX|8btv2!Q{D-OJm)T#imjA!h8prw;ZJD#J?T!x~^xNy3Ni5wEd-SgToPPWn
z-qC;b?UfD)Hq!irj|cMvwybtR&y~PAFx*_4uaG3fhwOu!%kyJudqG~+fN4a5PxB_M
zqyqmjKix}!x~e_UZM9arQ%}na!rCmiFUtBv@6OFpH!`=jQQJn72N4@`Z+*FUi-5fU
zcme_AgNw+yMS>%)Vdn3CgvNhFjjFR3elscvl11j&x4r1`*RZ^-+YMui(mbOa#r=}z
zd^749@pIB~Ep+cE0Vzxyh)=7Pwj>YaFK*F0#yy{n-i=zHnvjl2c%2rnnP7i_>tp_*
z8U3(f3&TnFVmmKZCL1`3!nrc_WvQv5Px0Hd?Oslj+88}bDgAsjJ+2Y9aNl)vdOrSD?0dzo3k)Tz11w6&BHZ%S$*Su}`Lu6Xvta1O
zgT|JGCRo~V6-YnLk~gD|F|_Ht-vIieEOsQE*qTo+B~7C}$+*wA5pAt<0#$fy0t+!F
zIkn>tP_phgER0gr%xw2<=yh+kE{QL+&ly_xw*-#4!<0TPcgo`ThYg3_IaT3aE!`?~
zk_o)JJ#Qpj@75CjObd9q`wO0{ySgqBVR(i#mMrHFDfUtC^zWHE*4B}3KM=JQsxlz&
zt2@f+z2NZHvF^rS^C8=5GmeD4qu*@pGkkt2-QH4Eq`CNmY=&XX^kaQljVG*

delta 178
zcmV;j08Rha6Y~KfiBL{Q4GJ0x0000DNk~Le0000Q0000K1Oos70AX%0jgcWse*kew
zL_t&-m1AHa4A|?+pBKP+@(k?^AK*MghNTP!U`2ob|NqFqnE(~v#=y|R!0iC#wJw7v7CWHmw_t)!r?s1z_*n9&rb-C`~3g^0&v4Q8jzjAwE>woX96;B7cwVa?JE(!
g0)jKh0F?&-Zd5J0iTNpq000002uVdwM6N<$f~h`67XSbN

diff --git a/docs/html/img63.png b/docs/html/img63.png
index 8be7967900ae804f139107fbe5ac58114175e0da..bb04ee281a7684cf7ebd35e56a712a4a1e858717 100644
GIT binary patch
delta 246
zcmVf
zL_t(2kz-&O1!Mre0Nir(>nbMTl4Eyd;9Q7HvPgh|;Wnxe2aLgb4oKXEuo<`a*@EnU
z4wGb207*iGxf$-W0j+0jfJyRv021pV!ki3wAfYn5cOU>{y?MaEz}m0_Y4OiBL{Q4GJ0x0000DNk~Le0006(0000Z1Oos70AY#4=8+*we+A}A
zL_t(&f$dmLXdGo2erC6m&1SPRLl14Nmd1m6D29cFfTp$u(W+1~C@Bi1wulFjvT-*3M8_63%PsJ%o7f50vBGqGe(HyTDKFfmd>M>~Vnfmh31d3?BvXz9EV
zyY31>cdIZ97da}sv_p&zQV*!AnhqV#3p=7IDa}@47A_XiAv0ULHSTF{*!QY{1=gV_+ady(dSofgd^sA)$VvjLOe^{rAhRe%_%g^wOR&ZJ$GJ80+kMha0!xL&5S03dnjQTbJbm
zcT5kn+T5x)A#Nd>jW|Uef65_#4#u;NMUsAwQ~QCZfW3N3+#2jP$M|<%@;juv>=T$S
zGmf6can6be3Rs7b6j6m^7`54<>+CJwKIW8kh;1kLeVvt(P#pz+PoStnW^<9lVf;2d
zZ8Kvt?@vTfkYj(cL&9;bc4!lOTbE7#SkfU{IWd?ANYca_`V#Dxf7y8}3LVTG^Ff=qo52!7)f3rrnQlUq#adrN*f1x?jXXD@e$tZq*+gEn{V4E;Lwb?}@+42a~
zgm0u4S<~O&Jun`*CLJTW^j|PH1Uk#>i4rspBPFJN)C!|394}Q5W
z2IlhZ9koCGxQUy%iJHXHr?6Vt5mSx8zc;Sv6xJIo;8I=TVK`Dde;n2(O&i_TW+Ec|NlWX$s3b#O6aJ$RVuSA-cd4AalBh?x8lYXw0c+
zeTlujYx^}4%_1Y7Tb*-Sl;N=wJFV^1Ar_Tok$ca_$3{?>D)5FI))bcKAUh<7uq7SB
zFqu>Re`v-!&%SN!%_G={a-xbM}bxM@su@bQh=I5ds
zo<(9rdgVO**O1Bc{4NV=3afTV4q*!}#@OD%e-hB1CdoL9j~!Msb1JQyDTdKZ>%gx;
zJI-3KL)dPKG9>H8*1py664i(-E~>ot0d`mgo_6Yxrmz%9Okv0SY&nE2xJYi^-y;$@
zk^bTV?c&s*{aD=w=2YVRtP&d!;|}m@Ci`sTko&!>
zfAS~Of1$v$$#4x!VTE7CMTagEKu4S|b3W_oaSNMPAAbn=G`w(G8B2Qc$F_J41#f=7
zL!~NAhC`Ub`d!SMz&vM7Gm|OuQYm&2f+xcvOkw>l=1*X9U&YI2ch>KvV(b7c!(@0F
kr?AV757pGr-TCmrII^fq{Y7)59eQNDBb591Am$ynek|X`-S}Ws0YZV~E7mv0y1wGGACZ`D-pf|
ff-}efl?MQBR4uxR`6-700000<2SrXqu0mjfpqEA!

diff --git a/docs/html/img65.png b/docs/html/img65.png
index 9e29b6013007cdb13330767b0145f5f70fbdfe98..840e98508fe53db0496cd7043ab0f280552007a2 100644
GIT binary patch
delta 199
zcmbQv^pMf0Gr-TCmrII^fq{Y7)59eQNQ(in91Am$ymj((Dv;6*@Ck7}aNxk^&70NK
z)Fzs$)Ze+dniD9&SQ6wH%;50sMjDWlFVdQ&MBb@0CkZ_ivR!s

delta 253
zcmaFJIGxF~Gr-TCmrII^fq{Y7)59eQNb3TzG7B@1{A4%pCXg}+@Ck7}aNxk^&70NK
z)EXKZCK{>KceWRs0Oc4>qrF&R
z8sj>KG>*;x{{8>Y#Bt1IhR{0}Ha>QiWNsgs6VL1$61E&ZvXe_gTe~DWM4fO}kku

diff --git a/docs/html/img66.png b/docs/html/img66.png
index 20b3af47774f08ea9db181512ac15dab71279e8c..0cb6f7f2055971aa47cdacbca58e6308d4f4b050 100644
GIT binary patch
delta 178
zcmV;j08Rg{1@i$RiBL{Q4GJ0x0000DNk~Le0000Q0000K1Oos70AX%0jgcWse*kew
zL_t&-m1AHa4A|?+pBKP+@(k?^AK*MghNTP!U`2ob|NqFqnE(~v#=y|R!0iC#wJw7v7CWHmw_t)!r?s1z_*n9&rb-C`~3g^0&v4Q8jzjAwE>woX96;B7cwVa?JE(!
g0)jKh0F?&-Zd5J0iTNpq000002uVdwM6N<$f`hohiBL{Q4GJ0x0000DNk~Le0001{0000U1Oos708~GCT#+G5e*!E?
zL_t(YiS1J{XcJKw{*LyNdu{UWCPgc>#lb;`1B(F{BM!QG9R$HbZ;?8c)1fL+o2`mS
z4~I@_rVK6;i69PYGPoUblGzXyL8ydC)ohLbe|IqlHk=)F$_GF1-uM0AfB*Y=4;bN}
z;ryFj8di#lDZ&nx)NjI0FpPH+e``+WgXLp?FJ}@Asa9f5%?XxXf3GLCu`q;BuVNA3
zug)2wd)yM;Ih?rk4W)t$jQw2SyNXgIzKD64QMRhMQZ3SsO;qIxrk__sz5Nh9x#*|!
z_l;xVKpkQh++xOvi8`Nv(L%sz#xO#_m}Vte;hQ$lvA?6
zgB^(C$DqxCNo~(#8E0wBCQ59lZS*frnHrn0#_!azCMbA{58AD0uooloZ96_MVv1u&
zX4M)F)6v;PRUEA&?NArCoUt}Aamz;e5rvyI-LIk45G;blT0q=;PoUos<6KsjrLR(B
zl1+3CD_K*|M+fosyz>$_e}ymY>l9ALs2qS&A*nt|Vh1EDHB80&s6l|P(Y|mjP{n>D5EVB*Pi9n?EkPQag3pauMo#o7|HOjZ+d&+X
zo*TRt!k48XHK#9hb`Xc8uTLdEe}eMiZ?YoD&$~z-VT2L>JAMJPSiQN!1b<%u0000<
KMNUMnLSTaYz8k~<

diff --git a/docs/html/img67.png b/docs/html/img67.png
index a9a08bc8be5a6aa40c7ecab970355e3db0bb7c27..8be7967900ae804f139107fbe5ac58114175e0da 100644
GIT binary patch
literal 1640
zcmV-u2ABDXP)
zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001
zbW%=J06^y0W&i*M=1D|BRA_Dx0B6gvok{vZLF5YgL){2g@u5owgu6u
zP%!DDJjiXVHPeH(IGQi
z?n*TsD&xLsA!eaq5gm$@y|Ty-C9Q?ntr)a7w^%R+w!z<_Xy?mwba8gl!C3d8;Pk7c
z`eKhUN>{sFUfL;obzNF@Om+BA_b}oI2ZeFdb2FS35ehKwrj0C3A&dwA5RPd{rAhRe%_%g^wOR&ZJ$GJ80+kMha0!x
zL&5S03dnjQTbJbmcT5kn+T5x)A#Nd>jW|Ue${~IZ#MSci}lQH5g|wb`NT>@D6t=9F}ZZ727Aot2VM9R+?*
zpr}J;bCJVg{5CypGh;LFPef3VV}G(k!f~y3XcK!|mredy(ji(oF_;HP(!?7266}`Q
zc`FJX+QRq^?W)6j#To)PrZprWA}CNhBplc3T~_C48T^Wd>7ovefxds!(GHLl6YM%m
z-viX&jzWjnP7QZ;O6*7+Yizy`X&G+37i&2yA}Gs5?T~O>t2=f4Jk_>-VDK#%M_f$y
z<@vFJGZxINSF)HI=&~?0G(-=mEwr;nw^E@;u5oq#w11&F(r4q}{K+VOf7@4f{9v0f
zKDF6JBiZr@)P!%O7FpBZ-#suMxh5SWx%6K!Hv~G%>xmLNM;kaaon;=kR8^>_mQ~(~
z(eNbQ&T>^@+#y*R;pgBSuzqm`goU7Uq96L!ycDa>ZKlGt+W*y|!Z=jjwmFa&PFJN)
zC!|394}Q5W2IlhZ9koCGxQUy%iJHXHr?6Vt5mSx8zc;Sv6xJIo;WBn3eD;ci
zsqqYAcg}IA0uv+k!)U!Q=oV?6DmoY(f?QRI0(vkGYn%R9v8LnO!{tlA;Ez!D&Hx`*ze
zHn3>Ssb_tOy}fJuH4@DtBc5BGb6S+)u@XD2?bIO_m1U88&&S6`P?sw3h8xxtmggWl
zB!{pi9l|h~Q~f7qMg82VuS1QFU&Cyf{>kf5Vyi34@K}lZ=UX4k@~HfK`qWZ+a+q`r
zyy1p5g;hHwhp=jgA`VX=`aadKeS}N2k`0GBeftN3yvs(g)Anm5^4}H7lyyp!;jt32
z3+Csd8lFXBM0({s{nwDm^ZYIgX$q@$NDg5OF2>m2!V=J)CdoL9j~!Msb1JQyDTdKZ
z>%gx;JI-3KL)dPKG9>H8*1py664i(-E~>ot0d`mgo_6Yxrmz%9Okv0SY&nE2xJYi^
z-y;$@k^bTV?c&s*{aD=w=2YVRtP&d!;|}m@Ci`sT
zko&!>@+Z@Op}@1ra1Bghg;Npo
mWOx~;u*;3(%ix1fHva)qia(|#P;(pr0000G4^bc
zk*z5WvQ7v|WcR!EJkReu=lT8qd*5^3^WNt==RVhUf6skg=lXoUpYP|oB8(ANj~x{}
z%EZKUOix$Gl!@s8h>3~0o%J9vB5I_71YY6B24?W4rlv(jMMb<~1@P2WSQc1HNJw-N
z2#+5>9&vK|E+N76l<9HVV*>*N0)ZfrDnTF<-lnCETUrVT2pHrVtO*EUu~--khJB8G
z7ag6JmNso*Adn=m$f9o6-2Z0Azg
z%H_m9eBayiBdR2;G*e#<=E=DZ9R_ioEFMDsF7A;kC7Anq{N)|DdDti#@8pj<+g>oDK4*=(aQSKJv(NfWJB
z-`rSzF@B>z>sm3_sL!Hp&rnBSMpGH)Eu>Y9y3$isKR;9*gY&xmm9_+W9$rOX_b92$
z^t~gutl$FOLkW{NnZOeqMXl$k93TfS_@|!Qjr5z`ZWOC6YK~H>`PG^JyV+g$mxl$tPNK
zC%Ma-H9Q*_XjzM?r0uI(@SdXjCEUHh)NYXz#G}5Ns0+)wC+`=YgC2Z*w>BDfx)$
zqeFQ`=D*3ZhIKP~ioVpbW(d3SwjnDz;@
zCg$}0yNlOj5`%B693|$xBc)#C8#RV&45=n5o@7*QO$8N~2}{Ny8E&FSB@(?@$k|$H
z6&;gN9Az6=wglm~NzLk|I(84T(8ksj%Jmb^DE?wl>uJuanU0SlHjbnksU}7`rMh(^
zDn6AWHJCBbUv#q3Ve~kIMW3wOb-QRowcw{BFNPKWEWa|_V?xEwn~IPU+qij!8krMm
zJRIF}9yDdZU(8xCA|>poNe%fg7^FiSJl&TMVEFNo#_zYp`HZFJaWUm`v%*l`{e5Y&
zzH~nfAM-sted;+@t+vWb*7**V7k`nMXNAq97|G@5lTJCe{R08~yLrF(`F~*G!g0>=
z^n_h0`-~^}Km~x*-0(=HAkX4vM8#xcBJ4wX_eT*zgv0WxcF9=ng3;b?_X_XH!QgVa
zqS;l0gV>DSpFe*5m@WHh6!6}2ePL%{fO9FO#^R~%d35jKA=(_07dNw(6#%#Gcml8P
zbXanhE(MQ~$_FpEY(
zj52%Uu1(v7pI6BG=6Dv72!lQ1PL{6|#5l2=hxEJg!~nb0VhopBxH8VqhLQNs4LWh*
zd~tlSuRojpDBmR{uKe~Uy1VGhbJntlHJL?R2>3>@>@^_s-kg>BTjCLB(9L83eI=FJ
zttl;iK^z%7d93U~j`Unndl7zFwR%L7&&+Q+#AYc04fEPEmd~k^>15&ULc>lvW4#4%
z*}`vmLtn^nrS8Yk7E6b+J!nRF5n}#!bMhtU>Jce?GL`LfZN4`?`Fo~sG1}kvDIPyy
zDu?bh>pF&l@rHJvdGlExs&r&61AkUqL=Sg*pK|~H&3tLJwbMW@+7sT(bib14a!KBp
z#JS*X?}aV0b%%r%9A#KPX<<>h2|2DRMB;}eKFITkVu7-SMX?-kp3=Yhg)RG)P^crM
zGfn>M2}k>=3QxCY6#pcEH;CN_9MlA81B4&Lt@+s-tVIp6&*Eou6qe)yJ_@k?M!f<#
z#0IDao`h15uvwuFvnWHERjn2;&?h@`WputBj5-K4I)2N#|1n+W^-etR9!i&{86Af8
zziNP~HpRhr?dDH=Et@^v0SM101zOzFq#pR$MGjs6J~cdgU&R<|aXi#FP95a=ti9tC
zW#)=k7Wz@4TYLqHlDMufE|*}~H!`Z^MUN(92RbHZ;>x3P9faH$r?iA|=1Ec3UR&9M
z#2x;p*m)tcxJ;gQA7L`z69MI%on3Q-=FqmpX}#7iZ69-7#Nv1uoKLxN7>fq_n$MVT
z=d9k;1u~@A!NlyKSB>{0d|umwYCm#4GNy+-N|$Gu={Fa_8H(UWHYU$lXD5dbxCTI_
zNSC4ag~Mg$A_z4ZItW1?-1OYNc~h!&99xh1Rop`E!)rv^UQW__Ldm_jd_6B;+Q=$0
zk&LAovG=UDi%D19#D=E?1lL+;xGjCSxYVXA{8nCIe4@JTNq38dG=r?-HA?HbYF2l!P3n*J1
zGF+Ge0R<2WkPBR+g~F%Z+}T{)poF;UIL!~?%2
zHBA6|G1TnJkhr?Cz0qQpIUmN-nz
zY|36lDi~<=Vh%7`Dobc5!oGaX`pveu#?K1>M4`~AK#yfQXDS;#wZvpAm_tWvbkHb71Yii4EPuKNi7
zt-eIH1u;O%s*VY)j`qQT8W}owqU<~Yp*j&J{fmC6SVj9nv3>PwcWB142?-lP-~1H>
zFl6JHG|2gDB2xNKeLE4x*#<=6Nmv|FKPA9s#ASCXB|Wa2P}1D$A2;Y8>vyufS4L-7
z%ZD%5qg{fl=wI_eL5t6=KOc%u&m4$-XDh9h}>qr5{Q8F?`;geQEfa!NxdjD
z7>?wkDY7u`CBo?9&KU!JmGyU_?$L@?g)#XQBkG}je^QN^p&E+f^ss?{vV?lJsO+EK
z
zhHw6KYe3k_QN|H{sMQ|3WaRqOwRce2e`{Sj#2&EQH)mC`T3`Fq64k^%6kFl2KJVYS
zH@!mHNs;ClgZW4KFE$>ry&ZL@Q{en|K_nczHMZ0zx&DrDnn%W3tI}RE}>!Y+nr9!^XhFASU%jIuI(LfrK#uqnTCS4#V9k2
zqTc=#L7QXHGhw~XB=1rVo?b_ERtum-Y`Ynq9nzqsn2zu)+lKlr-w;lyJz$>=caGh`
z>M5Z2OFJQ^P4^#s{eMZk@`RqAplkOJFq985)RXB!-m#I#J-?
zbvOOtX9=^C2N7c0s$fG{oia2N)3EtONY{-Up_c>m)0`d*x42Ol|A$xBpHM6Oj88^@
z`S)^tg^uk(*VGj&?#PX3%8qR4O!r_Dw(~S(atgsOLh-!Xy!%T1%R-oO
z?dx!R5dO%2!C;L~tJbEr%|TTzT{--)={B2Sdwt-lfwrf#nt9;&iV~^$w6O7eiDM(D
z!kd62-OGYra`2Sa9Do9zj74@hOrYsC7n8OBN?T*q)bU%8_HlX>8LO}L(GR0JWP$jy
zdg;w7wwjX#*{f-t>UP$71#n|$Z*O9MOQ-)J;$umv4X#rcz&kuFNfl~!?GB!UBEk^io74VH18d!c0#}Wa^tB_EH+Vv&
z!lzAxz;Ki2ip(_;lcC>satng@E`x!}^_%!?fP@QtSr4)PkW
zdgf!=XGwJ7xQ&1oTrA8pC$F9SobUhBY1d{}Oz#%53bKD~01vM$SASA!T##c+&}#Jg
oU1(ifh-3@N6u)&NdiH0)>8Sy1IJ#v8xHMwYgClfGwd{ia2awfIB>(^b

diff --git a/docs/html/img68.png b/docs/html/img68.png
index 75cf014049375b166d4c0162412045a9c50ef5bf..0cb6f7f2055971aa47cdacbca58e6308d4f4b050 100644
GIT binary patch
literal 243
zcmeAS@N?(olHy`uVBq!ia0vp^Qa~)i!VDx6^9*`{ltF+`i0gp^2R3istfr>c(9q!H
zSbK{&w$LWpQ42K@toI0?5%J1|39R0ul{Qu8XaM)66!rX&f8E2ZOGa2QJ
o8>z>=)fU{x)MR{uVJbUAUWo3l&Yzm?K+73CUHx3vIVCg!0DGKUYXATM

literal 4873
zcmdT|c{o&W`D$RD3D2!DIgd0v9JgV3hL+TV=x#^O-;;m
zOloSX;1j{rSE*cFT+YtUfRpBm3g>6eEd>Q&F!)VsDpx#LD`EGbgod_ZFoc%`OH0dk
zXXjHd)w==hJ$H=ZCM=g`J_4pZXJFcwP5p`U8JyK=ANV5<_7J3%*FJrvyi;(4#lXJq
z>;xr8ddJN*INts+^%iOsb6kUNuRJU)rj`3uaGv?o31hvpG&6CB9x2)cx#3`-XeIN+
zOkygxLFog^EW;R%aGASV6rNO(`zSA84!1_l!k_oKxH9tVK$NPFx&MzBNYhJkW<{ah
z=Oe@h(M!3+9w}t1zwmiq^N{NXa2+QTy^ME+A-j+-#kZBVCq_f-+(%Sxm7mx8t*$Vv
z-&EymCYuKMGsrR7F!f%Y&CoQ^}iZVZJAg_XmyN_38`tAr14{j@*nnR+sxY
zV(2Rk9gYyGdE@!5*U7rfs9?JPX$GQFmTj!iQ6-sgjLxq6#-D*ztSG|1*pcf0t=sBB
z&m_;z4t^`i=(3scEx0$8H2rC1JM^I*BX4Mh
z&*V){{Cmva5j8@qL|46md@1=U{p3hENy*pVe(|2PtpO(d)%9&TT<$+l+tg+AsRI)&
z!tP%Y553i=PM~DZa24iu6Mj6SoB5o`PQ>REam$%chu+$h38e`KHFX3CbXwBy-0@hn
zq8buUT~o|o=o#&bL!X(yI(~;&jo*acB3xXQCsc@5GnY_hEzB=P6Sd(Pbs=&ohS418
z%MoW?4z~-AHq7*%)<>Ty<0@FXzR!83bN}FrIuDf`@(5q&H-$yZv=c5^rVyTDw#PP$
zH=Z$5dMOC5N58j)6KAs5ha512>&1LF5sz&82D9RTo_eTo#Z8r?9T5w*E0Rd`%R@!&
zhaUT{5x&ve-0M9d_E1t4RG8}^np1Y{y4P{IPVA60cax3-I*&~f_#dp;hS_~k(dh>K
z)N_nlZ58&kiyW0tO2C*o<28K^ngV>Z8iy$U8D^Z@?7b1e1p3CuE8Re`sJ1K4wmN}U
zPTSUMet7Z-70+Qy?e%OI)
zr1h=RLGQ?EgPorPD}wiCm4kx%_CT_{@=$EsDp|dn+Z)cmbVVaSkG-X9)@Mx=WSVdX
zQ&`ZpCpm^@b@}k_u_?Vf8`7H>wL!CIm)~$hwM)%~@vdVtDK*qHs>!P_
zr@Nn=eI>Oba?*3bwoO8gZ3Wlz;ndNT9$5j?>V?w5Y*h6rc(jS}ScPM9MP0fK559!e
zU)|&)T<>nXy6i&bJrtD_@b>h_Xd;zq8hjuZwUG~1fq7gWF9;De6@}r&cfHF2DSw<3
zEyHE@px=u(8kkbc|4~?OQ8K9D{_DbyI?eVXYUyyh3WlyymIZFK1oMzJZCu{35c|wB
zG;Id9p{JjJ6XLWZ8b)8?Rg4vP2%`w%BTRQ^6h#Toi{Peyk}r(a0$9Ptvoe8Ko$
zgg{l6H~a92t7eMpa)N;A0ylsifT1?9Bd8qWK>Aa0DTot2DTuCYngBj=QgF6yqPdEb
z2HA7X>m+>TNk`6+#raEQ_}2%}hQ5hh_OkgezAyqxaXDINtRla~=EW>&drB?;{NpJg
zVLdTc2^}vQ7|z+~(vuwYqSuI4H>=TwQ>Vq!g+~L?ORsBT{p+*Md#>XBji}B>#=Mk!
z%y%>&Z~>JdhOg7@I*Y@B#*owYp$I7-UT>!F%=w_ahyg#YcJdkl`SMg=P+!61^DsCR
z|C~I3T6T3!qth2-p||99^L*SjTz6z7bUG@Xt`EmNYR(Hs(zWV}a5_d5dnGl2`52vH
zeSQ3Z2rGE#aJyZbgiWSBsUa{h7AECZ5Q~SlHhHCOKASv)G%`3BL6tHtv=32u+I7v(1+_Z4TevtM27YD@`)j6<
zOmuw3t&Tp{u-{}g*PlRw1cRfHY_cp*i8Y1<3yH`p`!w?*JoJMaop%Kk=nn|bR921cH!Y9ZSx0U`6#BkaP*_}H#hA#9iL3^msv@ZQs`M)&+_XG
zP261YpjC?r^#@PUu=92TY~PA&nudi}dbe~tWjl@VfCQn6Rg_$2cPg!}P7lWnzd9ki
z0N)!Oe?y|vXHH(0hcnTneZ1x@`6B_#L*S3p%QpXnZ14Fplfana@5YaQEy!w}KplKP
zss{6(@MA1&Dt5gGItwj~YWFt~EMee@XWi=CI^yv1LQcKQGXu%$`6?gLfCa1jA>p4a
zxS=b^tjvwAIV5Wr8zU1L9O8W)d5Z8Gm?7|G-?Vb%Ip5NxE-Z8#>@%T#l57VJrU=~U
z^y)zT9lxmktiOAakJ4=|$6XvM{jGL+$+H#UCFNa~Y>rJ}XLXSTKo#W^D1C(*4)D>w
z-}G6o7ZssQZF60!+{NYaBLJ5UL;^y4<+{n_pe=)9ZY3fkd#2YX^CU-M9_DCUh~JtU)%(HK
zann{tYB)x%>yHM}V-k5;URKdmH%B##R!)rGZ5311RD(fRd-ivE%_6!F0#yd+5U<=^
zOhBq)cMQ+ui11B?yKi-dCUk&_@ok?QOf-ETT$~mOS?N@#$ip@jciTO{M-mO{Gt!~n
z=_VgibLmjnKtFk3;^7VgM&K4ZTo2l@rf*a;u%^Gw?L0k+2RJX;`)E=6mP9>
z-!Ad)=}(>=v#{HvWvWHRjW?DI&MuZMT8NcE0yn;kZ@%7?2`msV7I$g={uHOfyWL>5
z&D2}vc23ZDU!S?>qlp*g(#Fj!}@t$4dasp*&
za8^qtvXZne_dl{|N;fm6gn1KALLAI;4|VSlRQ9xAT3*KbCX>!|6MVgl7@xI3W1N3K
ztA9ip0)`y_9O|r+u4}I;_=Yl}MgY_ZLipstkm4OS{~(S5FJ8rU7YVUqM12TUF=*?@
zuOX!tjsryxiGpuDRFq(u0swc_kQ|g_cR>o2PyOS?>_CMTakxxU0aJbj-v12i6nz$i}%qqzR1y
zx6x%=iI}Y(Stf5`{=3E3+349i3#+2|zkEn9<()+VD+!*ckX!0P^y=hRnof=eG3n46
zd!q_Ze0Tf!#mn+83=fDAue!f3MTBidy7nD0DW4KsVgFyawD`R)QY9d=x9%J#qlD%o
zxe1s)1o5#W5r1i8y?il`Z=Z^P+`5_LriU2{p9Yhs1ON=)>pM^B^eR6E`Ue;7C`DbLf+aH;Gp1foL
z6?ae$9_esXSglhkB5p1`;V;gw$HozT;jn&2_VVVltB}(fdS`xJ#?o!jRxRX1v*R(c
z$1@XdXD6Br+{c=B93+2#$g5-YzfV(^`RzE!4IOhn0eq7jzp15L<7XwEFK6RW0Xa8`
z3yx03@*})s`t@=y;4llM3~TjOC;1$pfE}4GM_w!6-L`r5?gGOIggrGJ4!<47&eAo54BVd+8dR0IC|v{%Z|-UlOC-EO3GtW
z_2`+!N~|)#t^|tLECIyd(j!-$n-?tb*xtw>&Z9Zhs5IeD`XjDmogzF=*09v#c*+&E
zi!Ok#bj7EnN4crDP^AWrelKZC+Ijl5N-`)fBT?R$^7+Q{5DxsNaCtw*3
z>dB4amx#Gy%)Y*I^Q3^jQ>JcT1)jb07V2Vcbd&snrzGU-cZ+ZTI_xEFmpm~R7zb=5
OvA}fT+ND=+h5rL^RWJ$w

diff --git a/docs/html/img69.png b/docs/html/img69.png
index 2b37abe9aed5e746f412357432711f7325a54f81..9e29b6013007cdb13330767b0145f5f70fbdfe98 100644
GIT binary patch
delta 214
zcmV;{04e{%1(yOLiBL{Q4GJ0x0000DNk~Le0000j0000Z1Oos70P;Sb*^wbje*l$9
zL_t(2kz-(>6)1mRSB^!P@dHNzKNfLj0j>aM2($kF|NjCA#x$4`?gR!72LxjaOdQDO
zKY(Dg!^F7?7?>^~7)xQ|a{?G%1;82m&rg7g@A?1#BPs&|IxrXzuo{B_2An5>g!JwW
z5C#HpF8~r(`8PlqaKQR0KY)Q#EP-PJn1KfPKCtnji-AGk-i=trN5Q}V0Ck5kE0rbh
QrvLx|07*qoM6N<$g6Tg?%m4rY

delta 644
zcmV-~0(T9$iBL{Q4GJ0x0000DNk~Le0001^0000S1Oos70RP?+6OkcHe*!>B
zL_t(YiS1O+YZE~jeVb&PtZ_GcQIxDT9z;Y4TciXJQIC4+3VJhik9v_sr3lp$@Zhma
z4?Pu%_zwhnC|+uE=q-l@kz529iwgdzE2RV}8o$|@so6FL>7l1Q!pwZ%_uiY#uLVXJ
zVT41+mv$DNEwF=zE+O
z4z=u|usi2_;HQ)&aYFRvxV@dI<@S=xNbSx^W+f?0LN|fat1C(qYIha)SL&22KH7N0
zYM&%Y?LNTttVbjZSf2GMzH;Y>7C^{Y{jaQG1Fvz8_GrOO`Pa~;TtkoUe^RH^rR9S8
zOFM(}M5=-Y5yfc1h#+Jv7P4_V@(5WM>$FE5=+Qk)QO)ODI&*oGfkqwN(mlK*QV(O^
zvO}>^V*4s&6iXS=X{uagxT#QU;mBkY7nqrage8@*Wa0&FWEo4Fj4J%N>{5#_hRc|x
zZWpdvs^Q}Ec%ZJc3rp}Zu{v7LgsQF$@1Ir!gKaBBE3v&zWh+1c<4Yg?$zshu#pR$;MDloEuDVjB
zl}>_@j`0D-^t&!)iZ5lE3UCUj415Fsft&kNnTzp*oG%W4+5bd79F%3B4dcVX9D(hD
e6CKp;u<-|;h{pdP8r>@Z0000#lb;`1B(F{BM!QG9R$HbZ;?8c)1fL+o2`mS
z4~I@_rVK6;i69PYGPoUblGzXyL8ydC)ohLbe|IqlHk=)F$_GF1-uM0AfB*Y=4;bN}
z;ryFj8di#lDZ&nx)NjI0FpPH+e``+WgXLp?FJ}@Asa9f5%?XxXf3GLCu`q;BuVNA3
zug)2wd)yM;Ih?rk4W)t$jQw2SyNXgIzKD64QMRhMQZ3SsO;qIxrk__sz5Nh9x#*|!
z_l;xVKpkQh++xOvi8`Nv(L%sz#xO#_m}Vte;hQ$lvA?6
zgB^(C$DqxCNo~(#8E0wBCQ59lZS*frnHrn0#_!azCMbA{58AD0uooloZ96_MVv1u&
zX4M)F)6v;PRUEA&?NArCoUt}Aamz;e5rvyI-LIk45G;blT0q=;PoUos<6KsjrLR(B
zl1+3CD_K*|M+fosyz>$_e}ymY>l9ALs2qS&A*nt|Vh1EDHB80&s6l|P(Y|mjP{n>D5EVB*Pi9n?EkPQag3pauMo#o7|HOjZ+d&+X
zo*TRt!k48XHK#9hb`Xc8uTLdEe}eMiZ?YoD&$~z-VT2L>JAMJPSiQN!1b<%u0000<
KMNUMnLSTZXW8iBL{Q4GJ0x0000DNk~Le0000k0000U1Oos70HN(MsgWT|e*oP{
zL_t(2kz-(>2VlJerpg-7C2YYY%LjDv|6r2s0lK&zn2bRYli$9X@c;ws_w5Wtn?V*x
zS3JH762Hu#&U}Gkk^s{L4~FkR{s!I;nLvs?f#E3s2ZrkmydUxy{DA@!Al7hv;7ee7
zz`bbYB9)E4d4-M?oUB3;`hZ24V$oxj7RUuCrbMn#aK0
z;LiZ^2WxvxKx`eu@An1_pZ7DIIdi7DG4^bc
zk*z5WvQ7v|WcR!EJkReu=lT8qd*5^3^WNt==RVhUf6skg=lXoUpYP|oB8(ANj~x{}
z%EZKUOix$Gl!@s8h>3~0o%J9vB5I_71YY6B24?W4rlv(jMMb<~1@P2WSQc1HNJw-N
z2#+5>9&vK|E+N76l<9HVV*>*N0)ZfrDnTF<-lnCETUrVT2pHrVtO*EUu~--khJB8G
z7ag6JmNso*Adn=m$f9o6-2Z0Azg
z%H_m9eBayiBdR2;G*e#<=E=DZ9R_ioEFMDsF7A;kC7Anq{N)|DdDti#@8pj<+g>oDK4*=(aQSKJv(NfWJB
z-`rSzF@B>z>sm3_sL!Hp&rnBSMpGH)Eu>Y9y3$isKR;9*gY&xmm9_+W9$rOX_b92$
z^t~gutl$FOLkW{NnZOeqMXl$k93TfS_@|!Qjr5z`ZWOC6YK~H>`PG^JyV+g$mxl$tPNK
zC%Ma-H9Q*_XjzM?r0uI(@SdXjCEUHh)NYXz#G}5Ns0+)wC+`=YgC2Z*w>BDfx)$
zqeFQ`=D*3ZhIKP~ioVpbW(d3SwjnDz;@
zCg$}0yNlOj5`%B693|$xBc)#C8#RV&45=n5o@7*QO$8N~2}{Ny8E&FSB@(?@$k|$H
z6&;gN9Az6=wglm~NzLk|I(84T(8ksj%Jmb^DE?wl>uJuanU0SlHjbnksU}7`rMh(^
zDn6AWHJCBbUv#q3Ve~kIMW3wOb-QRowcw{BFNPKWEWa|_V?xEwn~IPU+qij!8krMm
zJRIF}9yDdZU(8xCA|>poNe%fg7^FiSJl&TMVEFNo#_zYp`HZFJaWUm`v%*l`{e5Y&
zzH~nfAM-sted;+@t+vWb*7**V7k`nMXNAq97|G@5lTJCe{R08~yLrF(`F~*G!g0>=
z^n_h0`-~^}Km~x*-0(=HAkX4vM8#xcBJ4wX_eT*zgv0WxcF9=ng3;b?_X_XH!QgVa
zqS;l0gV>DSpFe*5m@WHh6!6}2ePL%{fO9FO#^R~%d35jKA=(_07dNw(6#%#Gcml8P
zbXanhE(MQ~$_FpEY(
zj52%Uu1(v7pI6BG=6Dv72!lQ1PL{6|#5l2=hxEJg!~nb0VhopBxH8VqhLQNs4LWh*
zd~tlSuRojpDBmR{uKe~Uy1VGhbJntlHJL?R2>3>@>@^_s-kg>BTjCLB(9L83eI=FJ
zttl;iK^z%7d93U~j`Unndl7zFwR%L7&&+Q+#AYc04fEPEmd~k^>15&ULc>lvW4#4%
z*}`vmLtn^nrS8Yk7E6b+J!nRF5n}#!bMhtU>Jce?GL`LfZN4`?`Fo~sG1}kvDIPyy
zDu?bh>pF&l@rHJvdGlExs&r&61AkUqL=Sg*pK|~H&3tLJwbMW@+7sT(bib14a!KBp
z#JS*X?}aV0b%%r%9A#KPX<<>h2|2DRMB;}eKFITkVu7-SMX?-kp3=Yhg)RG)P^crM
zGfn>M2}k>=3QxCY6#pcEH;CN_9MlA81B4&Lt@+s-tVIp6&*Eou6qe)yJ_@k?M!f<#
z#0IDao`h15uvwuFvnWHERjn2;&?h@`WputBj5-K4I)2N#|1n+W^-etR9!i&{86Af8
zziNP~HpRhr?dDH=Et@^v0SM101zOzFq#pR$MGjs6J~cdgU&R<|aXi#FP95a=ti9tC
zW#)=k7Wz@4TYLqHlDMufE|*}~H!`Z^MUN(92RbHZ;>x3P9faH$r?iA|=1Ec3UR&9M
z#2x;p*m)tcxJ;gQA7L`z69MI%on3Q-=FqmpX}#7iZ69-7#Nv1uoKLxN7>fq_n$MVT
z=d9k;1u~@A!NlyKSB>{0d|umwYCm#4GNy+-N|$Gu={Fa_8H(UWHYU$lXD5dbxCTI_
zNSC4ag~Mg$A_z4ZItW1?-1OYNc~h!&99xh1Rop`E!)rv^UQW__Ldm_jd_6B;+Q=$0
zk&LAovG=UDi%D19#D=E?1lL+;xGjCSxYVXA{8nCIe4@JTNq38dG=r?-HA?HbYF2l!P3n*J1
zGF+Ge0R<2WkPBR+g~F%Z+}T{)poF;UIL!~?%2
zHBA6|G1TnJkhr?Cz0qQpIUmN-nz
zY|36lDi~<=Vh%7`Dobc5!oGaX`pveu#?K1>M4`~AK#yfQXDS;#wZvpAm_tWvbkHb71Yii4EPuKNi7
zt-eIH1u;O%s*VY)j`qQT8W}owqU<~Yp*j&J{fmC6SVj9nv3>PwcWB142?-lP-~1H>
zFl6JHG|2gDB2xNKeLE4x*#<=6Nmv|FKPA9s#ASCXB|Wa2P}1D$A2;Y8>vyufS4L-7
z%ZD%5qg{fl=wI_eL5t6=KOc%u&m4$-XDh9h}>qr5{Q8F?`;geQEfa!NxdjD
z7>?wkDY7u`CBo?9&KU!JmGyU_?$L@?g)#XQBkG}je^QN^p&E+f^ss?{vV?lJsO+EK
z
zhHw6KYe3k_QN|H{sMQ|3WaRqOwRce2e`{Sj#2&EQH)mC`T3`Fq64k^%6kFl2KJVYS
zH@!mHNs;ClgZW4KFE$>ry&ZL@Q{en|K_nczHMZ0zx&DrDnn%W3tI}RE}>!Y+nr9!^XhFASU%jIuI(LfrK#uqnTCS4#V9k2
zqTc=#L7QXHGhw~XB=1rVo?b_ERtum-Y`Ynq9nzqsn2zu)+lKlr-w;lyJz$>=caGh`
z>M5Z2OFJQ^P4^#s{eMZk@`RqAplkOJFq985)RXB!-m#I#J-?
zbvOOtX9=^C2N7c0s$fG{oia2N)3EtONY{-Up_c>m)0`d*x42Ol|A$xBpHM6Oj88^@
z`S)^tg^uk(*VGj&?#PX3%8qR4O!r_Dw(~S(atgsOLh-!Xy!%T1%R-oO
z?dx!R5dO%2!C;L~tJbEr%|TTzT{--)={B2Sdwt-lfwrf#nt9;&iV~^$w6O7eiDM(D
z!kd62-OGYra`2Sa9Do9zj74@hOrYsC7n8OBN?T*q)bU%8_HlX>8LO}L(GR0JWP$jy
zdg;w7wwjX#*{f-t>UP$71#n|$Z*O9MOQ-)J;$umv4X#rcz&kuFNfl~!?GB!UBEk^io74VH18d!c0#}Wa^tB_EH+Vv&
z!lzAxz;Ki2ip(_;lcC>satng@E`x!}^_%!?fP@QtSr4)PkW
zdgf!=XGwJ7xQ&1oTrA8pC$F9SobUhBY1d{}Oz#%53bKD~01vM$SASA!T##c+&}#Jg
oU1(ifh-3@N6u)&NdiH0)>8Sy1IJ#v8xHMwYgClfGwd{ia2awfIB>(^b

literal 476
zcmV<20VDp2P)
zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001
zbW%=J06^y0W&i*IT1iAfR5*=eU>Ncs_5g@v&mdAc^93;FPo#4G4`3>fNaaiqKqTt{
zB9t=zt~QWiV2H0SVAr+)@wfNc2H;lCYrs@s%fP9~pvls}U%0)qjP3T9;G
zWehw4{~34-fT|v_0R6xT@7x<8rGrUDs
zewpD5Oj=2-9c
SeS`P_0000D$RD3D2!DIgd0v9JgV3hL+TV=x#^O-;;m
zOloSX;1j{rSE*cFT+YtUfRpBm3g>6eEd>Q&F!)VsDpx#LD`EGbgod_ZFoc%`OH0dk
zXXjHd)w==hJ$H=ZCM=g`J_4pZXJFcwP5p`U8JyK=ANV5<_7J3%*FJrvyi;(4#lXJq
z>;xr8ddJN*INts+^%iOsb6kUNuRJU)rj`3uaGv?o31hvpG&6CB9x2)cx#3`-XeIN+
zOkygxLFog^EW;R%aGASV6rNO(`zSA84!1_l!k_oKxH9tVK$NPFx&MzBNYhJkW<{ah
z=Oe@h(M!3+9w}t1zwmiq^N{NXa2+QTy^ME+A-j+-#kZBVCq_f-+(%Sxm7mx8t*$Vv
z-&EymCYuKMGsrR7F!f%Y&CoQ^}iZVZJAg_XmyN_38`tAr14{j@*nnR+sxY
zV(2Rk9gYyGdE@!5*U7rfs9?JPX$GQFmTj!iQ6-sgjLxq6#-D*ztSG|1*pcf0t=sBB
z&m_;z4t^`i=(3scEx0$8H2rC1JM^I*BX4Mh
z&*V){{Cmva5j8@qL|46md@1=U{p3hENy*pVe(|2PtpO(d)%9&TT<$+l+tg+AsRI)&
z!tP%Y553i=PM~DZa24iu6Mj6SoB5o`PQ>REam$%chu+$h38e`KHFX3CbXwBy-0@hn
zq8buUT~o|o=o#&bL!X(yI(~;&jo*acB3xXQCsc@5GnY_hEzB=P6Sd(Pbs=&ohS418
z%MoW?4z~-AHq7*%)<>Ty<0@FXzR!83bN}FrIuDf`@(5q&H-$yZv=c5^rVyTDw#PP$
zH=Z$5dMOC5N58j)6KAs5ha512>&1LF5sz&82D9RTo_eTo#Z8r?9T5w*E0Rd`%R@!&
zhaUT{5x&ve-0M9d_E1t4RG8}^np1Y{y4P{IPVA60cax3-I*&~f_#dp;hS_~k(dh>K
z)N_nlZ58&kiyW0tO2C*o<28K^ngV>Z8iy$U8D^Z@?7b1e1p3CuE8Re`sJ1K4wmN}U
zPTSUMet7Z-70+Qy?e%OI)
zr1h=RLGQ?EgPorPD}wiCm4kx%_CT_{@=$EsDp|dn+Z)cmbVVaSkG-X9)@Mx=WSVdX
zQ&`ZpCpm^@b@}k_u_?Vf8`7H>wL!CIm)~$hwM)%~@vdVtDK*qHs>!P_
zr@Nn=eI>Oba?*3bwoO8gZ3Wlz;ndNT9$5j?>V?w5Y*h6rc(jS}ScPM9MP0fK559!e
zU)|&)T<>nXy6i&bJrtD_@b>h_Xd;zq8hjuZwUG~1fq7gWF9;De6@}r&cfHF2DSw<3
zEyHE@px=u(8kkbc|4~?OQ8K9D{_DbyI?eVXYUyyh3WlyymIZFK1oMzJZCu{35c|wB
zG;Id9p{JjJ6XLWZ8b)8?Rg4vP2%`w%BTRQ^6h#Toi{Peyk}r(a0$9Ptvoe8Ko$
zgg{l6H~a92t7eMpa)N;A0ylsifT1?9Bd8qWK>Aa0DTot2DTuCYngBj=QgF6yqPdEb
z2HA7X>m+>TNk`6+#raEQ_}2%}hQ5hh_OkgezAyqxaXDINtRla~=EW>&drB?;{NpJg
zVLdTc2^}vQ7|z+~(vuwYqSuI4H>=TwQ>Vq!g+~L?ORsBT{p+*Md#>XBji}B>#=Mk!
z%y%>&Z~>JdhOg7@I*Y@B#*owYp$I7-UT>!F%=w_ahyg#YcJdkl`SMg=P+!61^DsCR
z|C~I3T6T3!qth2-p||99^L*SjTz6z7bUG@Xt`EmNYR(Hs(zWV}a5_d5dnGl2`52vH
zeSQ3Z2rGE#aJyZbgiWSBsUa{h7AECZ5Q~SlHhHCOKASv)G%`3BL6tHtv=32u+I7v(1+_Z4TevtM27YD@`)j6<
zOmuw3t&Tp{u-{}g*PlRw1cRfHY_cp*i8Y1<3yH`p`!w?*JoJMaop%Kk=nn|bR921cH!Y9ZSx0U`6#BkaP*_}H#hA#9iL3^msv@ZQs`M)&+_XG
zP261YpjC?r^#@PUu=92TY~PA&nudi}dbe~tWjl@VfCQn6Rg_$2cPg!}P7lWnzd9ki
z0N)!Oe?y|vXHH(0hcnTneZ1x@`6B_#L*S3p%QpXnZ14Fplfana@5YaQEy!w}KplKP
zss{6(@MA1&Dt5gGItwj~YWFt~EMee@XWi=CI^yv1LQcKQGXu%$`6?gLfCa1jA>p4a
zxS=b^tjvwAIV5Wr8zU1L9O8W)d5Z8Gm?7|G-?Vb%Ip5NxE-Z8#>@%T#l57VJrU=~U
z^y)zT9lxmktiOAakJ4=|$6XvM{jGL+$+H#UCFNa~Y>rJ}XLXSTKo#W^D1C(*4)D>w
z-}G6o7ZssQZF60!+{NYaBLJ5UL;^y4<+{n_pe=)9ZY3fkd#2YX^CU-M9_DCUh~JtU)%(HK
zann{tYB)x%>yHM}V-k5;URKdmH%B##R!)rGZ5311RD(fRd-ivE%_6!F0#yd+5U<=^
zOhBq)cMQ+ui11B?yKi-dCUk&_@ok?QOf-ETT$~mOS?N@#$ip@jciTO{M-mO{Gt!~n
z=_VgibLmjnKtFk3;^7VgM&K4ZTo2l@rf*a;u%^Gw?L0k+2RJX;`)E=6mP9>
z-!Ad)=}(>=v#{HvWvWHRjW?DI&MuZMT8NcE0yn;kZ@%7?2`msV7I$g={uHOfyWL>5
z&D2}vc23ZDU!S?>qlp*g(#Fj!}@t$4dasp*&
za8^qtvXZne_dl{|N;fm6gn1KALLAI;4|VSlRQ9xAT3*KbCX>!|6MVgl7@xI3W1N3K
ztA9ip0)`y_9O|r+u4}I;_=Yl}MgY_ZLipstkm4OS{~(S5FJ8rU7YVUqM12TUF=*?@
zuOX!tjsryxiGpuDRFq(u0swc_kQ|g_cR>o2PyOS?>_CMTakxxU0aJbj-v12i6nz$i}%qqzR1y
zx6x%=iI}Y(Stf5`{=3E3+349i3#+2|zkEn9<()+VD+!*ckX!0P^y=hRnof=eG3n46
zd!q_Ze0Tf!#mn+83=fDAue!f3MTBidy7nD0DW4KsVgFyawD`R)QY9d=x9%J#qlD%o
zxe1s)1o5#W5r1i8y?il`Z=Z^P+`5_LriU2{p9Yhs1ON=)>pM^B^eR6E`Ue;7C`DbLf+aH;Gp1foL
z6?ae$9_esXSglhkB5p1`;V;gw$HozT;jn&2_VVVltB}(fdS`xJ#?o!jRxRX1v*R(c
z$1@XdXD6Br+{c=B93+2#$g5-YzfV(^`RzE!4IOhn0eq7jzp15L<7XwEFK6RW0Xa8`
z3yx03@*})s`t@=y;4llM3~TjOC;1$pfE}4GM_w!6-L`r5?gGOIggrGJ4!<47&eAo54BVd+8dR0IC|v{%Z|-UlOC-EO3GtW
z_2`+!N~|)#t^|tLECIyd(j!-$n-?tb*xtw>&Z9Zhs5IeD`XjDmogzF=*09v#c*+&E
zi!Ok#bj7EnN4crDP^AWrelKZC+Ijl5N-`)fBT?R$^7+Q{5DxsNaCtw*3
z>dB4amx#Gy%)Y*I^Q3^jQ>JcT1)jb07V2Vcbd&snrzGU-cZ+ZTI_xEFmpm~R7zb=5
OvA}fT+ND=+h5rL^RWJ$w

literal 310
zcmeAS@N?(olHy`uVBq!ia0vp^+CVJF!VDzckNkQIqznRlLR=3VIIwy1W;HdnhK2?o
zAD?B*mPtxV78e)W+uP5aIg^KnCoL@vsMgrnxVN`AGBUEWz1RfEXDkWw3ubV5b^|22
z#nZ(xL}Oxd!UENVz0I+A#CCtEe{-lR!c~&rU_;$~z9UB+`bv&IUM-OLjGJdN%M3Li
zp&avuDha8iL?=-K}R1#=s}A1-YRP)KLG&CJ$Tu8_EleGa?i4jq1{FQ*QinU?s}
zJE1~#I>W=OMl1#OtcLfBiq#Ba*po6B*z*44k>?3@JhZWtXa9X^gFkgK1<%gRd^YJi
z(;VIeb~Xb8zXXP4wl;@0P9B|S5w?etdhXs{3<`_MpLLl}*v~!$bU%ZqtDnm{r-UW|
D&H8i5

diff --git a/docs/html/img73.png b/docs/html/img73.png
index 7f9a996cabb8675b2bf42f977572d8dc5748d7ee..2b37abe9aed5e746f412357432711f7325a54f81 100644
GIT binary patch
delta 673
zcmV;S0$%;i0>T9$iBL{Q4GJ0x0000DNk~Le0001^0000S1Oos70RP?+6Okbl224y$
zrlzKmJ05?DhjTOl0004WQchC$o2+p+dr_3E
zH6BDn2wS8C4^fYL>I!-@bdP$GMWqPU67b-$OAkF2iuex%dMI9Ma_B9G1(93?7mEu1
zs4JxeDH^}onW@<}2I--vJi^R;-}l~|%&!GT7-4^eL&xNxWM1^@+qj#l4|5<=t=Si6
zLm^ADA~C4OZ6?}J=|dIiK#s?NX(>zMx9EGE7Y?=Tp|CsWd*G*(C2>OZ<+#0_sO9#O
z%Si3cNoFM}OF}n+)2k~=6KZ!A_gCtaD?ZwI!)l)-N$ozs^sGlD3s|1@DZX;&hZaD{
zSp9#mtY8DLagO$A!A$wr(4|~MkM2^Z)TQNu`Aa*4^F*qG1`)+*!H6JaEEckHI`Rlv
z7wfb~9q7?LOi|6}TRL-jlYvGZ+|oU~BT^4z-m*inQDXZlWE4vo(P^q&WVoqNYvIUb
z6Bn47g@h%Quw>!|ZDbisn~W;_xa?AkFNS~1n5AwPu3D<$;`4Z*uCwG5IMizL!cYkx
zVLZ1~rRjX-v2Oe62twv^9?A0C@xpWVaqnARbJ0-)c1hCpDMbCpL#5&(bRro+!-DdX
z;-hARrsOhK7qW@7@$sn79y_%;?0mPe^$P8F`{~0kCbP=OiBL{Q4GJ0x0000DNk~Le0000n0000F1Oos70KdXI@{u7F2BxN_
zr>CcpJ05@bl+dgI0004WQchCz%-6#NI1EZ>V6{HqIO7#M(Pe)R+(-#+6bNM@42Urt2^O{ebmK^90?
zJiZDNzs#V{e1Tz-0Mi5yhVMZB2Hp>uK#Dzq;VAzHhU*NxAMzOdfdUgC)^L2_OJI7y
zd60q2^Za3B#5s0#2`M}RC6u<{G;Vr{|kjM^mzl{tt82C>zFvvbn28pl=
za56AB7cjhJUfsX0|zig03&Zb
Ur~UIXA^-pY07*qoM6N<$g4p#_cmMzZ

diff --git a/docs/html/img75.png b/docs/html/img75.png
index 499ac4c53062de58e3799dd70612f24f6071cc04..4131707b3e5fd355d3c1b049ecaf15af2bab9f09 100644
GIT binary patch
delta 412
zcmV;N0b~B~3ETrAiBL{Q4GJ0x0000DNk~Le000160000U1Oos70I`jKb&(-Ue*s!a
zL_t(IjbmUK@*wsAh-A+oQaSSlFy&9Aa{dosDvwCzObj5H^GXAbMkYQkmuP$KM
zwgBhz{yhT=inc)lLfq-WWd<)+)
z#DE;let{LFoZqm*+_U-vMEPg&<`Rg9niOj=2-9ceS`P_0000=yEgdZA56f>O-ptss3wVnFU5`B$2ijPIZw96#^vLHTMSe}>^x_UKb-o#u9v@x>
zdY@a3C-k3unNezOeTDfnp{!!Lj>ef02gZZHNks)z6N!io)eEelgLPNXQR^;8?rg*A
zbnqFD!5Q2v)Tk6
z1qSh9JYf(!7^N-_>CC5*vH~t-Ok$F%Aw?CuCK8cK^3E<`Cv*$BY6pv$Z9+ed#=Itm
zo|LtGi$&lbE-uZYhv5WFht5o4w!})5;uYX&CGMSURlX^1dZvq&8)-hcs(MZjuNo9ql
z!mT4b8Hk8sEpg$GS*gt-6lyU{iN_$G6HFx%P)VMWe<-98(pei#hW{?AFkWl>bFCd7
zd)12L5{f)k@AHqZCKB{SEf2@j2_qKCeO8Czr`Kip1;eUy&
zEwh=(7-VgkD6+OpJhHY-)|ScIGFe+DYs+M9nXE07wPldCW&X-!)|N@cf4(jACucle
VH0=

diff --git a/docs/html/img76.png b/docs/html/img76.png
index 10647c53d6bf705d4d1e1aea6d35c3cefd3a0616..ba3d4c05d9047e97c2a39fcb7d76c08d8e058a92 100644
GIT binary patch
literal 310
zcmeAS@N?(olHy`uVBq!ia0vp^+CVJF!VDzckNkQIqznRlLR=3VIIwy1W;HdnhK2?o
zAD?B*mPtxV78e)W+uP5aIg^KnCoL@vsMgrnxVN`AGBUEWz1RfEXDkWw3ubV5b^|22
z#nZ(xL}Oxd!UENVz0I+A#CCtEe{-lR!c~&rU_;$~z9UB+`bv&IUM-OLjGJdN%M3Li
zp&avuDha8iL?=-K}R1#=s}A1-YRP)KLG&CJ$Tu8_EleGa?i4jq1{FQ*QinU?s}
zJE1~#I>W=OMl1#OtcLfBiq#Ba*po6B*z*44k>?3@JhZWtXa9X^gFkgK1<%gRd^YJi
z(;VIeb~Xb8zXXP4wl;@0P9B|S5w?etdhXs{3<`_MpLLl}*v~!$bU%ZqtDnm{r-UW|
D&H8i5

literal 278
zcmV+x0qOpUP)CBx)F4OY2sA&7Bbp*r&&_%HxDoU`ALYzj?i^-a_2x!SRbGRCeb0`81A7(pdxHENJ>QFTYxIlhtxmbXeB`szxP9jBYmprjY?MYK69hRD%{oK>z>%07*qoM6N<$f<$_8UjP6A

diff --git a/docs/html/img77.png b/docs/html/img77.png
index b55484779514ae6573b4e107dad2b5786a794ba2..7f9a996cabb8675b2bf42f977572d8dc5748d7ee 100644
GIT binary patch
delta 297
zcmV+^0oMMm1I+>CcpJ05@bl+dgI0004WQchCz%-6#NI1EZ>V6{HqIO7#M(Pe)R+(-#+6bNM@42Urt2^O{edxiUgm+2JQ>&7jT*LUh6v&kD~w>wEI4T@x6^G
z60BF3A8<662;kC*3RppeBm{G!NeD7o@J>3DT4r?5Z40-4s71MSxrr?p`pRY
z$7k8HWs;JT#l^+;_VzPp&g9|YNlQxusx>w??(OZ3jEwATFE#=48B2ovf*Bm1-2h3>
z@^oN
z4O?X!BoBxkP-a+kQ-6ce8}`{Iy$=ODHYNN#a9&5`0K3UU-NW@0PVg1)@8vO;_~CD4
zaKg@?t#bocfsuiQxWS&31dbUy1m0<+Gq*9ZU7MV6I8bg=d#Wzp$PzdylDXd

literal 160
zcmeAS@N?(olHy`uVBq!ia0vp^5gTe~DWM4f
DKXEO{

diff --git a/docs/html/img79.png b/docs/html/img79.png
index 9c2f557f161eb8a6eb56591e6d2cad01878cd239..499ac4c53062de58e3799dd70612f24f6071cc04 100644
GIT binary patch
literal 1264
zcmV
zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001
zbW%=J06^y0W&i*LZb?KzRA_!&1O5<&CJjTjiH)6>4OjgK|yRAebAsU
zUBy%cF%9BFkd_6jC{YX)ELf>q2qJ<-A4GjIYZWS_CV8o#46;)Cq{Q1$w$ZxViJ{nv
zO}+QK^K)l*CX+}N#W}F^bMN`S^PTy-%Lm*j+;zh;Z5g+0id9ojjQv2P-p0AReaK_0
zC@}ZHOOX)Q9vOrD8!VNB+>j@I%}Hki6#^vLHTMSe}>
z^x_UKb-o#u9v@x>dY@a3C-k3unNezOeTDfnp{!!Lj>ef02gZZHNks)z6N!io)eEel
zgLPNXQR^;8?rg*AbnqFD!Sc7%F89Nv7;@jB(Hx(h
zSs(P?S#I{%R;wJC?X2vg6g=mTN}L(K=$voX(c_rDR)kQ)iHA{*S
zvz|zgWgace(g&*3k~Q>M`3WV?*)G;W!wCw}-p5`G2XM1W;8)(Y
z^^AOHwTj93dg0Qfa=;3iB}H|TkCBK}l4jSSpW%dC=NFE^c-_IutZ#Py3k%nGUxhJu
zfxEQrMVzu{p?!bxN)6lZ73|-S@=vBXx(vDW6zy*)g??zHD&tDFjTZ(wX8A2PzxImc
zI&Tm2b@|=hj!M8ERhKa{eCh#8ZLVFa63w=4sjRTL(8{d&5i=gXEESbWs)7)E~+qI
zYx{Gp9UgntisKTBJXP=WkFO>Y^h7NW$I}Sutc@neH<)XO)=KsYh!^*^b6ZOI&m#G$
z%#h)KiL5QNnaCJqZJ8*twoE*-woKNR$=WhmTPADEWNn$OEt9onkhNw0%4F7-NyLA?
aE%PU5JY6*H5RM=K0000B34jDhKnW1qNCNzM
zX1AEyouZ}>U>i%_2uU{N9|D*yU=%Q0z$jq0fKk9~0i%G~0!9I|1&jh_3m65=7BC8!
zEnpNdht{XByzR0GO$NS4%wK@vyuR_{vUOfhRwL@oH_2I!p+kJ)#=qO#fej+mcGvzL
zVQs^MH{R~9{7c9k&?Z9H?%E&GJDV<4KsO3^@mKx?eP4zklddI;4$F+bu9CwocyrJD
zfDbQZz4M1@wCHy}P`hmQmkgxO97oaZfnDZks+mK!EBsXeuFfBkxbRyKB}L-O?$)TY
zZ8^imW^7)VfsRd6C!iZ;p)aN~c}+~9HmG;YrOxZlAhIaGKHURS7JVWn!Slj=EBG(vm#l}@1>k721PS_OOv-|C+HER?U4
z8szYz@YYO_k0nXqk35afUWSxu3Ds1mSBiSFu?(Tn#qy3XG4w2X&&uBf{1!eqi=y)D
z(FabO;(?>DGu0h&R?8`HZqa($K8h*6L={z2*$A_uW~VEI#znkpO0>;xTt}P}%HISe
zbLkTYf7W73Mm`hP1?#iU9y2K1=8?-(iuPJT`+G!f2vYRLH1FQy>iOP?sSX*-Qccm?
zp3;WM!7Kbt0QV0O_Quc761OLf7S$fyW_3lH&_aF*;?*=#eJ376TWY3zB`K$n
z-mM?}natQv$u1H4k4VyI@eAL?@(G;)$DPWO8`W8VN@hU1Y8d|2E5CU^1Tb5`C_Vul
WLFj@$^iJ9U0000CBx)F4OY2sA&7Bbp*r&&_%HxDoU`ALYzj?i^-a_2x!SRbGRCeb0`81A7(pdxHENJ>QFTYxIlhtxmbXeB`szxP9jBYmprjY?MYK69hRD%{oK>z>%07*qoM6N<$f<$_8UjP6A

literal 344
zcmeAS@N?(olHy`uVBq!ia0vp^ra;Wc!VDy9OFeagltF+`i0gp^2R3istfr>c(9q!H
zq
niAv54%<9Y>o<;^6np7D6AGT_!%5l35^dW<%tDnm{r-UW|axs33

diff --git a/docs/html/img81.png b/docs/html/img81.png
index 0630d10e7c0ad4f5e97fb442d4d694673767a85f..b55484779514ae6573b4e107dad2b5786a794ba2 100644
GIT binary patch
delta 366
zcmV-!0g?Ws3a$eoiBL{Q4GJ0x0000DNk~Le0001u0000U1Oos70ONvydyyeae*r8>
zL_t(YiDO_G?m(P6I$z&~u|htesY}2mfvyt_{=!tdqN(Fkz#)OI6NUF4LpA>g91{4<
zdGQfUar~1d1fDTG
z{mW2-Y0kWNK!E0+2ki_Dyaf#Re?j;WnuINg_zTyE-5iGZU%}K;28KBT42wbdKbpjU
z5aEGo4w^5)(ZZR)!0?QLZy^X@=0ufP8UQ4g;}0JYhzG_Gw*v#iG@#Ew_#iim1fRkN
z?hEV}aGCR7>pK#UqW~DR`#yv5y^Samtd}2fG?xhA(uoRKL4+g(bD~KIL^5!N2H?~Q
z0nGn_09*1$k(frn6rgpWIG8{{g0HQBph2Tx6pR8OI71b1fLi7N04GKJqcCdUQUCw|
M07*qoM6N<$g7Zt7-2eap

delta 1259
zcmVyD18VLvuIUB
z3l$#}D{+OQMYQNcsJ__v1AWmXFAB;c3w`iGNpFLOl(^ezW3d&Rc+R=Avom*hHVH=Y
zz~0O~_dDnN=G(h>Ccu`)om<;(e=~9OKkkr;%HWvQ5HWCvFLi$l0nQwn9BC_x7%L*s=c<8H6YLy(!9By+59Yg1aJlOaCf#ix0
z3T|Oo=Xemgp~CUp+Pi~Af6-9!$>0p2O?4K~Hr<&w?65~MjLbk@oMB|sZb-NAA3FK0OyUci(keNG
zITWmU3}bS!-A!gA9HdEdG8nsKvDo1`o@l6OGP*$zdy#gLD7Gone~vQV&)ZKam(s~^
zbc$w)IlK+rP4$5tpTqHVp~JV{rMh@6RYu1^y*7QiXxbqN-H+qF7b5^#=u(+1*04BZ
zX_XwpY}oNQ=H=oj@T9?^b26BApj$a*(NNK3@^#)2vBL{Z>>$M8w?$6>pmQ{H1aM+C
zWXF|iH6OC0y)ejYe+2CILbX?-Y6vd~Cm?jP5rD(|PJi`RBz_*#Dg$Q2jS@
zY)9toXWS}N2JP>l*7`mA3?jTBq@P6Ja0HO}Q11?YmS58V*iGJ6_3V9()G71+_6rw&pmM`^n&WY$MG
z;D&0gUDCB?3ZET<;C>R`HhFQlRJ-xR`s~<2Zv#DAC6@_v9Tl;o*G-NZ96Be1wj)%?
zc8G?GCX=Hye|?S+J7;E(!+yiV(wV@H-OI1QS-Dii^2`wzU8T~T%s$vh51gNtuT5jy
z9umE4nw~6lv2=zHLjE!{rSCm%buve9AyQi^l~PaOc0Nm;@BH>mBna+D06d>O6+4)%64_qZ7L&YdZe_rQgV7ZaPKPQh)umgTe~DWM4f
DKXEO{

literal 434
zcmV;j0ZsmiP)
zv$G~9CV+r|OiWCsrluJg8FO=UKR-X2nVAd>3}$9#0000pGc%2ijagY)iHCDE00001
zbW%=J06^y0W&i*IFiAu~R5*=eU>Kf&{X0I{`T{V;JON2;2M~+n)^Zt4G8rHV{byi!
zeHXWm|48ij|G&b7{t~4_q7)%SNC$g8h-^d>LesJ3xqap41_s98)dmn9@8*KE!TjQl
zp@TVIkuRCy9s{odQvpQB0}#pa?%lhGKzhCdh7LZC0%iqB34jDhKnW1qNCNzM
zX1AEyouZ}>U>i%_2uU{N9|D*yU=%Q0z$jq0fKk9~0i%G~0!9I|1&jh_3m65=7BC8!
zEnpNdht{XByzR0GO$NS4%wK@vyuR_{vUOfhRwL@oH_2I!p+kJ)#=qO#fej+mcGvzL
zVQs^MH{R~9{7c9k&?Z9H?%E&GJDV<4KsO3^@mKx?eP4zklddI;4$F+bu9CwocyrJD
zfDbQZz4M1@wCHy}P`hmQmkgxO97oaZfnDZks+mK!EBsXeuFfBkxbRyKB}L-O?$)TY
zZ8^imW^7)VfsRd6C!iZ;p)aN~c}+~9HmG;YrOxZlAhIaGKHURS7JVWn!Slj=EBG(vm#l}@1>k721PS_OOv-|C+HER?U4
z8szYz@YYO_k0nXqk35afUWSxu3Ds1mSBiSFu?(Tn#qy3XG4w2X&&uBf{1!eqi=y)D
z(FabO;(?>DGu0h&R?8`HZqa($K8h*6L={z2*$A_uW~VEI#znkpO0>;xTt}P}%HISe
zbLkTYf7W73Mm`hP1?#iU9y2K1=8?-(iuPJT`+G!f2vYRLH1FQy>iOP?sSX*-Qccm?
zp3;WM!7Kbt0QV0O_Quc761OLf7S$fyW_3lH&_aF*;?*=#eJ376TWY3zB`K$n
z-mM?}natQv$u1H4k4VyI@eAL?@(G;)$DPWO8`W8VN@hU1Y8d|2E5CU^1Tb5`C_Vul
WLFj@$^iJ9U0000Oic(!VDynJ8Jd;DT4r?5Z40-4s71MSxrr?p`pRY
z$7k8HWs;JT#l^+;_VzPp&g9|YNlQxusx>w??(OZ3jEwATFE#=48B2ovf*Bm1-2h3R
z@pN$v(U_Q=us}C~k3mTK0?TU&2_4Btfkz|k4Gc7lKiE46KAF#;Bq<%hGE?D-t3l+y
z#@CFG-)A-NR8V6+oIXL~{%LL<);(-KtnVFt*xLRkIR4|W;Xfr&!St_r1`p5sgSU1v
z-H`kxInVG9yJ2F}Wr-bhf*RSySd*cib#!q}AS$}Rc
b{KkqnnPf#?lTkQ3sQSrd3A6BwlDGCX5v
zILHk|G7O9xfaZhU{cbbE@5co!#zn>q_cj6%`#y69p!r}B$-uxkfq`KnLjVIO0|-en
cFtCCo0RO`}fO>33+W-In07*qoM6N<$f4?w
zg!SnW#})S18c+C{r`K$KIF+qb;q$@zw(>WeJnoKK(~Lw4Y94qqY_brRF#90&!J1)a
zjrb2H3!Wof4qSTD#v8U>XK9!*hshyH>P${?+kbyD18VLvuIUB
z3l$#}D{+OQMYQNcsJ__v1AWmXFAB;c3w`iGNpFLOl(^ezW3d&Rc+R=Avom*hHVH=Y
zz~0O~_dDnN=G(h>Ccu`)om<;(e=~9OKkkr;%HWvQ5HWCvFLi$l0nQwn9BC_x7%L*s=c<8H6YLy(!9By+59Yg1aJlOaCf#ix0
z3T|Oo=Xemgp~CUp+Pi~Af6-9!$>0p2O?4K~Hr<&w?65~MjLbk@oMB|sZb-NAA3FK0OyUci(keNG
zITWmU3}bS!-A!gA9HdEdG8nsKvDo1`o@l6OGP*$zdy#gLD7Gone~vQV&)ZKam(s~^
zbc$w)IlK+rP4$5tpTqHVp~JV{rMh@6RYu1^y*7QiXxbqN-H+qF7b5^#=u(+1*04BZ
zX_XwpY}oNQ=H=oj@T9?^b26BApj$a*(NNK3@^#)2vBL{Z>>$M8w?$6>pmQ{H1aM+C
zWXF|iH6OC0y)ejYe+2CILbX?-Y6vd~Cm?jP5rD(|PJi`RBz_*#Dg$Q2jS@
zY)9toXWS}N2JP>l*7`mA3?jTBq@P6Ja0HO}Q11?YmS58V*iGJ6_3V9()G71+_6rw&pmM`^n&WY$MG
z;D&0gUDCB?3ZET<;C>R`HhFQlRJ-xR`s~<2Zv#DAC6@_v9Tl;o*G-NZ96Be1wj)%?
zc8G?GCX=Hye|?S+J7;E(!+yiV(wV@H-OI1QS-Dii^2`wzU8T~T%s$vh51gNtuT5jy
z9umE4nw~6lv2=zHLjE!{rSCm%buve9AyQi^l~PaOc0Nm;@BH>mBna+D06d>O6+4)%64_qZ7L&YdZe_rQgV7ZaPKPQh)um%*N@O1TaS?83{1OWRwJ+uG-

diff --git a/docs/html/img86.png b/docs/html/img86.png
index f110f1aaa4e6923f001a24c6f1a612529e557925..ff0dce4a6e8d3ffda29a2fc6f8ebc51984d5560f 100644
GIT binary patch
delta 411
zcmV;M0c8HV0kQ)niBL{Q4GJ0x0000DNk~Le0001D0000W1Oos702>>yS^xk5Fp(u9
ze+&!^W@csp001*HGmVXnSy@?$hjTOl0004WQchC+O9}6>(d^!2SeITViQB|oJNE;g)_xAQC
z&Y!pv$YCrA@(X5gcy=QV$Z_;^aSY*@nVjIj{BWtlq??VYOcRp09|ST4ZI+M_V_F%^
z!;{@GMYP4L)ydUxL(`N3|Aah-pgGdYOb*9R$Rs2HjmY9Enp4+5*yG2>lhd;8RAjJSU)f@C^PUsKoR7h03sP1Pz0GE)I~5^{({bxEU@pd||L>U@+o@V`^u3%kY$;nK7LKXi>W`)FK96V*`eW@}nRp{RVpS
zD#T?IftWLafn@>%P&eZRcu*7o?PYZU`wQ+(j*lSY_koy50rCzMYW&!OZlnPKTIw{0
TvLhH~00000NkvXXu0mjf>JfPt|9MLzZb>jyZ8`2s^c1K-{YC@O%0|KJ?{4-7wn
zB&rIapah)5^ngJDLj_QfR{+E)|G@P?hJo_}OhpCAiGIc38DxMW20#wq%L^<8whVk9
zkX4v|5_ra73sebmDj)v`z6bw7f0iQI@}M0k|DOS@kAZBPTL2h%zvEA_oO41A`z)P!?G*gaHfqhs@!AfT;i}BIZEgE2au=
eOrcRQNB{t7z)Q)n;iX*w0000SF^9<^N$N~aaoc}`wEbV$B__YuEUk6mv0!HR@L`yl
Ytrn{`|KdiV0~kDA{an^DJ0&y$0QBoP&j0`b

delta 417
zcmV;S0bc&@0pSB7iBL{Q4GJ0x0000DNk~Le0000`0000W1Oos70CyeYUy&h8e*s@f
zL_t(IjbmUKiog_8h#O3@-eF*{1kw>l!CdwS42%UR%3=?&egHFU85op-6lVgM7tg@A
z_X3JS<_iq}z>NP;^Bus{PX-2lRE7K>7$m?9JqVuzVxa$1CzBfc(Jy
z0qg`mpexcDwlGX!djN6}!fHN_0-#TTegJ6)Ie{yH^B_Yz1K1K|g+K`)Uk|EKhLypH
z6KKQI2@JIi0n8{0r!jDaG9CzkSpAlpp3D!km6qelxt^*wPU>w44wc`@B}b$0^>!1l_8K}0t165
zau5bEFbXh;GBC(8V1f`VV$di=1>6rX#h{4-4SdC-8JoIMFl+$;eDYh=s>x*(00000
LNkvXXu0mjfvTK`d

diff --git a/docs/html/img89.png b/docs/html/img89.png
index 79daf7977a2479dc269373bb350b4608f4f01513..17e67867f65da71fb2bbdccd8511733de492d700 100644
GIT binary patch
delta 224
zcmcc0_?pqBGr-TCmrII^fq{Y7)59eQNJ|5;91Am$)HkoV3Zx7Id_r6g95}Ff^JXN){Iv+uPeubQG=cY%eweDrGDQ@(X5gcy=QV$jS6{aSV}|nw+4(
zyI~r8L*_9igVaM0I2Zl+7ROK=EGgHRS!Xc)GXrx!L(^&YCw2}6GXrCE|D~$
zCuzsYgo7XC4$jrSb?QSp6Z8G$UlY;|_c2QuFdn`8X2rc3?u)jwi_LLlW52M2p-`C9
W_)6@bO{G9v89ZJ6T-G@yGywo!kWgj-

literal 213
zcmeAS@N?(olHy`uVBq!ia0vp^LO{&V!VDy(S2QUCDct~{5Z40-4s71MSxrr?p`pRY
z$7k8HWs;JT#l^)lXU^o|;YmwN11dB&Hty~1jf{+J=HWdBA81_n=8KbLh*
G2~7ZP7eU?t

diff --git a/docs/html/img90.png b/docs/html/img90.png
index 23d1fd06ae8c5336507b5e721b7c1e14b7f3198c..f110f1aaa4e6923f001a24c6f1a612529e557925 100644
GIT binary patch
delta 161
zcmbQwvWro*Gr-TCmrII^fq{Y7)59eQNb>+O9}6>(d^!2SeITViQB|oJNE;g)_xAQC
z&Y!pv$YCrA@(X5gcy=QV$Z_;^aSY*@nVjIj{BWtlq??VYOcRp09|ST4ZI+M_V_F%^
z!;{@GMYP4L)ydUxL(`N3|Aah-pgGdYOb*9R$Rs2HjmY9;El@Kgywc5AzMs-tx6;4Lcr1F;^u#u7*d
zr5n{z?9I+ft7g{@`Cw<>``&!>=6y2@fBZL-R2nXarq_0Vg!hT4XNK;X^y$J|wOp{D
z0&kp|Ls(;~5)-5aH_Ys>+q-2c1%Cq6qT0oPSw;T+0Y?73jP_p$le{uu0
zl%U2Qn5CEQ7#?I;)2|WE;;gM_{k<~N2D00000
LNkvXXu0mjfu(9L*

diff --git a/docs/html/img91.png b/docs/html/img91.png
index b7f166e98ae5cedbf5dc4528e630f0cc068fe874..68a5bd7a5cc0bcfe40765ab95333f441964bf416 100644
GIT binary patch
delta 332
zcmV-S0ki&^0*nJ8iBL{Q4GJ0x0000DNk~Le0000&0000W1Oos708~b^ijg5pe*p?f
zL_t(IjbmUKbifo-h#SF-J;1>JfPt|9MLzZb>jyZ8`2s^c1K-{YC@O%0|KJ?{4-7wn
zB&rIapah)5^ngJDLj_QfR{+E)|G@P?hJo_}OhpCAiGIc38DxMW20#wq%L^<8whVk9
zkX4v|5_ra73sebmDj)v`z6bw7f0iQI@}M0k|DOS@kAZBPTL2h%zvEA_oO41A`z)P!?G*gaHfqhs@!AfT;i}BIZEgE2au=
eOrcRQNB{t7z)Q)n;iX*w00004`3|7CBwJ(0=iHsjKPl~CEtfCwdJ{e0ed~eIoh^Y=CHL7eICf!y|6K
z3w!}cR>7p&8Di}iE*pcG(#}v*FF&mZn;*cyD8Rr8Hm43(@QecLgEP3m0X$LwtgufW
TAIG+o00000NkvXXu0mjfm~~Q!

diff --git a/docs/html/img92.png b/docs/html/img92.png
index 448dd74a369fe97a2c715e2961577e9ffceadc51..f47c909318b84edeac01982eb49e1073a623011a 100644
GIT binary patch
delta 416
zcmV;R0bl;01K|T9iBL{Q4GJ0x0000DNk~Le0000`0000W1Oos70CyeYUy&h9e_u&N
zK~y-6V_+DHz!X!68%(m^VPLQX(h*0&T=oYHj0GslVh^x>05fbE7?gn&X9AcP&%n3$
z0*XTB3k?6jjQ>#c9l+F21_pjqh5R2FB)|+k2%iIDp#p|NrUwkX0zjJa07Ll)2F~wR
z0n!zZuX0|1Dr9c}5?h|z7cj^Ge?<(yPT+fafnkz>8N&wN51D))kQ6e;yibE7BRZFic>30CEt*YCetvpih8)0BHv~fh&OXAVWI?*b-!gKnWmU52{dxmBEM;
zXv5M847Cga%qR+{F>r-49teO~{g#`dU6}I%UqW$%Kf?#OXTXMRVR*#Nc6VU|#51vV
z48J!pIGZb5H|rZ$z>D(0000<
KMNUMnLSTX|u$v$N

delta 351
zcmV-l0igcj1E2#TiBL{Q4GJ0x0000DNk~Le000180000W1Oos70D|Lb?~x%)e;!Fh
zK~y-6V_+Eiz?4XJ8z2<>1BUQYf{Mi%7~&zUcm`$%mI(xuzrM@B!2bZu{K>!;z^6dS
z{J#tgj16Fx0>c~zhJ!??XSfJra9&_|!@zJ3S&rMU_&Wo?d$A*$`p+N+-vr
z#`FpMJ3=CJnOiu;|xd$lDXJudzWZ()7U_b?o5c@(Hu!3nAH6qaT!2JM2
x1_=1t3ebh1>5btlb_+1T1|rpsf>D4A008IaSV^O|XjcFL002ovPDHLkV1h>Hj`{!q

diff --git a/docs/html/img93.png b/docs/html/img93.png
index 619cdc20c36c9f1dda53af67f01bf2c4e8daadf7..79daf7977a2479dc269373bb350b4608f4f01513 100644
GIT binary patch
literal 213
zcmeAS@N?(olHy`uVBq!ia0vp^LO{&V!VDy(S2QUCDct~{5Z40-4s71MSxrr?p`pRY
z$7k8HWs;JT#l^)lXU^o|;YmwN11dB&Hty~1jf{+J=HWdBA81_n=8KbLh*
G2~7ZP7eU?t

literal 347
zcmeAS@N?(olHy`uVBq!ia0vp^PC%@{!VDxs+%|UsDct~{5Z40-4ydWAH8eE%`1mYa
zwoFn|vbea|-rj!Z%$YnqJZWiZn>TMZHa70666=m;PC858jy3x
z)5S5wqBl7~!lvOQ<8&VJDd$oXZnVX+o@SOPea*w?e6PuK9~)bnxkX40`{W*;9ibm`
z7$(}z&=QNk?ES#ldsEtjV1~l?i7OI5O@79^<5QdB%tr1vSIQ-{DsBqT;ET~;1ue*b?`g-}
zcAAB)ZMwj!o`dew_i9u!Gxsxluog4B8CVz;Nw`njxgN@xNAVV`|6

diff --git a/docs/html/img94.png b/docs/html/img94.png
index 656e70682e1d7cdd4b8772cd14b1ef7662ebab7c..23d1fd06ae8c5336507b5e721b7c1e14b7f3198c 100644
GIT binary patch
delta 480
zcmV<60U!Q|0-ppSiBL{Q4GJ0x0000DNk~Le0001L0000W1Oos700_+Ru8|>2e*v9I
zL_t(IjqOuGO9DX@{&Y2U#T|b^*rB^n&?Qo#C%s6r*cQ{WxW7*
zG&SBt_>rHE<}KMg2LcDcyCBVTX;67eXl!vOMeeN4Vv~ZTWQ@Sdv*FWPK$Doa91L}A
zl9ZWHvh_A{1GSW(#vYiZm>qzBEsmW;yE(})i)eqd(E7Afvg#|yY5>GQe_61kWx=8x
zvj|)wcLV;aOT!Xmt%NWVv^u7X6LyPHE*;9^g4~EMIr3)seO+S@uc(813U0?8H5AcU
z1&`sd5ioeGwRP1c>G4bok*PRWo?QX=aEVyN=3MYFXBQqf-4{_#({Kv#2cyGdI52-I
zP~nNnX;%%YLq-`owzDkBHpjsiRdNUZCK+wt*yyaT#e*lI_
zL_t&-m1AI_J>d2${yy7+fkA%zW+2b>lfW|r-Ukeq8PtKi2ki_-3~UqF6Bv$ylrClX
z&oGUF;{#s;ki(h4pv>@}lh=UX0c45;<3WbZnH&aU1wbB00iOcHy$!7GH32{#D+7Z7
z11FF%4ar(_pjimeFZ}_D$M=+$9UdkJoIwVtJOCq_F!z&M`xXEI002ovPDHLkV1f>*
BNb3Lq

diff --git a/docs/html/img95.png b/docs/html/img95.png
index 64a226104322935b9424a773601b169af88e6b51..b7f166e98ae5cedbf5dc4528e630f0cc068fe874 100644
GIT binary patch
delta 216
zcmV;}04M+b0-6FLiBL{Q4GJ0x0000DNk~Le0000p0000U1Oos70CT-N@sS}+f0#)`
zK~yM_V_={UU@X8T!?*VWx=<;M!H*#&--jx-<+*(Udp*NCu$&*V6mz^HU&6b&4DMht
z_UlMed>jSL7asg)c*lSw2Q`o@fd2!-QU<7V`TCKhrZI4ZawafrfM{wLKz0VhBW}J6
zd;v&S!KB(5V(l0%8-tkA&QMc7F0BWfAHcvUz`zMMrw&)}i~{O|Gq}J3JW>FxuumQz
S$F`IJ0000u63_&4L!2bajEe!i`DB}3IA0ELB{J4_Jy8uK|83jWV007z>5<{NzgcIoi
O00001BUQYf{Mi%7~&zUcm`$%mI(xuzrM@B!2bZu{K>!;z^6dS{J#tgj16Fx0>c~z
zhJ!??XSfJra9&_|!@zJ3S&rMU_&Wo?d$A*$`p+N+-v!~6&B47MNwsAk?fAb_cVk3&7fQilH^!ULOn<_`=p46G>r#`FpMJ
z3=CJnOiu;|xd$lDNoQqX5M5btl
lb_+1T1|rpsf>D4A008IaSV^O|XjcFL002ovPDHLkV1jh)oCp8_

delta 148
zcmZ3$yq;0NGr-TCmrII^fq{Y7)59eQNb>+O9}6>(d^!2SeITV3;1l9{;J^VjHMNPR
zDlra4ZLff$j3q&S!3+-1ZlnP@#-1*YAsjQ46Ati2bel=1Gr-TCmrII^fq{Y7)59eQNILeEtK71#Fg8E&
zK8Ci;fanB0)|LC&7m69jJb7ewpp4;F(1QH;o_5S_r&-wArVFg<
za`iwFV`Jmq-rmT_$jC_ViHLyu{>Hn>%*!lZ
z%NiVgd-}i!(b;y<9baZMu<6W_l=$bo5x_}jJL*g%e9v$?^#
zH1ULr`}{_HEOG`0GwOsYjvc6BR66^icXoYa?_(7hx{A~cba*EuvRXGcHvUv#KCCRV-138FPQ__nuG#Si
z6fzqsg}5xZBJ}M$);bIA?9t&h37gPp$e<`tAIA`VqNnK~8^g6v=DcFZxB`J*WAJqK
LV|7{Ql+XkKpWSYo

diff --git a/docs/html/img98.png b/docs/html/img98.png
index 01d4adf86a28ba38bbaeda453eaa6b8d20124d34..656e70682e1d7cdd4b8772cd14b1ef7662ebab7c 100644
GIT binary patch
delta 199
zcmV;&0672V1Be14iBL{Q4GJ0x0000DNk~Le0000Q0000U1Oos70KoMV>yaT#e*lI_
zL_t&-m1AI_J>d2${yy7+fkA%zW+2b>lfW|r-Ukeq8PtKi2ki_-3~UqF6Bv$ylrClX
z&oGUF;{#s;ki(h4pv>@}lh=UX0c45;<3WbZnH&aU1wbB00iOcHy$!7GH32{#D+7Z7
z11FF%4ar(_pjimeFZ}_D$M=+$9UdkJoIwVtJOCq_F!z&M`xXEI002ovPDHLkV1h*y
BNihHb

delta 422
zcmV;X0a^Zt0_FoDiBL{Q4GJ0x0000DNk~Le0000?0000W1Oos707{R8Iguete*t7k
zL_t(IjqQ@ZOT$1E$G%{4R^aB)zmbeCZLK?gD50lz|P^qD`H=8c&a%20~Q=}EeO
ztHK%3NLj&=;Xt}iwLNnvgUG05e@y9JuJhk&@^Fe({?0~f$
z+?=@R0;h>$&s|*D>#!2xV9I_?En-WWj~7_ONU?Z?Biw-}!ij8BlP9x*>0$(nxMDr_
zh>l1@FH1uqzOs#g(opsk)2i1#dZCt(3)7-lzyRfaYym4wF{9OpEI*(ld>Ac<+Lixq
zQul+BI6`Mm9f99td!y#ig^)wV<4*)fDAteb;zB<9#6*D*%+`S&;jjn{i7f-?@KB^Z
z$#U(=l?D@lH+{u)H)XlZSPhZI*t-l<_>c~ELa)dkjUJDO>Pu63_&4L!2bajEe!i`DB}3IA0ELB{J4_Jy8uK|83jWV007z>5<{NzgcIoi
O00006#$Xt9~kBr
zJ21=zv-k~wB783|a4Iq^^YMRRE8uou_zz++@PV!53Ya6nQ2-PIvY~
 
  • psb_amn -- Global minimum absolute value
  • psb_snd -- Send data + HREF="node114.html">psb_nrm2 -- Global 2-norm reduction
  • psb_rcv -- Receive data + HREF="node115.html">psb_snd -- Send data +
  • psb_rcv -- Receive data
    -
  • Error handling
  • Utilities -
  • @@ -139,7 +139,7 @@ Specified as: an integer variable.
  • It is an error to specify a value for $np$ greater than the number of processes available in the underlying base parallel environment. @@ -150,26 +150,26 @@ Specified as: an integer variable. diff --git a/docs/html/node101.html b/docs/html/node101.html index dfd0a604..5b1d6453 100644 --- a/docs/html/node101.html +++ b/docs/html/node101.html @@ -23,26 +23,26 @@ @@ -101,7 +101,7 @@ Specified as: an integer value. $-1 \le iam \le np-1$
    np
    Number of processes in the PSBLAS virtual parallel machine. @@ -125,14 +125,14 @@ Specified as: an integer variable.
    --> $0 \le iam \le np-1$;
  • If the user has requested on psb_init a number of processes less than the total available in the parallel execution environment, the remaining processes will have on return $iam=-1$; the only call involving icontxt that any such process may execute is to psb_exit. diff --git a/docs/html/node102.html b/docs/html/node102.html index 5f8dc244..a47b5306 100644 --- a/docs/html/node102.html +++ b/docs/html/node102.html @@ -23,26 +23,26 @@ @@ -101,7 +101,7 @@ Specified as: a logical variable, default value: true.
  • This routine may be called even if a previous call to psb_info has returned with $iam=-1$; indeed, it it is the only routine that may be called with argument icontxt in this situation. @@ -122,26 +122,26 @@ Specified as: a logical variable, default value: true. diff --git a/docs/html/node103.html b/docs/html/node103.html index 4dc35680..cfea712f 100644 --- a/docs/html/node103.html +++ b/docs/html/node103.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node104.html b/docs/html/node104.html index d63914d6..0598f739 100644 --- a/docs/html/node104.html +++ b/docs/html/node104.html @@ -23,26 +23,26 @@ @@ -60,7 +60,7 @@ call psb_get_rank(rank, icontxt, id)

    This subroutine returns the MPI rank of the PSBLAS process $id$

    Type:
    @@ -95,7 +95,7 @@ Specified as: an integer value. $0 \le id \le np-1$
    @@ -107,7 +107,7 @@ Specified as: an integer value. - next - up - previous - contents
    - Next: Next: psb_barrier Sinchronization - Up: Up: Parallel environment routines - Previous: Previous: psb_get_rank Get -   Contents

    diff --git a/docs/html/node106.html b/docs/html/node106.html index e3f33617..b3fa7726 100644 --- a/docs/html/node106.html +++ b/docs/html/node106.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node107.html b/docs/html/node107.html index 4ed9556c..38a9b41c 100644 --- a/docs/html/node107.html +++ b/docs/html/node107.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node108.html b/docs/html/node108.html index 6c4c6cf1..08c7ae18 100644 --- a/docs/html/node108.html +++ b/docs/html/node108.html @@ -23,26 +23,26 @@ @@ -106,7 +106,7 @@ Specified as: an integer value $0<= root <= np-1$, default 0 diff --git a/docs/html/node109.html b/docs/html/node109.html index 551dbe87..4db84594 100644 --- a/docs/html/node109.html +++ b/docs/html/node109.html @@ -23,26 +23,26 @@ @@ -94,7 +94,7 @@ scalar, or a rank 1 or 2 array. Type, kind, rank and size must agree on all pro
    root
    Process to hold the final sum, or $-1$ to make it available on all processes.
    @@ -109,7 +109,7 @@ Specified as: an integer value $-1<= root <= np-1$, default -1.
    @@ -150,26 +150,26 @@ Type, kind, rank and size must agree on all processes. diff --git a/docs/html/node11.html b/docs/html/node11.html index 45baf9c6..4b9ac393 100644 --- a/docs/html/node11.html +++ b/docs/html/node11.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node110.html b/docs/html/node110.html index 1b4376d1..38ebc06e 100644 --- a/docs/html/node110.html +++ b/docs/html/node110.html @@ -23,26 +23,26 @@ @@ -94,7 +94,7 @@ scalar, or a rank 1 or 2 array. Type, kind, rank and size must agree on all pro
    root
    Process to hold the final maximum, or $-1$ to make it available on all processes.
    @@ -109,7 +109,7 @@ Specified as: an integer value $-1<= root <= np-1$, default -1.
    @@ -149,26 +149,26 @@ scalar, or a rank 1 or 2 array. Type, kind, rank and size must agree on all pro diff --git a/docs/html/node111.html b/docs/html/node111.html index e02d317b..7d6b75e5 100644 --- a/docs/html/node111.html +++ b/docs/html/node111.html @@ -23,26 +23,26 @@ @@ -94,7 +94,7 @@ scalar, or a rank 1 or 2 array. Type, kind, rank and size must agree on all pro
    root
    Process to hold the final value, or $-1$ to make it available on all processes.
    @@ -109,7 +109,7 @@ Specified as: an integer value $-1<= root <= np-1$, default -1.
    @@ -151,26 +151,26 @@ Type, kind, rank and size must agree on all processes. diff --git a/docs/html/node112.html b/docs/html/node112.html index ac2d00ad..1caffe50 100644 --- a/docs/html/node112.html +++ b/docs/html/node112.html @@ -23,26 +23,26 @@ @@ -94,7 +94,7 @@ scalar, or a rank 1 or 2 array. Type, kind, rank and size must agree on all pro
    root
    Process to hold the final value, or $-1$ to make it available on all processes.
    @@ -109,7 +109,7 @@ Specified as: an integer value $-1<= root <= np-1$, default -1.
    @@ -149,26 +149,26 @@ scalar, or a rank 1 or 2 array. Type, kind, rank and size must agree on all pro diff --git a/docs/html/node113.html b/docs/html/node113.html index fa016fed..ed8dd494 100644 --- a/docs/html/node113.html +++ b/docs/html/node113.html @@ -23,26 +23,26 @@ @@ -94,7 +94,7 @@ scalar, or a rank 1 or 2 array. Type, kind, rank and size must agree on all pro
    root
    Process to hold the final value, or $-1$ to make it available on all processes.
    @@ -109,7 +109,7 @@ Specified as: an integer value $-1<= root <= np-1$, default -1.
    @@ -151,26 +151,26 @@ Type, kind, rank and size must agree on all processes. diff --git a/docs/html/node114.html b/docs/html/node114.html index efbd8b82..8705ed4b 100644 --- a/docs/html/node114.html +++ b/docs/html/node114.html @@ -3,8 +3,8 @@ -psb_snd -- Send data - +psb_nrm2 -- Global 2-norm reduction + @@ -23,45 +23,46 @@

    -psb_snd -- Send data +psb_nrm2 -- Global 2-norm reduction

    -call psb_snd(icontxt, dat, dst, m)
    +call psb_nrm2(icontxt, dat, root)
     

    -This subroutine sends a packet of data to a destination. +This subroutine implements a 2-norm value reduction +operation based on the underlying communication library.

    Type:
    -
    Synchronous: see usage notes. +
    Synchronous.
    On Entry
    @@ -79,65 +80,38 @@ Intent: in. Specified as: an integer variable.
    dat
    -
    The data to be sent. +
    The local contribution to the global minimum.
    Scope: local.
    Type: required.
    -Intent: in. +Intent: inout.
    -Specified as: an integer, real or complex variable, which may be a -scalar, or a rank 1 or 2 array, or a character or logical scalar. Type, kind and rank must agree on sender and receiver process; if $m$ is -not specified, size must agree as well. +Specified as: a real variable, which may be a +scalar, or a rank 1 array. Kind, rank and size must agree on all processes.
    -
    dst
    -
    Destination process. -
    -Scope: global. -
    -Type: required. -
    -Intent: in. -
    -Specified as: an integer value -$0<= dst <= np-1$. -
    -
    m
    -
    Number of rows. +
    root
    +
    Process to hold the final value, or $-1$ to make it available + on all processes.
    Scope: global.
    -Type: Optional. +Type: optional.
    Intent: in.
    Specified as: an integer value $0<= m <= size(dat,1)$. -
    -When $dat$ is a rank 2 array, specifies the number of rows to be sent -independently of the leading dimension $size(dat,1)$; must have the -same value on sending and receiving processes. -
    + ALT="$-1<= root <= np-1$">, default -1. +

    @@ -145,17 +119,57 @@ same value on sending and receiving processes.

    On Return
    +
    dat
    +
    On destination process(es), the result of the 2-norm reduction. +
    +Scope: global. +
    +Type: required. +
    +Intent: inout. +
    +Specified as: a real variable, which may be a +scalar, or a rank 1 array. +
    +Kind, rank and size must agree on all processes. +

    Notes

      -
    1. This subroutine implies a synchronization, but only between the - calling process and the destination process This reduction is appropriate to compute the results of multiple + (local) NRM2 operations at the same time. +
    2. +
    3. Denoting by the value of the variable $dst$. + ALT="$dat$"> on process + $i$, the output $res$ is equivalent to the computation of +

      +
      + + + +
      +
      +

      +with care taken to avoid unnecessary overflow. +
    4. +
    5. The dat argument is both input and output, and its + value may be changed even on processes different from the final + result destination.
    @@ -163,26 +177,26 @@ same value on sending and receiving processes. diff --git a/docs/html/node115.html b/docs/html/node115.html index fe5ecb79..6cec0e29 100644 --- a/docs/html/node115.html +++ b/docs/html/node115.html @@ -3,8 +3,8 @@ -psb_rcv -- Receive data - +psb_snd -- Send data + @@ -14,6 +14,7 @@ + @@ -22,45 +23,45 @@

    -psb_rcv -- Receive data +psb_snd -- Send data

    -call psb_rcv(icontxt, dat, src, m)
    +call psb_snd(icontxt, dat, dst, m)
     

    -This subroutine receives a packet of data to a destination. +This subroutine sends a packet of data to a destination.

    Type:
    -
    Synchronous: see usage notes. +
    Synchronous: see usage notes.
    On Entry
    @@ -77,8 +78,24 @@ Intent: in.
    Specified as: an integer variable.
    -
    src
    -
    Source process. +
    dat
    +
    The data to be sent. +
    +Scope: local. +
    +Type: required. +
    +Intent: in. +
    +Specified as: an integer, real or complex variable, which may be a +scalar, or a rank 1 or 2 array, or a character or logical scalar. Type, kind and rank must agree on sender and receiver process; if $m$ is +not specified, size must agree as well. +
    +
    dst
    +
    Destination process.
    Scope: global.
    @@ -87,12 +104,12 @@ Type: required. Intent: in.
    Specified as: an integer value $0<= src <= np-1$. + WIDTH="145" HEIGHT="30" ALIGN="MIDDLE" BORDER="0" + SRC="img141.png" + ALT="$0<= dst <= np-1$">.
    m
    Number of rows. @@ -108,16 +125,16 @@ Specified as: an integer value $0<= m <= size(dat,1)$.
    When $dat$ is a rank 2 array, specifies the number of rows to be sent independently of the leading dimension $size(dat,1)$; must have the same value on sending and receiving processes.
    @@ -128,22 +145,6 @@ same value on sending and receiving processes.
    On Return
    -
    dat
    -
    The data to be received. -
    -Scope: local. -
    -Type: required. -
    -Intent: inout. -
    -Specified as: an integer, real or complex variable, which may be a -scalar, or a rank 1 or 2 array, or a character or logical scalar. Type, kind and rank must agree on sender and receiver process; if $m$ is -not specified, size must agree as well. -

    @@ -151,10 +152,10 @@ not specified, size must agree as well.

    1. This subroutine implies a synchronization, but only between the - calling process and the source process $src$. + calling process and the destination process $dst$.
    @@ -162,26 +163,26 @@ not specified, size must agree as well. diff --git a/docs/html/node116.html b/docs/html/node116.html index 722847c9..36fffd05 100644 --- a/docs/html/node116.html +++ b/docs/html/node116.html @@ -3,8 +3,8 @@ -Error handling - +psb_rcv -- Receive data + @@ -14,327 +14,174 @@ - - - + + -

    -Error handling -

    - -

    -The PSBLAS library error handling policy has been completely rewritten -in version 2.0. The idea behind the design of this new error handling -strategy is to keep error messages on a stack allowing the user to -trace back up to the point where the first error message has been -generated. Every routine in the PSBLAS-2.0 library has, as last -non-optional argument, an integer info variable; whenever, -inside the routine, an error is detected, this variable is set to a -value corresponding to a specific error code. Then this error code is -also pushed on the error stack and then either control is returned to -the caller routine or the execution is aborted, depending on the users -choice. At the time when the execution is aborted, an error message is -printed on standard output with a level of verbosity than can be -chosen by the user. If the execution is not aborted, then, the caller -routine checks the value returned in the info variable and, if -not zero, an error condition is raised. This process continues on all the -levels of nested calls until the level where the user decides to abort -the program execution. - -

    -Figure 9 shows the layout of a generic psb_foo -routine with respect to the PSBLAS-2.0 error handling policy. It is -possible to see how, whenever an error condition is detected, the -info variable is set to the corresponding error code which is, -then, pushed on top of the stack by means of the -psb_errpush. An error condition may be directly detected inside -a routine or indirectly checking the error code returned returned by a -called routine. Whenever an error is encountered, after it has been -pushed on stack, the program execution skips to a point where the -error condition is handled; the error condition is handled either by -returning control to the caller routine or by calling the -psb\_error routine which prints the content of the error stack -and aborts the program execution, according to the choice made by the -user with psb_set_erraction. The default is to print the error -and terminate the program, but the user may choose to handle the error -explicitly. - -

    - -

    - - - -
    Figure 9: -The layout of a generic psb_foo - routine with respect to PSBLAS-2.0 error handling policy.
    -
    - -
    - -\fbox{\TheSbox} -
    -
    - -

    -Figure 10 reports a sample error message generated by -the PSBLAS-2.0 library. This error has been generated by the fact that -the user has chosen the invalid “FOO” storage format to represent -the sparse matrix. From this error message it is possible to see that -the error has been detected inside the psb_cest subroutine -called by psb_spasb ... by process 0 (i.e. the root process). - -

    - -

    - - - -
    Figure 10: -A sample PSBLAS-2.0 error - message. Process 0 detected an error condition inside the psb_cest subroutine
    -
    - -
    - -\fbox{\TheSbox} -
    -
    - -

    -ifstarsubroutinesubroutinepsb_errpushPushes an error code onto the error - stack +

    +psb_rcv -- Receive data +

    -
    -\begin{lstlisting}
-call psb_errpush(err_c, r_name, i_err, a_err)
-\end{lstlisting} -
    +

    +call psb_rcv(icontxt, dat, src, m)
    +

    +This subroutine receives a packet of data to a destination.

    Type:
    -
    Asynchronous. +
    Synchronous: see usage notes.
    -
    On Entry
    +
    On Entry
    -
    err_c
    -
    the error code +
    icontxt
    +
    the communication context identifying the virtual + parallel machine.
    -Scope: local +Scope: global.
    -Type: required +Type: required.
    Intent: in.
    -Specified as: an integer. +Specified as: an integer variable.
    -
    r_name
    -
    the soutine where the error has been caught. +
    src
    +
    Source process.
    -Scope: local +Scope: global.
    -Type: required +Type: required.
    Intent: in.
    -Specified as: a string. -
    -
    i_err
    -
    addional info for error code -
    -Scope: local -
    -Type: optional -
    -Specified as: an integer array -
    -
    a_err
    -
    addional info for error code -
    -Scope: local -
    -Type: optional -
    -Specified as: a string. -
    -
    - -

    -ifstarsubroutinesubroutinepsb_errorPrints the error stack content and aborts - execution - -

    -
    - +\begin{lstlisting}
-call psb_error(icontxt)
-\end{lstlisting} -
    - -

    -

    -
    Type:
    -
    Asynchronous. -
    -
    On Entry
    -
    -
    -
    icontxt
    -
    the communication context. + ALT="$0<= src <= np-1$">. +
    +
    m
    +
    Number of rows.
    -Scope: global +Scope: global.
    -Type: optional +Type: Optional.
    Intent: in.
    -Specified as: an integer. +Specified as: an integer value +$0<= m <= size(dat,1)$. +
    +When $dat$ is a rank 2 array, specifies the number of rows to be sent +independently of the leading dimension $size(dat,1)$; must have the +same value on sending and receiving processes.
    -

    -ifstarsubroutinesubroutinepsb_set_errverbositySets the verbosity of error - messages. - -

    -
    -\begin{lstlisting}
-call psb_set_errverbosity(v)
-\end{lstlisting} -
    -

    -
    Type:
    -
    Asynchronous. -
    -
    On Entry
    +
    On Return
    -
    v
    -
    the verbosity level +
    dat
    +
    The data to be received.
    -Scope: global +Scope: local.
    -Type: required +Type: required.
    -Intent: in. +Intent: inout.
    -Specified as: an integer. +Specified as: an integer, real or complex variable, which may be a +scalar, or a rank 1 or 2 array, or a character or logical scalar. Type, kind and rank must agree on sender and receiver process; if $m$ is +not specified, size must agree as well.

    -ifstarsubroutinesubroutinepsb_set_erractionSet the type of action to be - taken upon error condition. - -

    -
    -\begin{lstlisting}
-call psb_set_erraction(err_act)
-\end{lstlisting} -
    +Notes -

    -

    -
    Type:
    -
    Asynchronous. -
    -
    On Entry
    -
    -
    -
    err_act
    -
    the type of action. -
    -Scope: global -
    -Type: required -
    -Intent: in. -
    -Specified as: an integer. Possible values: psb_act_ret, -psb_act_abort. -
    -
    +
      +
    1. This subroutine implies a synchronization, but only between the + calling process and the source process $src$. +
    2. +

    diff --git a/docs/html/node117.html b/docs/html/node117.html index 6d648c85..0372bfcb 100644 --- a/docs/html/node117.html +++ b/docs/html/node117.html @@ -3,8 +3,8 @@ -Utilities - +Error handling + @@ -14,8 +14,8 @@ - - + + @@ -23,69 +23,320 @@ -

    - -
    -Utilities +

    +Error handling

    -We have some utilities available for input and output of -sparse matrices; the interfaces to these routines are available in the -module psb_util_mod. - -

    -


    - -Subsections - - - -

    +The PSBLAS library error handling policy has been completely rewritten +in version 2.0. The idea behind the design of this new error handling +strategy is to keep error messages on a stack allowing the user to +trace back up to the point where the first error message has been +generated. Every routine in the PSBLAS-2.0 library has, as last +non-optional argument, an integer info variable; whenever, +inside the routine, an error is detected, this variable is set to a +value corresponding to a specific error code. Then this error code is +also pushed on the error stack and then either control is returned to +the caller routine or the execution is aborted, depending on the users +choice. At the time when the execution is aborted, an error message is +printed on standard output with a level of verbosity than can be +chosen by the user. If the execution is not aborted, then, the caller +routine checks the value returned in the info variable and, if +not zero, an error condition is raised. This process continues on all the +levels of nested calls until the level where the user decides to abort +the program execution. + +

    +Figure 9 shows the layout of a generic psb_foo +routine with respect to the PSBLAS-2.0 error handling policy. It is +possible to see how, whenever an error condition is detected, the +info variable is set to the corresponding error code which is, +then, pushed on top of the stack by means of the +psb_errpush. An error condition may be directly detected inside +a routine or indirectly checking the error code returned returned by a +called routine. Whenever an error is encountered, after it has been +pushed on stack, the program execution skips to a point where the +error condition is handled; the error condition is handled either by +returning control to the caller routine or by calling the +psb\_error routine which prints the content of the error stack +and aborts the program execution, according to the choice made by the +user with psb_set_erraction. The default is to print the error +and terminate the program, but the user may choose to handle the error +explicitly. + +

    + +

    + + + +
    Figure 9: +The layout of a generic psb_foo + routine with respect to PSBLAS-2.0 error handling policy.
    +
    + +
    + +\fbox{\TheSbox} +
    +
    + +

    +Figure 10 reports a sample error message generated by +the PSBLAS-2.0 library. This error has been generated by the fact that +the user has chosen the invalid “FOO” storage format to represent +the sparse matrix. From this error message it is possible to see that +the error has been detected inside the psb_cest subroutine +called by psb_spasb ... by process 0 (i.e. the root process). + +

    + +

    + + + +
    Figure 10: +A sample PSBLAS-2.0 error + message. Process 0 detected an error condition inside the psb_cest subroutine
    +
    + +
    + +\fbox{\TheSbox} +
    +
    + +

    +ifstarsubroutinesubroutinepsb_errpushPushes an error code onto the error + stack + +

    +
    +\begin{lstlisting}
+call psb_errpush(err_c, r_name, i_err, a_err)
+\end{lstlisting} +
    + +

    +

    +
    Type:
    +
    Asynchronous. +
    +
    On Entry
    +
    +
    +
    err_c
    +
    the error code +
    +Scope: local +
    +Type: required +
    +Intent: in. +
    +Specified as: an integer. +
    +
    r_name
    +
    the soutine where the error has been caught. +
    +Scope: local +
    +Type: required +
    +Intent: in. +
    +Specified as: a string. +
    +
    i_err
    +
    addional info for error code +
    +Scope: local +
    +Type: optional +
    +Specified as: an integer array +
    +
    a_err
    +
    addional info for error code +
    +Scope: local +
    +Type: optional +
    +Specified as: a string. +
    +
    + +

    +ifstarsubroutinesubroutinepsb_errorPrints the error stack content and aborts + execution + +

    +
    +\begin{lstlisting}
+call psb_error(icontxt)
+\end{lstlisting} +
    + +

    +

    +
    Type:
    +
    Asynchronous. +
    +
    On Entry
    +
    +
    +
    icontxt
    +
    the communication context. +
    +Scope: global +
    +Type: optional +
    +Intent: in. +
    +Specified as: an integer. +
    +
    + +

    +ifstarsubroutinesubroutinepsb_set_errverbositySets the verbosity of error + messages. + +

    +
    +\begin{lstlisting}
+call psb_set_errverbosity(v)
+\end{lstlisting} +
    + +

    +

    +
    Type:
    +
    Asynchronous. +
    +
    On Entry
    +
    +
    +
    v
    +
    the verbosity level +
    +Scope: global +
    +Type: required +
    +Intent: in. +
    +Specified as: an integer. +
    +
    + +

    +ifstarsubroutinesubroutinepsb_set_erractionSet the type of action to be + taken upon error condition. + +

    +
    +\begin{lstlisting}
+call psb_set_erraction(err_act)
+\end{lstlisting} +
    + +

    +

    +
    Type:
    +
    Asynchronous. +
    +
    On Entry
    +
    +
    +
    err_act
    +
    the type of action. +
    +Scope: global +
    +Type: required +
    +Intent: in. +
    +Specified as: an integer. Possible values: psb_act_ret, +psb_act_abort. +
    +
    + +

    + +

    + diff --git a/docs/html/node118.html b/docs/html/node118.html index 599c2e06..51ceff35 100644 --- a/docs/html/node118.html +++ b/docs/html/node118.html @@ -3,8 +3,8 @@ -hb_read -- Read a sparse matrix from a file in the Harwell-Boeing format - +Utilities + @@ -14,146 +14,78 @@ - + - + -

    - hb_read -- Read a sparse matrix from a file in the - Harwell-Boeing format -

    - -

    -
    -\begin{lstlisting}
-call hb_read(a, iret, iunit, filename, b, mtitle)
-\end{lstlisting} +

    +
    +Utilities +

    -

    -
    Type:
    -
    Asynchronous. -
    -
    On Entry
    -
    -
    -
    filename
    -
    The name of the file to be read. -
    -Type:optional. -
    -Specified as: a character variable containing a valid file name, or --, in which case the default input unit 5 (i.e. standard input -in Unix jargon) is used. Default: -. -
    -
    iunit
    -
    The Fortran file unit number. -
    -Type:optional. -
    -Specified as: an integer value. Only meaningful if filename is not -. -
    -
    - -

    -

    -
    On Return
    -
    -
    -
    a
    -
    the sparse matrix read from file. -
    -Type:required. -
    -Specified as: a structured data of type spdatapsb_Tspmat_type. -
    -
    b
    -
    Rigth hand side(s). -
    -Type: Optional -
    -An array of type real or complex, rank 2 and having the ALLOCATABLE -attribute; will be allocated and filled in if the input file contains -a right hand side, otherwise will be left in the UNALLOCATED state. -
    -
    mtitle
    -
    Matrix title. -
    -Type: Optional -
    -A charachter variable of length 72 holding a copy of the -matrix title as specified by the Harwell-Boeing format and contained -in the input file. -
    -
    iret
    -
    Error code. -
    -Type: required -
    -An integer value; 0 means no error has been detected. -
    -
    +We have some utilities available for input and output of +sparse matrices; the interfaces to these routines are available in the +module psb_util_mod.

    +


    + +Subsections - - + + +

    diff --git a/docs/html/node119.html b/docs/html/node119.html index cd4e702c..6610f191 100644 --- a/docs/html/node119.html +++ b/docs/html/node119.html @@ -3,8 +3,8 @@ -hb_write -- Write a sparse matrix to a file in the Harwell-Boeing format - +hb_read -- Read a sparse matrix from a file in the Harwell-Boeing format + @@ -16,50 +16,50 @@ - + -

    -hb_write -- Write a sparse matrix to a file - in the Harwell-Boeing format +

    + hb_read -- Read a sparse matrix from a file in the + Harwell-Boeing format


    \begin{lstlisting}
-call hb_write(a, iret, iunit, filename, key, rhs, mtitle)
+call hb_read(a, iret, iunit, filename, b, mtitle)
 \end{lstlisting}
    @@ -71,29 +71,13 @@ call hb_write(a, iret, iunit, filename, key, rhs, mtitle)

    On Entry
    -
    a
    -
    the sparse matrix to be written. -
    -Type:required. -
    -Specified as: a structured data of type spdatapsb_Tspmat_type. -
    -
    b
    -
    Rigth hand side. -
    -Type: Optional -
    -An array of type real or complex, rank 1 and having the ALLOCATABLE -attribute; will be allocated and filled in if the input file contains -a right hand side. -
    filename
    -
    The name of the file to be written to. +
    The name of the file to be read.
    Type:optional.
    Specified as: a character variable containing a valid file name, or --, in which case the default output unit 6 (i.e. standard output +-, in which case the default input unit 5 (i.e. standard input in Unix jargon) is used. Default: -.
    iunit
    @@ -103,30 +87,37 @@ Type:optional.
    Specified as: an integer value. Only meaningful if filename is not -. -
    key
    -
    Matrix key. + + +

    +

    +
    On Return
    +
    +
    +
    a
    +
    the sparse matrix read from file. +
    +Type:required. +
    +Specified as: a structured data of type spdatapsb_Tspmat_type. +
    +
    b
    +
    Rigth hand side(s).
    Type: Optional
    -A charachter variable of length 8 holding the -matrix key as specified by the Harwell-Boeing format and to be -written to file. +An array of type real or complex, rank 2 and having the ALLOCATABLE +attribute; will be allocated and filled in if the input file contains +a right hand side, otherwise will be left in the UNALLOCATED state.
    mtitle
    Matrix title.
    Type: Optional
    -A charachter variable of length 72 holding the -matrix title as specified by the Harwell-Boeing format and to be -written to file. -
    -
    - -

    -

    -
    On Return
    -
    +A charachter variable of length 72 holding a copy of the +matrix title as specified by the Harwell-Boeing format and contained +in the input file.
    iret
    Error code. @@ -141,26 +132,26 @@ An integer value; 0 means no error has been detected. diff --git a/docs/html/node12.html b/docs/html/node12.html index 3b5d602d..c6856edc 100644 --- a/docs/html/node12.html +++ b/docs/html/node12.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node120.html b/docs/html/node120.html index d3692040..b796086e 100644 --- a/docs/html/node120.html +++ b/docs/html/node120.html @@ -3,8 +3,8 @@ -mm_mat_read -- Read a sparse matrix from a file in the MatrixMarket format - +hb_write -- Write a sparse matrix to a file in the Harwell-Boeing format + @@ -16,50 +16,50 @@ - + -

    -mm_mat_read -- Read a sparse matrix from a - file in the MatrixMarket format +

    +hb_write -- Write a sparse matrix to a file + in the Harwell-Boeing format


    \begin{lstlisting}
-call mm_mat_read(a, iret, iunit, filename)
+call hb_write(a, iret, iunit, filename, key, rhs, mtitle)
 \end{lstlisting}
    @@ -71,13 +71,29 @@ call mm_mat_read(a, iret, iunit, filename)

    On Entry
    +
    a
    +
    the sparse matrix to be written. +
    +Type:required. +
    +Specified as: a structured data of type spdatapsb_Tspmat_type. +
    +
    b
    +
    Rigth hand side. +
    +Type: Optional +
    +An array of type real or complex, rank 1 and having the ALLOCATABLE +attribute; will be allocated and filled in if the input file contains +a right hand side. +
    filename
    -
    The name of the file to be read. +
    The name of the file to be written to.
    Type:optional.
    Specified as: a character variable containing a valid file name, or --, in which case the default input unit 5 (i.e. standard input +-, in which case the default output unit 6 (i.e. standard output in Unix jargon) is used. Default: -.
    iunit
    @@ -87,6 +103,24 @@ Type:optional.
    Specified as: an integer value. Only meaningful if filename is not -.
    +
    key
    +
    Matrix key. +
    +Type: Optional +
    +A charachter variable of length 8 holding the +matrix key as specified by the Harwell-Boeing format and to be +written to file. +
    +
    mtitle
    +
    Matrix title. +
    +Type: Optional +
    +A charachter variable of length 72 holding the +matrix title as specified by the Harwell-Boeing format and to be +written to file. +

    @@ -94,13 +128,6 @@ Specified as: an integer value. Only meaningful if filename is not -On Return

    -
    a
    -
    the sparse matrix read from file. -
    -Type:required. -
    -Specified as: a structured data of type spdatapsb_Tspmat_type. -
    iret
    Error code.
    @@ -111,7 +138,31 @@ An integer value; 0 means no error has been detected.

    -


    + + + diff --git a/docs/html/node121.html b/docs/html/node121.html index dacbb994..52f273d2 100644 --- a/docs/html/node121.html +++ b/docs/html/node121.html @@ -3,8 +3,8 @@ -mm_array_read -- Read a dense array from a file in the MatrixMarket format - +mm_mat_read -- Read a sparse matrix from a file in the MatrixMarket format + @@ -16,50 +16,50 @@ - + -

    -mm_array_read -- Read a dense array from a +

    +mm_mat_read -- Read a sparse matrix from a file in the MatrixMarket format


    \begin{lstlisting}
-call mm_array_read(b, iret, iunit, filename)
+call mm_mat_read(a, iret, iunit, filename)
 \end{lstlisting}
    @@ -94,14 +94,12 @@ Specified as: an integer value. Only meaningful if filename is not -On Return

    -
    b
    -
    Rigth hand side(s). +
    a
    +
    the sparse matrix read from file.
    -Type: required +Type:required.
    -An array of type real or complex, rank 1 or 2 and having the ALLOCATABLE -attribute; will be allocated and filled in if the input file contains -a right hand side, otherwise will be left in the UNALLOCATED state. +Specified as: a structured data of type spdatapsb_Tspmat_type.
    iret
    Error code. diff --git a/docs/html/node122.html b/docs/html/node122.html index 27dc3d18..557f80d0 100644 --- a/docs/html/node122.html +++ b/docs/html/node122.html @@ -3,8 +3,8 @@ -mm_mat_write -- Write a sparse matrix to a file in the MatrixMarket format - +mm_array_read -- Read a dense array from a file in the MatrixMarket format + @@ -16,52 +16,54 @@ - + -

    -mm_mat_write -- Write a sparse matrix to a +

    +mm_array_read -- Read a dense array from a file in the MatrixMarket format


    \begin{lstlisting}
-call mm_mat_write(a, mtitle, iret, iunit, filename)
+call mm_array_read(b, iret, iunit, filename)
 \end{lstlisting}
    + +

    Type:
    Asynchronous. @@ -69,28 +71,13 @@ call mm_mat_write(a, mtitle, iret, iunit, filename)
    On Entry
    -
    a
    -
    the sparse matrix to be written. -
    -Type:required. -
    -Specified as: a structured data of type spdatapsb_Tspmat_type. -
    -
    mtitle
    -
    Matrix title. -
    -Type: required -
    -A charachter variable holding a descriptive title for the matrix to be - written to file. -
    filename
    -
    The name of the file to be written to. +
    The name of the file to be read.
    Type:optional.
    Specified as: a character variable containing a valid file name, or --, in which case the default output unit 6 (i.e. standard output +-, in which case the default input unit 5 (i.e. standard input in Unix jargon) is used. Default: -.
    iunit
    @@ -107,6 +94,15 @@ Specified as: an integer value. Only meaningful if filename is not -On Return
    +
    b
    +
    Rigth hand side(s). +
    +Type: required +
    +An array of type real or complex, rank 1 or 2 and having the ALLOCATABLE +attribute; will be allocated and filled in if the input file contains +a right hand side, otherwise will be left in the UNALLOCATED state. +
    iret
    Error code.
    diff --git a/docs/html/node123.html b/docs/html/node123.html index 1dc181f9..bcd55f5e 100644 --- a/docs/html/node123.html +++ b/docs/html/node123.html @@ -3,8 +3,8 @@ -mm_array_write -- Write a dense array from a file in the MatrixMarket format - +mm_mat_write -- Write a sparse matrix to a file in the MatrixMarket format + @@ -14,55 +14,54 @@ + - + -

    -mm_array_write -- Write a dense array from a +

    +mm_mat_write -- Write a sparse matrix to a file in the MatrixMarket format


    \begin{lstlisting}
-call mm_array_write(b, iret, iunit, filename)
+call mm_mat_write(a, mtitle, iret, iunit, filename)
 \end{lstlisting}
    - -

    Type:
    Asynchronous. @@ -70,19 +69,28 @@ call mm_array_write(b, iret, iunit, filename)
    On Entry
    -
    b
    -
    Rigth hand side(s). +
    a
    +
    the sparse matrix to be written. +
    +Type:required. +
    +Specified as: a structured data of type spdatapsb_Tspmat_type. +
    +
    mtitle
    +
    Matrix title.
    Type: required
    -An array of type real or complex, rank 1 or 2; will be written..
    +A charachter variable holding a descriptive title for the matrix to be + written to file. +

    filename
    -
    The name of the file to be written. +
    The name of the file to be written to.
    Type:optional.
    Specified as: a character variable containing a valid file name, or --, in which case the default input unit 5 (i.e. standard input +-, in which case the default output unit 6 (i.e. standard output in Unix jargon) is used. Default: -.
    iunit
    diff --git a/docs/html/node124.html b/docs/html/node124.html index 56ba1c09..1ea293a1 100644 --- a/docs/html/node124.html +++ b/docs/html/node124.html @@ -3,8 +3,8 @@ -Preconditioner routines - +mm_array_write -- Write a dense array from a file in the MatrixMarket format + @@ -14,84 +14,101 @@ - - - + + -

    - -
    -Preconditioner routines -

    +

    +mm_array_write -- Write a dense array from a + file in the MatrixMarket format +

    -The base PSBLAS library contains the implementation of two simple -preconditioning techniques: +
    +\begin{lstlisting}
+call mm_array_write(b, iret, iunit, filename)
+\end{lstlisting} +
    -

      -
    • Diagonal Scaling -
    • -
    • Block Jacobi with ILU(0) factorization -
    • -
    -The supporting data type and subroutine interfaces are defined in the -module psb_prec_mod. -The old interfaces psb_precinit and psb_precbld are still supported for -backward compatibility +

    +

    +
    Type:
    +
    Asynchronous. +
    +
    On Entry
    +
    +
    +
    b
    +
    Rigth hand side(s). +
    +Type: required +
    +An array of type real or complex, rank 1 or 2; will be written..
    +
    filename
    +
    The name of the file to be written. +
    +Type:optional. +
    +Specified as: a character variable containing a valid file name, or +-, in which case the default input unit 5 (i.e. standard input +in Unix jargon) is used. Default: -. +
    +
    iunit
    +
    The Fortran file unit number. +
    +Type:optional. +
    +Specified as: an integer value. Only meaningful if filename is not -. +
    +

    -


    - -Subsections +
    +
    On Return
    +
    +
    +
    iret
    +
    Error code. +
    +Type: required +
    +An integer value; 0 means no error has been detected. +
    +
    - - +



    diff --git a/docs/html/node125.html b/docs/html/node125.html index ff0b640a..8457a092 100644 --- a/docs/html/node125.html +++ b/docs/html/node125.html @@ -3,8 +3,8 @@ -init -- Initialize a preconditioner - +Preconditioner routines + @@ -14,126 +14,85 @@ - - - + + + -

    -init -- Initialize a preconditioner -

    +

    + +
    +Preconditioner routines +

    -

    -call prec%init(ptype, info)
    -
    +The base PSBLAS library contains the implementation of two simple +preconditioning techniques: -

    -

    -
    Type:
    -
    Asynchronous. -
    -
    On Entry
    -
    -
    -
    ptype
    -
    the type of preconditioner. -Scope: global -
    -Type: required -
    -Intent: in. -
    -Specified as: a character string, see usage notes. -
    -
    On Exit
    -

    -

    -
    prec
    -
    Scope: local -
    -Type: required -
    -Intent: inout. -
    -Specified as: a preconditioner data structure precdatapsb_prec_type. -
    -
    info
    -
    Scope: global -
    -Type: required -
    -Intent: out. -
    -Error code: if no error, 0 is returned. -
    -
    -Notes -Legal inputs to this subroutine are interpreted depending on the -$ptype$ string as follows4: -
    -
    NONE
    -
    No preconditioning, i.e. the preconditioner is just a copy - operator. -
    -
    DIAG
    -
    Diagonal scaling; each entry of the input vector is - multiplied by the reciprocal of the sum of the absolute values of - the coefficients in the corresponding row of matrix $A$; -
    -
    BJAC
    -
    Precondition by a factorization of the - block-diagonal of matrix $A$, where block boundaries are determined - by the data allocation boundaries for each process; requires no - communication. Only the incomplete factorization $ILU(0)$ is - currently implemented. -
    -
    +
      +
    • Diagonal Scaling +
    • +
    • Block Jacobi with ILU(0) factorization +
    • +
    +The supporting data type and subroutine interfaces are defined in the +module psb_prec_mod. +The old interfaces psb_precinit and psb_precbld are still supported for +backward compatibility



    + +Subsections + + + +

    diff --git a/docs/html/node126.html b/docs/html/node126.html index deaa93f6..911c5042 100644 --- a/docs/html/node126.html +++ b/docs/html/node126.html @@ -3,8 +3,8 @@ -build -- Builds a preconditioner - +init -- Initialize a preconditioner + @@ -16,179 +16,124 @@ - + -

    -build -- Builds a preconditioner +

    +init -- Initialize a preconditioner

    -call prec%build(a, desc_a, info[,amold,vmold,imold])
    +call prec%init(ptype, info)
     

    Type:
    -
    Synchronous. +
    Asynchronous.
    On Entry
    -
    a
    -
    the system sparse matrix. -Scope: local +
    ptype
    +
    the type of preconditioner. +Scope: global
    Type: required
    -Intent: in, target. +Intent: in.
    -Specified as: a sparse matrix data structure spdatapsb_Tspmat_type. +Specified as: a character string, see usage notes. +
    +
    On Exit
    +

    prec
    -
    the preconditioner. -
    -Scope: local +
    Scope: local
    Type: required
    Intent: inout.
    -Specified as: an already initialized precondtioner data structure precdatapsb_prec_type -
    -
    desc_a
    -
    the problem communication descriptor. -Scope: local -
    -Type: required -
    -Intent: in, target. -
    -Specified as: a communication descriptor data structure descdatapsb_desc_type. +Specified as: a preconditioner data structure precdatapsb_prec_type.
    -
    amold
    -
    The desired dynamic type for the internal matrix storage. -
    -Scope: local. -
    -Type: optional. -
    -Intent: in. -
    -Specified as: an object of a class derived from spbasedatapsb_T_base_sparse_mat. -
    -
    vmold
    -
    The desired dynamic type for the internal vector storage. -
    -Scope: local. -
    -Type: optional. -
    -Intent: in. -
    -Specified as: an object of a class derived from vbasedatapsb_T_base_vect_type. -
    -
    imold
    -
    The desired dynamic type for the internal integer vector storage. -
    -Scope: local. +
    info
    +
    Scope: global
    -Type: optional. +Type: required
    -Intent: in. +Intent: out.
    -Specified as: an object of a class derived from (integer) vbasedatapsb_T_base_vect_type. +Error code: if no error, 0 is returned.
    - -

    +Notes +Legal inputs to this subroutine are interpreted depending on the +$ptype$ string as follows4:

    -
    On Return
    -
    +
    NONE
    +
    No preconditioning, i.e. the preconditioner is just a copy + operator.
    -
    prec
    -
    the preconditioner. -
    -Scope: local -
    -Type: required -
    -Intent: inout. -
    -Specified as: a precondtioner data structure precdatapsb_prec_type -
    -
    info
    -
    Error code. -
    -Scope: local -
    -Type: required -
    -Intent: out. -
    -An integer value; 0 means no error has been detected. +
    DIAG
    +
    Diagonal scaling; each entry of the input vector is + multiplied by the reciprocal of the sum of the absolute values of + the coefficients in the corresponding row of matrix $A$; +
    +
    BJAC
    +
    Precondition by a factorization of the + block-diagonal of matrix $A$, where block boundaries are determined + by the data allocation boundaries for each process; requires no + communication. Only the incomplete factorization $ILU(0)$ is + currently implemented.
    -The amold, vmold and imold arguments may be -employed to interface with special devices, such as GPUs and other -accelerators.

    - -

    - +

    diff --git a/docs/html/node127.html b/docs/html/node127.html index 01d2e04c..8b9f0e3d 100644 --- a/docs/html/node127.html +++ b/docs/html/node127.html @@ -3,8 +3,8 @@ -apply -- Preconditioner application routine - +build -- Builds a preconditioner + @@ -16,47 +16,45 @@ - + -

    -apply -- Preconditioner application - routine +

    +build -- Builds a preconditioner

    -call prec%apply(x,y,desc_a,info,trans,work)
    -call prec%apply(x,desc_a,info,trans)
    +call prec%build(a, desc_a, info[,amold,vmold,imold])
     

    @@ -67,54 +65,69 @@ call prec%apply(x,desc_a,info,trans)

    On Entry
    -
    prec
    -
    the preconditioner. +
    a
    +
    the system sparse matrix. Scope: local
    Type: required
    -Intent: in. +Intent: in, target.
    -Specified as: a preconditioner data structure precdatapsb_prec_type. +Specified as: a sparse matrix data structure spdatapsb_Tspmat_type.
    -
    x
    -
    the source vector. +
    prec
    +
    the preconditioner. +
    Scope: local
    Type: required
    Intent: inout.
    -Specified as: a rank one array or an object of type vdatapsb_T_vect_type. -
    +Specified as: an already initialized precondtioner data structure precdatapsb_prec_type +

    desc_a
    -
    the problem communication descriptor. +
    the problem communication descriptor. Scope: local
    Type: required
    +Intent: in, target. +
    +Specified as: a communication descriptor data structure descdatapsb_desc_type. +
    +
    amold
    +
    The desired dynamic type for the internal matrix storage. +
    +Scope: local. +
    +Type: optional. +
    Intent: in.
    -Specified as: a communication data structure descdatapsb_desc_type. +Specified as: an object of a class derived from spbasedatapsb_T_base_sparse_mat.
    -
    trans
    -
    Scope: +
    vmold
    +
    The desired dynamic type for the internal vector storage. +
    +Scope: local.
    -Type: optional +Type: optional.
    Intent: in.
    -Specified as: a character. +Specified as: an object of a class derived from vbasedatapsb_T_base_vect_type.
    -
    work
    -
    an optional work space -Scope: local +
    imold
    +
    The desired dynamic type for the internal integer vector storage.
    -Type: optional +Scope: local.
    -Intent: inout. +Type: optional.
    -Specified as: a double precision array. +Intent: in. +
    +Specified as: an object of a class derived from (integer) vbasedatapsb_T_base_vect_type.
    @@ -123,16 +136,17 @@ Specified as: a double precision array.
    On Return
    -
    y
    -
    the destination vector. +
    prec
    +
    the preconditioner. +
    Scope: local
    Type: required
    Intent: inout.
    -Specified as: a rank one array or an object of type vdatapsb_T_vect_type. -
    +Specified as: a precondtioner data structure precdatapsb_prec_type +

    info
    Error code.
    @@ -145,9 +159,36 @@ Intent: out. An integer value; 0 means no error has been detected.
    +The amold, vmold and imold arguments may be +employed to interface with special devices, such as GPUs and other +accelerators.

    -


    + + + diff --git a/docs/html/node128.html b/docs/html/node128.html index 1fe31481..8905355e 100644 --- a/docs/html/node128.html +++ b/docs/html/node128.html @@ -3,8 +3,8 @@ -descr -- Prints a description of current preconditioner - +apply -- Preconditioner application routine + @@ -16,53 +16,53 @@ - + -

    -descr -- Prints a description of current - preconditioner +

    +apply -- Preconditioner application + routine

    -call prec%descr()
    -call prec%descr(iout, root)
    +call prec%apply(x,y,desc_a,info,trans,work)
    +call prec%apply(x,desc_a,info,trans)
     

    Type:
    -
    Asynchronous. +
    Synchronous.
    On Entry
    @@ -77,33 +77,72 @@ Intent: in.
    Specified as: a preconditioner data structure precdatapsb_prec_type.
    -
    iout
    -
    output unit. +
    x
    +
    the source vector. +Scope: local +
    +Type: required +
    +Intent: inout. +
    +Specified as: a rank one array or an object of type vdatapsb_T_vect_type. +
    +
    desc_a
    +
    the problem communication descriptor. Scope: local
    +Type: required +
    +Intent: in. +
    +Specified as: a communication data structure descdatapsb_desc_type. +
    +
    trans
    +
    Scope: +
    Type: optional
    Intent: in.
    -Specified as: an integer number. Default: default output unit. +Specified as: a character.
    -
    root
    -
    Process from which to print +
    work
    +
    an optional work space Scope: local
    Type: optional
    -Intent: in. +Intent: inout. +
    +Specified as: a double precision array. +
    +
    + +

    +

    +
    On Return
    +
    +
    +
    y
    +
    the destination vector. +Scope: local +
    +Type: required +
    +Intent: inout. +
    +Specified as: a rank one array or an object of type vdatapsb_T_vect_type. +
    +
    info
    +
    Error code. +
    +Scope: local +
    +Type: required +
    +Intent: out.
    -Specified as: an integer number between 0 and $np-1$, in which case -the specified process will print the description, or $-1$, in which case -all processes will print. Default: 0. +An integer value; 0 means no error has been detected.
    diff --git a/docs/html/node129.html b/docs/html/node129.html index a2c27a0a..618c5cc7 100644 --- a/docs/html/node129.html +++ b/docs/html/node129.html @@ -3,8 +3,8 @@ -clone -- clone current preconditioner - +descr -- Prints a description of current preconditioner + @@ -16,45 +16,47 @@ - + -

    -clone -- clone current +

    +descr -- Prints a description of current preconditioner

    +

    -call  prec%clone(precout,info)
    +call prec%descr()
    +call prec%descr(iout, root)
     

    @@ -67,21 +69,41 @@ call prec%clone(precout,info)

    prec
    the preconditioner. +Scope: local
    -Scope: local. -
    - - -

    -

    -
    On Return
    -
    +Type: required +
    +Intent: in. +
    +Specified as: a preconditioner data structure precdatapsb_prec_type.
    -
    precout
    -
    A copy of the input object. +
    iout
    +
    output unit. +Scope: local +
    +Type: optional +
    +Intent: in. +
    +Specified as: an integer number. Default: default output unit.
    -
    info
    -
    Return code. +
    root
    +
    Process from which to print +Scope: local +
    +Type: optional +
    +Intent: in. +
    +Specified as: an integer number between 0 and $np-1$, in which case +the specified process will print the description, or $-1$, in which case +all processes will print. Default: 0.
    diff --git a/docs/html/node13.html b/docs/html/node13.html index 41f19a65..f4ae181b 100644 --- a/docs/html/node13.html +++ b/docs/html/node13.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node130.html b/docs/html/node130.html index 417e761a..ef704e03 100644 --- a/docs/html/node130.html +++ b/docs/html/node130.html @@ -3,8 +3,8 @@ -free -- Free a preconditioner - +clone -- clone current preconditioner + @@ -14,46 +14,47 @@ + - + -

    -free -- Free a preconditioner +

    +clone -- clone current + preconditioner

    -

    -call prec%free(info)
    +call  prec%clone(precout,info)
     

    @@ -68,37 +69,21 @@ call prec%free(info)

    the preconditioner.
    Scope: local. -
    -Type: required -
    -Intent: inout. -
    -Specified as: a preconditioner data structure precdatapsb_prec_type. -
    -
    On Exit
    -

    +

    + + +

    +

    +
    On Return
    +
    -
    prec
    -
    Scope: local -
    -Type: required -
    -Intent: inout. -
    -Specified as: a preconditioner data structure precdatapsb_prec_type. +
    precout
    +
    A copy of the input object.
    info
    -
    Scope: global -
    -Type: required -
    -Intent: out. -
    -Error code: if no error, 0 is returned. +
    Return code.
    -Notes -Releases all internal storage.



    diff --git a/docs/html/node131.html b/docs/html/node131.html index 1426c2f7..6ffd6d59 100644 --- a/docs/html/node131.html +++ b/docs/html/node131.html @@ -3,8 +3,8 @@ -Iterative Methods - +free -- Free a preconditioner + @@ -14,62 +14,93 @@ - - - + + -

    - -
    -Iterative Methods -

    +

    +free -- Free a preconditioner +

    -In this chapter we provide routines for preconditioners and iterative -methods. The interfaces for Krylov subspace methods are available in -the module psb_krylov_mod. +

    +call prec%free(info)
    +

    -


    - -Subsections +
    +
    Type:
    +
    Asynchronous. +
    +
    On Entry
    +
    +
    +
    prec
    +
    the preconditioner. +
    +Scope: local. +
    +Type: required +
    +Intent: inout. +
    +Specified as: a preconditioner data structure precdatapsb_prec_type. +
    +
    On Exit
    +

    +

    +
    prec
    +
    Scope: local +
    +Type: required +
    +Intent: inout. +
    +Specified as: a preconditioner data structure precdatapsb_prec_type. +
    +
    info
    +
    Scope: global +
    +Type: required +
    +Intent: out. +
    +Error code: if no error, 0 is returned. +
    +
    +Notes +Releases all internal storage. - - +



    diff --git a/docs/html/node132.html b/docs/html/node132.html index 0da8f1c1..9e339e70 100644 --- a/docs/html/node132.html +++ b/docs/html/node132.html @@ -3,8 +3,8 @@ -psb_krylov -- Krylov Methods Driver Routine - +Iterative Methods + @@ -14,418 +14,63 @@ - - + + + -

    -
    -psb_krylov -- Krylov Methods Driver - Routine -

    - -

    -This subroutine is a driver that provides a general interface for all -the Krylov-Subspace family methods implemented in PSBLAS version 2. - -

    -The stopping criterion can take the following values: -

    -
    1
    -
    normwise backward error in the infinity -norm; the iteration is stopped when -

    -
    - - -\begin{displaymath}err = \frac{\Vert r_i\Vert}{(\Vert A\Vert\Vert x_i\Vert+\Vert b\Vert)} < eps \end{displaymath} -
    -
    -

    -
    -
    2
    -
    Relative residual in the 2-norm; the iteration is stopped -when -

    -
    - - -\begin{displaymath}err = \frac{\Vert r_i\Vert}{\Vert b\Vert _2} < eps \end{displaymath} -
    -
    -

    -
    -
    3
    -
    Relative residual reduction in the 2-norm; the iteration is stopped -when -

    -
    - - -\begin{displaymath}err = \frac{\Vert r_i\Vert}{\Vert r_0\Vert _2} < eps \end{displaymath} -
    -
    -

    -
    -
    -The behaviour is controlled by the istop argument (see -later). In the above formulae, $x_i$ is the tentative solution and -$r_i=b-Ax_i$ the corresponding residual at the $i$-th iteration. - -

    -
    -\begin{lstlisting}
-call psb_krylov(method,a,prec,b,x,eps,desc_a,info,&
-& itmax,iter,err,itrace,irst,istop,cond)
-\end{lstlisting} +

    +
    +Iterative Methods +

    -

    -
    Type:
    -
    Synchronous. -
    -
    On Entry
    -
    -
    -
    method
    -
    a string that defines the iterative method to be - used. Supported values are: -
    -
    CG:
    -
    the Conjugate Gradient method; - -
    -
    CGS:
    -
    the Conjugate Gradient Stabilized method; +In this chapter we provide routines for preconditioners and iterative +methods. The interfaces for Krylov subspace methods are available in +the module psb_krylov_mod.

    -

    -
    GCR:
    -
    the Generalized Conjugate Residual method; - -
    -
    FCG:
    -
    the Flexible Conjugate Gradient method5; - -

    -

    -
    BICG:
    -
    the Bi-Conjugate Gradient method; - -
    -
    BICGSTAB:
    -
    the Bi-Conjugate Gradient Stabilized method; - -
    -
    BICGSTABL:
    -
    the Bi-Conjugate Gradient Stabilized method with restarting; - -
    -
    RGMRES:
    -
    the Generalized Minimal Residual method with restarting. - -
    -
    -
    -
    a
    -
    the local portion of global sparse matrix -$A$. -
    -Scope: local -
    -Type: required -
    -Intent: in. -
    -Specified as: a structured data of type spdatapsb_Tspmat_type. -
    -
    prec
    -
    The data structure containing the preconditioner. -
    -Scope: local -
    -Type: required -
    -Intent: in. -
    -Specified as: a structured data of type precdatapsb_prec_type. -
    -
    b
    -
    The RHS vector. -
    -Scope: local -
    -Type: required -
    -Intent: in. -
    -Specified as: a rank one array or an object of type vdatapsb_T_vect_type. -
    -
    x
    -
    The initial guess. -
    -Scope: local -
    -Type: required -
    -Intent: inout. -
    -Specified as: a rank one array or an object of type vdatapsb_T_vect_type. -
    -
    eps
    -
    The stopping tolerance. -
    -Scope: global -
    -Type: required -
    -Intent: in. -
    -Specified as: a real number. -
    -
    desc_a
    -
    contains data structures for communications. -
    -Scope: local -
    -Type: required -
    -Intent: in. -
    -Specified as: a structured data of type descdatapsb_desc_type. -
    -
    itmax
    -
    The maximum number of iterations to perform. -
    -Scope: global -
    -Type: optional -
    -Intent: in. -
    -Default: $itmax = 1000$. -
    -Specified as: an integer variable $itmax \ge 1$. -
    -
    itrace
    -
    If $>0$ print out an informational message about - convergence every $itrace$ iterations. -
    -Scope: global -
    -Type: optional -
    -Intent: in. -
    -
    irst
    -
    An integer specifying the restart parameter. -
    -Scope: global -
    -Type: optional. -
    -Intent: in. -
    -Values: $irst>0$. This is employed for the BiCGSTABL or RGMRES -methods, otherwise it is ignored. - -

    -

    -
    istop
    -
    An integer specifying the stopping criterion. -
    -Scope: global -
    -Type: optional. -
    -Intent: in. -
    -Values: 1: use the normwise backward error, 2: use the scaled 2-norm -of the residual, 3: use the residual reduction in the 2-norm. Default: 2. -
    -
    On Return
    -
    -
    -
    x
    -
    The computed solution. -
    -Scope: local -
    -Type: required -
    -Intent: inout. -
    -Specified as: a rank one array or an object of type vdatapsb_T_vect_type. -
    -
    iter
    -
    The number of iterations performed. -
    -Scope: global -
    -Type: optional -
    -Intent: out. -
    -Returned as: an integer variable. -
    -
    err
    -
    The convergence estimate on exit. -
    -Scope: global -
    -Type: optional -
    -Intent: out. -
    -Returned as: a real number. -
    -
    cond
    -
    An estimate of the condition number of matrix $A$; only - available with the $CG$ method on real data. -
    -Scope: global -
    -Type: optional -
    -Intent: out. -
    -Returned as: a real number. A correct result will be greater than or -equal to one; if specified for non-real data, or an error occurred, -zero is returned. -
    -
    info
    -
    Error code. -
    -Scope: local -
    -Type: required -
    -Intent: out. -
    -An integer value; 0 means no error has been detected. -
    -
    - -

    - -

    - -

    - -

    - -

    - +

    + +Subsections + + + +

    diff --git a/docs/html/node133.html b/docs/html/node133.html index 60673a69..810fbf44 100644 --- a/docs/html/node133.html +++ b/docs/html/node133.html @@ -3,8 +3,8 @@ -Bibliography - +psb_krylov -- Krylov Methods Driver Routine + @@ -14,167 +14,418 @@ - - - + + +
    +
    - -

    -Bibliography -

    1 -
    - D. Barbieri, V. Cardellini, S. Filippone and D. Rouson -Design Patterns for Scientific Computations on Sparse Matrices, - HPSS 2011, Algorithms and Programming Tools for Next-Generation High-Performance Scientific Software, Bordeaux, Sep. 2011 + +

    +
    +psb_krylov -- Krylov Methods Driver + Routine +

    -

    2 -
    -G. Bella, S. Filippone, A. De Maio and M. Testa, -A Simulation Model for Forest Fires, -in J. Dongarra, K. Madsen, J. Wasniewski, editors, -Proceedings of PARA 04 Workshop on State of the Art -in Scientific Computing, pp. 546-553, Lecture Notes in Computer Science, -Springer, 2005. -

    3 -
    A. Buttari, D. di Serafino, P. D'Ambra, S. Filippone,
    -2LEV-D2P4: a package of high-performance preconditioners,
    -Applicable Algebra in Engineering, Communications and Computing, -Volume 18, Number 3, May, 2007, pp. 223-239 -

    4 -
    P. D'Ambra, S. Filippone, D. Di Serafino
    -On the Development of PSBLAS-based Parallel Two-level Schwarz Preconditioners -
    -Applied Numerical Mathematics, Elsevier Science, -Volume 57, Issues 11-12, November-December 2007, Pages 1181-1196. +This subroutine is a driver that provides a general interface for all +the Krylov-Subspace family methods implemented in PSBLAS version 2. + +

    +The stopping criterion can take the following values: +

    +
    1
    +
    normwise backward error in the infinity +norm; the iteration is stopped when +

    +
    + + +\begin{displaymath}err = \frac{\Vert r_i\Vert}{(\Vert A\Vert\Vert x_i\Vert+\Vert b\Vert)} < eps \end{displaymath} +
    +
    +

    +
    +
    2
    +
    Relative residual in the 2-norm; the iteration is stopped +when +

    +
    + + +\begin{displaymath}err = \frac{\Vert r_i\Vert}{\Vert b\Vert _2} < eps \end{displaymath} +
    +
    +

    +
    +
    3
    +
    Relative residual reduction in the 2-norm; the iteration is stopped +when +

    +
    + + +\begin{displaymath}err = \frac{\Vert r_i\Vert}{\Vert r_0\Vert _2} < eps \end{displaymath} +
    +
    +

    +
    +
    +The behaviour is controlled by the istop argument (see +later). In the above formulae, $x_i$ is the tentative solution and +$r_i=b-Ax_i$ the corresponding residual at the $i$-th iteration.

    -

    5 -
    - Dongarra, J. J., DuCroz, J., Hammarling, S. and Hanson, R., -An Extended Set of Fortran Basic Linear Algebra Subprograms, -ACM Trans. Math. Softw. vol. 14, 1-17, 1988. -

    6 -
    - Dongarra, J., DuCroz, J., Hammarling, S. and Duff, I., -A Set of level 3 Basic Linear Algebra Subprograms, -ACM Trans. Math. Softw. vol. 16, 1-17, 1990. -

    7 -
    -J. J. Dongarra and R. C. Whaley, -A User's Guide to the BLACS v. 1.1, -Lapack Working Note 94, Tech. Rep. UT-CS-95-281, University of -Tennessee, March 1995 (updated May 1997). -

    8 -
    -I. Duff, M. Marrone, G. Radicati and C. Vittoli, -Level 3 Basic Linear Algebra Subprograms for Sparse Matrices: -a User Level Interface, -ACM Transactions on Mathematical Software, 23(3), pp. 379-401, 1997. -

    9 -
    -I. Duff, M. Heroux and R. Pozo, -An Overview of the Sparse Basic Linear -Algebra Subprograms: the New Standard from the BLAS Technical Forum, -ACM Transactions on Mathematical Software, 28(2), pp. 239-267, 2002. -

    10 -
    -S. Filippone and M. Colajanni, -PSBLAS: A Library for Parallel Linear Algebra -Computation on Sparse Matrices,
    -ACM Transactions on Mathematical Software, 26(4), pp. 527-550, 2000. -

    11 -
    -S. Filippone and A. Buttari, -Object-Oriented Techniques for Sparse Matrix Computations in Fortran 2003, +\begin{lstlisting}
+call psb_krylov(method,a,prec,b,x,eps,desc_a,info,&
+& itmax,iter,err,itrace,irst,istop,cond)
+\end{lstlisting}
    -ACM Transactions on Mathematical Software, 38(4), 2012. -

    12 -
    -S. Filippone, P. D'Ambra, M. Colajanni, -Using a Parallel Library of Sparse Linear Algebra in a Fluid Dynamics -Applications Code on Linux Clusters, -in G. Joubert, A. Murli, F. Peters, M. Vanneschi, editors, -Parallel Computing - Advances & Current Issues, -pp. 441-448, Imperial College Press, 2002. -

    13 -
    - Gamma, E., Helm, R., Johnson, R., and Vlissides, - J. 1995. - Design Patterns: Elements of Reusable Object-Oriented Software. - Addison-Wesley.

    -

    14 -
    -Karypis, G. and Kumar, V., -METIS: Unstructured Graph Partitioning and Sparse Matrix - Ordering System. -Minneapolis, MN 55455: University of Minnesota, Department of - Computer Science, 1995. -Internet Address: http://www.cs.umn.edu/~karypis. -

    15 +
    +
    Type:
    +
    Synchronous. +
    +
    On Entry
    -Lawson, C., Hanson, R., Kincaid, D. and Krogh, F., - Basic Linear Algebra Subprograms for Fortran usage, -ACM Trans. Math. Softw. vol. 5, 38-329, 1979. +
    +
    method
    +
    a string that defines the iterative method to be + used. Supported values are: +
    +
    CG:
    +
    the Conjugate Gradient method; + +
    +
    CGS:
    +
    the Conjugate Gradient Stabilized method;

    -

    16 -
    -Machiels, L. and Deville, M. -Fortran 90: An entry to object-oriented programming for the solution - of partial differential equations. -ACM Trans. Math. Softw. vol. 23, 32-49. -

    17 -
    -Metcalf, M., Reid, J. and Cohen, M. -Fortran 95/2003 explained. -Oxford University Press, 2004. -

    18 -
    -Rouson, D.W.I., Xia, J., Xu, X.: Scientific Software Design: The - Object-Oriented Way. Cambridge University Press (2011) +
    +
    GCR:
    +
    the Generalized Conjugate Residual method; + +
    +
    FCG:
    +
    the Flexible Conjugate Gradient method5; + +

    +

    +
    BICG:
    +
    the Bi-Conjugate Gradient method; + +
    +
    BICGSTAB:
    +
    the Bi-Conjugate Gradient Stabilized method; + +
    +
    BICGSTABL:
    +
    the Bi-Conjugate Gradient Stabilized method with restarting; + +
    +
    RGMRES:
    +
    the Generalized Minimal Residual method with restarting. + +
    +
    +
    +
    a
    +
    the local portion of global sparse matrix +$A$. +
    +Scope: local +
    +Type: required +
    +Intent: in. +
    +Specified as: a structured data of type spdatapsb_Tspmat_type. +
    +
    prec
    +
    The data structure containing the preconditioner. +
    +Scope: local +
    +Type: required +
    +Intent: in. +
    +Specified as: a structured data of type precdatapsb_prec_type. +
    +
    b
    +
    The RHS vector. +
    +Scope: local +
    +Type: required +
    +Intent: in. +
    +Specified as: a rank one array or an object of type vdatapsb_T_vect_type. +
    +
    x
    +
    The initial guess. +
    +Scope: local +
    +Type: required +
    +Intent: inout. +
    +Specified as: a rank one array or an object of type vdatapsb_T_vect_type. +
    +
    eps
    +
    The stopping tolerance. +
    +Scope: global +
    +Type: required +
    +Intent: in. +
    +Specified as: a real number. +
    +
    desc_a
    +
    contains data structures for communications. +
    +Scope: local +
    +Type: required +
    +Intent: in. +
    +Specified as: a structured data of type descdatapsb_desc_type. +
    +
    itmax
    +
    The maximum number of iterations to perform. +
    +Scope: global +
    +Type: optional +
    +Intent: in. +
    +Default: $itmax = 1000$. +
    +Specified as: an integer variable $itmax \ge 1$. +
    +
    itrace
    +
    If $>0$ print out an informational message about + convergence every $itrace$ iterations. +
    +Scope: global +
    +Type: optional +
    +Intent: in. +
    +
    irst
    +
    An integer specifying the restart parameter. +
    +Scope: global +
    +Type: optional. +
    +Intent: in. +
    +Values: $irst>0$. This is employed for the BiCGSTABL or RGMRES +methods, otherwise it is ignored.

    -

    19 + +
    istop
    +
    An integer specifying the stopping criterion. +
    +Scope: global +
    +Type: optional. +
    +Intent: in. +
    +Values: 1: use the normwise backward error, 2: use the scaled 2-norm +of the residual, 3: use the residual reduction in the 2-norm. Default: 2. +
    +
    On Return
    -M. Snir, S. Otto, S. Huss-Lederman, D. Walker and J. Dongarra, -MPI: The Complete Reference. Volume 1 - The MPI Core, second edition, -MIT Press, 1998. +
    +
    x
    +
    The computed solution. +
    +Scope: local +
    +Type: required +
    +Intent: inout. +
    +Specified as: a rank one array or an object of type vdatapsb_T_vect_type. +
    +
    iter
    +
    The number of iterations performed. +
    +Scope: global +
    +Type: optional +
    +Intent: out. +
    +Returned as: an integer variable. +
    +
    err
    +
    The convergence estimate on exit. +
    +Scope: global +
    +Type: optional +
    +Intent: out. +
    +Returned as: a real number. +
    +
    cond
    +
    An estimate of the condition number of matrix $A$; only + available with the $CG$ method on real data. +
    +Scope: global +
    +Type: optional +
    +Intent: out. +
    +Returned as: a real number. A correct result will be greater than or +equal to one; if specified for non-real data, or an error occurred, +zero is returned. +
    +
    info
    +
    Error code. +
    +Scope: local +
    +Type: required +
    +Intent: out. +
    +An integer value; 0 means no error has been detected. +

    -


    + +

    + +

    + +

    + +

    + diff --git a/docs/html/node14.html b/docs/html/node14.html index 071e643d..1b308c1c 100644 --- a/docs/html/node14.html +++ b/docs/html/node14.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node15.html b/docs/html/node15.html index fedad50b..735ad45e 100644 --- a/docs/html/node15.html +++ b/docs/html/node15.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node16.html b/docs/html/node16.html index e084853d..1310193d 100644 --- a/docs/html/node16.html +++ b/docs/html/node16.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node17.html b/docs/html/node17.html index dafa0487..2be31ac9 100644 --- a/docs/html/node17.html +++ b/docs/html/node17.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node18.html b/docs/html/node18.html index 3183fca1..311565c5 100644 --- a/docs/html/node18.html +++ b/docs/html/node18.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node19.html b/docs/html/node19.html index 928541fa..ff38f45c 100644 --- a/docs/html/node19.html +++ b/docs/html/node19.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node2.html b/docs/html/node2.html index 8e0073d4..49fdb96e 100644 --- a/docs/html/node2.html +++ b/docs/html/node2.html @@ -23,26 +23,26 @@ @@ -68,7 +68,7 @@ passing.

    The PSBLAS library version 3 is implemented in the Fortran 2003 [17] programming language, with reuse and/or + HREF="node134.html#metcalf">17] programming language, with reuse and/or adaptation of existing Fortran 77 and Fortran 95 software, plus a handful of C routines. @@ -78,11 +78,11 @@ mostly in the handling of requirements for evolution and adaptation of the library to new computing architectures and integration of new algorithms. For a detailed discussion of our design see [11]; other + HREF="node134.html#Sparse03">11]; other works discussing advanced programming in Fortran 2003 include [1,18]; sufficient support for + HREF="node134.html#DesPat:11">1,18]; sufficient support for Fortran 2003 is now available from many compilers, including the GNU Fortran compiler from the Free Software Foundation (as of version 4.8). @@ -91,7 +91,7 @@ Previous approaches have been based on mixing Fortran 95, with its support for object-based design, with other languages; these have been advocated by a number of authors, e.g. [16]. Moreover, the Fortran 95 facilities for dynamic + HREF="node134.html#machiels">16]. Moreover, the Fortran 95 facilities for dynamic memory management and interface overloading greatly enhance the usability of the PSBLAS subroutines. In this way, the library can take care of runtime memory @@ -102,12 +102,12 @@ implementation or compilation time. The presentation of the PSBLAS library follows the general structure of the proposal for serial Sparse BLAS [8,9], which in its turn is based on the + HREF="node134.html#sblas97">8,9], which in its turn is based on the proposal for BLAS on dense matrices [15,5,6]. + HREF="node134.html#BLAS1">15,5,6].

    The applicability of sparse iterative solvers to many different areas @@ -142,26 +142,26 @@ computational fluid dynamics applications.

    diff --git a/docs/html/node20.html b/docs/html/node20.html index de929193..2661f1dc 100644 --- a/docs/html/node20.html +++ b/docs/html/node20.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node21.html b/docs/html/node21.html index e8c89960..0f35d26b 100644 --- a/docs/html/node21.html +++ b/docs/html/node21.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node22.html b/docs/html/node22.html index 822a19d7..2834ff8a 100644 --- a/docs/html/node22.html +++ b/docs/html/node22.html @@ -22,26 +22,26 @@ diff --git a/docs/html/node23.html b/docs/html/node23.html index 773886dd..cb1b759b 100644 --- a/docs/html/node23.html +++ b/docs/html/node23.html @@ -23,26 +23,26 @@ @@ -57,9 +57,9 @@ The spdatapsb_Tspmat_type class contains all information about the local portion of the sparse matrix and its storage mode. Its design is based on the STATE design pattern [13] as detailed + HREF="node134.html#DesignPatterns">13] as detailed in [11]; the type declaration is shown in + HREF="node134.html#Sparse03">11]; the type declaration is shown in figure 4 where T is a placeholder for the data type and precision variants
    @@ -142,74 +142,74 @@ variants are obtained by conversion to/from it. Subsections diff --git a/docs/html/node24.html b/docs/html/node24.html index 40c0a7e9..7c430127 100644 --- a/docs/html/node24.html +++ b/docs/html/node24.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node25.html b/docs/html/node25.html index 124e9ef9..2946e8c2 100644 --- a/docs/html/node25.html +++ b/docs/html/node25.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node26.html b/docs/html/node26.html index 544a3837..017007ef 100644 --- a/docs/html/node26.html +++ b/docs/html/node26.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node27.html b/docs/html/node27.html index ed4ae9d8..632b31ad 100644 --- a/docs/html/node27.html +++ b/docs/html/node27.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node28.html b/docs/html/node28.html index 96260d80..d7c99061 100644 --- a/docs/html/node28.html +++ b/docs/html/node28.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node29.html b/docs/html/node29.html index a025b9aa..3fe8307b 100644 --- a/docs/html/node29.html +++ b/docs/html/node29.html @@ -25,26 +25,26 @@ of a sparse matrix"> diff --git a/docs/html/node3.html b/docs/html/node3.html index 0b33a78c..68ce75bc 100644 --- a/docs/html/node3.html +++ b/docs/html/node3.html @@ -23,26 +23,26 @@ @@ -75,7 +75,7 @@ calls to the serial sparse BLAS subroutines. In a similar way, the inter-process message exchanges are encapsulated in an applicaiton layer that has been strongly inspired by the Basic Linear Algebra Communication Subroutines (BLACS) library [7]. + HREF="node134.html#BLACS">7]. Usually there is no need to deal directly with MPI; however, in some cases, MPI routines are used directly to improve efficiency. For further details on our communication layer see Sec. 7. @@ -131,7 +131,7 @@ equation indices to processes. In particular it is consistent with the usage of graph partitioning tools commonly available in the literature, e.g. METIS [14]. + HREF="node134.html#METIS">14]. Dense vectors conform to sparse matrices, that is, the entries of a vector follow the same distribution of the matrix rows. @@ -151,44 +151,44 @@ bottleneck would make this option unattractive in most cases. Subsections diff --git a/docs/html/node30.html b/docs/html/node30.html index 5e0a9949..6747d3ff 100644 --- a/docs/html/node30.html +++ b/docs/html/node30.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node31.html b/docs/html/node31.html index d2698743..717f71d2 100644 --- a/docs/html/node31.html +++ b/docs/html/node31.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node32.html b/docs/html/node32.html index b3137473..552eb010 100644 --- a/docs/html/node32.html +++ b/docs/html/node32.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node33.html b/docs/html/node33.html index 6303a477..d8e5a4df 100644 --- a/docs/html/node33.html +++ b/docs/html/node33.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node34.html b/docs/html/node34.html index 524a0661..ddd40de5 100644 --- a/docs/html/node34.html +++ b/docs/html/node34.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node35.html b/docs/html/node35.html index a3ddef24..f1196058 100644 --- a/docs/html/node35.html +++ b/docs/html/node35.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node36.html b/docs/html/node36.html index 8b3077f7..2245d9bf 100644 --- a/docs/html/node36.html +++ b/docs/html/node36.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node37.html b/docs/html/node37.html index b0ed495c..152d3ad3 100644 --- a/docs/html/node37.html +++ b/docs/html/node37.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node38.html b/docs/html/node38.html index ca301bde..9e05ea68 100644 --- a/docs/html/node38.html +++ b/docs/html/node38.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node39.html b/docs/html/node39.html index 14985dbf..be187000 100644 --- a/docs/html/node39.html +++ b/docs/html/node39.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node4.html b/docs/html/node4.html index 6648616d..d76c8d2d 100644 --- a/docs/html/node4.html +++ b/docs/html/node4.html @@ -23,26 +23,26 @@ @@ -123,8 +123,8 @@ Overlap points do not usually exist in the basic data distributions; however they are a feature of Domain Decomposition Schwarz preconditioners which are the subject of related research work [4,3]. + HREF="node134.html#2007c">4,3].

    We denote the sets of internal, boundary and halo points for a given @@ -195,26 +195,26 @@ points in the literature.

    diff --git a/docs/html/node40.html b/docs/html/node40.html index 624b2ccb..c2dccdae 100644 --- a/docs/html/node40.html +++ b/docs/html/node40.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node41.html b/docs/html/node41.html index 10c1385a..5592942a 100644 --- a/docs/html/node41.html +++ b/docs/html/node41.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node42.html b/docs/html/node42.html index 1f32240d..f9eb9bf9 100644 --- a/docs/html/node42.html +++ b/docs/html/node42.html @@ -22,26 +22,26 @@ diff --git a/docs/html/node43.html b/docs/html/node43.html index 7e01116f..c7ac8e93 100644 --- a/docs/html/node43.html +++ b/docs/html/node43.html @@ -23,26 +23,26 @@ @@ -120,44 +120,44 @@ private memory. Subsections diff --git a/docs/html/node44.html b/docs/html/node44.html index 93f06053..47c59af6 100644 --- a/docs/html/node44.html +++ b/docs/html/node44.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node45.html b/docs/html/node45.html index 6cbe9433..62166a2c 100644 --- a/docs/html/node45.html +++ b/docs/html/node45.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node46.html b/docs/html/node46.html index 2321e206..73c5d998 100644 --- a/docs/html/node46.html +++ b/docs/html/node46.html @@ -25,26 +25,26 @@ of a dense vector"> diff --git a/docs/html/node47.html b/docs/html/node47.html index ee7dc916..36a66b41 100644 --- a/docs/html/node47.html +++ b/docs/html/node47.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node48.html b/docs/html/node48.html index 1046887b..5ed4481d 100644 --- a/docs/html/node48.html +++ b/docs/html/node48.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node49.html b/docs/html/node49.html index e800d006..7ecefb7a 100644 --- a/docs/html/node49.html +++ b/docs/html/node49.html @@ -22,26 +22,26 @@ diff --git a/docs/html/node5.html b/docs/html/node5.html index 39e42345..38abd7be 100644 --- a/docs/html/node5.html +++ b/docs/html/node5.html @@ -23,26 +23,26 @@ @@ -167,26 +167,26 @@ whose current value is 3.4.0 diff --git a/docs/html/node50.html b/docs/html/node50.html index 1cc48eea..17b67e03 100644 --- a/docs/html/node50.html +++ b/docs/html/node50.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node51.html b/docs/html/node51.html index 5a3211b2..8bcbb081 100644 --- a/docs/html/node51.html +++ b/docs/html/node51.html @@ -22,26 +22,26 @@ diff --git a/docs/html/node52.html b/docs/html/node52.html index 6ef8884f..c8636525 100644 --- a/docs/html/node52.html +++ b/docs/html/node52.html @@ -23,26 +23,26 @@ @@ -58,32 +58,32 @@ Computational routines Subsections diff --git a/docs/html/node53.html b/docs/html/node53.html index 07beea59..72690b09 100644 --- a/docs/html/node53.html +++ b/docs/html/node53.html @@ -23,26 +23,26 @@ @@ -78,7 +78,7 @@ call psb_geaxpby(alpha, x, beta, y, desc_a, info)


    -
    +
    @@ -253,26 +253,26 @@ An integer value; 0 means no error has been detected. diff --git a/docs/html/node54.html b/docs/html/node54.html index a5b17d42..d08b64d4 100644 --- a/docs/html/node54.html +++ b/docs/html/node54.html @@ -23,26 +23,26 @@ @@ -110,10 +110,10 @@ dot \leftarrow x^H y

    -psb_gedot(x, y, desc_a, info)
    +psb_gedot(x, y, desc_a, info [,global])
     

    -
    +
    Table 1: Data types
    @@ -215,7 +215,20 @@ Type: required Intent: in.
    Specified as: an object of type descdatapsb_desc_type. - + +
    global
    +
    Specifies whether the computation should include the + global reduction across all processes. +
    +Scope: global +
    +Type: optional. +
    +Intent: in. +
    +Specified as: a logical scalar. +Default: global=.true. +

    On Return
    @@ -230,7 +243,8 @@ Specified as: an object of type descdatapsb_desc_type. SRC="img21.png" ALT="$y$">.
    -Scope: global +Scope: global unless the optional variable +global=.false. as been specified
    Specified as: a number of the data type indicated in Table 2. @@ -247,30 +261,55 @@ An integer value; 0 means no error has been detected. +

    +Notes + +

      +
    1. The computation of a global result requires a global + communication, which entails a significant overhead. It may be + necessary and/or advisable to compute multiple dot products at the same + time; in this case, it is possible to improve the runtime efficiency + by using the following scheme: +
      +\begin{lstlisting}
+vres(1) = psb_gedot(x1,y1,desc_a,info,global=.false.)
+vres(...
+...,y3,desc_a,info,global=.false.)
+call psb_sum(ictxt,vres(1:3))
+\end{lstlisting} +
      +In this way the global communication, which for small sizes is a + latency-bound operation, is invoked only once. +
    2. +
    +

    diff --git a/docs/html/node55.html b/docs/html/node55.html index aa9a2014..55e32c88 100644 --- a/docs/html/node55.html +++ b/docs/html/node55.html @@ -23,26 +23,26 @@ @@ -71,7 +71,7 @@ res(i) \leftarrow x(:,i)^T y(:,i) \begin{displaymath}res(i) \leftarrow x(:,i)^T y(:,i)\end{displaymath}
    @@ -89,7 +89,7 @@ used. If $y$ are of rank one, then $res$ is a scalar, else it is a rank one array. @@ -98,7 +98,7 @@ is a rank one array. call psb_gedots(res, x, y, desc_a, info)

    -
    +
    Table 2: Data types
    @@ -107,7 +107,7 @@ Data types
    Table 3: Data types
    $res$,
    - next - up - previous - contents
    - Next: Next: psb_normi Infinity-Norm - Up: Up: Computational routines - Previous: Previous: psb_gedot Dot -   Contents diff --git a/docs/html/node56.html b/docs/html/node56.html index b2816af3..07e94989 100644 --- a/docs/html/node56.html +++ b/docs/html/node56.html @@ -23,26 +23,26 @@ @@ -74,7 +74,7 @@ amax \leftarrow \max_i |x_i| \begin{displaymath}amax \leftarrow \max_i \vert x_i\vert\end{displaymath}
    @@ -93,7 +93,7 @@ amax \leftarrow \max_i {(|re(x_i)| + |im(x_i)|)} \begin{displaymath}amax \leftarrow \max_i {(\vert re(x_i)\vert + \vert im(x_i)\vert)}\end{displaymath}
    @@ -101,13 +101,13 @@ amax \leftarrow \max_i {(|re(x_i)| + |im(x_i)|)}

    -psb_geamax(x, desc_a, info)
    -psb_normi(x, desc_a, info)
    +psb_geamax(x, desc_a, info [,global])
    +psb_normi(x, desc_a, info [,global])
     


    -
    +
    @@ -116,7 +116,7 @@ Data types
    Table 4: Data types
    $amax$ required Intent: in.
    Specified as: an object of type descdatapsb_desc_type. + +
    global
    +
    Specifies whether the computation should include the + global reduction across all processes. +
    +Scope: global +
    +Type: optional. +
    +Intent: in. +
    +Specified as: a logical scalar. +Default: global=.true. +

    @@ -195,7 +209,8 @@ Specified as: an object of type descdatapsb_desc_type. SRC="img20.png" ALT="$x$">
    .
    -Scope: global +Scope: global unless the optional variable +global=.false. as been specified
    Specified as: a long precision real number. @@ -212,30 +227,55 @@ An integer value; 0 means no error has been detected. +

    +Notes + +

      +
    1. The computation of a global result requires a global + communication, which entails a significant overhead. It may be + necessary and/or advisable to compute multiple norms at the same + time; in this case, it is possible to improve the runtime efficiency + by using the following scheme: +
      +\begin{lstlisting}
+vres(1) = psb_geamax(x1,desc_a,info,global=.false.)
+vres(2)...
+...(x3,desc_a,info,global=.false.)
+call psb_amx(ictxt,vres(1:3))
+\end{lstlisting} +
      +In this way the global communication, which for small sizes is a + latency-bound operation, is invoked only once. +
    2. +
    +

    diff --git a/docs/html/node57.html b/docs/html/node57.html index d15507ad..b5285a3e 100644 --- a/docs/html/node57.html +++ b/docs/html/node57.html @@ -23,26 +23,26 @@ @@ -68,7 +68,7 @@ res(i) \leftarrow \max_k |x(k,i)| \begin{displaymath}res(i) \leftarrow \max_k \vert x(k,i)\vert \end{displaymath}
    @@ -81,7 +81,7 @@ call psb_geamaxs(res, x, desc_a, info)


    -
    +
    @@ -90,7 +90,7 @@ Data types
    Table 5: Data types
    $res$
    - next - up - previous - contents
    - Next: Next: psb_norm1 1-Norm - Up: Up: Computational routines - Previous: Previous: psb_normi Infinity-Norm -   Contents diff --git a/docs/html/node58.html b/docs/html/node58.html index 53075a58..5cb839b1 100644 --- a/docs/html/node58.html +++ b/docs/html/node58.html @@ -23,26 +23,26 @@ @@ -73,7 +73,7 @@ asum \leftarrow \|x_i\| \begin{displaymath}asum \leftarrow \Vert x_i\Vert\end{displaymath}
    @@ -92,7 +92,7 @@ asum \leftarrow \|re(x)\|_1 + \|im(x)\|_1 \begin{displaymath}asum \leftarrow \Vert re(x)\Vert _1 + \Vert im(x)\Vert _1\end{displaymath}
    @@ -100,13 +100,13 @@ asum \leftarrow \|re(x)\|_1 + \|im(x)\|_1

    -psb_geasum(x, desc_a, info)
    -psb_norm1(x, desc_a, info)
    +psb_geasum(x, desc_a, info [,global])
    +psb_norm1(x, desc_a, info [,global])
     


    -
    +
    @@ -115,7 +115,7 @@ Data types
    Table 6: Data types
    $asum$ required Intent: in.
    Specified as: an object of type descdatapsb_desc_type. - + +
    global
    +
    Specifies whether the computation should include the + global reduction across all processes. +
    +Scope: global +
    +Type: optional. +
    +Intent: in. +
    +Specified as: a logical scalar. +Default: global=.true. +

    On Return
    @@ -194,7 +207,8 @@ Specified as: an object of type descdatapsb_desc_type. SRC="img20.png" ALT="$x$">
    .
    -Scope: global +Scope: global unless the optional variable +global=.false. as been specified
    Specified as: a long precision real number. @@ -211,30 +225,55 @@ An integer value; 0 means no error has been detected. +

    +Notes + +

      +
    1. The computation of a global result requires a global + communication, which entails a significant overhead. It may be + necessary and/or advisable to compute multiple norms at the same + time; in this case, it is possible to improve the runtime efficiency + by using the following scheme: +
      +\begin{lstlisting}
+vres(1) = psb_geasum(x1,desc_a,info,global=.false.)
+vres(2)...
+...(x3,desc_a,info,global=.false.)
+call psb_sum(ictxt,vres(1:3))
+\end{lstlisting} +
      +In this way the global communication, which for small sizes is a + latency-bound operation, is invoked only once. +
    2. +
    +

    diff --git a/docs/html/node59.html b/docs/html/node59.html index 160a0e61..088bd7b3 100644 --- a/docs/html/node59.html +++ b/docs/html/node59.html @@ -23,26 +23,26 @@ @@ -68,7 +68,7 @@ res(i) \leftarrow \max_k |x(k,i)| \begin{displaymath}res(i) \leftarrow \max_k \vert x(k,i)\vert \end{displaymath}
    @@ -93,7 +93,7 @@ res(i) \leftarrow \|x_i\| \begin{displaymath}res(i) \leftarrow \Vert x_i\Vert\end{displaymath}
    @@ -112,7 +112,7 @@ res(i) \leftarrow \|re(x)\|_1 + \|im(x)\|_1 \begin{displaymath}res(i) \leftarrow \Vert re(x)\Vert _1 + \Vert im(x)\Vert _1\end{displaymath}
    @@ -125,7 +125,7 @@ call psb_geasums(res, x, desc_a, info)


    -
    +
    @@ -134,7 +134,7 @@ Data types
    Table 7: Data types
    $res$
    - next - up - previous - contents
    - Next: Next: psb_norm2 2-Norm - Up: Up: Computational routines - Previous: Previous: psb_norm1 1-Norm -   Contents diff --git a/docs/html/node6.html b/docs/html/node6.html index 911bf87c..c3a74f22 100644 --- a/docs/html/node6.html +++ b/docs/html/node6.html @@ -23,26 +23,26 @@ @@ -247,33 +247,33 @@ from optimal. Subsections diff --git a/docs/html/node60.html b/docs/html/node60.html index aee04698..77a6ca43 100644 --- a/docs/html/node60.html +++ b/docs/html/node60.html @@ -23,26 +23,26 @@ @@ -73,7 +73,7 @@ nrm2 \leftarrow \sqrt{x^T x} \begin{displaymath}nrm2 \leftarrow \sqrt{x^T x}\end{displaymath}
    @@ -92,7 +92,7 @@ nrm2 \leftarrow \sqrt{x^H x} \begin{displaymath}nrm2 \leftarrow \sqrt{x^H x}\end{displaymath}
    @@ -100,7 +100,7 @@ nrm2 \leftarrow \sqrt{x^H x}


    -
    +
    @@ -109,7 +109,7 @@ Data types
    Table 8: Data types
    $nrm2$

    -psb_genrm2(x, desc_a, info)
    -psb_norm2(x, desc_a, info)
    +psb_genrm2(x, desc_a, info [,global])
    +psb_norm2(x, desc_a, info [,global])
     

    @@ -182,6 +182,20 @@ Type: required Intent: in.
    Specified as: an object of type descdatapsb_desc_type. + +

    global
    +
    Specifies whether the computation should include the + global reduction across all processes. +
    +Scope: global +
    +Type: optional. +
    +Intent: in. +
    +Specified as: a logical scalar. +Default: global=.true. +

    @@ -194,7 +208,8 @@ Specified as: an object of type descdatapsb_desc_type. SRC="img20.png" ALT="$x$">
    .
    -Scope: global +Scope: global unless the optional variable +global=.false. as been specified
    Type: required
    @@ -213,30 +228,55 @@ An integer value; 0 means no error has been detected. +

    +Notes + +

      +
    1. The computation of a global result requires a global + communication, which entails a significant overhead. It may be + necessary and/or advisable to compute multiple norms at the same + time; in this case, it is possible to improve the runtime efficiency + by using the following scheme: +
      +\begin{lstlisting}
+vres(1) = psb_genrm2(x1,desc_a,info,global=.false.)
+vres(2)...
+...x3,desc_a,info,global=.false.)
+call psb_nrm2(ictxt,vres(1:3))
+\end{lstlisting} +
      +In this way the global communication, which for small sizes is a + latency-bound operation, is invoked only once. +
    2. +
    +

    diff --git a/docs/html/node61.html b/docs/html/node61.html index b6f55a63..b37cc637 100644 --- a/docs/html/node61.html +++ b/docs/html/node61.html @@ -23,26 +23,26 @@ @@ -68,7 +68,7 @@ res(i) \leftarrow \|x(:,i)\|_2 \begin{displaymath}res(i) \leftarrow \Vert x(:,i)\Vert _2 \end{displaymath}
    @@ -81,7 +81,7 @@ call psb_genrm2s(res, x, desc_a, info)


    -
    +
    @@ -90,7 +90,7 @@ Data types
    Table 9: Data types
    $res$
    - next - up - previous - contents
    - Next: Next: psb_norm1 1-Norm - Up: Up: Computational routines - Previous: Previous: psb_norm2 2-Norm -   Contents diff --git a/docs/html/node62.html b/docs/html/node62.html index d05c0035..72370acc 100644 --- a/docs/html/node62.html +++ b/docs/html/node62.html @@ -23,26 +23,26 @@ @@ -69,7 +69,7 @@ nrm1 \leftarrow \|A\|_1 \begin{displaymath}nrm1 \leftarrow \Vert A\Vert _1 \end{displaymath}
    @@ -89,7 +89,7 @@ where:


    -
    +
    diff --git a/docs/html/node63.html b/docs/html/node63.html index 4493b074..8403b32b 100644 --- a/docs/html/node63.html +++ b/docs/html/node63.html @@ -23,26 +23,26 @@ @@ -69,7 +69,7 @@ nrmi \leftarrow \|A\|_\infty \begin{displaymath}nrmi \leftarrow \Vert A\Vert _\infty \end{displaymath}
    @@ -89,7 +89,7 @@ where:


    -
    +
    Table 10: Data types
    diff --git a/docs/html/node64.html b/docs/html/node64.html index ce477479..c1563adc 100644 --- a/docs/html/node64.html +++ b/docs/html/node64.html @@ -23,26 +23,26 @@ @@ -69,7 +69,7 @@ y \leftarrow \alpha A x + \beta y
    Table 11: Data types
    @@ -89,7 +89,7 @@ y \leftarrow \alpha A^T x + \beta y
    \begin{displaymath}
 y \leftarrow \alpha A x + \beta y
 \end{displaymath}
    @@ -109,7 +109,7 @@ y \leftarrow \alpha A^H x + \beta y
    \begin{displaymath}
 y \leftarrow \alpha A^T x + \beta y
 \end{displaymath}
    @@ -127,7 +127,7 @@ where: ALT="$x$">
    is the global dense matrix $x_{:, :}$
    $y$
    is the global dense matrix $y_{:, :}$

    -
    +
    \begin{displaymath}
 y \leftarrow \alpha A^H x + \beta y
 \end{displaymath}
    @@ -337,7 +337,7 @@ Intent: in.
    Default: $trans = N$
    Specified as: a character variable. @@ -400,26 +400,26 @@ An integer value; 0 means no error has been detected. diff --git a/docs/html/node65.html b/docs/html/node65.html index 5a1e9e66..99711134 100644 --- a/docs/html/node65.html +++ b/docs/html/node65.html @@ -22,26 +22,26 @@ @@ -72,7 +72,7 @@ y &\leftarrow& \alpha T^{-H} D x + \beta y\\ --> \begin{eqnarray*}
 y &\leftarrow& \alpha T^{-1} x + \beta y\\
 y &\leftarrow& \al...
@@ -91,7 +91,7 @@ where:
  ALT=
    is the global dense matrix $x_{:, :}$
    $y$
    is the global dense matrix $y_{:, :}$
    $T$
    is the global sparse block triangular submatrix $T$
    $D$
    is the scaling diagonal matrix.
    @@ -129,7 +129,7 @@ call psb_spsm(alpha, t, x, beta, y, desc_a, info,&


    -
    +
    Table 12: Data types
    @@ -138,7 +138,7 @@ Data types
    Table 13: Data types
    $T$, SRC="img21.png" ALT="$y$">, $D$, 13.
    the global portion of the sparse matrix $T$.
    Scope: local @@ -309,7 +309,7 @@ Intent: in.
    Default: $trans = N$
    Specified as: a character variable. @@ -335,7 +335,7 @@ Intent: in.
    Default: $unitd = U$
    Specified as: a character variable. @@ -381,7 +381,7 @@ Default: $diag(1) = 1 (no scaling)$
    Specified as: a rank one array containing numbers of the type @@ -442,26 +442,26 @@ An integer value; 0 means no error has been detected. diff --git a/docs/html/node66.html b/docs/html/node66.html index c051c5e1..cdc88a27 100644 --- a/docs/html/node66.html +++ b/docs/html/node66.html @@ -23,26 +23,26 @@ @@ -61,13 +61,13 @@ routines not tied to a discretization space see Subsections diff --git a/docs/html/node67.html b/docs/html/node67.html index 086ef163..015b053d 100644 --- a/docs/html/node67.html +++ b/docs/html/node67.html @@ -23,26 +23,26 @@ @@ -67,7 +67,7 @@ x \leftarrow x \begin{displaymath}x \leftarrow x \end{displaymath}
    @@ -84,7 +84,7 @@ where:


    -
    +
    @@ -126,7 +126,7 @@ Data types
    \begin{lstlisting}
 call psb_halo(x, desc_a, info)
 call psb_halo(x, desc_a, info, work, data)
@@ -230,7 +230,7 @@ An integer value that contains an error code.
 </DD>
 </DL>
 
-<DIV ALIGN= +
    Table 14: Data types
    @@ -238,12 +238,12 @@ Sample discretization mesh.
    \includegraphics[scale=0.45]{figures/try8x8.eps} \includegraphics[scale=0.45]{figures/try8x8}
    @@ -606,26 +606,26 @@ following: diff --git a/docs/html/node68.html b/docs/html/node68.html index 02386b3b..3421d633 100644 --- a/docs/html/node68.html +++ b/docs/html/node68.html @@ -23,26 +23,26 @@ @@ -66,7 +66,7 @@ x \leftarrow Q x \begin{displaymath}x \leftarrow Q x \end{displaymath}
    @@ -84,22 +84,22 @@ where:
    $Q$
    is the overlap operator; it is the composition of two operators $ P_a$ and $ P^{T}$.


    -
    +
    Figure 7: Sample discretization mesh.
    @@ -135,7 +135,7 @@ Data types
    \begin{lstlisting}
 call psb_ovrl(x, desc_a, info)
 call psb_ovrl(x, desc_a, info, update=update_type, work=work)
@@ -186,13 +186,13 @@ Specified as: a structured data of type descdata<TT>psb_desc_type</TT>.
 <DT><STRONG>update = psb_add_</STRONG></DT>
 <DD>Sum overlap entries, i.e. apply <SPAN CLASS=$P^T$;
    update = psb_avg_
    Average overlap entries, i.e. apply $P_aP^T$;
    @@ -205,7 +205,7 @@ Default: $update\_type = psb\_avg\_ $
    Scope: global @@ -269,18 +269,18 @@ An integer value; 0 means no error has been detected.
  • The operator $ P^{T}$ performs the reduction sum of overlap elements; it is a “prolongation” operator $P^T$ that replicates overlap elements, accounting for the physical replication of data;
  • The operator $ P_a$ performs a scaling on the overlap elements by the amount of replication; thus, when combined with the reduction operator, it implements the average of replicated elements over all of @@ -290,7 +290,7 @@ their instances.

    -

    +
  • Table 15: Data types
    @@ -298,12 +298,12 @@ Sample discretization mesh.
    \includegraphics[scale=0.65]{figures/try8x8_ov.eps} \includegraphics[scale=0.65]{figures/try8x8_ov}
    @@ -734,26 +734,26 @@ following (showing a transition among the two subdomains) diff --git a/docs/html/node69.html b/docs/html/node69.html index 410ac3ae..cadf089f 100644 --- a/docs/html/node69.html +++ b/docs/html/node69.html @@ -23,26 +23,26 @@ @@ -68,7 +68,7 @@ glob\_x \leftarrow collect(loc\_x_i) \begin{displaymath}glob\_x \leftarrow collect(loc\_x_i) \end{displaymath}
    @@ -77,19 +77,19 @@ where:
    $glob\_x$
    is the global submatrix $glob\_x_{1:m,1:n}$
    $loc\_x_i$
    is the local portion of global dense matrix on process
    $collect$
    is the collect function.
    @@ -107,7 +107,7 @@ process

    -
    +
    Figure 8: Sample discretization mesh.
    @@ -116,7 +116,7 @@ Data types
    Table 16: Data types
    @@ -146,7 +146,7 @@ Data types
    \begin{lstlisting}
 call psb_gather(glob_x, loc_x, desc_a, info, root)
 call psb_gather(glob_x, loc_x, desc_a, info, root)
@@ -165,7 +165,7 @@ call psb_gather(glob_x, loc_x, desc_a, info, root)
 <DD>the local portion of global dense matrix
 <SPAN CLASS=$glob\_x$.
    Scope: local @@ -191,7 +191,7 @@ Specified as: a structured data of type descdatapsb_desc_type.
    root
    The process that holds the global copy. If $root=-1$ all the processes will have a copy of the global vector.
    @@ -206,10 +206,10 @@ Specified as: an integer variable $-1\le root\le np-1$, default $-1$.
    On Return
    @@ -243,26 +243,26 @@ An integer value; 0 means no error has been detected. diff --git a/docs/html/node7.html b/docs/html/node7.html index 9f09abe4..db996b73 100644 --- a/docs/html/node7.html +++ b/docs/html/node7.html @@ -22,26 +22,26 @@ diff --git a/docs/html/node70.html b/docs/html/node70.html index ae0bfb6e..1cd035c2 100644 --- a/docs/html/node70.html +++ b/docs/html/node70.html @@ -22,26 +22,26 @@ @@ -66,7 +66,7 @@ loc\_x_i \leftarrow scatter(glob\_x) \begin{displaymath}loc\_x_i \leftarrow scatter(glob\_x) \end{displaymath}
    @@ -75,19 +75,19 @@ where:
    $glob\_x$
    is the global matrix $glob\_x_{1:m,1:n}$
    $loc\_x_i$
    is the local portion of global dense matrix on process
    $scatter$
    is the scatter function.
    @@ -105,7 +105,7 @@ process

    -
    +
    $x_i, y$ Subroutine
    @@ -114,7 +114,7 @@ Data types
    Table 17: Data types
    @@ -144,7 +144,7 @@ Data types
    \begin{lstlisting}
 call psb_scatter(glob_x, loc_x, desc_a, info, root, mold)
 \end{lstlisting} @@ -183,7 +183,7 @@ Specified as: a structured data of type descdatapsb_desc_type.
    root
    The process that holds the global copy. If $root=-1$ all the processes have a copy of the global vector.
    @@ -198,7 +198,7 @@ Specified as: an integer variable $-1\le root\le np-1$, default psb_root_, i.e. process 0.
    @@ -221,7 +221,7 @@ only allowed when loc_x is of type vdatapsb_T_vect_type.
    the local portion of global dense matrix $glob\_x$.
    Scope: local @@ -250,26 +250,26 @@ An integer value; 0 means no error has been detected. diff --git a/docs/html/node71.html b/docs/html/node71.html index f391b28c..7c38ec5a 100644 --- a/docs/html/node71.html +++ b/docs/html/node71.html @@ -23,26 +23,26 @@ @@ -60,70 +60,70 @@ Data management routines Subsections diff --git a/docs/html/node72.html b/docs/html/node72.html index 1ba59536..fd420f32 100644 --- a/docs/html/node72.html +++ b/docs/html/node72.html @@ -23,26 +23,26 @@ @@ -91,11 +91,11 @@ Specified as: an integer value. --> $i\in \{1\dots mg\}$ is allocated to process $vg(i)$.
    Scope:global. @@ -109,7 +109,7 @@ Specified as: an integer array.
    flag
    Specifies whether entries in $vg$ are zero- or one-based.
    Scope:global. @@ -120,10 +120,10 @@ Intent: in.
    Specified as: an integer value $0,1$, default $0$.

    @@ -153,7 +153,7 @@ Specified as: a subroutine.

    Data allocation: the set of global indices $vl(1:nl)$ belonging to the calling process.
    Scope:local. @@ -205,10 +205,10 @@ Specified as: a logical value, default: .true.
    Data allocation: the set of local indices $lidx(1:nl)$ to be assigned to the global indices $vl$.
    Scope:local. @@ -301,10 +301,10 @@ An integer value; 0 means no error has been detected. --> $0\le pv(i) < np$; if $nv>1$ we have an index assigned to multiple processes, i.e. we have an overlap among the subdomains. @@ -319,23 +319,23 @@ An integer value; 0 means no error has been detected. --> $i\in \{1\dots mg\}$ is assigned to process $vg(i)$. The vector vg must be identical on all calling processes; its entries may have the ranges $(0\dots np-1)$ or $(1\dots np)$ according to the value of flag. The size $mg$ may be specified via the optional argument mg; the default is to use the entire vector vg, thus having mg=size(vg). @@ -345,7 +345,7 @@ An integer value; 0 means no error has been detected. vl(1:nl) assigned to the current process; thus, the global problem size $mg$ is given by the range of the aggregate of the individual vectors vl specified in the calling processes. The size may be specified via the optional @@ -354,7 +354,7 @@ An integer value; 0 means no error has been detected. If globalcheck=.true. the subroutine will check how many times each entry in the global index space $(1\dots mg)$ is specified in the input lists vl, thus allowing for the presence of overlap in the input, and checking for “orphan” @@ -378,10 +378,10 @@ An integer value; 0 means no error has been detected. the result is a generalized row-block distribution in which each process $I$ gets assigned a consecutive chunk of $N_I=nl$ global indices.
    @@ -423,26 +423,26 @@ An integer value; 0 means no error has been detected. diff --git a/docs/html/node73.html b/docs/html/node73.html index 185949be..b61c998f 100644 --- a/docs/html/node73.html +++ b/docs/html/node73.html @@ -23,26 +23,26 @@ @@ -66,15 +66,15 @@ linear system coefficient matrix), storing them as necessary into the communication descriptor. In the first form the edges are specified as pairs of indices $ia(i),ja(i)$; the starting index $ia(i)$ should belong to the current process. In the second form only the remote indices $ja(i)$ are specified.

    @@ -107,7 +107,7 @@ Intent: in.
    Specified as: an integer array of length $nz$.

    ja
    @@ -121,7 +121,7 @@ Intent: in.
    Specified as: an integer array of length $nz$.
    mask
    @@ -136,7 +136,7 @@ Intent: in.
    Specified as: a logical array of length $nz$, default .true..
    lidx
    @@ -150,7 +150,7 @@ Intent: in.
    Specified as: an integer array of length $nz$. @@ -193,7 +193,7 @@ Intent: out.
    Specified as: an integer array of length $nz$.
    jla
    @@ -207,7 +207,7 @@ Intent: out.
    Specified as: an integer array of length $nz$.

    @@ -232,26 +232,26 @@ nor the end vertex belong to the current process.

    diff --git a/docs/html/node74.html b/docs/html/node74.html index 780ad701..90153fc2 100644 --- a/docs/html/node74.html +++ b/docs/html/node74.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node75.html b/docs/html/node75.html index 60eeb141..c5b2b262 100644 --- a/docs/html/node75.html +++ b/docs/html/node75.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node76.html b/docs/html/node76.html index 76628cf8..d963d0cf 100644 --- a/docs/html/node76.html +++ b/docs/html/node76.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node77.html b/docs/html/node77.html index d3f949e5..0fc117c8 100644 --- a/docs/html/node77.html +++ b/docs/html/node77.html @@ -23,26 +23,26 @@ @@ -101,7 +101,7 @@ Intent: in.
    Specified as: an integer value $nl\ge 0$.
    extype
    @@ -171,26 +171,26 @@ An integer value; 0 means no error has been detected. diff --git a/docs/html/node78.html b/docs/html/node78.html index de936a1e..a6434f72 100644 --- a/docs/html/node78.html +++ b/docs/html/node78.html @@ -23,26 +23,26 @@ @@ -128,7 +128,7 @@ An integer value; 0 means no error has been detected.
  • Providing a good estimate for the number of nonzeroes $nnz$ in the assembled matrix may substantially improve performance in the matrix build phase, as it will reduce or eliminate the need for diff --git a/docs/html/node79.html b/docs/html/node79.html index d5c86fdb..985137fd 100644 --- a/docs/html/node79.html +++ b/docs/html/node79.html @@ -23,26 +23,26 @@ @@ -88,7 +88,7 @@ Intent: in.
    Specified as: an integer array of size $nz$.
    ja
    @@ -102,7 +102,7 @@ Intent: in.
    Specified as: an integer array of size $nz$.
    val
    @@ -116,11 +116,11 @@ Intent: in.
    Specified as: an array of size $nz$. Must be of the same type and kind of the coefficients of the sparse matrix $a$.
    desc_a
    @@ -211,14 +211,14 @@ An integer value; 0 means no error has been detected. --> $ia(i),ja(i),val(i)$, for $i=1,\dots,nz$; these triples should belong to the current process, i.e. $ia(i)$ should be one of the local indices, but are otherwise arbitrary;
  • @@ -246,26 +246,26 @@ An integer value; 0 means no error has been detected. diff --git a/docs/html/node8.html b/docs/html/node8.html index 9b1e1251..b4bd2652 100644 --- a/docs/html/node8.html +++ b/docs/html/node8.html @@ -22,26 +22,26 @@ @@ -94,26 +94,26 @@ as: diff --git a/docs/html/node80.html b/docs/html/node80.html index 23728587..0b772b19 100644 --- a/docs/html/node80.html +++ b/docs/html/node80.html @@ -23,26 +23,26 @@ @@ -182,26 +182,26 @@ An integer value; 0 means no error has been detected. diff --git a/docs/html/node81.html b/docs/html/node81.html index 6e688f10..ad0cecc9 100644 --- a/docs/html/node81.html +++ b/docs/html/node81.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node82.html b/docs/html/node82.html index 245b17c3..178b059d 100644 --- a/docs/html/node82.html +++ b/docs/html/node82.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node83.html b/docs/html/node83.html index a9a4eac7..738de733 100644 --- a/docs/html/node83.html +++ b/docs/html/node83.html @@ -23,26 +23,26 @@ @@ -87,7 +87,7 @@ Intent: in.
    Specified as: Integer scalar, default $1$. It is not a valid argument if in.
    Specified as: Integer scalar, default $1$. It is not a valid argument if @@ -68,7 +68,7 @@ call psb_geins(m, irw, val, x, desc_a, info [,dupl,local])
    m
    Number of rows in $val$ to be inserted.
    Scope:local. @@ -86,11 +86,11 @@ Specified as: an integer value. ALT="$i$"> of $val$ will be inserted into the local row corresponding to the global row index $irw(i)$. Scope:local.
    @@ -194,26 +194,26 @@ An integer value; 0 means no error has been detected. diff --git a/docs/html/node85.html b/docs/html/node85.html index c66eadd8..d398962f 100644 --- a/docs/html/node85.html +++ b/docs/html/node85.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node86.html b/docs/html/node86.html index 887b910b..727ea53c 100644 --- a/docs/html/node86.html +++ b/docs/html/node86.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node87.html b/docs/html/node87.html index 1b2b4598..a2f92e49 100644 --- a/docs/html/node87.html +++ b/docs/html/node87.html @@ -23,26 +23,26 @@ @@ -72,7 +72,7 @@ call psb_gelp(trans, iperm, x, info) SRC="img1.png" ALT="$A$"> or $A^T$.
    Scope: local @@ -86,7 +86,7 @@ Specified as: a single character with value 'N' for $A$ or 'T' for $A^T$.
    iperm
    diff --git a/docs/html/node88.html b/docs/html/node88.html index 0f4f81e0..dc1ef1f3 100644 --- a/docs/html/node88.html +++ b/docs/html/node88.html @@ -23,26 +23,26 @@ @@ -186,26 +186,26 @@ An integer value; 0 means no error has been detected. diff --git a/docs/html/node89.html b/docs/html/node89.html index b4ae68ff..8f9fe79e 100644 --- a/docs/html/node89.html +++ b/docs/html/node89.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node9.html b/docs/html/node9.html index d5d0565c..0a5a735c 100644 --- a/docs/html/node9.html +++ b/docs/html/node9.html @@ -23,26 +23,26 @@ @@ -109,132 +109,132 @@ developer's documentation. Subsections diff --git a/docs/html/node90.html b/docs/html/node90.html index 84cafa51..06a82601 100644 --- a/docs/html/node90.html +++ b/docs/html/node90.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node91.html b/docs/html/node91.html index 8f42455e..d636cd7a 100644 --- a/docs/html/node91.html +++ b/docs/html/node91.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node92.html b/docs/html/node92.html index 71988886..874ce23a 100644 --- a/docs/html/node92.html +++ b/docs/html/node92.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node93.html b/docs/html/node93.html index 9abcf1fa..675e81fa 100644 --- a/docs/html/node93.html +++ b/docs/html/node93.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node94.html b/docs/html/node94.html index 5d30b949..b58a1ece 100644 --- a/docs/html/node94.html +++ b/docs/html/node94.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node95.html b/docs/html/node95.html index b53e1e39..e82e5e78 100644 --- a/docs/html/node95.html +++ b/docs/html/node95.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node96.html b/docs/html/node96.html index 4d678841..9804dc41 100644 --- a/docs/html/node96.html +++ b/docs/html/node96.html @@ -23,26 +23,26 @@ @@ -78,7 +78,7 @@ Intent: in.
    Specified as: an integer $>0$.
    a
    @@ -114,7 +114,7 @@ Intent: in.
    Specified as: an integer $>0$. When append is true, specifies how many entries in the output vectors are already filled. @@ -129,10 +129,10 @@ Intent: in.
    Specified as: an integer $>0$, default: $row$.

    @@ -207,12 +207,12 @@ An integer value; 0 means no error has been detected.

    1. The output $nz$ is always the size of the output generated by the current call; thus, if append=.true., the total output size will be $nzin+nz$, with the newly extracted coefficients stored in entries nzin+1:nzin+nz of the array arguments;
    2. @@ -229,26 +229,26 @@ An integer value; 0 means no error has been detected. diff --git a/docs/html/node97.html b/docs/html/node97.html index ed85f3cd..7f94cf70 100644 --- a/docs/html/node97.html +++ b/docs/html/node97.html @@ -23,26 +23,26 @@ diff --git a/docs/html/node98.html b/docs/html/node98.html index c93a9d41..da637e10 100644 --- a/docs/html/node98.html +++ b/docs/html/node98.html @@ -22,26 +22,26 @@ @@ -70,7 +70,7 @@ call psb_hsort(x,ix,dir,flag)

      These serial routines sort a sequence $X$ into ascending or descending order. The argument meaning is identical for the three calls; the only difference is the algorithm used to accomplish the @@ -96,7 +96,7 @@ Type:optional.
      Specified as: an integer array of (at least) the same size as $X$.

      dir
      @@ -120,7 +120,7 @@ default psb_lsort_up_.
      flag
      Whether to keep the original values in $IX$.
      Type:optional. @@ -182,10 +182,10 @@ position as the corresponding entries in $flag = psb\_sort\_ovw\_idx\_$ then the entries in $ix(1:n)$ where $ix(i) \leftarrow
 i$; thus, upon return from the subroutine, for each index ; thus, upon return from the subroutine, for each SRC="img4.png" ALT="$i$"> we have in $ix(i)$ the position that the item $x(i)$ occupied in the original data sequence; @@ -219,16 +219,16 @@ i$">; thus, upon return from the subroutine, for each --> $flag = psb\_sort\_keep\_idx\_$ the routine will assume that the entries in $ix(:)$ have already been initialized by the user;
    3. The three sorting algorithms have a similar $O(n \log n)$ expected running time; in the average case quicksort will be the fastest and merge-sort the slowest. However note that: @@ -236,7 +236,7 @@ i$">; thus, upon return from the subroutine, for each
      1. The worst case running time for quicksort is $O(n^2)$; the algorithm implemented here follows the well-known median-of-three heuristics, but the worst case may still apply; @@ -244,7 +244,7 @@ i$">; thus, upon return from the subroutine, for each
      2. The worst case running time for merge-sort and heap-sort is $O(n \log n)$ as the average case;
      3. The merge-sort algorithm is implemented to take advantage of @@ -264,26 +264,26 @@ i$">; thus, upon return from the subroutine, for each diff --git a/docs/html/node99.html b/docs/html/node99.html index 846e4c02..95f9a443 100644 --- a/docs/html/node99.html +++ b/docs/html/node99.html @@ -14,7 +14,7 @@ - + @@ -23,26 +23,26 @@ @@ -60,42 +60,44 @@ Parallel environment routines Subsections

        diff --git a/docs/html/userhtml.html b/docs/html/userhtml.html index c99b1d18..eba632d1 100644 --- a/docs/html/userhtml.html +++ b/docs/html/userhtml.html @@ -338,68 +338,70 @@ of a dense vector
      4. psb_amn -- Global minimum absolute value
      5. psb_snd -- Send data + HREF="node114.html">psb_nrm2 -- Global 2-norm reduction
      6. psb_rcv -- Receive data + HREF="node115.html">psb_snd -- Send data +
      7. psb_rcv -- Receive data
        -
      8. Error handling
      9. Utilities -
          + HREF="node117.html">Error handling
        • hb_read -- Read a sparse matrix from a file in the - Harwell-Boeing format + HREF="node118.html">Utilities +
          -
        • Preconditioner routines -
          • init -- Initialize a preconditioner + HREF="node125.html">Preconditioner routines +
            -
          • Iterative Methods -

            diff --git a/docs/psblas-3.5.pdf b/docs/psblas-3.5.pdf index c734bf6e..296c255d 100644 --- a/docs/psblas-3.5.pdf +++ b/docs/psblas-3.5.pdf @@ -442,7 +442,7 @@ stream endstream endobj -551 0 obj +555 0 obj << /Length 585 >> @@ -470,7 +470,7 @@ ET endstream endobj -561 0 obj +565 0 obj << /Length 77 >> @@ -485,7 +485,7 @@ ET endstream endobj -612 0 obj +616 0 obj << /Length 16991 >> @@ -1085,19 +1085,19 @@ endobj /Type /ObjStm /N 100 /First 865 -/Length 7353 +/Length 7128 >> stream 403 0 407 44 408 70 411 114 412 140 415 184 416 220 419 264 420 297 423 341 424 368 427 412 428 441 431 485 432 512 435 556 436 583 439 627 440 652 443 696 -444 721 447 765 448 790 451 834 452 859 455 903 456 928 459 972 460 997 463 1041 -464 1066 467 1108 468 1139 471 1183 472 1212 475 1256 476 1283 479 1327 480 1368 483 1412 -484 1450 487 1492 488 1518 491 1562 492 1587 495 1631 496 1657 499 1702 500 1734 503 1779 -504 1813 507 1858 508 1891 511 1936 512 1971 515 2014 516 2055 519 2100 520 2127 523 2172 -524 2200 527 2245 528 2273 531 2318 532 2346 535 2391 536 2411 539 2456 540 2483 543 2526 -544 2561 547 2606 548 2634 549 2679 552 2793 553 2849 3 2905 550 2959 560 3064 562 3178 -559 3235 611 3301 563 3795 564 3941 565 4087 566 4239 567 4391 568 4543 569 4700 570 4852 -571 4998 572 5150 573 5306 574 5453 575 5600 576 5748 577 5896 578 6044 579 6192 580 6340 +444 721 447 765 448 790 451 834 452 859 455 903 456 928 459 972 460 998 463 1042 +464 1067 467 1111 468 1136 471 1178 472 1209 475 1253 476 1282 479 1326 480 1353 483 1397 +484 1438 487 1482 488 1520 491 1562 492 1588 495 1632 496 1657 499 1702 500 1728 503 1773 +504 1805 507 1850 508 1884 511 1929 512 1962 515 2007 516 2042 519 2085 520 2126 523 2171 +524 2198 527 2243 528 2271 531 2316 532 2344 535 2389 536 2417 539 2462 540 2482 543 2527 +544 2554 547 2597 548 2632 551 2677 552 2705 553 2750 556 2864 557 2920 3 2976 554 3030 +564 3135 566 3249 563 3306 615 3372 567 3866 568 4012 569 4158 570 4310 571 4462 572 4614 +573 4771 574 4923 575 5069 576 5221 577 5377 578 5524 579 5671 580 5819 581 5967 582 6115 % 403 0 obj << /S /GoTo /D (section*.79) >> % 407 0 obj @@ -1153,149 +1153,153 @@ stream % 456 0 obj << /S /GoTo /D (section*.92) >> % 459 0 obj -(psb\137snd) +(psb\137nrm2) % 460 0 obj << /S /GoTo /D (section*.93) >> % 463 0 obj -(psb\137rcv) +(psb\137snd) % 464 0 obj -<< /S /GoTo /D (section.8) >> +<< /S /GoTo /D (section*.94) >> % 467 0 obj -(8 Error handling) +(psb\137rcv) % 468 0 obj -<< /S /GoTo /D (section*.94) >> +<< /S /GoTo /D (section.8) >> % 471 0 obj -(psb\137errpush) +(8 Error handling) % 472 0 obj << /S /GoTo /D (section*.95) >> % 475 0 obj -(psb\137error) +(psb\137errpush) % 476 0 obj << /S /GoTo /D (section*.96) >> % 479 0 obj -(psb\137set\137errverbosity) +(psb\137error) % 480 0 obj << /S /GoTo /D (section*.97) >> % 483 0 obj -(psb\137set\137erraction) +(psb\137set\137errverbosity) % 484 0 obj -<< /S /GoTo /D (section.9) >> +<< /S /GoTo /D (section*.98) >> % 487 0 obj -(9 Utilities) +(psb\137set\137erraction) % 488 0 obj -<< /S /GoTo /D (section*.98) >> +<< /S /GoTo /D (section.9) >> % 491 0 obj -(hb\137read) +(9 Utilities) % 492 0 obj << /S /GoTo /D (section*.99) >> % 495 0 obj -(hb\137write) +(hb\137read) % 496 0 obj << /S /GoTo /D (section*.100) >> % 499 0 obj -(mm\137mat\137read) +(hb\137write) % 500 0 obj << /S /GoTo /D (section*.101) >> % 503 0 obj -(mm\137array\137read) +(mm\137mat\137read) % 504 0 obj << /S /GoTo /D (section*.102) >> % 507 0 obj -(mm\137mat\137write) +(mm\137array\137read) % 508 0 obj << /S /GoTo /D (section*.103) >> % 511 0 obj -(mm\137array\137write) +(mm\137mat\137write) % 512 0 obj -<< /S /GoTo /D (section.10) >> +<< /S /GoTo /D (section*.104) >> % 515 0 obj -(10 Preconditioner routines) +(mm\137array\137write) % 516 0 obj -<< /S /GoTo /D (section*.104) >> +<< /S /GoTo /D (section.10) >> % 519 0 obj -(prec\045init) +(10 Preconditioner routines) % 520 0 obj << /S /GoTo /D (section*.105) >> % 523 0 obj -(prec\045build) +(prec\045init) % 524 0 obj << /S /GoTo /D (section*.106) >> % 527 0 obj -(prec\045apply) +(prec\045build) % 528 0 obj << /S /GoTo /D (section*.107) >> % 531 0 obj -(prec\045descr) +(prec\045apply) % 532 0 obj << /S /GoTo /D (section*.108) >> % 535 0 obj -(clone) +(prec\045descr) % 536 0 obj << /S /GoTo /D (section*.109) >> % 539 0 obj -(prec\045free) +(clone) % 540 0 obj -<< /S /GoTo /D (section.11) >> +<< /S /GoTo /D (section*.110) >> % 543 0 obj -(11 Iterative Methods) +(prec\045free) % 544 0 obj -<< /S /GoTo /D (section*.110) >> +<< /S /GoTo /D (section.11) >> % 547 0 obj -(psb\137krylov) +(11 Iterative Methods) % 548 0 obj -<< /S /GoTo /D [549 0 R /Fit] >> -% 549 0 obj +<< /S /GoTo /D (section*.111) >> +% 551 0 obj +(psb\137krylov) +% 552 0 obj +<< /S /GoTo /D [553 0 R /Fit] >> +% 553 0 obj << /Type /Page -/Contents 551 0 R -/Resources 550 0 R +/Contents 555 0 R +/Resources 554 0 R /MediaBox [0 0 595.276 841.89] -/Parent 558 0 R +/Parent 562 0 R >> -% 552 0 obj +% 556 0 obj << -/D [549 0 R /XYZ 98.895 753.953 null] +/D [553 0 R /XYZ 98.895 753.953 null] >> -% 553 0 obj +% 557 0 obj << -/D [549 0 R /XYZ 99.895 716.092 null] +/D [553 0 R /XYZ 99.895 716.092 null] >> % 3 0 obj << -/D [549 0 R /XYZ 99.895 716.092 null] +/D [553 0 R /XYZ 99.895 716.092 null] >> -% 550 0 obj +% 554 0 obj << -/Font << /F16 554 0 R /F18 555 0 R /F27 556 0 R /F8 557 0 R >> +/Font << /F16 558 0 R /F18 559 0 R /F27 560 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 560 0 obj +% 564 0 obj << /Type /Page -/Contents 561 0 R -/Resources 559 0 R +/Contents 565 0 R +/Resources 563 0 R /MediaBox [0 0 595.276 841.89] -/Parent 558 0 R +/Parent 562 0 R >> -% 562 0 obj +% 566 0 obj << -/D [560 0 R /XYZ 149.705 753.953 null] +/D [564 0 R /XYZ 149.705 753.953 null] >> -% 559 0 obj +% 563 0 obj << -/Font << /F8 557 0 R >> +/Font << /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 611 0 obj +% 615 0 obj << /Type /Page -/Contents 612 0 R -/Resources 610 0 R +/Contents 616 0 R +/Resources 614 0 R /MediaBox [0 0 595.276 841.89] -/Parent 558 0 R -/Annots [ 563 0 R 564 0 R 565 0 R 566 0 R 567 0 R 568 0 R 569 0 R 570 0 R 571 0 R 572 0 R 573 0 R 574 0 R 575 0 R 576 0 R 577 0 R 578 0 R 579 0 R 580 0 R 581 0 R 582 0 R 583 0 R 584 0 R 585 0 R 586 0 R 587 0 R 588 0 R 589 0 R 590 0 R 591 0 R 592 0 R 593 0 R 594 0 R 595 0 R 596 0 R 597 0 R 598 0 R 599 0 R 600 0 R 601 0 R 602 0 R 603 0 R 604 0 R 605 0 R 606 0 R 607 0 R 608 0 R ] +/Parent 562 0 R +/Annots [ 567 0 R 568 0 R 569 0 R 570 0 R 571 0 R 572 0 R 573 0 R 574 0 R 575 0 R 576 0 R 577 0 R 578 0 R 579 0 R 580 0 R 581 0 R 582 0 R 583 0 R 584 0 R 585 0 R 586 0 R 587 0 R 588 0 R 589 0 R 590 0 R 591 0 R 592 0 R 593 0 R 594 0 R 595 0 R 596 0 R 597 0 R 598 0 R 599 0 R 600 0 R 601 0 R 602 0 R 603 0 R 604 0 R 605 0 R 606 0 R 607 0 R 608 0 R 609 0 R 610 0 R 611 0 R 612 0 R ] >> -% 563 0 obj +% 567 0 obj << /Type /Annot /Subtype /Link @@ -1303,7 +1307,7 @@ stream /Rect [98.899 683.007 179.001 691.918] /A << /S /GoTo /D (section.1) >> >> -% 564 0 obj +% 568 0 obj << /Type /Annot /Subtype /Link @@ -1311,7 +1315,7 @@ stream /Rect [98.899 660.882 202.863 669.793] /A << /S /GoTo /D (section.2) >> >> -% 565 0 obj +% 569 0 obj << /Type /Annot /Subtype /Link @@ -1319,7 +1323,7 @@ stream /Rect [113.843 648.802 225.868 657.713] /A << /S /GoTo /D (subsection.2.1) >> >> -% 566 0 obj +% 570 0 obj << /Type /Annot /Subtype /Link @@ -1327,7 +1331,7 @@ stream /Rect [113.843 634.785 210.675 645.633] /A << /S /GoTo /D (subsection.2.2) >> >> -% 567 0 obj +% 571 0 obj << /Type /Annot /Subtype /Link @@ -1335,7 +1339,7 @@ stream /Rect [113.843 622.706 232.122 633.554] /A << /S /GoTo /D (subsection.2.3) >> >> -% 568 0 obj +% 572 0 obj << /Type /Annot /Subtype /Link @@ -1343,7 +1347,7 @@ stream /Rect [136.757 610.626 296.409 621.474] /A << /S /GoTo /D (subsubsection.2.3.1) >> >> -% 569 0 obj +% 573 0 obj << /Type /Annot /Subtype /Link @@ -1351,7 +1355,7 @@ stream /Rect [113.843 598.546 227.777 609.394] /A << /S /GoTo /D (subsection.2.4) >> >> -% 570 0 obj +% 574 0 obj << /Type /Annot /Subtype /Link @@ -1359,7 +1363,7 @@ stream /Rect [98.899 578.358 258.112 587.269] /A << /S /GoTo /D (section.3) >> >> -% 571 0 obj +% 575 0 obj << /Type /Annot /Subtype /Link @@ -1367,7 +1371,7 @@ stream /Rect [113.843 564.341 249.529 575.189] /A << /S /GoTo /D (subsection.3.1) >> >> -% 572 0 obj +% 576 0 obj << /Type /Annot /Subtype /Link @@ -1375,7 +1379,7 @@ stream /Rect [136.757 552.261 257.001 563.11] /A << /S /GoTo /D (subsubsection.3.1.1) >> >> -% 573 0 obj +% 577 0 obj << /Type /Annot /Subtype /Link @@ -1383,7 +1387,7 @@ stream /Rect [168.638 540.182 231.021 551.03] /A << /S /GoTo /D (section*.2) >> >> -% 574 0 obj +% 578 0 obj << /Type /Annot /Subtype /Link @@ -1391,7 +1395,7 @@ stream /Rect [168.638 528.102 227.395 538.95] /A << /S /GoTo /D (section*.3) >> >> -% 575 0 obj +% 579 0 obj << /Type /Annot /Subtype /Link @@ -1399,7 +1403,7 @@ stream /Rect [168.638 516.022 236.832 526.871] /A << /S /GoTo /D (section*.4) >> >> -% 576 0 obj +% 580 0 obj << /Type /Annot /Subtype /Link @@ -1407,7 +1411,7 @@ stream /Rect [168.638 503.943 233.207 514.791] /A << /S /GoTo /D (section*.5) >> >> -% 577 0 obj +% 581 0 obj << /Type /Annot /Subtype /Link @@ -1415,7 +1419,7 @@ stream /Rect [168.638 491.863 236.832 502.711] /A << /S /GoTo /D (section*.6) >> >> -% 578 0 obj +% 582 0 obj << /Type /Annot /Subtype /Link @@ -1423,26 +1427,10 @@ stream /Rect [168.638 479.783 219.602 490.133] /A << /S /GoTo /D (section*.7) >> >> -% 579 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [168.638 469.641 195.537 478.552] -/A << /S /GoTo /D (section*.8) >> ->> -% 580 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [168.638 457.561 192.769 466.361] -/A << /S /GoTo /D (section*.9) >> ->> endstream endobj -665 0 obj +669 0 obj << /Length 20672 >> @@ -1557,7 +1545,7 @@ BT 0 g 0 G [-962(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(36)]TJ + [-1084(37)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.08 Td [(psb)]TJ @@ -1571,7 +1559,7 @@ BT 0 g 0 G [-326(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(37)]TJ + [-1084(38)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.08 Td [(psb)]TJ @@ -1585,7 +1573,7 @@ BT 0 g 0 G [-262(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(38)]TJ + [-1084(40)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.079 Td [(psb)]TJ @@ -1599,7 +1587,7 @@ BT 0 g 0 G [-326(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(40)]TJ + [-1084(42)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.08 Td [(psb)]TJ @@ -1613,7 +1601,7 @@ BT 0 g 0 G [-265(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(41)]TJ + [-1084(44)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.08 Td [(psb)]TJ @@ -1627,7 +1615,7 @@ BT 0 g 0 G [-326(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(42)]TJ + [-1084(45)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.079 Td [(psb)]TJ @@ -1641,7 +1629,7 @@ BT 0 g 0 G [-548(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(43)]TJ + [-1084(46)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.08 Td [(psb)]TJ @@ -1655,7 +1643,7 @@ BT 0 g 0 G [-490(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(44)]TJ + [-1084(47)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.08 Td [(psb)]TJ @@ -1669,12 +1657,12 @@ BT 0 g 0 G [-929(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(46)]TJ + [-1084(49)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG /F27 9.9626 Tf -33.53 -22.125 Td [(5)-925(Comm)32(unication)-383(r)-1(ou)1(t)-1(ines)]TJ 0 g 0 G - [-19454(49)]TJ + [-19454(52)]TJ 0 0 1 rg 0 0 1 RG /F8 9.9626 Tf 14.944 -12.08 Td [(psb)]TJ ET @@ -1687,7 +1675,7 @@ BT 0 g 0 G [-495(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(50)]TJ + [-1084(53)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.079 Td [(psb)]TJ @@ -1701,7 +1689,7 @@ BT 0 g 0 G [-659(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ 0 g 0 G - [-1084(53)]TJ + [-1084(56)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.08 Td [(psb)]TJ @@ -1715,7 +1703,7 @@ BT 0 g 0 G [-326(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(57)]TJ + [-1084(60)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.08 Td [(psb)]TJ @@ -1729,12 +1717,12 @@ BT 0 g 0 G [-932(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1083(59)]TJ + [-1083(62)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG /F27 9.9626 Tf -33.53 -22.125 Td [(6)-925(Data)-383(managem)-1(e)1(n)31(t)-383(routines)]TJ 0 g 0 G - [-18205(61)]TJ + [-18205(64)]TJ 0 0 1 rg 0 0 1 RG /F8 9.9626 Tf 14.944 -12.08 Td [(psb)]TJ ET @@ -1747,7 +1735,7 @@ BT 0 g 0 G [-273(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(61)]TJ + [-1084(64)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.08 Td [(psb)]TJ @@ -1761,7 +1749,7 @@ BT 0 g 0 G [-879(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(65)]TJ + [-1084(68)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.079 Td [(psb)]TJ @@ -1775,7 +1763,7 @@ BT 0 g 0 G [-657(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1083(67)]TJ + [-1083(70)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.08 Td [(psb)]TJ @@ -1789,7 +1777,7 @@ BT 0 g 0 G [-607(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(68)]TJ + [-1084(71)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.08 Td [(psb)]TJ @@ -1803,7 +1791,7 @@ BT 0 g 0 G [-520(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(69)]TJ + [-1084(72)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.079 Td [(psb)]TJ @@ -1817,7 +1805,7 @@ BT 0 g 0 G [-912(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(70)]TJ + [-1084(73)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.08 Td [(psb)]TJ @@ -1831,7 +1819,7 @@ BT 0 g 0 G [-323(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(72)]TJ + [-1084(75)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.08 Td [(psb)]TJ @@ -1845,7 +1833,7 @@ BT 0 g 0 G [-929(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(73)]TJ + [-1084(76)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.08 Td [(psb)]TJ @@ -1859,7 +1847,7 @@ BT 0 g 0 G [-707(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1083(75)]TJ + [-1083(78)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.079 Td [(psb)]TJ @@ -1873,7 +1861,7 @@ BT 0 g 0 G [-570(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(77)]TJ + [-1084(80)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.08 Td [(psb)]TJ @@ -1887,7 +1875,7 @@ BT 0 g 0 G [-431(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ 0 g 0 G - [-1084(78)]TJ + [-1084(81)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.08 Td [(psb)]TJ @@ -1901,7 +1889,7 @@ BT 0 g 0 G [-329(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(79)]TJ + [-1084(82)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.079 Td [(psb)]TJ @@ -1915,7 +1903,7 @@ BT 0 g 0 G [-934(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(80)]TJ + [-1084(83)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.08 Td [(psb)]TJ @@ -1929,7 +1917,7 @@ BT 0 g 0 G [-712(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(82)]TJ + [-1084(85)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.08 Td [(psb)]TJ @@ -1943,7 +1931,7 @@ BT 0 g 0 G [-576(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(83)]TJ + [-1084(86)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.079 Td [(psb)]TJ @@ -1957,7 +1945,7 @@ BT 0 g 0 G [-551(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(84)]TJ + [-1084(87)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -12.08 Td [(psb)]TJ @@ -1985,7 +1973,7 @@ BT 0 g 0 G [-747(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1083(85)]TJ + [-1083(88)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -52.879 -12.08 Td [(psb)]TJ @@ -2013,7 +2001,7 @@ BT 0 g 0 G [-748(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1083(87)]TJ + [-1083(90)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -47.068 -12.08 Td [(psb)]TJ @@ -2034,7 +2022,7 @@ BT 0 g 0 G [-880(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(88)]TJ + [-1084(91)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -28.869 -12.079 Td [(psb)]TJ @@ -2055,7 +2043,7 @@ BT 0 g 0 G [-746(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1083(89)]TJ + [-1083(92)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -49.57 -12.08 Td [(psb)]TJ @@ -2076,7 +2064,7 @@ BT 0 g 0 G [-824(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(90)]TJ + [-1084(93)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -28.869 -12.08 Td [(psb)]TJ @@ -2097,7 +2085,7 @@ BT 0 g 0 G [-691(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(91)]TJ + [-1084(94)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -42.374 -12.079 Td [(psb)]TJ @@ -2118,7 +2106,7 @@ BT 0 g 0 G [-354(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1083(92)]TJ + [-1083(95)]TJ 0 g 0 G 0 g 0 G 118.688 -29.888 Td [(ii)]TJ @@ -2127,9 +2115,9 @@ ET endstream endobj -710 0 obj +715 0 obj << -/Length 17570 +/Length 18018 >> stream 0 g 0 G @@ -2154,7 +2142,7 @@ BT 0 g 0 G [-605(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(93)]TJ + [-1084(96)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -35.456 -11.955 Td [(psb)]TJ @@ -2175,7 +2163,7 @@ BT 0 g 0 G [-433(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(94)]TJ + [-1084(97)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -31.637 -11.955 Td [(psb)]TJ @@ -2189,19 +2177,19 @@ BT 0 g 0 G [-740(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1084(96)]TJ + [-1084(99)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -11.956 Td [(Sorting)-333(utilities)]TJ 0 g 0 G [-519(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-1083(97)]TJ + [-583(100)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG /F27 9.9626 Tf -14.944 -21.917 Td [(7)-925(P)32(arallel)-384(en)32(vironmen)32(t)-383(routines)]TJ 0 g 0 G - [-16891(99)]TJ + [-16316(102)]TJ 0 0 1 rg 0 0 1 RG /F8 9.9626 Tf 14.944 -11.956 Td [(psb)]TJ ET @@ -2214,7 +2202,7 @@ BT 0 g 0 G [-829(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-583(100)]TJ + [-583(103)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -11.955 Td [(psb)]TJ @@ -2228,7 +2216,7 @@ BT 0 g 0 G [-690(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(101)]TJ + [-584(104)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -11.955 Td [(psb)]TJ @@ -2242,7 +2230,7 @@ BT 0 g 0 G [-690(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(102)]TJ + [-584(105)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -11.955 Td [(psb)]TJ @@ -2263,7 +2251,7 @@ BT 0 g 0 G [-1024(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-583(103)]TJ + [-583(106)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -35.456 -11.955 Td [(psb)]TJ @@ -2284,7 +2272,7 @@ BT 0 g 0 G [-994(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(104)]TJ + [-584(107)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -35.456 -11.955 Td [(psb)]TJ @@ -2298,7 +2286,7 @@ BT 0 g 0 G [-440(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(105)]TJ + [-584(108)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -11.956 Td [(psb)]TJ @@ -2312,7 +2300,7 @@ BT 0 g 0 G [-931(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)]TJ 0 g 0 G - [-584(106)]TJ + [-584(109)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -11.955 Td [(psb)]TJ @@ -2326,7 +2314,7 @@ BT 0 g 0 G [-742(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(107)]TJ + [-584(110)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -11.955 Td [(psb)]TJ @@ -2340,7 +2328,7 @@ BT 0 g 0 G [-795(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(108)]TJ + [-584(111)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -11.955 Td [(psb)]TJ @@ -2354,7 +2342,7 @@ BT 0 g 0 G [-546(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)]TJ 0 g 0 G - [-584(109)]TJ + [-584(112)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -11.955 Td [(psb)]TJ @@ -2368,7 +2356,7 @@ BT 0 g 0 G [-468(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-583(110)]TJ + [-583(113)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -11.955 Td [(psb)]TJ @@ -2382,7 +2370,7 @@ BT 0 g 0 G [-662(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(111)]TJ + [-584(114)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -11.956 Td [(psb)]TJ @@ -2396,7 +2384,7 @@ BT 0 g 0 G [-468(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-583(112)]TJ + [-583(115)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -11.955 Td [(psb)]TJ @@ -2410,7 +2398,7 @@ BT 0 g 0 G [-440(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(113)]TJ + [-584(116)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -11.955 Td [(psb)]TJ @@ -2420,11 +2408,11 @@ q []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 133.425 469.018 Td [(snd)]TJ +/F8 9.9626 Tf 133.425 469.018 Td [(nrm2)]TJ 0 g 0 G - [-823(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ + [-826(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(114)]TJ + [-584(117)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -11.955 Td [(psb)]TJ @@ -2434,292 +2422,322 @@ q []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 133.425 457.063 Td [(rcv)]TJ +/F8 9.9626 Tf 133.425 457.063 Td [(snd)]TJ +0 g 0 G + [-823(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ +0 g 0 G + [-584(118)]TJ +0 g 0 G +0 0 1 rg 0 0 1 RG + -18.586 -11.955 Td [(psb)]TJ +ET +q +1 0 0 1 130.436 445.307 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 133.425 445.108 Td [(rcv)]TJ 0 g 0 G [-965(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(115)]TJ + [-584(119)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG /F27 9.9626 Tf -33.53 -21.918 Td [(8)-925(Error)-383(handling)]TJ 0 g 0 G - [-23812(116)]TJ + [-23812(120)]TJ 0 0 1 rg 0 0 1 RG /F8 9.9626 Tf 14.944 -11.955 Td [(psb)]TJ ET q -1 0 0 1 130.436 423.389 cm +1 0 0 1 130.436 411.434 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 133.425 423.19 Td [(errpush)]TJ +/F8 9.9626 Tf 133.425 411.235 Td [(errpush)]TJ 0 g 0 G [-595(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(118)]TJ + [-584(122)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -18.586 -11.955 Td [(psb)]TJ ET q -1 0 0 1 130.436 411.434 cm +1 0 0 1 130.436 399.479 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 133.425 411.235 Td [(error)]TJ +/F8 9.9626 Tf 133.425 399.28 Td [(error)]TJ 0 g 0 G [-987(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(119)]TJ + [-584(123)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG - -18.586 -11.955 Td [(psb)]TJ + -18.586 -11.956 Td [(psb)]TJ ET q -1 0 0 1 130.436 399.479 cm +1 0 0 1 130.436 387.524 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 133.425 399.28 Td [(set)]TJ +/F8 9.9626 Tf 133.425 387.324 Td [(set)]TJ ET q -1 0 0 1 146.255 399.479 cm +1 0 0 1 146.255 387.524 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 149.244 399.28 Td [(errv)28(erb)-28(osit)28(y)]TJ +/F8 9.9626 Tf 149.244 387.324 Td [(errv)28(erb)-28(osit)28(y)]TJ 0 g 0 G [-977(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(120)]TJ + [-584(124)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG - -34.405 -11.956 Td [(psb)]TJ + -34.405 -11.955 Td [(psb)]TJ ET q -1 0 0 1 130.436 387.524 cm +1 0 0 1 130.436 375.568 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 133.425 387.324 Td [(set)]TJ +/F8 9.9626 Tf 133.425 375.369 Td [(set)]TJ ET q -1 0 0 1 146.255 387.524 cm +1 0 0 1 146.255 375.568 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 149.244 387.324 Td [(erraction)]TJ +/F8 9.9626 Tf 149.244 375.369 Td [(erraction)]TJ 0 g 0 G [-735(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ 0 g 0 G - [-584(121)]TJ + [-584(125)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -/F27 9.9626 Tf -49.349 -21.917 Td [(9)-925(Utilities)]TJ +/F27 9.9626 Tf -49.349 -21.918 Td [(9)-925(Utilities)]TJ 0 g 0 G - [-27238(122)]TJ + [-27238(126)]TJ 0 0 1 rg 0 0 1 RG -/F8 9.9626 Tf 14.944 -11.956 Td [(h)28(b)]TJ +/F8 9.9626 Tf 14.944 -11.955 Td [(h)28(b)]TJ ET q -1 0 0 1 126.23 353.651 cm +1 0 0 1 126.23 341.695 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 129.219 353.451 Td [(read)]TJ +/F8 9.9626 Tf 129.219 341.496 Td [(read)]TJ 0 g 0 G [-859(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(123)]TJ + [-584(127)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -14.38 -11.955 Td [(h)28(b)]TJ ET q -1 0 0 1 126.23 341.695 cm +1 0 0 1 126.23 329.74 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 129.219 341.496 Td [(write)]TJ +/F8 9.9626 Tf 129.219 329.541 Td [(write)]TJ 0 g 0 G [-526(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(124)]TJ + [-584(128)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -14.38 -11.955 Td [(mm)]TJ ET q -1 0 0 1 132.042 329.74 cm +1 0 0 1 132.042 317.785 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 135.03 329.541 Td [(mat)]TJ +/F8 9.9626 Tf 135.03 317.586 Td [(mat)]TJ ET q -1 0 0 1 152.786 329.74 cm +1 0 0 1 152.786 317.785 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 155.775 329.541 Td [(read)]TJ +/F8 9.9626 Tf 155.775 317.586 Td [(read)]TJ 0 g 0 G [-527(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(125)]TJ + [-584(129)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -40.936 -11.955 Td [(mm)]TJ ET q -1 0 0 1 132.042 317.785 cm +1 0 0 1 132.042 305.83 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 135.03 317.586 Td [(arra)28(y)]TJ +/F8 9.9626 Tf 135.03 305.631 Td [(arra)28(y)]TJ ET q -1 0 0 1 158.376 317.785 cm +1 0 0 1 158.376 305.83 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 161.365 317.586 Td [(read)]TJ +/F8 9.9626 Tf 161.365 305.631 Td [(read)]TJ 0 g 0 G [-744(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(126)]TJ + [-584(130)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -46.526 -11.955 Td [(mm)]TJ ET q -1 0 0 1 132.042 305.83 cm +1 0 0 1 132.042 293.875 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 135.03 305.631 Td [(mat)]TJ +/F8 9.9626 Tf 135.03 293.676 Td [(mat)]TJ ET q -1 0 0 1 152.786 305.83 cm +1 0 0 1 152.786 293.875 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 155.775 305.631 Td [(write)]TJ +/F8 9.9626 Tf 155.775 293.676 Td [(write)]TJ 0 g 0 G [-972(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-583(127)]TJ + [-583(131)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG - -40.936 -11.955 Td [(mm)]TJ + -40.936 -11.956 Td [(mm)]TJ ET q -1 0 0 1 132.042 293.875 cm +1 0 0 1 132.042 281.92 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 135.03 293.676 Td [(arra)28(y)]TJ +/F8 9.9626 Tf 135.03 281.72 Td [(arra)28(y)]TJ ET q -1 0 0 1 158.376 293.875 cm +1 0 0 1 158.376 281.92 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 161.365 293.676 Td [(write)]TJ +/F8 9.9626 Tf 161.365 281.72 Td [(write)]TJ 0 g 0 G [-410(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-583(128)]TJ + [-583(132)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -/F27 9.9626 Tf -61.47 -21.918 Td [(10)-350(Preconditioner)-383(routi)-1(n)1(es)]TJ +/F27 9.9626 Tf -61.47 -21.917 Td [(10)-350(Preconditioner)-383(routi)-1(n)1(es)]TJ 0 g 0 G - [-19367(129)]TJ + [-19367(133)]TJ 0 0 1 rg 0 0 1 RG -/F8 9.9626 Tf 14.944 -11.955 Td [(prec%init)]TJ +/F8 9.9626 Tf 14.944 -11.956 Td [(prec%init)]TJ 0 g 0 G [-803(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-583(130)]TJ + [-583(134)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG - 0 -11.956 Td [(prec%build)]TJ + 0 -11.955 Td [(prec%build)]TJ 0 g 0 G [-858(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(131)]TJ + [-584(135)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG 0 -11.955 Td [(prec%apply)]TJ 0 g 0 G [-664(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(133)]TJ + [-584(137)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG 0 -11.955 Td [(prec%descr)]TJ 0 g 0 G [-850(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-584(134)]TJ + [-584(138)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG 0 -11.955 Td [(clone)]TJ 0 g 0 G [-417(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-583(135)]TJ + [-583(139)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG - 0 -11.955 Td [(prec%free)]TJ + 0 -11.956 Td [(prec%free)]TJ 0 g 0 G [-717(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-583(136)]TJ + [-583(140)]TJ 0 g 0 G 0 0 1 rg 0 0 1 RG -/F27 9.9626 Tf -14.944 -21.918 Td [(11)-350(Iterativ)32(e)-384(Metho)-31(ds)]TJ +/F27 9.9626 Tf -14.944 -21.917 Td [(11)-350(Iterativ)32(e)-384(Metho)-31(ds)]TJ 0 g 0 G - [-22176(137)]TJ + [-22176(141)]TJ 0 0 1 rg 0 0 1 RG -/F8 9.9626 Tf 14.944 -11.955 Td [(psb)]TJ +/F8 9.9626 Tf 14.944 -11.956 Td [(psb)]TJ ET q -1 0 0 1 130.436 166.353 cm +1 0 0 1 130.436 154.398 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 133.425 166.154 Td [(krylo)28(v)]TJ +/F8 9.9626 Tf 133.425 154.199 Td [(krylo)28(v)]TJ 0 g 0 G [-382(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)-500(.)]TJ 0 g 0 G - [-583(138)]TJ + [-583(142)]TJ 0 g 0 G 0 g 0 G - 134.175 -75.716 Td [(iii)]TJ + 134.175 -63.761 Td [(iii)]TJ 0 g 0 G ET endstream endobj -615 0 obj +619 0 obj << /Type /ObjStm /N 100 /First 924 -/Length 16082 +/Length 16089 >> stream -581 0 582 149 583 298 584 455 585 607 586 763 587 912 588 1061 589 1210 590 1358 -591 1507 592 1656 593 1805 594 1954 595 2103 596 2252 597 2401 598 2550 599 2699 600 2848 -601 2997 602 3145 603 3294 604 3451 605 3603 606 3759 607 3908 608 4056 613 4205 614 4261 -610 4317 664 4409 609 4911 616 5060 617 5209 618 5361 619 5513 620 5660 621 5809 622 5957 -623 6104 624 6252 625 6401 626 6550 627 6699 628 6848 629 6996 630 7145 631 7294 632 7441 -633 7590 634 7737 635 7885 636 8033 637 8181 638 8330 639 8476 640 8624 641 8773 642 8922 -643 9071 644 9220 645 9369 646 9518 647 9667 648 9816 649 9965 650 10114 651 10263 652 10412 -653 10561 654 10709 655 10857 656 11005 657 11154 658 11303 659 11451 660 11598 661 11746 666 11893 -663 11950 709 12029 662 12491 667 12640 668 12788 669 12933 670 13081 671 13226 672 13375 673 13523 -674 13672 675 13819 676 13968 677 14117 678 14266 679 14415 680 14564 681 14712 682 14861 683 15009 -% 581 0 obj +583 0 584 148 585 296 586 445 587 594 588 751 589 903 590 1059 591 1208 592 1357 +593 1506 594 1654 595 1803 596 1952 597 2101 598 2250 599 2399 600 2548 601 2697 602 2846 +603 2995 604 3144 605 3293 606 3441 607 3590 608 3747 609 3899 610 4055 611 4204 612 4352 +617 4501 618 4557 614 4613 668 4705 613 5207 620 5356 621 5505 622 5657 623 5809 624 5956 +625 6105 626 6253 627 6400 628 6548 629 6697 630 6846 631 6995 632 7144 633 7292 634 7441 +635 7590 636 7737 637 7886 638 8033 639 8181 640 8329 641 8477 642 8626 643 8772 644 8920 +645 9069 646 9218 647 9367 648 9516 649 9665 650 9814 651 9963 652 10112 653 10261 654 10410 +655 10559 656 10708 657 10857 658 11005 659 11153 660 11301 661 11450 662 11599 663 11747 664 11894 +665 12042 670 12189 667 12246 714 12325 666 12795 671 12944 672 13092 673 13237 674 13385 675 13530 +676 13679 677 13827 678 13976 679 14123 680 14272 681 14421 682 14570 683 14719 684 14868 685 15016 +% 583 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [168.638 469.641 195.537 478.552] +/A << /S /GoTo /D (section*.8) >> +>> +% 584 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [168.638 457.561 192.769 466.361] +/A << /S /GoTo /D (section*.9) >> +>> +% 585 0 obj << /Type /Annot /Subtype /Link @@ -2727,7 +2745,7 @@ stream /Rect [168.638 443.544 284.769 454.392] /A << /S /GoTo /D (section*.10) >> >> -% 582 0 obj +% 586 0 obj << /Type /Annot /Subtype /Link @@ -2735,7 +2753,7 @@ stream /Rect [168.638 431.464 283.717 442.313] /A << /S /GoTo /D (section*.11) >> >> -% 583 0 obj +% 587 0 obj << /Type /Annot /Subtype /Link @@ -2743,7 +2761,7 @@ stream /Rect [136.757 421.322 248.228 430.233] /A << /S /GoTo /D (subsubsection.3.1.2) >> >> -% 584 0 obj +% 588 0 obj << /Type /Annot /Subtype /Link @@ -2751,7 +2769,7 @@ stream /Rect [113.843 407.305 223.654 418.153] /A << /S /GoTo /D (subsection.3.2) >> >> -% 585 0 obj +% 589 0 obj << /Type /Annot /Subtype /Link @@ -2759,7 +2777,7 @@ stream /Rect [136.757 395.225 273.19 406.074] /A << /S /GoTo /D (subsubsection.3.2.1) >> >> -% 586 0 obj +% 590 0 obj << /Type /Annot /Subtype /Link @@ -2767,7 +2785,7 @@ stream /Rect [168.638 383.146 212.767 393.496] /A << /S /GoTo /D (section*.12) >> >> -% 587 0 obj +% 591 0 obj << /Type /Annot /Subtype /Link @@ -2775,7 +2793,7 @@ stream /Rect [168.638 371.066 209.141 381.914] /A << /S /GoTo /D (section*.13) >> >> -% 588 0 obj +% 592 0 obj << /Type /Annot /Subtype /Link @@ -2783,7 +2801,7 @@ stream /Rect [168.638 358.986 220.239 369.336] /A << /S /GoTo /D (section*.14) >> >> -% 589 0 obj +% 593 0 obj << /Type /Annot /Subtype /Link @@ -2791,7 +2809,7 @@ stream /Rect [168.638 346.906 206.374 357.49] /A << /S /GoTo /D (section*.15) >> >> -% 590 0 obj +% 594 0 obj << /Type /Annot /Subtype /Link @@ -2799,7 +2817,7 @@ stream /Rect [168.638 336.764 197.529 345.675] /A << /S /GoTo /D (section*.16) >> >> -% 591 0 obj +% 595 0 obj << /Type /Annot /Subtype /Link @@ -2807,7 +2825,7 @@ stream /Rect [168.638 322.747 205.765 333.595] /A << /S /GoTo /D (section*.17) >> >> -% 592 0 obj +% 596 0 obj << /Type /Annot /Subtype /Link @@ -2815,7 +2833,7 @@ stream /Rect [168.638 310.667 262.143 321.516] /A << /S /GoTo /D (section*.18) >> >> -% 593 0 obj +% 597 0 obj << /Type /Annot /Subtype /Link @@ -2823,7 +2841,7 @@ stream /Rect [168.638 298.588 328.909 309.436] /A << /S /GoTo /D (section*.19) >> >> -% 594 0 obj +% 598 0 obj << /Type /Annot /Subtype /Link @@ -2831,7 +2849,7 @@ stream /Rect [168.638 288.445 193.932 296.858] /A << /S /GoTo /D (section*.20) >> >> -% 595 0 obj +% 599 0 obj << /Type /Annot /Subtype /Link @@ -2839,7 +2857,7 @@ stream /Rect [168.638 274.428 194.485 285.276] /A << /S /GoTo /D (section*.21) >> >> -% 596 0 obj +% 600 0 obj << /Type /Annot /Subtype /Link @@ -2847,7 +2865,7 @@ stream /Rect [168.638 264.286 218.025 273.197] /A << /S /GoTo /D (section*.22) >> >> -% 597 0 obj +% 601 0 obj << /Type /Annot /Subtype /Link @@ -2855,7 +2873,7 @@ stream /Rect [168.638 250.269 205.765 261.117] /A << /S /GoTo /D (section*.23) >> >> -% 598 0 obj +% 602 0 obj << /Type /Annot /Subtype /Link @@ -2863,7 +2881,7 @@ stream /Rect [168.638 238.189 207.979 249.037] /A << /S /GoTo /D (section*.24) >> >> -% 599 0 obj +% 603 0 obj << /Type /Annot /Subtype /Link @@ -2871,7 +2889,7 @@ stream /Rect [168.638 228.047 183.941 236.958] /A << /S /GoTo /D (section*.25) >> >> -% 600 0 obj +% 604 0 obj << /Type /Annot /Subtype /Link @@ -2879,7 +2897,7 @@ stream /Rect [168.638 215.967 186.709 224.613] /A << /S /GoTo /D (section*.26) >> >> -% 601 0 obj +% 605 0 obj << /Type /Annot /Subtype /Link @@ -2887,7 +2905,7 @@ stream /Rect [168.638 201.95 255.944 212.798] /A << /S /GoTo /D (section*.27) >> >> -% 602 0 obj +% 606 0 obj << /Type /Annot /Subtype /Link @@ -2895,7 +2913,7 @@ stream /Rect [168.638 191.808 192.769 200.719] /A << /S /GoTo /D (section*.28) >> >> -% 603 0 obj +% 607 0 obj << /Type /Annot /Subtype /Link @@ -2903,7 +2921,7 @@ stream /Rect [136.757 179.728 248.228 188.639] /A << /S /GoTo /D (subsubsection.3.2.2) >> >> -% 604 0 obj +% 608 0 obj << /Type /Annot /Subtype /Link @@ -2911,7 +2929,7 @@ stream /Rect [113.843 167.648 265.358 176.448] /A << /S /GoTo /D (subsection.3.3) >> >> -% 605 0 obj +% 609 0 obj << /Type /Annot /Subtype /Link @@ -2919,7 +2937,7 @@ stream /Rect [136.757 155.568 239.898 164.48] /A << /S /GoTo /D (subsubsection.3.3.1) >> >> -% 606 0 obj +% 610 0 obj << /Type /Annot /Subtype /Link @@ -2927,7 +2945,7 @@ stream /Rect [168.638 141.552 212.767 151.902] /A << /S /GoTo /D (section*.29) >> >> -% 607 0 obj +% 611 0 obj << /Type /Annot /Subtype /Link @@ -2935,7 +2953,7 @@ stream /Rect [168.638 131.409 197.529 140.32] /A << /S /GoTo /D (section*.30) >> >> -% 608 0 obj +% 612 0 obj << /Type /Annot /Subtype /Link @@ -2943,29 +2961,29 @@ stream /Rect [168.638 119.329 186.183 127.742] /A << /S /GoTo /D (section*.31) >> >> -% 613 0 obj +% 617 0 obj << -/D [611 0 R /XYZ 98.895 753.953 null] +/D [615 0 R /XYZ 98.895 753.953 null] >> -% 614 0 obj +% 618 0 obj << -/D [611 0 R /XYZ 99.895 724.062 null] +/D [615 0 R /XYZ 99.895 724.062 null] >> -% 610 0 obj +% 614 0 obj << -/Font << /F16 554 0 R /F27 556 0 R /F8 557 0 R >> +/Font << /F16 558 0 R /F27 560 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 664 0 obj +% 668 0 obj << /Type /Page -/Contents 665 0 R -/Resources 663 0 R +/Contents 669 0 R +/Resources 667 0 R /MediaBox [0 0 595.276 841.89] -/Parent 558 0 R -/Annots [ 609 0 R 616 0 R 617 0 R 618 0 R 619 0 R 620 0 R 621 0 R 622 0 R 623 0 R 624 0 R 625 0 R 626 0 R 627 0 R 628 0 R 629 0 R 630 0 R 631 0 R 632 0 R 633 0 R 634 0 R 635 0 R 636 0 R 637 0 R 638 0 R 639 0 R 640 0 R 641 0 R 642 0 R 643 0 R 644 0 R 645 0 R 646 0 R 647 0 R 648 0 R 649 0 R 650 0 R 651 0 R 652 0 R 653 0 R 654 0 R 655 0 R 656 0 R 657 0 R 658 0 R 659 0 R 660 0 R 661 0 R ] +/Parent 562 0 R +/Annots [ 613 0 R 620 0 R 621 0 R 622 0 R 623 0 R 624 0 R 625 0 R 626 0 R 627 0 R 628 0 R 629 0 R 630 0 R 631 0 R 632 0 R 633 0 R 634 0 R 635 0 R 636 0 R 637 0 R 638 0 R 639 0 R 640 0 R 641 0 R 642 0 R 643 0 R 644 0 R 645 0 R 646 0 R 647 0 R 648 0 R 649 0 R 650 0 R 651 0 R 652 0 R 653 0 R 654 0 R 655 0 R 656 0 R 657 0 R 658 0 R 659 0 R 660 0 R 661 0 R 662 0 R 663 0 R 664 0 R 665 0 R ] >> -% 609 0 obj +% 613 0 obj << /Type /Annot /Subtype /Link @@ -2973,7 +2991,7 @@ stream /Rect [219.447 703.195 259.342 713.546] /A << /S /GoTo /D (section*.32) >> >> -% 616 0 obj +% 620 0 obj << /Type /Annot /Subtype /Link @@ -2981,7 +2999,7 @@ stream /Rect [219.447 693.053 243.579 701.964] /A << /S /GoTo /D (section*.33) >> >> -% 617 0 obj +% 621 0 obj << /Type /Annot /Subtype /Link @@ -2989,7 +3007,7 @@ stream /Rect [164.653 680.973 318.825 689.884] /A << /S /GoTo /D (subsection.3.4) >> >> -% 618 0 obj +% 622 0 obj << /Type /Annot /Subtype /Link @@ -2997,7 +3015,7 @@ stream /Rect [164.653 666.956 277.397 677.805] /A << /S /GoTo /D (subsection.3.5) >> >> -% 619 0 obj +% 623 0 obj << /Type /Annot /Subtype /Link @@ -3005,7 +3023,7 @@ stream /Rect [149.709 644.831 285.838 655.679] /A << /S /GoTo /D (section.4) >> >> -% 620 0 obj +% 624 0 obj << /Type /Annot /Subtype /Link @@ -3013,7 +3031,7 @@ stream /Rect [164.653 632.751 220.931 643.599] /A << /S /GoTo /D (section*.34) >> >> -% 621 0 obj +% 625 0 obj << /Type /Annot /Subtype /Link @@ -3021,7 +3039,7 @@ stream /Rect [164.653 620.672 209.031 631.52] /A << /S /GoTo /D (section*.35) >> >> -% 622 0 obj +% 626 0 obj << /Type /Annot /Subtype /Link @@ -3029,7 +3047,7 @@ stream /Rect [164.653 608.592 212.96 619.44] /A << /S /GoTo /D (section*.36) >> >> -% 623 0 obj +% 627 0 obj << /Type /Annot /Subtype /Link @@ -3037,7 +3055,7 @@ stream /Rect [164.653 596.512 210.719 607.36] /A << /S /GoTo /D (section*.37) >> >> -% 624 0 obj +% 628 0 obj << /Type /Annot /Subtype /Link @@ -3045,7 +3063,7 @@ stream /Rect [164.653 584.432 222.093 595.281] /A << /S /GoTo /D (section*.38) >> >> -% 625 0 obj +% 629 0 obj << /Type /Annot /Subtype /Link @@ -3053,7 +3071,7 @@ stream /Rect [164.653 572.353 212.933 583.201] /A << /S /GoTo /D (section*.39) >> >> -% 626 0 obj +% 630 0 obj << /Type /Annot /Subtype /Link @@ -3061,7 +3079,7 @@ stream /Rect [164.653 560.273 221.318 571.121] /A << /S /GoTo /D (section*.40) >> >> -% 627 0 obj +% 631 0 obj << /Type /Annot /Subtype /Link @@ -3069,7 +3087,7 @@ stream /Rect [164.653 548.193 212.933 559.042] /A << /S /GoTo /D (section*.41) >> >> -% 628 0 obj +% 632 0 obj << /Type /Annot /Subtype /Link @@ -3077,7 +3095,7 @@ stream /Rect [164.653 536.114 221.29 546.962] /A << /S /GoTo /D (section*.42) >> >> -% 629 0 obj +% 633 0 obj << /Type /Annot /Subtype /Link @@ -3085,7 +3103,7 @@ stream /Rect [164.653 524.034 212.933 534.882] /A << /S /GoTo /D (section*.43) >> >> -% 630 0 obj +% 634 0 obj << /Type /Annot /Subtype /Link @@ -3093,7 +3111,7 @@ stream /Rect [164.653 511.954 210.719 522.802] /A << /S /GoTo /D (section*.44) >> >> -% 631 0 obj +% 635 0 obj << /Type /Annot /Subtype /Link @@ -3101,7 +3119,7 @@ stream /Rect [164.653 499.875 211.3 510.723] /A << /S /GoTo /D (section*.45) >> >> -% 632 0 obj +% 636 0 obj << /Type /Annot /Subtype /Link @@ -3109,7 +3127,7 @@ stream /Rect [164.653 487.795 206.927 498.643] /A << /S /GoTo /D (section*.46) >> >> -% 633 0 obj +% 637 0 obj << /Type /Annot /Subtype /Link @@ -3117,7 +3135,7 @@ stream /Rect [149.709 467.607 290.134 476.518] /A << /S /GoTo /D (section.5) >> >> -% 634 0 obj +% 638 0 obj << /Type /Annot /Subtype /Link @@ -3125,7 +3143,7 @@ stream /Rect [164.653 453.59 203.496 464.438] /A << /S /GoTo /D (section*.47) >> >> -% 635 0 obj +% 639 0 obj << /Type /Annot /Subtype /Link @@ -3133,7 +3151,7 @@ stream /Rect [164.653 441.51 201.863 452.358] /A << /S /GoTo /D (section*.48) >> >> -% 636 0 obj +% 640 0 obj << /Type /Annot /Subtype /Link @@ -3141,7 +3159,7 @@ stream /Rect [164.653 429.43 212.933 440.279] /A << /S /GoTo /D (section*.49) >> >> -% 637 0 obj +% 641 0 obj << /Type /Annot /Subtype /Link @@ -3149,7 +3167,7 @@ stream /Rect [164.653 417.351 214.648 428.199] /A << /S /GoTo /D (section*.50) >> >> -% 638 0 obj +% 642 0 obj << /Type /Annot /Subtype /Link @@ -3157,7 +3175,7 @@ stream /Rect [149.709 395.225 302.58 406.074] /A << /S /GoTo /D (section.6) >> >> -% 639 0 obj +% 643 0 obj << /Type /Annot /Subtype /Link @@ -3165,7 +3183,7 @@ stream /Rect [164.653 383.146 205.71 393.994] /A << /S /GoTo /D (section*.51) >> >> -% 640 0 obj +% 644 0 obj << /Type /Annot /Subtype /Link @@ -3173,7 +3191,7 @@ stream /Rect [164.653 371.066 207.426 381.914] /A << /S /GoTo /D (section*.52) >> >> -% 641 0 obj +% 645 0 obj << /Type /Annot /Subtype /Link @@ -3181,7 +3199,7 @@ stream /Rect [164.653 358.986 209.639 369.834] /A << /S /GoTo /D (section*.53) >> >> -% 642 0 obj +% 646 0 obj << /Type /Annot /Subtype /Link @@ -3189,7 +3207,7 @@ stream /Rect [164.653 346.906 210.138 357.755] /A << /S /GoTo /D (section*.54) >> >> -% 643 0 obj +% 647 0 obj << /Type /Annot /Subtype /Link @@ -3197,7 +3215,7 @@ stream /Rect [164.653 334.827 210.996 345.675] /A << /S /GoTo /D (section*.55) >> >> -% 644 0 obj +% 648 0 obj << /Type /Annot /Subtype /Link @@ -3205,7 +3223,7 @@ stream /Rect [164.653 322.747 222.591 333.595] /A << /S /GoTo /D (section*.56) >> >> -% 645 0 obj +% 649 0 obj << /Type /Annot /Subtype /Link @@ -3213,7 +3231,7 @@ stream /Rect [164.653 310.667 205.212 321.516] /A << /S /GoTo /D (section*.57) >> >> -% 646 0 obj +% 650 0 obj << /Type /Annot /Subtype /Link @@ -3221,7 +3239,7 @@ stream /Rect [164.653 298.588 206.927 309.436] /A << /S /GoTo /D (section*.58) >> >> -% 647 0 obj +% 651 0 obj << /Type /Annot /Subtype /Link @@ -3229,7 +3247,7 @@ stream /Rect [164.653 286.508 209.141 297.356] /A << /S /GoTo /D (section*.59) >> >> -% 648 0 obj +% 652 0 obj << /Type /Annot /Subtype /Link @@ -3237,7 +3255,7 @@ stream /Rect [164.653 274.428 210.497 285.276] /A << /S /GoTo /D (section*.60) >> >> -% 649 0 obj +% 653 0 obj << /Type /Annot /Subtype /Link @@ -3245,7 +3263,7 @@ stream /Rect [164.653 262.349 204.132 273.197] /A << /S /GoTo /D (section*.61) >> >> -% 650 0 obj +% 654 0 obj << /Type /Annot /Subtype /Link @@ -3253,7 +3271,7 @@ stream /Rect [164.653 250.269 205.156 261.117] /A << /S /GoTo /D (section*.62) >> >> -% 651 0 obj +% 655 0 obj << /Type /Annot /Subtype /Link @@ -3261,7 +3279,7 @@ stream /Rect [164.653 238.189 206.872 249.037] /A << /S /GoTo /D (section*.63) >> >> -% 652 0 obj +% 656 0 obj << /Type /Annot /Subtype /Link @@ -3269,7 +3287,7 @@ stream /Rect [164.653 226.109 209.086 236.958] /A << /S /GoTo /D (section*.64) >> >> -% 653 0 obj +% 657 0 obj << /Type /Annot /Subtype /Link @@ -3277,7 +3295,7 @@ stream /Rect [164.653 214.03 210.442 224.878] /A << /S /GoTo /D (section*.65) >> >> -% 654 0 obj +% 658 0 obj << /Type /Annot /Subtype /Link @@ -3285,7 +3303,7 @@ stream /Rect [164.653 201.95 202.942 212.798] /A << /S /GoTo /D (section*.66) >> >> -% 655 0 obj +% 659 0 obj << /Type /Annot /Subtype /Link @@ -3293,7 +3311,7 @@ stream /Rect [164.653 189.87 231.978 200.719] /A << /S /GoTo /D (section*.67) >> >> -% 656 0 obj +% 660 0 obj << /Type /Annot /Subtype /Link @@ -3301,7 +3319,7 @@ stream /Rect [164.653 177.791 231.978 188.639] /A << /S /GoTo /D (section*.68) >> >> -% 657 0 obj +% 661 0 obj << /Type /Annot /Subtype /Link @@ -3309,7 +3327,7 @@ stream /Rect [164.653 165.711 226.233 176.559] /A << /S /GoTo /D (section*.69) >> >> -% 658 0 obj +% 662 0 obj << /Type /Annot /Subtype /Link @@ -3317,7 +3335,7 @@ stream /Rect [164.653 153.631 243.059 164.48] /A << /S /GoTo /D (section*.70) >> >> -% 659 0 obj +% 663 0 obj << /Type /Annot /Subtype /Link @@ -3325,7 +3343,7 @@ stream /Rect [164.653 141.552 219.038 152.4] /A << /S /GoTo /D (section*.71) >> >> -% 660 0 obj +% 664 0 obj << /Type /Annot /Subtype /Link @@ -3333,7 +3351,7 @@ stream /Rect [164.653 129.472 235.863 140.32] /A << /S /GoTo /D (section*.72) >> >> -% 661 0 obj +% 665 0 obj << /Type /Annot /Subtype /Link @@ -3341,25 +3359,25 @@ stream /Rect [164.653 117.392 243.64 128.24] /A << /S /GoTo /D (section*.73) >> >> -% 666 0 obj +% 670 0 obj << -/D [664 0 R /XYZ 149.705 753.953 null] +/D [668 0 R /XYZ 149.705 753.953 null] >> -% 663 0 obj +% 667 0 obj << -/Font << /F8 557 0 R /F27 556 0 R >> +/Font << /F8 561 0 R /F27 560 0 R >> /ProcSet [ /PDF /Text ] >> -% 709 0 obj +% 714 0 obj << /Type /Page -/Contents 710 0 R -/Resources 708 0 R +/Contents 715 0 R +/Resources 713 0 R /MediaBox [0 0 595.276 841.89] -/Parent 558 0 R -/Annots [ 662 0 R 667 0 R 668 0 R 669 0 R 670 0 R 671 0 R 672 0 R 673 0 R 674 0 R 675 0 R 676 0 R 677 0 R 678 0 R 679 0 R 680 0 R 681 0 R 682 0 R 683 0 R 684 0 R 685 0 R 686 0 R 687 0 R 688 0 R 689 0 R 690 0 R 691 0 R 692 0 R 693 0 R 694 0 R 695 0 R 696 0 R 697 0 R 698 0 R 699 0 R 700 0 R 701 0 R 702 0 R 703 0 R 704 0 R 705 0 R 706 0 R 707 0 R ] +/Parent 562 0 R +/Annots [ 666 0 R 671 0 R 672 0 R 673 0 R 674 0 R 675 0 R 676 0 R 677 0 R 678 0 R 679 0 R 680 0 R 681 0 R 682 0 R 683 0 R 684 0 R 685 0 R 686 0 R 687 0 R 688 0 R 689 0 R 690 0 R 691 0 R 692 0 R 693 0 R 694 0 R 695 0 R 696 0 R 697 0 R 698 0 R 699 0 R 700 0 R 701 0 R 702 0 R 703 0 R 704 0 R 705 0 R 706 0 R 707 0 R 708 0 R 709 0 R 710 0 R 711 0 R 712 0 R ] >> -% 662 0 obj +% 666 0 obj << /Type /Annot /Subtype /Link @@ -3367,7 +3385,7 @@ stream /Rect [113.843 703.195 182.591 714.044] /A << /S /GoTo /D (section*.74) >> >> -% 667 0 obj +% 671 0 obj << /Type /Annot /Subtype /Link @@ -3375,7 +3393,7 @@ stream /Rect [113.843 691.24 176.558 702.088] /A << /S /GoTo /D (section*.75) >> >> -% 668 0 obj +% 672 0 obj << /Type /Annot /Subtype /Link @@ -3383,7 +3401,7 @@ stream /Rect [113.843 679.285 158 690.133] /A << /S /GoTo /D (section*.76) >> >> -% 669 0 obj +% 673 0 obj << /Type /Annot /Subtype /Link @@ -3391,7 +3409,7 @@ stream /Rect [113.843 667.33 183.443 678.178] /A << /S /GoTo /D (section*.77) >> >> -% 670 0 obj +% 674 0 obj << /Type /Annot /Subtype /Link @@ -3399,7 +3417,7 @@ stream /Rect [98.899 647.349 264.868 656.26] /A << /S /GoTo /D (section.7) >> >> -% 671 0 obj +% 675 0 obj << /Type /Annot /Subtype /Link @@ -3407,7 +3425,7 @@ stream /Rect [113.843 633.457 149.366 644.305] /A << /S /GoTo /D (section*.78) >> >> -% 672 0 obj +% 676 0 obj << /Type /Annot /Subtype /Link @@ -3415,7 +3433,7 @@ stream /Rect [113.843 621.502 150.749 632.35] /A << /S /GoTo /D (section*.79) >> >> -% 673 0 obj +% 677 0 obj << /Type /Annot /Subtype /Link @@ -3423,7 +3441,7 @@ stream /Rect [113.843 609.547 150.749 620.395] /A << /S /GoTo /D (section*.80) >> >> -% 674 0 obj +% 678 0 obj << /Type /Annot /Subtype /Link @@ -3431,7 +3449,7 @@ stream /Rect [113.843 597.591 193.91 608.44] /A << /S /GoTo /D (section*.81) >> >> -% 675 0 obj +% 679 0 obj << /Type /Annot /Subtype /Link @@ -3439,7 +3457,7 @@ stream /Rect [113.843 585.636 170.968 596.484] /A << /S /GoTo /D (section*.82) >> >> -% 676 0 obj +% 680 0 obj << /Type /Annot /Subtype /Link @@ -3447,7 +3465,7 @@ stream /Rect [113.843 573.681 160.989 584.529] /A << /S /GoTo /D (section*.83) >> >> -% 677 0 obj +% 681 0 obj << /Type /Annot /Subtype /Link @@ -3455,7 +3473,7 @@ stream /Rect [113.843 561.726 163.839 572.574] /A << /S /GoTo /D (section*.84) >> >> -% 678 0 obj +% 682 0 obj << /Type /Annot /Subtype /Link @@ -3463,7 +3481,7 @@ stream /Rect [113.843 549.771 157.972 560.619] /A << /S /GoTo /D (section*.85) >> >> -% 679 0 obj +% 683 0 obj << /Type /Annot /Subtype /Link @@ -3471,7 +3489,7 @@ stream /Rect [113.843 537.816 157.446 548.664] /A << /S /GoTo /D (section*.86) >> >> -% 680 0 obj +% 684 0 obj << /Type /Annot /Subtype /Link @@ -3479,7 +3497,7 @@ stream /Rect [113.843 525.86 152.188 536.709] /A << /S /GoTo /D (section*.87) >> >> -% 681 0 obj +% 685 0 obj << /Type /Annot /Subtype /Link @@ -3487,26 +3505,10 @@ stream /Rect [113.843 513.905 152.963 524.753] /A << /S /GoTo /D (section*.88) >> >> -% 682 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 501.95 151.026 512.798] -/A << /S /GoTo /D (section*.89) >> ->> -% 683 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 489.995 152.963 500.843] -/A << /S /GoTo /D (section*.90) >> ->> endstream endobj -715 0 obj +720 0 obj << /Length 79 >> @@ -3521,7 +3523,7 @@ ET endstream endobj -729 0 obj +734 0 obj << /Length 8518 >> @@ -3577,7 +3579,7 @@ ET endstream endobj -749 0 obj +754 0 obj << /Length 5579 >> @@ -3624,20 +3626,20 @@ ET endstream endobj -745 0 obj +750 0 obj << /Type /XObject /Subtype /Form /FormType 1 /PTEX.FileName (./figures/psblas.pdf) /PTEX.PageNumber 1 -/PTEX.InfoDict 752 0 R +/PTEX.InfoDict 757 0 R /BBox [0 0 197 215] /Resources << /ProcSet [ /PDF /Text ] /ExtGState << -/R7 753 0 R ->>/Font << /R8 754 0 R>> +/R7 758 0 R +>>/Font << /R8 759 0 R>> >> /Length 898 /Filter /FlateDecode @@ -3658,7 +3660,7 @@ x Ͻ'Ǜa>=|9hBu湣$Lq5k^޽;>NiZ\V+9D8NLG׻~0+'mw>o;{=EaѲ8S4%ǥ_N#OΏ endstream endobj -756 0 obj +761 0 obj << /Filter /FlateDecode /Subtype /Type1C @@ -3678,7 +3680,7 @@ p IZt4w!}^gh9@^ ҅s2=3B2H>yn7C#h-whGtBVպ`u1F3vo34\z",P&+ڻoB03xs!F/m'~n?vaD+5t0 +ԷsRztJxFzQ`/d2j@7G.?wyc$OI(SMEߌ| ^`2!-"VIN"̂B-e/uV9:6:.ǰMɪH endstream endobj -762 0 obj +767 0 obj << /Length 8854 >> @@ -3727,7 +3729,7 @@ ET endstream endobj -778 0 obj +783 0 obj << /Length 5346 >> @@ -3804,20 +3806,20 @@ ET endstream endobj -775 0 obj +780 0 obj << /Type /XObject /Subtype /Form /FormType 1 /PTEX.FileName (./figures/points.pdf) /PTEX.PageNumber 1 -/PTEX.InfoDict 781 0 R +/PTEX.InfoDict 786 0 R /BBox [0 0 274 308] /Resources << /ProcSet [ /PDF /Text ] /ExtGState << -/R7 782 0 R ->>/Font << /R8 783 0 R>> +/R7 787 0 R +>>/Font << /R8 788 0 R>> >> /Length 1397 /Filter /FlateDecode @@ -3827,7 +3829,7 @@ x  3B=bAH}ϩc?ׄe]_?dwGad"沾}e4ߠ,s,_x/w׷~[Z.1uoO*x/22T<ᜇd&o/VC1V^dR 9^Ӿ͚zzõ7!SjJRWZSNm ide3fyRO|J_F~]~z2}VНm΀sQ<I}y5N p%UW@E$|pxE`&U %AIU0G]&MJxT.)~C8}~WۢvKK,8͗&`[C*ONs m 9؆u!`{P9mKI7oB*O샹~̳'^IavRy!zw'`x"0.Ѥb'i|sP:-%X/[^#ahdPY/)Zq&-VֽONtnGY& ˒וB̜Mnng%#؜ǂ"d;)(\X0}Zp#`ӆS%Hvţf``-+ЎQ49Ç,xO/,f,zinv$-܌`?禩|,7c;@!os]?ݲta0yҥZdyORܐ<%9䃀[}拇6m8uIPhf>m))YꓠҐ<%9䃀[}kWOr= A} 0' 9S,ir+\_uݿѐE?{'ȋB#4_$&`[qq&/> M5^_'`[BO% /]07o[qq &/M 5^_'n޶4.16sܥ%]!CgVe@ٖ$)5-5}?Lg+ |>{>hO‘jX5~,>0x},1c X€5Xb$3 څt=>tp8Շ$i>-%TXJR#gL“-J/0jȶw.ickZ,Ԥ^kU Wjǂ.UEzgP,"e̋:t!*%~ *Q@emPM1:ޒX(4 N]J' endstream endobj -790 0 obj +795 0 obj << /Length 5462 >> @@ -3917,7 +3919,7 @@ ET endstream endobj -795 0 obj +800 0 obj << /Length 8659 >> @@ -3965,7 +3967,7 @@ ET endstream endobj -809 0 obj +814 0 obj << /Length 7694 >> @@ -4059,252 +4061,276 @@ ET endstream endobj -712 0 obj +717 0 obj << /Type /ObjStm /N 100 /First 910 -/Length 12684 +/Length 12961 >> stream -684 0 685 147 686 296 687 445 688 590 689 739 690 888 691 1037 692 1186 693 1331 -694 1480 695 1627 696 1777 697 1927 698 2077 699 2227 700 2374 701 2524 702 2673 703 2822 -704 2972 705 3122 706 3272 707 3418 711 3566 708 3622 714 3701 716 3815 713 3872 728 3938 -717 4144 718 4293 719 4444 720 4596 721 4750 722 4901 723 5050 724 5199 725 5347 726 5495 -7 5643 727 5697 748 5789 752 5939 753 6180 754 6222 755 6608 742 6908 743 7053 744 7201 -11 7348 751 7404 747 7459 761 7579 746 7729 758 7875 759 8024 763 8172 15 8228 769 8283 -771 8340 760 8397 777 8592 781 8734 782 8848 783 8890 773 8959 774 9107 779 9255 780 9312 -19 9369 776 9425 789 9584 786 9726 787 9872 791 10019 788 10075 794 10180 796 10294 23 10351 -798 10407 799 10464 800 10521 801 10577 802 10634 803 10690 804 10745 805 10802 793 10859 808 10989 -792 11123 810 11271 811 11327 812 11383 813 11439 814 11494 815 11550 816 11606 817 11662 818 11718 -% 684 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 478.04 153.24 488.888] -/A << /S /GoTo /D (section*.91) >> ->> -% 685 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 466.085 149.421 476.933] -/A << /S /GoTo /D (section*.92) >> ->> +686 0 687 148 688 297 689 444 690 593 691 742 692 891 693 1037 694 1186 695 1335 +696 1484 697 1633 698 1779 699 1926 700 2076 701 2225 702 2375 703 2525 704 2674 705 2821 +706 2971 707 3119 708 3269 709 3418 710 3567 711 3716 712 3862 716 4011 713 4067 719 4146 +721 4260 718 4317 733 4383 722 4589 723 4738 724 4889 725 5041 726 5195 727 5346 728 5495 +729 5644 730 5792 731 5940 7 6088 732 6142 753 6234 757 6384 758 6625 759 6667 760 7053 +747 7353 748 7498 749 7646 11 7793 756 7849 752 7904 766 8024 751 8174 763 8320 764 8469 +768 8617 15 8673 774 8728 776 8785 765 8842 782 9037 786 9179 787 9293 788 9335 778 9404 +779 9552 784 9700 785 9757 19 9814 781 9870 794 10029 791 10171 792 10317 796 10464 793 10520 +799 10625 801 10739 23 10796 803 10852 804 10909 805 10966 806 11022 807 11079 808 11135 809 11190 +810 11247 798 11304 813 11434 797 11568 815 11716 816 11772 817 11828 818 11884 819 11939 820 11995 % 686 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 454.129 148.009 464.978] -/A << /S /GoTo /D (section*.93) >> +/Rect [113.843 501.95 151.026 512.798] +/A << /S /GoTo /D (section*.89) >> >> % 687 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [98.899 432.212 190.188 443.06] -/A << /S /GoTo /D (section.8) >> +/Rect [113.843 489.995 152.963 500.843] +/A << /S /GoTo /D (section*.90) >> >> % 688 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 420.256 167.188 431.105] -/A << /S /GoTo /D (section*.94) >> +/Rect [113.843 478.04 153.24 488.888] +/A << /S /GoTo /D (section*.91) >> >> % 689 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 408.301 155.537 419.149] -/A << /S /GoTo /D (section*.95) >> +/Rect [113.843 466.085 157.142 476.933] +/A << /S /GoTo /D (section*.92) >> >> % 690 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 396.346 202.129 407.194] -/A << /S /GoTo /D (section*.96) >> +/Rect [113.843 454.129 149.421 464.978] +/A << /S /GoTo /D (section*.93) >> >> % 691 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 384.391 189.039 395.239] -/A << /S /GoTo /D (section*.97) >> +/Rect [113.843 442.174 148.009 453.022] +/A << /S /GoTo /D (section*.94) >> >> % 692 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [98.899 364.41 156.061 373.321] -/A << /S /GoTo /D (section.9) >> +/Rect [98.899 420.256 190.188 431.105] +/A << /S /GoTo /D (section.8) >> >> % 693 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 352.455 149.061 361.366] -/A << /S /GoTo /D (section*.98) >> +/Rect [113.843 408.301 167.188 419.149] +/A << /S /GoTo /D (section*.95) >> >> % 694 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 340.5 152.382 349.411] -/A << /S /GoTo /D (section*.99) >> +/Rect [113.843 396.346 155.537 407.194] +/A << /S /GoTo /D (section*.96) >> >> % 695 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 328.545 175.617 337.456] -/A << /S /GoTo /D (section*.100) >> +/Rect [113.843 384.391 202.129 395.239] +/A << /S /GoTo /D (section*.97) >> >> % 696 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 314.652 181.207 325.501] -/A << /S /GoTo /D (section*.101) >> +/Rect [113.843 372.436 189.039 383.284] +/A << /S /GoTo /D (section*.98) >> >> % 697 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 304.634 178.938 313.281] -/A << /S /GoTo /D (section*.102) >> +/Rect [98.899 352.455 156.061 361.366] +/A << /S /GoTo /D (section.9) >> >> % 698 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 290.742 184.528 301.325] -/A << /S /GoTo /D (section*.103) >> +/Rect [113.843 340.5 149.061 349.411] +/A << /S /GoTo /D (section*.99) >> >> % 699 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [98.899 270.761 234.475 279.672] -/A << /S /GoTo /D (section.10) >> +/Rect [113.843 328.545 152.382 337.456] +/A << /S /GoTo /D (section*.100) >> >> % 700 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 256.869 157.374 268.271] -/A << /S /GoTo /D (section*.104) >> +/Rect [113.843 316.59 175.617 325.501] +/A << /S /GoTo /D (section*.101) >> >> % 701 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 244.914 164.57 256.316] -/A << /S /GoTo /D (section*.105) >> +/Rect [113.843 302.697 181.207 313.545] +/A << /S /GoTo /D (section*.102) >> >> % 702 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 232.959 166.507 244.36] -/A << /S /GoTo /D (section*.106) >> +/Rect [113.843 292.679 178.938 301.325] +/A << /S /GoTo /D (section*.103) >> >> % 703 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 221.004 164.653 232.405] -/A << /S /GoTo /D (section*.107) >> +/Rect [113.843 278.787 184.528 289.37] +/A << /S /GoTo /D (section*.104) >> >> % 704 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 210.986 137.975 219.897] -/A << /S /GoTo /D (section*.108) >> +/Rect [98.899 258.806 234.475 267.717] +/A << /S /GoTo /D (section.10) >> >> % 705 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 197.093 158.232 208.495] -/A << /S /GoTo /D (section*.109) >> +/Rect [113.843 244.914 157.374 256.316] +/A << /S /GoTo /D (section*.105) >> >> % 706 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [98.899 177.113 206.49 186.024] -/A << /S /GoTo /D (section.11) >> +/Rect [113.843 232.959 164.57 244.36] +/A << /S /GoTo /D (section*.106) >> >> % 707 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [113.843 163.22 161.57 174.068] +/Rect [113.843 221.004 166.507 232.405] +/A << /S /GoTo /D (section*.107) >> +>> +% 708 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [113.843 209.048 164.653 220.45] +/A << /S /GoTo /D (section*.108) >> +>> +% 709 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [113.843 199.03 137.975 207.941] +/A << /S /GoTo /D (section*.109) >> +>> +% 710 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [113.843 185.138 158.232 196.54] /A << /S /GoTo /D (section*.110) >> >> % 711 0 obj << -/D [709 0 R /XYZ 98.895 753.953 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [98.899 165.157 206.49 174.068] +/A << /S /GoTo /D (section.11) >> +>> +% 712 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [113.843 151.265 161.57 162.113] +/A << /S /GoTo /D (section*.111) >> >> -% 708 0 obj +% 716 0 obj << -/Font << /F8 557 0 R /F27 556 0 R >> +/D [714 0 R /XYZ 98.895 753.953 null] +>> +% 713 0 obj +<< +/Font << /F8 561 0 R /F27 560 0 R >> /ProcSet [ /PDF /Text ] >> -% 714 0 obj +% 719 0 obj << /Type /Page -/Contents 715 0 R -/Resources 713 0 R +/Contents 720 0 R +/Resources 718 0 R /MediaBox [0 0 595.276 841.89] -/Parent 558 0 R +/Parent 562 0 R >> -% 716 0 obj +% 721 0 obj << -/D [714 0 R /XYZ 149.705 753.953 null] +/D [719 0 R /XYZ 149.705 753.953 null] >> -% 713 0 obj +% 718 0 obj << -/Font << /F8 557 0 R >> +/Font << /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 728 0 obj +% 733 0 obj << /Type /Page -/Contents 729 0 R -/Resources 727 0 R +/Contents 734 0 R +/Resources 732 0 R /MediaBox [0 0 595.276 841.89] -/Parent 731 0 R -/Annots [ 717 0 R 718 0 R 719 0 R 720 0 R 721 0 R 722 0 R 723 0 R 724 0 R 725 0 R 726 0 R ] +/Parent 736 0 R +/Annots [ 722 0 R 723 0 R 724 0 R 725 0 R 726 0 R 727 0 R 728 0 R 729 0 R 730 0 R 731 0 R ] >> -% 717 0 obj +% 722 0 obj << /Type /Annot /Subtype /Link @@ -4312,7 +4338,7 @@ stream /Rect [408.982 586.91 420.937 595.323] /A << /S /GoTo /D (cite.metcalf) >> >> -% 718 0 obj +% 723 0 obj << /Type /Annot /Subtype /Link @@ -4320,7 +4346,7 @@ stream /Rect [277.684 514.913 289.639 523.326] /A << /S /GoTo /D (cite.Sparse03) >> >> -% 719 0 obj +% 724 0 obj << /Type /Annot /Subtype /Link @@ -4328,7 +4354,7 @@ stream /Rect [265.763 502.958 272.737 511.371] /A << /S /GoTo /D (cite.DesPat:11) >> >> -% 720 0 obj +% 725 0 obj << /Type /Annot /Subtype /Link @@ -4336,7 +4362,7 @@ stream /Rect [276.283 502.958 288.238 511.371] /A << /S /GoTo /D (cite.RouXiaXu:11) >> >> -% 721 0 obj +% 726 0 obj << /Type /Annot /Subtype /Link @@ -4344,7 +4370,7 @@ stream /Rect [210.166 442.916 222.121 451.329] /A << /S /GoTo /D (cite.machiels) >> >> -% 722 0 obj +% 727 0 obj << /Type /Annot /Subtype /Link @@ -4352,7 +4378,7 @@ stream /Rect [241.566 370.919 248.54 379.332] /A << /S /GoTo /D (cite.sblas97) >> >> -% 723 0 obj +% 728 0 obj << /Type /Annot /Subtype /Link @@ -4360,7 +4386,7 @@ stream /Rect [252.056 370.919 259.03 379.332] /A << /S /GoTo /D (cite.sblas02) >> >> -% 724 0 obj +% 729 0 obj << /Type /Annot /Subtype /Link @@ -4368,7 +4394,7 @@ stream /Rect [227.473 358.964 239.428 367.377] /A << /S /GoTo /D (cite.BLAS1) >> >> -% 725 0 obj +% 730 0 obj << /Type /Annot /Subtype /Link @@ -4376,7 +4402,7 @@ stream /Rect [243.524 358.964 250.498 367.377] /A << /S /GoTo /D (cite.BLAS2) >> >> -% 726 0 obj +% 731 0 obj << /Type /Annot /Subtype /Link @@ -4386,23 +4412,23 @@ stream >> % 7 0 obj << -/D [728 0 R /XYZ 99.895 716.092 null] +/D [733 0 R /XYZ 99.895 716.092 null] >> -% 727 0 obj +% 732 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F17 730 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F17 735 0 R >> /ProcSet [ /PDF /Text ] >> -% 748 0 obj +% 753 0 obj << /Type /Page -/Contents 749 0 R -/Resources 747 0 R +/Contents 754 0 R +/Resources 752 0 R /MediaBox [0 0 595.276 841.89] -/Parent 731 0 R -/Annots [ 742 0 R 743 0 R 744 0 R ] +/Parent 736 0 R +/Annots [ 747 0 R 748 0 R 749 0 R ] >> -% 752 0 obj +% 757 0 obj << /Producer (GPL Ghostscript 9.04) /CreationDate (D:20111215145523+01'00') @@ -4411,15 +4437,15 @@ stream /Creator (fig2dev Version 3.2 Patchlevel 5d) /Author (sfilippo@donald \(Salvatore Filippone\)) >> -% 753 0 obj +% 758 0 obj << /Type /ExtGState /OPM 1 >> -% 754 0 obj +% 759 0 obj << /BaseFont /JEJNJE+Times-Roman -/FontDescriptor 755 0 R +/FontDescriptor 760 0 R /Type /Font /FirstChar 32 /LastChar 116 @@ -4427,7 +4453,7 @@ stream /Encoding /WinAnsiEncoding /Subtype /Type1 >> -% 755 0 obj +% 760 0 obj << /Type /FontDescriptor /FontName /JEJNJE+Times-Roman @@ -4441,9 +4467,9 @@ stream /MissingWidth 500 /XHeight 460 /CharSet (/A/B/F/I/L/M/P/S/a/c/e/f/g/i/l/n/o/p/r/s/space/t/three/two/zero) -/FontFile3 756 0 R +/FontFile3 761 0 R >> -% 742 0 obj +% 747 0 obj << /Type /Annot /Subtype /Link @@ -4451,7 +4477,7 @@ stream /Rect [310.543 541.042 317.517 551.89] /A << /S /GoTo /D (figure.1) >> >> -% 743 0 obj +% 748 0 obj << /Type /Annot /Subtype /Link @@ -4459,7 +4485,7 @@ stream /Rect [446.018 471.248 452.992 479.661] /A << /S /GoTo /D (cite.BLACS) >> >> -% 744 0 obj +% 749 0 obj << /Type /Annot /Subtype /Link @@ -4469,28 +4495,28 @@ stream >> % 11 0 obj << -/D [748 0 R /XYZ 150.705 677.433 null] +/D [753 0 R /XYZ 150.705 677.433 null] >> -% 751 0 obj +% 756 0 obj << -/D [748 0 R /XYZ 258.703 263.3 null] +/D [753 0 R /XYZ 258.703 263.3 null] >> -% 747 0 obj +% 752 0 obj << -/Font << /F8 557 0 R /F16 554 0 R /F11 750 0 R >> -/XObject << /Im1 745 0 R >> +/Font << /F8 561 0 R /F16 558 0 R /F11 755 0 R >> +/XObject << /Im1 750 0 R >> /ProcSet [ /PDF /Text ] >> -% 761 0 obj +% 766 0 obj << /Type /Page -/Contents 762 0 R -/Resources 760 0 R +/Contents 767 0 R +/Resources 765 0 R /MediaBox [0 0 595.276 841.89] -/Parent 731 0 R -/Annots [ 746 0 R 758 0 R 759 0 R ] +/Parent 736 0 R +/Annots [ 751 0 R 763 0 R 764 0 R ] >> -% 746 0 obj +% 751 0 obj << /Type /Annot /Subtype /Link @@ -4498,7 +4524,7 @@ stream /Rect [219.5 609.491 231.455 617.904] /A << /S /GoTo /D (cite.METIS) >> >> -% 758 0 obj +% 763 0 obj << /Type /Annot /Subtype /Link @@ -4506,7 +4532,7 @@ stream /Rect [210.854 546.467 217.316 558.506] /A << /S /GoTo /D (Hfootnote.1) >> >> -% 759 0 obj +% 764 0 obj << /Type /Annot /Subtype /Link @@ -4514,54 +4540,54 @@ stream /Rect [155.908 188.124 162.37 200.163] /A << /S /GoTo /D (Hfootnote.2) >> >> -% 763 0 obj +% 768 0 obj << -/D [761 0 R /XYZ 98.895 753.953 null] +/D [766 0 R /XYZ 98.895 753.953 null] >> % 15 0 obj << -/D [761 0 R /XYZ 99.895 515.919 null] +/D [766 0 R /XYZ 99.895 515.919 null] >> -% 769 0 obj +% 774 0 obj << -/D [761 0 R /XYZ 115.138 167.688 null] +/D [766 0 R /XYZ 115.138 167.688 null] >> -% 771 0 obj +% 776 0 obj << -/D [761 0 R /XYZ 115.138 158.184 null] +/D [766 0 R /XYZ 115.138 158.184 null] >> -% 760 0 obj +% 765 0 obj << -/Font << /F8 557 0 R /F17 730 0 R /F30 764 0 R /F7 765 0 R /F16 554 0 R /F11 750 0 R /F10 766 0 R /F14 767 0 R /F27 556 0 R /F32 768 0 R /F31 770 0 R >> +/Font << /F8 561 0 R /F17 735 0 R /F30 769 0 R /F7 770 0 R /F16 558 0 R /F11 755 0 R /F10 771 0 R /F14 772 0 R /F27 560 0 R /F32 773 0 R /F31 775 0 R >> /ProcSet [ /PDF /Text ] >> -% 777 0 obj +% 782 0 obj << /Type /Page -/Contents 778 0 R -/Resources 776 0 R +/Contents 783 0 R +/Resources 781 0 R /MediaBox [0 0 595.276 841.89] -/Parent 731 0 R -/Annots [ 773 0 R 774 0 R ] +/Parent 736 0 R +/Annots [ 778 0 R 779 0 R ] >> -% 781 0 obj +% 786 0 obj << /Producer (ESP Ghostscript 815.03) /CreationDate (D:20070123225315) /ModDate (D:20070123225315) >> -% 782 0 obj +% 787 0 obj << /Type /ExtGState /OPM 1 >> -% 783 0 obj +% 788 0 obj << /BaseFont /Times-Roman /Type /Font /Subtype /Type1 >> -% 773 0 obj +% 778 0 obj << /Type /Annot /Subtype /Link @@ -4569,7 +4595,7 @@ stream /Rect [294.665 637.885 301.639 646.297] /A << /S /GoTo /D (cite.2007c) >> >> -% 774 0 obj +% 779 0 obj << /Type /Annot /Subtype /Link @@ -4577,34 +4603,34 @@ stream /Rect [305.735 637.885 312.709 646.297] /A << /S /GoTo /D (cite.2007d) >> >> -% 779 0 obj +% 784 0 obj << -/D [777 0 R /XYZ 149.705 753.953 null] +/D [782 0 R /XYZ 149.705 753.953 null] >> -% 780 0 obj +% 785 0 obj << -/D [777 0 R /XYZ 303.562 347.015 null] +/D [782 0 R /XYZ 303.562 347.015 null] >> % 19 0 obj << -/D [777 0 R /XYZ 150.705 272.271 null] +/D [782 0 R /XYZ 150.705 272.271 null] >> -% 776 0 obj +% 781 0 obj << -/Font << /F27 556 0 R /F8 557 0 R /F14 767 0 R /F11 750 0 R /F10 766 0 R /F16 554 0 R >> -/XObject << /Im2 775 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F14 772 0 R /F11 755 0 R /F10 771 0 R /F16 558 0 R >> +/XObject << /Im2 780 0 R >> /ProcSet [ /PDF /Text ] >> -% 789 0 obj +% 794 0 obj << /Type /Page -/Contents 790 0 R -/Resources 788 0 R +/Contents 795 0 R +/Resources 793 0 R /MediaBox [0 0 595.276 841.89] -/Parent 731 0 R -/Annots [ 786 0 R 787 0 R ] +/Parent 736 0 R +/Annots [ 791 0 R 792 0 R ] >> -% 786 0 obj +% 791 0 obj << /Type /Annot /Subtype /Link @@ -4612,7 +4638,7 @@ stream /Rect [406.358 354.515 413.331 366.47] /A << /S /GoTo /D (section.3) >> >> -% 787 0 obj +% 792 0 obj << /Type /Annot /Subtype /Link @@ -4620,78 +4646,78 @@ stream /Rect [173.863 318.352 180.837 330.307] /A << /S /GoTo /D (section.6) >> >> -% 791 0 obj +% 796 0 obj << -/D [789 0 R /XYZ 98.895 753.953 null] +/D [794 0 R /XYZ 98.895 753.953 null] >> -% 788 0 obj +% 793 0 obj << -/Font << /F27 556 0 R /F8 557 0 R /F14 767 0 R /F30 764 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F14 772 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 794 0 obj +% 799 0 obj << /Type /Page -/Contents 795 0 R -/Resources 793 0 R +/Contents 800 0 R +/Resources 798 0 R /MediaBox [0 0 595.276 841.89] -/Parent 731 0 R +/Parent 736 0 R >> -% 796 0 obj +% 801 0 obj << -/D [794 0 R /XYZ 149.705 753.953 null] +/D [799 0 R /XYZ 149.705 753.953 null] >> % 23 0 obj << -/D [794 0 R /XYZ 150.705 716.092 null] +/D [799 0 R /XYZ 150.705 716.092 null] >> -% 798 0 obj +% 803 0 obj << -/D [794 0 R /XYZ 150.705 284.758 null] +/D [799 0 R /XYZ 150.705 284.758 null] >> -% 799 0 obj +% 804 0 obj << -/D [794 0 R /XYZ 150.705 263.953 null] +/D [799 0 R /XYZ 150.705 263.953 null] >> -% 800 0 obj +% 805 0 obj << -/D [794 0 R /XYZ 150.705 242.87 null] +/D [799 0 R /XYZ 150.705 242.87 null] >> -% 801 0 obj +% 806 0 obj << -/D [794 0 R /XYZ 150.705 221.788 null] +/D [799 0 R /XYZ 150.705 221.788 null] >> -% 802 0 obj +% 807 0 obj << -/D [794 0 R /XYZ 150.705 188.75 null] +/D [799 0 R /XYZ 150.705 188.75 null] >> -% 803 0 obj +% 808 0 obj << -/D [794 0 R /XYZ 150.705 167.6 null] +/D [799 0 R /XYZ 150.705 167.6 null] >> -% 804 0 obj +% 809 0 obj << -/D [794 0 R /XYZ 150.705 148.591 null] +/D [799 0 R /XYZ 150.705 148.591 null] >> -% 805 0 obj +% 810 0 obj << -/D [794 0 R /XYZ 150.705 132.072 null] +/D [799 0 R /XYZ 150.705 132.072 null] >> -% 793 0 obj +% 798 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F11 750 0 R /F30 764 0 R /F9 797 0 R /F17 730 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F11 755 0 R /F30 769 0 R /F9 802 0 R /F17 735 0 R >> /ProcSet [ /PDF /Text ] >> -% 808 0 obj +% 813 0 obj << /Type /Page -/Contents 809 0 R -/Resources 807 0 R +/Contents 814 0 R +/Resources 812 0 R /MediaBox [0 0 595.276 841.89] -/Parent 826 0 R -/Annots [ 792 0 R ] +/Parent 831 0 R +/Annots [ 797 0 R ] >> -% 792 0 obj +% 797 0 obj << /Type /Annot /Subtype /Link @@ -4699,46 +4725,34 @@ stream /Rect [176.109 690.964 182.571 703.28] /A << /S /GoTo /D (Hfootnote.3) >> >> -% 810 0 obj -<< -/D [808 0 R /XYZ 98.895 753.953 null] ->> -% 811 0 obj -<< -/D [808 0 R /XYZ 99.895 716.092 null] ->> -% 812 0 obj -<< -/D [808 0 R /XYZ 99.895 686.739 null] ->> -% 813 0 obj -<< -/D [808 0 R /XYZ 99.895 618.93 null] ->> -% 814 0 obj -<< -/D [808 0 R /XYZ 99.895 596.257 null] ->> % 815 0 obj << -/D [808 0 R /XYZ 99.895 573.861 null] +/D [813 0 R /XYZ 98.895 753.953 null] >> % 816 0 obj << -/D [808 0 R /XYZ 99.895 539.509 null] +/D [813 0 R /XYZ 99.895 716.092 null] >> % 817 0 obj << -/D [808 0 R /XYZ 99.895 517.113 null] +/D [813 0 R /XYZ 99.895 686.739 null] >> % 818 0 obj << -/D [808 0 R /XYZ 99.895 494.716 null] +/D [813 0 R /XYZ 99.895 618.93 null] +>> +% 819 0 obj +<< +/D [813 0 R /XYZ 99.895 596.257 null] +>> +% 820 0 obj +<< +/D [813 0 R /XYZ 99.895 573.861 null] >> endstream endobj -831 0 obj +836 0 obj << /Length 7473 >> @@ -4794,7 +4808,7 @@ ET endstream endobj -842 0 obj +847 0 obj << /Length 8440 >> @@ -4939,7 +4953,7 @@ ET endstream endobj -852 0 obj +857 0 obj << /Length 6827 >> @@ -5074,7 +5088,7 @@ ET endstream endobj -865 0 obj +870 0 obj << /Length 5421 >> @@ -5193,7 +5207,7 @@ ET endstream endobj -876 0 obj +881 0 obj << /Length 5152 >> @@ -5321,7 +5335,7 @@ ET endstream endobj -880 0 obj +885 0 obj << /Length 4083 >> @@ -5424,7 +5438,7 @@ ET endstream endobj -885 0 obj +890 0 obj << /Length 5794 >> @@ -5584,7 +5598,7 @@ ET endstream endobj -893 0 obj +898 0 obj << /Length 9961 >> @@ -5975,7 +5989,7 @@ ET endstream endobj -901 0 obj +906 0 obj << /Length 4142 >> @@ -6059,7 +6073,7 @@ ET endstream endobj -905 0 obj +910 0 obj << /Length 3830 >> @@ -6156,198 +6170,75 @@ ET endstream endobj -910 0 obj +832 0 obj << -/Length 4817 +/Type /ObjStm +/N 100 +/First 865 +/Length 8968 >> stream -0 g 0 G -0 g 0 G -BT -/F27 9.9626 Tf 150.705 706.129 Td [(get)]TJ -ET -q -1 0 0 1 166.827 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 170.264 706.129 Td [(fm)32(t)-383(|)-384(Short)-383(description)-384(of)-383(the)-383(dynamic)-384(t)32(yp)-32(e)]TJ -0 g 0 G -0 g 0 G -/F30 9.9626 Tf -19.559 -18.389 Td [(write\050*,*\051)-525(a%get_fmt\050\051)]TJ -0 g 0 G -/F27 9.9626 Tf 0 -20.78 Td [(T)32(yp)-32(e:)]TJ -0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ -0 g 0 G -/F27 9.9626 Tf -33.797 -19.47 Td [(On)-383(En)32(try)]TJ -0 g 0 G -0 g 0 G - 0 -19.47 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(sparse)-334(matrix)]TJ 14.355 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ -0 g 0 G - -57.285 -32.735 Td [(On)-383(Return)]TJ -0 g 0 G -0 g 0 G - 0 -19.47 Td [(F)96(unction)-384(v)64(alue)]TJ -0 g 0 G -/F8 9.9626 Tf 78.386 0 Td [(A)-484(short)-483(string)-484(describing)-484(the)-484(dynamic)-484(t)28(yp)-28(e)-483(of)-484(the)-484(matrix.)]TJ -53.48 -11.955 Td [(Prede\014ned)-333(v)55(alues)-333(include)]TJ/F30 9.9626 Tf 113.409 0 Td [(NULL)]TJ/F8 9.9626 Tf 20.921 0 Td [(,)]TJ/F30 9.9626 Tf 6.088 0 Td [(COO)]TJ/F8 9.9626 Tf 15.691 0 Td [(,)]TJ/F30 9.9626 Tf 6.089 0 Td [(CSR)]TJ/F8 9.9626 Tf 19.012 0 Td [(and)]TJ/F30 9.9626 Tf 19.371 0 Td [(CSC)]TJ/F8 9.9626 Tf 15.691 0 Td [(.)]TJ/F27 9.9626 Tf -241.178 -25.7 Td [(is)]TJ -ET -q -1 0 0 1 159.094 526.404 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 162.531 526.205 Td [(bld,)-383(is)]TJ -ET -q -1 0 0 1 193.834 526.404 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 197.271 526.205 Td [(up)-32(d,)-383(is)]TJ -ET -q -1 0 0 1 232.075 526.404 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 235.512 526.205 Td [(asb)-383(|)-384(Status)-383(c)32(hec)32(k)]TJ -0 g 0 G -0 g 0 G -/F30 9.9626 Tf -84.807 -18.39 Td [(if)-525(\050a%is_bld\050\051\051)-525(then)]TJ 0 -11.955 Td [(if)-525(\050a%is_upd\050\051\051)-525(then)]TJ 0 -11.955 Td [(if)-525(\050a%is_asb\050\051\051)-525(then)]TJ -0 g 0 G -/F27 9.9626 Tf 0 -20.78 Td [(T)32(yp)-32(e:)]TJ -0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ -0 g 0 G -/F27 9.9626 Tf -33.797 -19.47 Td [(On)-383(En)32(try)]TJ -0 g 0 G -0 g 0 G - 0 -19.47 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(sparse)-334(matrix)]TJ 14.356 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ -0 g 0 G - -57.285 -32.735 Td [(On)-383(Return)]TJ -0 g 0 G -0 g 0 G - 0 -19.47 Td [(F)96(unction)-384(v)64(alue)]TJ -0 g 0 G -/F8 9.9626 Tf 78.386 0 Td [(A)]TJ/F30 9.9626 Tf 9.728 0 Td [(logical)]TJ/F8 9.9626 Tf 38.869 0 Td [(v)56(alue)-227(indicating)-226(whether)-227(the)-226(m)-1(atr)1(ix)-227(is)-227(in)-226(the)-227(Build)1(,)]TJ -102.076 -11.955 Td [(Up)-28(date)-333(or)-333(Assem)27(bled)-333(state,)-333(resp)-28(ectiv)28(e)-1(l)1(y)83(.)]TJ/F27 9.9626 Tf -24.907 -25.7 Td [(is)]TJ -ET -q -1 0 0 1 159.094 322.57 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 162.531 322.37 Td [(lo)32(w)32(er,)-383(i)-1(s)]TJ -ET -q -1 0 0 1 204.44 322.57 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 207.877 322.37 Td [(upp)-32(er,)-383(is)]TJ -ET -q -1 0 0 1 252.65 322.57 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 256.087 322.37 Td [(triangle,)-384(is)]TJ -ET -q -1 0 0 1 309.931 322.57 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 313.368 322.37 Td [(unit)-383(|)-384(F)96(ormat)-383(c)32(hec)32(k)]TJ -0 g 0 G -0 g 0 G -/F30 9.9626 Tf -162.663 -18.389 Td [(if)-525(\050a%is_triangle\050\051\051)-525(then)]TJ 0 -11.955 Td [(if)-525(\050a%is_upper\050\051\051)-525(then)]TJ 0 -11.955 Td [(if)-525(\050a%is_lower\050\051\051)-525(then)]TJ 0 -11.955 Td [(if)-525(\050a%is_unit\050\051\051)-525(then)]TJ -0 g 0 G -/F27 9.9626 Tf 0 -20.78 Td [(T)32(yp)-32(e:)]TJ -0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ -0 g 0 G -/F27 9.9626 Tf -33.797 -19.47 Td [(On)-383(En)32(try)]TJ -0 g 0 G -0 g 0 G - 0 -19.47 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(sparse)-334(matrix)]TJ 14.356 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ -0 g 0 G - -57.285 -32.735 Td [(On)-383(Return)]TJ -0 g 0 G -0 g 0 G - 0 -19.47 Td [(F)96(unction)-384(v)64(alue)]TJ -0 g 0 G -/F8 9.9626 Tf 78.386 0 Td [(A)]TJ/F30 9.9626 Tf 10.615 0 Td [(logical)]TJ/F8 9.9626 Tf 39.755 0 Td [(v)56(alue)-316(indicating)-315(whether)-316(the)-315(matrix)-316(i)1(s)-316(triangular;)]TJ -103.849 -11.955 Td [(if)]TJ/F30 9.9626 Tf 8.895 0 Td [(is_triangle\050\051)]TJ/F8 9.9626 Tf 71.079 0 Td [(returns)]TJ/F30 9.9626 Tf 34.189 0 Td [(.true.)]TJ/F8 9.9626 Tf 34.466 0 Td [(c)28(hec)27(k)-309(also)-310(if)-309(it)-310(is)-309(lo)27(w)28(er,)-314(upp)-28(er)-309(and)-310(with)]TJ -148.629 -11.955 Td [(a)-333(unit)-334(\050i)1(.e)-1(.)-444(assumed\051)-333(diagonal.)]TJ -0 g 0 G - 141.967 -29.888 Td [(18)]TJ -0 g 0 G -ET - -endstream -endobj -827 0 obj +821 0 822 56 823 112 824 168 825 224 826 280 827 336 828 392 829 448 812 505 +835 635 811 777 833 929 837 1076 27 1133 838 1189 839 1246 840 1303 841 1360 842 1417 +843 1474 31 1531 834 1587 846 1730 844 1864 848 2011 35 2067 39 2122 849 2177 845 2234 +856 2352 850 2502 851 2649 852 2800 858 2952 859 3009 860 3066 861 3123 862 3180 863 3237 +864 3294 865 3351 866 3407 867 3464 855 3521 869 3613 853 3755 854 3907 871 4059 872 4115 +873 4171 874 4227 875 4283 876 4339 43 4396 47 4451 868 4504 880 4596 877 4738 878 4884 +882 5030 51 5087 55 5143 59 5199 879 5255 884 5373 886 5487 63 5543 67 5598 71 5653 +883 5708 889 5800 891 5914 75 5971 892 6027 79 6084 83 6140 888 6196 897 6288 893 6438 +894 6595 895 6745 899 6891 87 6947 91 7002 900 7057 901 7114 902 7171 896 7228 905 7333 +907 7447 95 7504 99 7560 103 7616 904 7673 909 7765 911 7879 107 7935 912 7991 111 8047 +% 821 0 obj << -/Type /ObjStm -/N 100 -/First 866 -/Length 9063 +/D [813 0 R /XYZ 99.895 539.509 null] >> -stream -819 0 820 56 821 112 822 168 823 224 824 280 807 337 830 467 806 609 828 761 -832 908 27 965 833 1021 834 1078 835 1135 836 1192 837 1249 838 1306 31 1363 829 1419 -841 1562 839 1696 843 1843 35 1899 39 1954 844 2009 840 2066 851 2184 845 2334 846 2481 -847 2632 853 2784 854 2841 855 2898 856 2955 857 3012 858 3069 859 3126 860 3183 861 3239 -862 3296 850 3353 864 3445 848 3587 849 3739 866 3891 867 3947 868 4003 869 4059 870 4115 -871 4171 43 4228 47 4283 863 4336 875 4428 872 4570 873 4716 877 4862 51 4919 55 4975 -59 5031 874 5087 879 5205 881 5319 63 5375 67 5430 71 5485 878 5540 884 5632 886 5746 -75 5803 887 5859 79 5916 83 5972 883 6028 892 6120 888 6270 889 6427 890 6577 894 6723 -87 6779 91 6834 895 6889 896 6946 897 7003 891 7060 900 7165 902 7279 95 7336 99 7392 -103 7448 899 7505 904 7597 906 7711 107 7767 907 7823 111 7879 115 7935 903 7991 909 8083 -% 819 0 obj +% 822 0 obj << -/D [808 0 R /XYZ 99.895 469.986 null] +/D [813 0 R /XYZ 99.895 517.113 null] >> -% 820 0 obj +% 823 0 obj << -/D [808 0 R /XYZ 99.895 440.855 null] +/D [813 0 R /XYZ 99.895 494.716 null] >> -% 821 0 obj +% 824 0 obj << -/D [808 0 R /XYZ 99.895 411.448 null] +/D [813 0 R /XYZ 99.895 469.986 null] >> -% 822 0 obj +% 825 0 obj << -/D [808 0 R /XYZ 99.895 393.995 null] +/D [813 0 R /XYZ 99.895 440.855 null] >> -% 823 0 obj +% 826 0 obj << -/D [808 0 R /XYZ 99.895 376.819 null] +/D [813 0 R /XYZ 99.895 411.448 null] >> -% 824 0 obj +% 827 0 obj << -/D [808 0 R /XYZ 115.138 139.255 null] +/D [813 0 R /XYZ 99.895 393.995 null] >> -% 807 0 obj +% 828 0 obj +<< +/D [813 0 R /XYZ 99.895 376.819 null] +>> +% 829 0 obj +<< +/D [813 0 R /XYZ 115.138 139.255 null] +>> +% 812 0 obj << -/Font << /F8 557 0 R /F30 764 0 R /F7 765 0 R /F32 768 0 R /F31 770 0 R /F45 825 0 R >> +/Font << /F8 561 0 R /F30 769 0 R /F7 770 0 R /F32 773 0 R /F31 775 0 R /F45 830 0 R >> /ProcSet [ /PDF /Text ] >> -% 830 0 obj +% 835 0 obj << /Type /Page -/Contents 831 0 R -/Resources 829 0 R +/Contents 836 0 R +/Resources 834 0 R /MediaBox [0 0 595.276 841.89] -/Parent 826 0 R -/Annots [ 806 0 R 828 0 R ] +/Parent 831 0 R +/Annots [ 811 0 R 833 0 R ] >> -% 806 0 obj +% 811 0 obj << /Type /Annot /Subtype /Link @@ -6355,7 +6246,7 @@ stream /Rect [269.731 674.788 284.454 683.699] /A << /S /GoTo /D (subsection.2.3) >> >> -% 828 0 obj +% 833 0 obj << /Type /Annot /Subtype /Link @@ -6363,57 +6254,57 @@ stream /Rect [169.998 271.903 176.972 282.751] /A << /S /GoTo /D (section.3) >> >> -% 832 0 obj +% 837 0 obj << -/D [830 0 R /XYZ 149.705 753.953 null] +/D [835 0 R /XYZ 149.705 753.953 null] >> % 27 0 obj << -/D [830 0 R /XYZ 150.705 716.092 null] +/D [835 0 R /XYZ 150.705 716.092 null] >> -% 833 0 obj +% 838 0 obj << -/D [830 0 R /XYZ 150.705 671.799 null] +/D [835 0 R /XYZ 150.705 671.799 null] >> -% 834 0 obj +% 839 0 obj << -/D [830 0 R /XYZ 150.705 649.383 null] +/D [835 0 R /XYZ 150.705 649.383 null] >> -% 835 0 obj +% 840 0 obj << -/D [830 0 R /XYZ 150.705 576.158 null] +/D [835 0 R /XYZ 150.705 576.158 null] >> -% 836 0 obj +% 841 0 obj << -/D [830 0 R /XYZ 150.705 530.385 null] +/D [835 0 R /XYZ 150.705 530.385 null] >> -% 837 0 obj +% 842 0 obj << -/D [830 0 R /XYZ 150.705 497.951 null] +/D [835 0 R /XYZ 150.705 497.951 null] >> -% 838 0 obj +% 843 0 obj << -/D [830 0 R /XYZ 150.705 478.303 null] +/D [835 0 R /XYZ 150.705 478.303 null] >> % 31 0 obj << -/D [830 0 R /XYZ 150.705 424.511 null] +/D [835 0 R /XYZ 150.705 424.511 null] >> -% 829 0 obj +% 834 0 obj << -/Font << /F27 556 0 R /F8 557 0 R /F11 750 0 R /F9 797 0 R /F30 764 0 R /F16 554 0 R /F17 730 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F11 755 0 R /F9 802 0 R /F30 769 0 R /F16 558 0 R /F17 735 0 R >> /ProcSet [ /PDF /Text ] >> -% 841 0 obj +% 846 0 obj << /Type /Page -/Contents 842 0 R -/Resources 840 0 R +/Contents 847 0 R +/Resources 845 0 R /MediaBox [0 0 595.276 841.89] -/Parent 826 0 R -/Annots [ 839 0 R ] +/Parent 831 0 R +/Annots [ 844 0 R ] >> -% 839 0 obj +% 844 0 obj << /Type /Annot /Subtype /Link @@ -6421,37 +6312,37 @@ stream /Rect [269.318 225.936 276.292 236.784] /A << /S /GoTo /D (section.6) >> >> -% 843 0 obj +% 848 0 obj << -/D [841 0 R /XYZ 98.895 753.953 null] +/D [846 0 R /XYZ 98.895 753.953 null] >> % 35 0 obj << -/D [841 0 R /XYZ 99.895 716.092 null] +/D [846 0 R /XYZ 99.895 716.092 null] >> % 39 0 obj << -/D [841 0 R /XYZ 99.895 331.305 null] +/D [846 0 R /XYZ 99.895 331.305 null] >> -% 844 0 obj +% 849 0 obj << -/D [841 0 R /XYZ 342.427 288.724 null] +/D [846 0 R /XYZ 342.427 288.724 null] >> -% 840 0 obj +% 845 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F30 764 0 R /F27 556 0 R /F14 767 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F30 769 0 R /F27 560 0 R /F14 772 0 R >> /ProcSet [ /PDF /Text ] >> -% 851 0 obj +% 856 0 obj << /Type /Page -/Contents 852 0 R -/Resources 850 0 R +/Contents 857 0 R +/Resources 855 0 R /MediaBox [0 0 595.276 841.89] -/Parent 826 0 R -/Annots [ 845 0 R 846 0 R 847 0 R ] +/Parent 831 0 R +/Annots [ 850 0 R 851 0 R 852 0 R ] >> -% 845 0 obj +% 850 0 obj << /Type /Annot /Subtype /Link @@ -6459,7 +6350,7 @@ stream /Rect [452.103 458.757 459.077 470.712] /A << /S /GoTo /D (section.6) >> >> -% 846 0 obj +% 851 0 obj << /Type /Annot /Subtype /Link @@ -6467,7 +6358,7 @@ stream /Rect [356.323 258.941 371.046 269.79] /A << /S /GoTo /D (subsection.3.3) >> >> -% 847 0 obj +% 852 0 obj << /Type /Annot /Subtype /Link @@ -6475,61 +6366,61 @@ stream /Rect [356.323 215.425 371.046 226.273] /A << /S /GoTo /D (subsection.3.3) >> >> -% 853 0 obj +% 858 0 obj << -/D [851 0 R /XYZ 149.705 753.953 null] +/D [856 0 R /XYZ 149.705 753.953 null] >> -% 854 0 obj +% 859 0 obj << -/D [851 0 R /XYZ 150.705 355.818 null] +/D [856 0 R /XYZ 150.705 355.818 null] >> -% 855 0 obj +% 860 0 obj << -/D [851 0 R /XYZ 150.705 340.197 null] +/D [856 0 R /XYZ 150.705 340.197 null] >> -% 856 0 obj +% 861 0 obj << -/D [851 0 R /XYZ 150.705 324.575 null] +/D [856 0 R /XYZ 150.705 324.575 null] >> -% 857 0 obj +% 862 0 obj << -/D [851 0 R /XYZ 150.705 308.954 null] +/D [856 0 R /XYZ 150.705 308.954 null] >> -% 858 0 obj +% 863 0 obj << -/D [851 0 R /XYZ 150.705 293.332 null] +/D [856 0 R /XYZ 150.705 293.332 null] >> -% 859 0 obj +% 864 0 obj << -/D [851 0 R /XYZ 150.705 179.041 null] +/D [856 0 R /XYZ 150.705 179.041 null] >> -% 860 0 obj +% 865 0 obj << -/D [851 0 R /XYZ 150.705 163.42 null] +/D [856 0 R /XYZ 150.705 163.42 null] >> -% 861 0 obj +% 866 0 obj << -/D [851 0 R /XYZ 150.705 147.798 null] +/D [856 0 R /XYZ 150.705 147.798 null] >> -% 862 0 obj +% 867 0 obj << -/D [851 0 R /XYZ 150.705 132.177 null] +/D [856 0 R /XYZ 150.705 132.177 null] >> -% 850 0 obj +% 855 0 obj << -/Font << /F27 556 0 R /F8 557 0 R /F14 767 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F14 772 0 R >> /ProcSet [ /PDF /Text ] >> -% 864 0 obj +% 869 0 obj << /Type /Page -/Contents 865 0 R -/Resources 863 0 R +/Contents 870 0 R +/Resources 868 0 R /MediaBox [0 0 595.276 841.89] -/Parent 826 0 R -/Annots [ 848 0 R 849 0 R ] +/Parent 831 0 R +/Annots [ 853 0 R 854 0 R ] >> -% 848 0 obj +% 853 0 obj << /Type /Annot /Subtype /Link @@ -6537,7 +6428,7 @@ stream /Rect [305.513 683.645 320.236 694.494] /A << /S /GoTo /D (subsection.3.3) >> >> -% 849 0 obj +% 854 0 obj << /Type /Annot /Subtype /Link @@ -6545,53 +6436,53 @@ stream /Rect [305.513 640.185 320.236 651.033] /A << /S /GoTo /D (subsection.3.3) >> >> -% 866 0 obj +% 871 0 obj << -/D [864 0 R /XYZ 98.895 753.953 null] +/D [869 0 R /XYZ 98.895 753.953 null] >> -% 867 0 obj +% 872 0 obj << -/D [864 0 R /XYZ 99.895 716.092 null] +/D [869 0 R /XYZ 99.895 716.092 null] >> -% 868 0 obj +% 873 0 obj << -/D [864 0 R /XYZ 99.895 615.842 null] +/D [869 0 R /XYZ 99.895 615.842 null] >> -% 869 0 obj +% 874 0 obj << -/D [864 0 R /XYZ 99.895 600.277 null] +/D [869 0 R /XYZ 99.895 600.277 null] >> -% 870 0 obj +% 875 0 obj << -/D [864 0 R /XYZ 99.895 584.712 null] +/D [869 0 R /XYZ 99.895 584.712 null] >> -% 871 0 obj +% 876 0 obj << -/D [864 0 R /XYZ 147.412 369.037 null] +/D [869 0 R /XYZ 147.412 369.037 null] >> % 43 0 obj << -/D [864 0 R /XYZ 99.895 209.589 null] +/D [869 0 R /XYZ 99.895 209.589 null] >> % 47 0 obj << -/D [864 0 R /XYZ 99.895 191.2 null] +/D [869 0 R /XYZ 99.895 191.2 null] >> -% 863 0 obj +% 868 0 obj << -/Font << /F8 557 0 R /F27 556 0 R /F30 764 0 R >> +/Font << /F8 561 0 R /F27 560 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 875 0 obj +% 880 0 obj << /Type /Page -/Contents 876 0 R -/Resources 874 0 R +/Contents 881 0 R +/Resources 879 0 R /MediaBox [0 0 595.276 841.89] -/Parent 826 0 R -/Annots [ 872 0 R 873 0 R ] +/Parent 831 0 R +/Annots [ 877 0 R 878 0 R ] >> -% 872 0 obj +% 877 0 obj << /Type /Annot /Subtype /Link @@ -6599,7 +6490,7 @@ stream /Rect [351.231 623.115 358.204 635.07] /A << /S /GoTo /D (section.1) >> >> -% 873 0 obj +% 878 0 obj << /Type /Annot /Subtype /Link @@ -6607,99 +6498,99 @@ stream /Rect [186.34 408.904 193.314 420.859] /A << /S /GoTo /D (section.1) >> >> -% 877 0 obj +% 882 0 obj << -/D [875 0 R /XYZ 149.705 753.953 null] +/D [880 0 R /XYZ 149.705 753.953 null] >> % 51 0 obj << -/D [875 0 R /XYZ 150.705 599.327 null] +/D [880 0 R /XYZ 150.705 599.327 null] >> % 55 0 obj << -/D [875 0 R /XYZ 150.705 385.116 null] +/D [880 0 R /XYZ 150.705 385.116 null] >> % 59 0 obj << -/D [875 0 R /XYZ 150.705 194.815 null] +/D [880 0 R /XYZ 150.705 194.815 null] >> -% 874 0 obj +% 879 0 obj << -/Font << /F27 556 0 R /F8 557 0 R /F14 767 0 R /F10 766 0 R /F30 764 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F14 772 0 R /F10 771 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 879 0 obj +% 884 0 obj << /Type /Page -/Contents 880 0 R -/Resources 878 0 R +/Contents 885 0 R +/Resources 883 0 R /MediaBox [0 0 595.276 841.89] -/Parent 882 0 R +/Parent 887 0 R >> -% 881 0 obj +% 886 0 obj << -/D [879 0 R /XYZ 98.895 753.953 null] +/D [884 0 R /XYZ 98.895 753.953 null] >> % 63 0 obj << -/D [879 0 R /XYZ 99.895 614.689 null] +/D [884 0 R /XYZ 99.895 614.689 null] >> % 67 0 obj << -/D [879 0 R /XYZ 99.895 363.684 null] +/D [884 0 R /XYZ 99.895 363.684 null] >> % 71 0 obj << -/D [879 0 R /XYZ 99.895 192.327 null] +/D [884 0 R /XYZ 99.895 192.327 null] >> -% 878 0 obj +% 883 0 obj << -/Font << /F27 556 0 R /F8 557 0 R /F30 764 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 884 0 obj +% 889 0 obj << /Type /Page -/Contents 885 0 R -/Resources 883 0 R +/Contents 890 0 R +/Resources 888 0 R /MediaBox [0 0 595.276 841.89] -/Parent 882 0 R +/Parent 887 0 R >> -% 886 0 obj +% 891 0 obj << -/D [884 0 R /XYZ 149.705 753.953 null] +/D [889 0 R /XYZ 149.705 753.953 null] >> % 75 0 obj << -/D [884 0 R /XYZ 150.705 611.434 null] +/D [889 0 R /XYZ 150.705 611.434 null] >> -% 887 0 obj +% 892 0 obj << -/D [884 0 R /XYZ 395.482 457.068 null] +/D [889 0 R /XYZ 395.482 457.068 null] >> % 79 0 obj << -/D [884 0 R /XYZ 150.705 412.181 null] +/D [889 0 R /XYZ 150.705 412.181 null] >> % 83 0 obj << -/D [884 0 R /XYZ 150.705 311.051 null] +/D [889 0 R /XYZ 150.705 311.051 null] >> -% 883 0 obj +% 888 0 obj << -/Font << /F27 556 0 R /F8 557 0 R /F30 764 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 892 0 obj +% 897 0 obj << /Type /Page -/Contents 893 0 R -/Resources 891 0 R +/Contents 898 0 R +/Resources 896 0 R /MediaBox [0 0 595.276 841.89] -/Parent 882 0 R -/Annots [ 888 0 R 889 0 R 890 0 R ] +/Parent 887 0 R +/Annots [ 893 0 R 894 0 R 895 0 R ] >> -% 888 0 obj +% 893 0 obj << /Type /Annot /Subtype /Link @@ -6707,7 +6598,7 @@ stream /Rect [137.251 429.829 149.206 438.242] /A << /S /GoTo /D (cite.DesignPatterns) >> >> -% 889 0 obj +% 894 0 obj << /Type /Annot /Subtype /Link @@ -6715,7 +6606,7 @@ stream /Rect [218.095 429.829 230.05 438.242] /A << /S /GoTo /D (cite.Sparse03) >> >> -% 890 0 obj +% 895 0 obj << /Type /Annot /Subtype /Link @@ -6723,154 +6614,272 @@ stream /Rect [408.687 427.339 415.661 439.294] /A << /S /GoTo /D (figure.4) >> >> -% 894 0 obj +% 899 0 obj << -/D [892 0 R /XYZ 98.895 753.953 null] +/D [897 0 R /XYZ 98.895 753.953 null] >> % 87 0 obj << -/D [892 0 R /XYZ 99.895 716.092 null] +/D [897 0 R /XYZ 99.895 716.092 null] >> % 91 0 obj << -/D [892 0 R /XYZ 99.895 485.606 null] +/D [897 0 R /XYZ 99.895 485.606 null] >> -% 895 0 obj +% 900 0 obj << -/D [892 0 R /XYZ 120.548 454.736 null] +/D [897 0 R /XYZ 120.548 454.736 null] >> -% 896 0 obj +% 901 0 obj << -/D [892 0 R /XYZ 404.863 316.287 null] +/D [897 0 R /XYZ 404.863 316.287 null] >> -% 897 0 obj +% 902 0 obj << -/D [892 0 R /XYZ 155.008 217.826 null] +/D [897 0 R /XYZ 155.008 217.826 null] >> -% 891 0 obj +% 896 0 obj << -/Font << /F27 556 0 R /F8 557 0 R /F30 764 0 R /F16 554 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F30 769 0 R /F16 558 0 R >> /ProcSet [ /PDF /Text ] >> -% 900 0 obj +% 905 0 obj << /Type /Page -/Contents 901 0 R -/Resources 899 0 R +/Contents 906 0 R +/Resources 904 0 R /MediaBox [0 0 595.276 841.89] -/Parent 882 0 R +/Parent 887 0 R >> -% 902 0 obj +% 907 0 obj << -/D [900 0 R /XYZ 149.705 753.953 null] +/D [905 0 R /XYZ 149.705 753.953 null] >> % 95 0 obj << -/D [900 0 R /XYZ 150.705 509.604 null] +/D [905 0 R /XYZ 150.705 509.604 null] >> % 99 0 obj << -/D [900 0 R /XYZ 150.705 491.094 null] +/D [905 0 R /XYZ 150.705 491.094 null] >> % 103 0 obj << -/D [900 0 R /XYZ 150.705 296.318 null] +/D [905 0 R /XYZ 150.705 296.318 null] >> -% 899 0 obj +% 904 0 obj << -/Font << /F8 557 0 R /F27 556 0 R /F30 764 0 R >> +/Font << /F8 561 0 R /F27 560 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 904 0 obj +% 909 0 obj << /Type /Page -/Contents 905 0 R -/Resources 903 0 R +/Contents 910 0 R +/Resources 908 0 R /MediaBox [0 0 595.276 841.89] -/Parent 882 0 R +/Parent 887 0 R >> -% 906 0 obj +% 911 0 obj << -/D [904 0 R /XYZ 98.895 753.953 null] +/D [909 0 R /XYZ 98.895 753.953 null] >> % 107 0 obj << -/D [904 0 R /XYZ 99.895 718.084 null] +/D [909 0 R /XYZ 99.895 718.084 null] >> -% 907 0 obj +% 912 0 obj << -/D [904 0 R /XYZ 99.895 532.185 null] +/D [909 0 R /XYZ 99.895 532.185 null] >> % 111 0 obj << -/D [904 0 R /XYZ 99.895 477.767 null] ->> -% 115 0 obj -<< -/D [904 0 R /XYZ 99.895 279.894 null] ->> -% 903 0 obj -<< -/Font << /F27 556 0 R /F30 764 0 R /F8 557 0 R >> -/ProcSet [ /PDF /Text ] ->> -% 909 0 obj -<< -/Type /Page -/Contents 910 0 R -/Resources 908 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 882 0 R +/D [909 0 R /XYZ 99.895 477.767 null] >> endstream endobj -915 0 obj +916 0 obj << -/Length 4390 +/Length 4817 >> stream 0 g 0 G 0 g 0 G BT -/F27 9.9626 Tf 99.895 706.129 Td [(cscn)32(v)-383(|)-384(Con)32(v)32(ert)-383(to)-384(a)-383(di\013eren)32(t)-383(storage)-384(format)]TJ +/F27 9.9626 Tf 150.705 706.129 Td [(get)]TJ +ET +q +1 0 0 1 166.827 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 170.264 706.129 Td [(fm)32(t)-383(|)-384(Short)-383(description)-384(of)-383(the)-383(dynamic)-384(t)32(yp)-32(e)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf 0 -18.389 Td [(call)-1050(a%cscnv\050b,info)-525([,)-525(type,)-525(mold,)-525(dupl]\051)]TJ 0 -11.956 Td [(call)-1050(a%cscnv\050info)-525([,)-525(type,)-525(mold,)-525(dupl]\051)]TJ +/F30 9.9626 Tf -19.559 -18.389 Td [(write\050*,*\051)-525(a%get_fmt\050\051)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -21.446 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf 0 -20.78 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.737 Td [(On)-383(En)32(try)]TJ -0 g 0 G -0 g 0 G - 0 -19.736 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(sparse)-334(matrix.)]TJ 14.356 -11.955 Td [(A)-333(v)55(ariable)-333(of)-333(t)27(yp)-27(e)]TJ/F30 9.9626 Tf 81.943 0 Td [(psb_Tspmat_type)]TJ/F8 9.9626 Tf 78.455 0 Td [(.)]TJ -160.398 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -80.359 -31.691 Td [(t)32(yp)-32(e)]TJ -0 g 0 G -/F8 9.9626 Tf 27.1 0 Td [(a)-333(string)-334(requesting)-333(a)-333(new)-334(format.)]TJ -2.193 -11.956 Td [(T)28(yp)-28(e:)-444(optional.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -19.736 Td [(mold)]TJ -0 g 0 G -/F8 9.9626 Tf 29.805 0 Td [(a)-312(v)56(ariable)-312(of)]TJ/F30 9.9626 Tf 56.396 0 Td [(class\050psb_T_base_sparse_mat\051)]TJ/F8 9.9626 Tf 149.557 0 Td [(requesting)-312(a)-312(new)-312(format.)]TJ -210.851 -11.955 Td [(T)28(yp)-28(e:)-444(optional.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -19.737 Td [(dupl)]TJ -0 g 0 G -/F8 9.9626 Tf 27.259 0 Td [(an)-268(in)28(teger)-268(v)56(alue)-268(sp)-28(eci\014ng)-267(ho)27(w)-267(to)-268(handle)-268(duplicates)-268(\050see)-268(Named)-267(Constan)27(ts)]TJ -2.352 -11.955 Td [(b)-28(elo)28(w\051)]TJ +/F27 9.9626 Tf -33.797 -19.47 Td [(On)-383(En)32(try)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -21.446 Td [(On)-383(Return)]TJ 0 g 0 G + 0 -19.47 Td [(a)]TJ 0 g 0 G - 0 -19.737 Td [(b,a)]TJ +/F8 9.9626 Tf 10.551 0 Td [(the)-333(sparse)-334(matrix)]TJ 14.355 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ 0 g 0 G -/F8 9.9626 Tf 20.098 0 Td [(A)-333(cop)27(y)-333(of)]TJ/F30 9.9626 Tf 45.386 0 Td [(a)]TJ/F8 9.9626 Tf 8.551 0 Td [(with)-333(a)-334(new)-333(storage)-333(format.)]TJ -49.128 -11.955 Td [(A)-333(v)55(ariable)-333(of)-333(t)27(yp)-27(e)]TJ/F30 9.9626 Tf 81.943 0 Td [(psb_Tspmat_type)]TJ/F8 9.9626 Tf 78.455 0 Td [(.)]TJ + -57.285 -32.735 Td [(On)-383(Return)]TJ 0 g 0 G -/F27 9.9626 Tf -185.305 -19.737 Td [(info)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Return)-333(co)-28(de.)]TJ -23.758 -21.446 Td [(The)]TJ/F30 9.9626 Tf 20.085 0 Td [(mold)]TJ/F8 9.9626 Tf 23.848 0 Td [(argumen)28(ts)-294(ma)28(y)-294(b)-28(e)-294(emplo)28(y)28(ed)-294(to)-294(in)28(terface)-294(with)-293(sp)-28(ecial)-294(devices,)-302(suc)28(h)-294(as)]TJ -43.933 -11.955 Td [(GPUs)-333(and)-334(other)-333(accelerators.)]TJ/F27 9.9626 Tf 0 -25.815 Td [(csclip)-383(|)-384(Reduce)-383(to)-383(a)-384(submatrix)]TJ + 0 -19.47 Td [(F)96(unction)-384(v)64(alue)]TJ +0 g 0 G +/F8 9.9626 Tf 78.386 0 Td [(A)-484(short)-483(string)-484(describing)-484(the)-484(dynamic)-484(t)28(yp)-28(e)-483(of)-484(the)-484(matrix.)]TJ -53.48 -11.955 Td [(Prede\014ned)-333(v)55(alues)-333(include)]TJ/F30 9.9626 Tf 113.409 0 Td [(NULL)]TJ/F8 9.9626 Tf 20.921 0 Td [(,)]TJ/F30 9.9626 Tf 6.088 0 Td [(COO)]TJ/F8 9.9626 Tf 15.691 0 Td [(,)]TJ/F30 9.9626 Tf 6.089 0 Td [(CSR)]TJ/F8 9.9626 Tf 19.012 0 Td [(and)]TJ/F30 9.9626 Tf 19.371 0 Td [(CSC)]TJ/F8 9.9626 Tf 15.691 0 Td [(.)]TJ/F27 9.9626 Tf -241.178 -25.7 Td [(is)]TJ +ET +q +1 0 0 1 159.094 526.404 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 162.531 526.205 Td [(bld,)-383(is)]TJ +ET +q +1 0 0 1 193.834 526.404 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 197.271 526.205 Td [(up)-32(d,)-383(is)]TJ +ET +q +1 0 0 1 232.075 526.404 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 235.512 526.205 Td [(asb)-383(|)-384(Status)-383(c)32(hec)32(k)]TJ +0 g 0 G +0 g 0 G +/F30 9.9626 Tf -84.807 -18.39 Td [(if)-525(\050a%is_bld\050\051\051)-525(then)]TJ 0 -11.955 Td [(if)-525(\050a%is_upd\050\051\051)-525(then)]TJ 0 -11.955 Td [(if)-525(\050a%is_asb\050\051\051)-525(then)]TJ +0 g 0 G +/F27 9.9626 Tf 0 -20.78 Td [(T)32(yp)-32(e:)]TJ +0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +0 g 0 G +/F27 9.9626 Tf -33.797 -19.47 Td [(On)-383(En)32(try)]TJ +0 g 0 G +0 g 0 G + 0 -19.47 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.551 0 Td [(the)-333(sparse)-334(matrix)]TJ 14.356 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ +0 g 0 G + -57.285 -32.735 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G + 0 -19.47 Td [(F)96(unction)-384(v)64(alue)]TJ +0 g 0 G +/F8 9.9626 Tf 78.386 0 Td [(A)]TJ/F30 9.9626 Tf 9.728 0 Td [(logical)]TJ/F8 9.9626 Tf 38.869 0 Td [(v)56(alue)-227(indicating)-226(whether)-227(the)-226(m)-1(atr)1(ix)-227(is)-227(in)-226(the)-227(Build)1(,)]TJ -102.076 -11.955 Td [(Up)-28(date)-333(or)-333(Assem)27(bled)-333(state,)-333(resp)-28(ectiv)28(e)-1(l)1(y)83(.)]TJ/F27 9.9626 Tf -24.907 -25.7 Td [(is)]TJ +ET +q +1 0 0 1 159.094 322.57 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 162.531 322.37 Td [(lo)32(w)32(er,)-383(i)-1(s)]TJ +ET +q +1 0 0 1 204.44 322.57 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 207.877 322.37 Td [(upp)-32(er,)-383(is)]TJ +ET +q +1 0 0 1 252.65 322.57 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 256.087 322.37 Td [(triangle,)-384(is)]TJ +ET +q +1 0 0 1 309.931 322.57 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 313.368 322.37 Td [(unit)-383(|)-384(F)96(ormat)-383(c)32(hec)32(k)]TJ +0 g 0 G +0 g 0 G +/F30 9.9626 Tf -162.663 -18.389 Td [(if)-525(\050a%is_triangle\050\051\051)-525(then)]TJ 0 -11.955 Td [(if)-525(\050a%is_upper\050\051\051)-525(then)]TJ 0 -11.955 Td [(if)-525(\050a%is_lower\050\051\051)-525(then)]TJ 0 -11.955 Td [(if)-525(\050a%is_unit\050\051\051)-525(then)]TJ +0 g 0 G +/F27 9.9626 Tf 0 -20.78 Td [(T)32(yp)-32(e:)]TJ +0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +0 g 0 G +/F27 9.9626 Tf -33.797 -19.47 Td [(On)-383(En)32(try)]TJ +0 g 0 G +0 g 0 G + 0 -19.47 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.551 0 Td [(the)-333(sparse)-334(matrix)]TJ 14.356 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ +0 g 0 G + -57.285 -32.735 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G + 0 -19.47 Td [(F)96(unction)-384(v)64(alue)]TJ +0 g 0 G +/F8 9.9626 Tf 78.386 0 Td [(A)]TJ/F30 9.9626 Tf 10.615 0 Td [(logical)]TJ/F8 9.9626 Tf 39.755 0 Td [(v)56(alue)-316(indicating)-315(whether)-316(the)-315(matrix)-316(i)1(s)-316(triangular;)]TJ -103.849 -11.955 Td [(if)]TJ/F30 9.9626 Tf 8.895 0 Td [(is_triangle\050\051)]TJ/F8 9.9626 Tf 71.079 0 Td [(returns)]TJ/F30 9.9626 Tf 34.189 0 Td [(.true.)]TJ/F8 9.9626 Tf 34.466 0 Td [(c)28(hec)27(k)-309(also)-310(if)-309(it)-310(is)-309(lo)27(w)28(er,)-314(upp)-28(er)-309(and)-310(with)]TJ -148.629 -11.955 Td [(a)-333(unit)-334(\050i)1(.e)-1(.)-444(assumed\051)-333(diagonal.)]TJ +0 g 0 G + 141.967 -29.888 Td [(18)]TJ +0 g 0 G +ET + +endstream +endobj +920 0 obj +<< +/Length 4390 +>> +stream +0 g 0 G +0 g 0 G +BT +/F27 9.9626 Tf 99.895 706.129 Td [(cscn)32(v)-383(|)-384(Con)32(v)32(ert)-383(to)-384(a)-383(di\013eren)32(t)-383(storage)-384(format)]TJ +0 g 0 G +0 g 0 G +/F30 9.9626 Tf 0 -18.389 Td [(call)-1050(a%cscnv\050b,info)-525([,)-525(type,)-525(mold,)-525(dupl]\051)]TJ 0 -11.956 Td [(call)-1050(a%cscnv\050info)-525([,)-525(type,)-525(mold,)-525(dupl]\051)]TJ +0 g 0 G +/F27 9.9626 Tf 0 -21.446 Td [(T)32(yp)-32(e:)]TJ +0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +0 g 0 G +/F27 9.9626 Tf -33.797 -19.737 Td [(On)-383(En)32(try)]TJ +0 g 0 G +0 g 0 G + 0 -19.736 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.551 0 Td [(the)-333(sparse)-334(matrix.)]TJ 14.356 -11.955 Td [(A)-333(v)55(ariable)-333(of)-333(t)27(yp)-27(e)]TJ/F30 9.9626 Tf 81.943 0 Td [(psb_Tspmat_type)]TJ/F8 9.9626 Tf 78.455 0 Td [(.)]TJ -160.398 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -80.359 -31.691 Td [(t)32(yp)-32(e)]TJ +0 g 0 G +/F8 9.9626 Tf 27.1 0 Td [(a)-333(string)-334(requesting)-333(a)-333(new)-334(format.)]TJ -2.193 -11.956 Td [(T)28(yp)-28(e:)-444(optional.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.736 Td [(mold)]TJ +0 g 0 G +/F8 9.9626 Tf 29.805 0 Td [(a)-312(v)56(ariable)-312(of)]TJ/F30 9.9626 Tf 56.396 0 Td [(class\050psb_T_base_sparse_mat\051)]TJ/F8 9.9626 Tf 149.557 0 Td [(requesting)-312(a)-312(new)-312(format.)]TJ -210.851 -11.955 Td [(T)28(yp)-28(e:)-444(optional.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.737 Td [(dupl)]TJ +0 g 0 G +/F8 9.9626 Tf 27.259 0 Td [(an)-268(in)28(teger)-268(v)56(alue)-268(sp)-28(eci\014ng)-267(ho)27(w)-267(to)-268(handle)-268(duplicates)-268(\050see)-268(Named)-267(Constan)27(ts)]TJ -2.352 -11.955 Td [(b)-28(elo)28(w\051)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -21.446 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G + 0 -19.737 Td [(b,a)]TJ +0 g 0 G +/F8 9.9626 Tf 20.098 0 Td [(A)-333(cop)27(y)-333(of)]TJ/F30 9.9626 Tf 45.386 0 Td [(a)]TJ/F8 9.9626 Tf 8.551 0 Td [(with)-333(a)-334(new)-333(storage)-333(format.)]TJ -49.128 -11.955 Td [(A)-333(v)55(ariable)-333(of)-333(t)27(yp)-27(e)]TJ/F30 9.9626 Tf 81.943 0 Td [(psb_Tspmat_type)]TJ/F8 9.9626 Tf 78.455 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -185.305 -19.737 Td [(info)]TJ +0 g 0 G +/F8 9.9626 Tf 23.758 0 Td [(Return)-333(co)-28(de.)]TJ -23.758 -21.446 Td [(The)]TJ/F30 9.9626 Tf 20.085 0 Td [(mold)]TJ/F8 9.9626 Tf 23.848 0 Td [(argumen)28(ts)-294(ma)28(y)-294(b)-28(e)-294(emplo)28(y)28(ed)-294(to)-294(in)28(terface)-294(with)-293(sp)-28(ecial)-294(devices,)-302(suc)28(h)-294(as)]TJ -43.933 -11.955 Td [(GPUs)-333(and)-334(other)-333(accelerators.)]TJ/F27 9.9626 Tf 0 -25.815 Td [(csclip)-383(|)-384(Reduce)-383(to)-383(a)-384(submatrix)]TJ 0 g 0 G 0 g 0 G /F30 9.9626 Tf 20.922 -18.389 Td [(call)-525(a%csclip\050b,info[,&)]TJ 15.691 -11.955 Td [(&)-525(imin,imax,jmin,jmax,rscale,cscale]\051)]TJ/F8 9.9626 Tf -21.669 -21.447 Td [(Returns)-222(the)-222(submatrix)]TJ/F30 9.9626 Tf 99.101 0 Td [(A\050imin:imax,jmin:jmax\051)]TJ/F8 9.9626 Tf 115.068 0 Td [(,)-244(optionally)-222(res)-1(calin)1(g)-223(ro)28(w/-)]TJ -229.113 -11.955 Td [(col)-333(indices)-334(to)-333(the)-333(range)]TJ/F30 9.9626 Tf 104.691 0 Td [(1:imax-imin+1,1:jmax-jmin+1)]TJ/F8 9.9626 Tf 141.219 0 Td [(.)]TJ @@ -6903,7 +6912,7 @@ ET endstream endobj -920 0 obj +925 0 obj << /Length 3769 >> @@ -6990,7 +6999,7 @@ ET endstream endobj -924 0 obj +929 0 obj << /Length 4823 >> @@ -7079,7 +7088,7 @@ ET endstream endobj -928 0 obj +933 0 obj << /Length 4738 >> @@ -7181,7 +7190,7 @@ ET endstream endobj -934 0 obj +939 0 obj << /Length 7666 >> @@ -7432,7 +7441,7 @@ ET endstream endobj -940 0 obj +945 0 obj << /Length 3183 >> @@ -7517,7 +7526,7 @@ ET endstream endobj -946 0 obj +951 0 obj << /Length 3935 >> @@ -7591,7 +7600,7 @@ ET endstream endobj -954 0 obj +959 0 obj << /Length 5381 >> @@ -7720,7 +7729,7 @@ ET endstream endobj -961 0 obj +966 0 obj << /Length 758 >> @@ -7754,7 +7763,7 @@ ET endstream endobj -965 0 obj +970 0 obj << /Length 158 >> @@ -7770,7 +7779,7 @@ ET endstream endobj -976 0 obj +981 0 obj << /Length 7361 >> @@ -7951,7 +7960,7 @@ ET endstream endobj -982 0 obj +987 0 obj << /Length 2655 >> @@ -8025,9 +8034,9 @@ ET endstream endobj -992 0 obj +996 0 obj << -/Length 7903 +/Length 7700 >> stream 0 g 0 G @@ -8040,99 +8049,99 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(gedot)-375(|)-375(Dot)-375(Pro)-31(duct)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-333(function)-334(computes)-333(dot)-333(pro)-28(duct)-333(b)-28(et)28(w)27(een)-333(t)28(w)28(o)-334(v)28(ectors)]TJ/F11 9.9626 Tf 252.332 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(and)]TJ/F11 9.9626 Tf 19.372 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -285.961 -11.956 Td [(If)]TJ/F11 9.9626 Tf 9.963 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(and)]TJ/F11 9.9626 Tf 19.372 0 Td [(y)]TJ/F8 9.9626 Tf 8.562 0 Td [(are)-333(real)-334(v)28(ectors)-333(it)-334(computes)-333(dot-pro)-28(duct)-333(as:)]TJ/F11 9.9626 Tf 101.783 -20.45 Td [(dot)]TJ/F14 9.9626 Tf 16.38 0 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(x)]TJ/F10 6.9738 Tf 5.694 4.113 Td [(T)]TJ/F11 9.9626 Tf 6.276 -4.113 Td [(y)]TJ/F8 9.9626 Tf -189.775 -20.451 Td [(Else)-333(if)]TJ/F11 9.9626 Tf 30.359 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(and)]TJ/F11 9.9626 Tf 19.371 0 Td [(y)]TJ/F8 9.9626 Tf 8.563 0 Td [(are)-333(complex)-334(v)28(ectors)-333(then)-334(it)-333(computes)-333(dot-pro)-28(duct)-333(as:)]TJ/F11 9.9626 Tf 80.747 -20.451 Td [(dot)]TJ/F14 9.9626 Tf 16.38 0 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(x)]TJ/F10 6.9738 Tf 5.693 4.113 Td [(H)]TJ/F11 9.9626 Tf 7.557 -4.113 Td [(y)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(gedot)-375(|)-375(Dot)-375(Pro)-31(duct)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-333(function)-334(computes)-333(dot)-333(pro)-28(duct)-333(b)-28(et)28(w)27(een)-333(t)28(w)28(o)-334(v)28(ectors)]TJ/F11 9.9626 Tf 252.332 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(and)]TJ/F11 9.9626 Tf 19.372 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -285.961 -11.956 Td [(If)]TJ/F11 9.9626 Tf 9.963 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(and)]TJ/F11 9.9626 Tf 19.372 0 Td [(y)]TJ/F8 9.9626 Tf 8.562 0 Td [(are)-333(real)-334(v)28(ectors)-333(it)-334(computes)-333(dot-pro)-28(duct)-333(as:)]TJ/F11 9.9626 Tf 101.783 -21.289 Td [(dot)]TJ/F14 9.9626 Tf 16.38 0 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(x)]TJ/F10 6.9738 Tf 5.694 4.113 Td [(T)]TJ/F11 9.9626 Tf 6.276 -4.113 Td [(y)]TJ/F8 9.9626 Tf -189.775 -21.29 Td [(Else)-333(if)]TJ/F11 9.9626 Tf 30.359 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(and)]TJ/F11 9.9626 Tf 19.371 0 Td [(y)]TJ/F8 9.9626 Tf 8.563 0 Td [(are)-333(complex)-334(v)28(ectors)-333(then)-334(it)-333(computes)-333(dot-pro)-28(duct)-333(as:)]TJ/F11 9.9626 Tf 80.747 -21.29 Td [(dot)]TJ/F14 9.9626 Tf 16.38 0 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(x)]TJ/F10 6.9738 Tf 5.693 4.113 Td [(H)]TJ/F11 9.9626 Tf 7.557 -4.113 Td [(y)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -190.415 -20.451 Td [(psb_gedot\050x,)-525(y,)-525(desc_a,)-525(info\051)]TJ +/F30 9.9626 Tf -190.415 -21.29 Td [(psb_gedot\050x,)-525(y,)-525(desc_a,)-525(info)-525([,global]\051)]TJ 0 g 0 G 0 g 0 G 0 g 0 G ET q -1 0 0 1 183.665 571.704 cm +1 0 0 1 183.665 567.173 cm []0 d 0 J 0.398 w 0 0 m 176.173 0 l S Q BT -/F11 9.9626 Tf 189.642 563.136 Td [(dot)]TJ/F8 9.9626 Tf 13.612 0 Td [(,)]TJ/F11 9.9626 Tf 6.089 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(y)]TJ/F27 9.9626 Tf 88.927 0 Td [(F)96(unction)]TJ +/F11 9.9626 Tf 189.642 558.606 Td [(dot)]TJ/F8 9.9626 Tf 13.612 0 Td [(,)]TJ/F11 9.9626 Tf 6.089 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(y)]TJ/F27 9.9626 Tf 88.927 0 Td [(F)96(unction)]TJ ET q -1 0 0 1 183.665 559.35 cm +1 0 0 1 183.665 554.82 cm []0 d 0 J 0.398 w 0 0 m 176.173 0 l S Q BT -/F8 9.9626 Tf 189.642 550.783 Td [(Short)-333(Precision)-334(Real)-3102(psb)]TJ +/F8 9.9626 Tf 189.642 546.252 Td [(Short)-333(Precision)-334(Real)-3102(psb)]TJ ET q -1 0 0 1 325.649 550.982 cm +1 0 0 1 325.649 546.451 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 328.638 550.783 Td [(gedot)]TJ -138.996 -11.956 Td [(Long)-333(Precision)-334(Real)-3314(psb)]TJ +/F8 9.9626 Tf 328.638 546.252 Td [(gedot)]TJ -138.996 -11.955 Td [(Long)-333(Precision)-334(Real)-3314(psb)]TJ ET q -1 0 0 1 325.649 539.027 cm +1 0 0 1 325.649 534.496 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 328.638 538.827 Td [(gedot)]TJ -138.996 -11.955 Td [(Short)-333(Precision)-334(Complex)-1200(psb)]TJ +/F8 9.9626 Tf 328.638 534.297 Td [(gedot)]TJ -138.996 -11.955 Td [(Short)-333(Precision)-334(Complex)-1200(psb)]TJ ET q -1 0 0 1 325.649 527.071 cm +1 0 0 1 325.649 522.541 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 328.638 526.872 Td [(gedot)]TJ -138.996 -11.955 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ +/F8 9.9626 Tf 328.638 522.342 Td [(gedot)]TJ -138.996 -11.956 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ ET q -1 0 0 1 325.649 515.116 cm +1 0 0 1 325.649 510.586 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 328.638 514.917 Td [(gedot)]TJ +/F8 9.9626 Tf 328.638 510.386 Td [(gedot)]TJ ET q -1 0 0 1 183.665 511.131 cm +1 0 0 1 183.665 506.601 cm []0 d 0 J 0.398 w 0 0 m 176.173 0 l S Q 0 g 0 G BT -/F8 9.9626 Tf 228.067 483.092 Td [(T)83(able)-333(2:)-444(Data)-334(t)28(yp)-28(es)]TJ +/F8 9.9626 Tf 228.067 478.561 Td [(T)83(able)-333(2:)-444(Data)-334(t)28(yp)-28(es)]TJ 0 g 0 G 0 g 0 G 0 g 0 G -/F27 9.9626 Tf -128.172 -31.542 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf -128.172 -32.717 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.339 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -33.797 -19.674 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.338 Td [(x)]TJ + 0 -19.674 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -167.933 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-55(jec)-1(t)-254(of)-255(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -167.933 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-55(jec)-1(t)-254(of)-255(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 244.743 0 Td [(psb)]TJ ET q -1 0 0 1 385.864 365.251 cm +1 0 0 1 385.864 358.875 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 389.002 365.052 Td [(T)]TJ +/F30 9.9626 Tf 389.002 358.675 Td [(T)]TJ ET q -1 0 0 1 394.86 365.251 cm +1 0 0 1 394.86 358.875 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 397.998 365.052 Td [(vect)]TJ +/F30 9.9626 Tf 397.998 358.675 Td [(vect)]TJ ET q -1 0 0 1 419.547 365.251 cm +1 0 0 1 419.547 358.875 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 422.685 365.052 Td [(type)]TJ +/F30 9.9626 Tf 422.685 358.675 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf -297.883 -11.955 Td [(con)28(taining)-375(n)27(u)1(m)27(b)-27(e)-1(r)1(s)-376(of)-375(t)28(yp)-28(e)-375(sp)-28(eci\014ed)-375(in)-375(T)83(able)]TJ 0 0 1 rg 0 0 1 RG @@ -8140,32 +8149,32 @@ BT 0 g 0 G [(.)-570(The)-376(rank)-375(of)]TJ/F11 9.9626 Tf 274.03 0 Td [(x)]TJ/F8 9.9626 Tf 9.432 0 Td [(m)28(ust)-376(b)-27(e)]TJ -283.462 -11.955 Td [(the)-333(same)-334(of)]TJ/F11 9.9626 Tf 53.466 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -83.615 -19.339 Td [(y)]TJ +/F27 9.9626 Tf -83.615 -19.674 Td [(y)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -167.481 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-55(jec)-1(t)-254(of)-255(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -167.481 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-55(jec)-1(t)-254(of)-255(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 244.743 0 Td [(psb)]TJ ET q -1 0 0 1 385.864 274.182 cm +1 0 0 1 385.864 267.47 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 389.002 273.982 Td [(T)]TJ +/F30 9.9626 Tf 389.002 267.27 Td [(T)]TJ ET q -1 0 0 1 394.86 274.182 cm +1 0 0 1 394.86 267.47 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 397.998 273.982 Td [(vect)]TJ +/F30 9.9626 Tf 397.998 267.27 Td [(vect)]TJ ET q -1 0 0 1 419.547 274.182 cm +1 0 0 1 419.547 267.47 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 422.685 273.982 Td [(type)]TJ +/F30 9.9626 Tf 422.685 267.27 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf -297.883 -11.955 Td [(con)28(taining)-378(n)27(um)28(b)-28(ers)-378(of)-378(t)28(yp)-28(e)-378(sp)-28(eci\014ed)-378(in)-379(T)84(able)]TJ 0 0 1 rg 0 0 1 RG @@ -8173,418 +8182,302 @@ BT 0 g 0 G [(.)-580(The)-378(rank)-378(of)]TJ/F11 9.9626 Tf 274.422 0 Td [(y)]TJ/F8 9.9626 Tf 9.01 0 Td [(m)28(ust)-379(b)-27(e)]TJ -283.432 -11.955 Td [(the)-333(same)-334(of)]TJ/F11 9.9626 Tf 53.466 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -84.067 -19.338 Td [(desc)]TJ +/F27 9.9626 Tf -84.067 -19.674 Td [(desc)]TJ ET q -1 0 0 1 121.81 230.933 cm +1 0 0 1 121.81 223.885 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 125.247 230.734 Td [(a)]TJ +/F27 9.9626 Tf 125.247 223.686 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(con)28(tains)-334(d)1(ata)-334(structures)-333(for)-333(com)-1(m)28(unications.)]TJ -10.996 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.551 0 Td [(con)28(tains)-334(d)1(ata)-334(structures)-333(for)-333(com)-1(m)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 135.658 0 Td [(psb)]TJ ET q -1 0 0 1 276.779 183.112 cm +1 0 0 1 276.779 176.064 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 279.917 182.913 Td [(desc)]TJ +/F30 9.9626 Tf 279.917 175.865 Td [(desc)]TJ ET q -1 0 0 1 301.466 183.112 cm +1 0 0 1 301.466 176.064 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 304.604 182.913 Td [(type)]TJ +/F30 9.9626 Tf 304.604 175.865 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -225.631 -19.339 Td [(On)-383(Return)]TJ -0 g 0 G -0 g 0 G - 0 -19.338 Td [(F)96(unction)-384(v)64(alue)]TJ -0 g 0 G -/F8 9.9626 Tf 78.387 0 Td [(is)-333(the)-334(dot)-333(pro)-28(duct)-333(of)-333(sub)28(v)27(ectors)]TJ/F11 9.9626 Tf 142.189 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(and)]TJ/F11 9.9626 Tf 19.371 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -229.297 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(n)28(um)28(b)-28(er)-333(of)-334(the)-333(data)-333(t)28(yp)-28(e)-334(ind)1(ic)-1(ated)-333(in)-333(T)83(able)]TJ -0 0 1 rg 0 0 1 RG - [-333(2)]TJ +/F27 9.9626 Tf -225.631 -19.674 Td [(global)]TJ 0 g 0 G - [(.)]TJ +/F8 9.9626 Tf 34.738 0 Td [(Sp)-28(eci\014es)-357(whether)-357(the)-357(computation)-358(shoul)1(d)-358(include)-357(the)-357(global)-357(reduction)]TJ -9.831 -11.955 Td [(across)-333(all)-334(pro)-27(ce)-1(sses.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ 0 g 0 G - 141.968 -29.888 Td [(31)]TJ + 71.78 -29.888 Td [(31)]TJ 0 g 0 G ET endstream endobj -998 0 obj +1003 0 obj << -/Length 625 +/Length 5129 >> stream 0 g 0 G 0 g 0 G -0 g 0 G BT -/F27 9.9626 Tf 150.705 706.129 Td [(info)]TJ -0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ +/F8 9.9626 Tf 175.611 706.129 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(logical)-333(scalar.)-445(Default:)]TJ/F30 9.9626 Tf 168.812 0 Td [(global=.true.)]TJ 0 g 0 G - 141.968 -567.87 Td [(32)]TJ +/F27 9.9626 Tf -193.718 -31.881 Td [(On)-383(Return)]TJ 0 g 0 G -ET - -endstream -endobj -1008 0 obj -<< -/Length 8468 ->> -stream 0 g 0 G + 0 -19.925 Td [(F)96(unction)-384(v)64(alue)]TJ 0 g 0 G -BT -/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ -ET -q -1 0 0 1 120.951 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 124.986 706.129 Td [(gedots)-375(|)-375(Generalized)-375(Dot)-375(Pro)-31(duct)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-392(subroutine)-392(computes)-392(a)-392(series)-392(of)-391(dot)-392(pro)-28(ducts)-392(among)-392(the)-392(columns)-392(of)-391(t)27(w)28(o)]TJ 0 -11.956 Td [(dense)-333(matrices)]TJ/F11 9.9626 Tf 67.11 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(and)]TJ/F11 9.9626 Tf 19.372 0 Td [(y)]TJ/F8 9.9626 Tf 5.241 0 Td [(:)]TJ/F11 9.9626 Tf 23.756 -11.955 Td [(r)-28(es)]TJ/F8 9.9626 Tf 14.081 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)]TJ/F14 9.9626 Tf 6.642 0 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(\050:)]TJ/F11 9.9626 Tf 6.642 0 Td [(;)-167(i)]TJ/F8 9.9626 Tf 7.86 0 Td [(\051)]TJ/F10 6.9738 Tf 3.874 4.114 Td [(T)]TJ/F11 9.9626 Tf 6.276 -4.114 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(\050:)]TJ/F11 9.9626 Tf 6.642 0 Td [(;)-167(i)]TJ/F8 9.9626 Tf 7.86 0 Td [(\051)]TJ -215.343 -15.687 Td [(If)-245(the)-245(matrices)-245(are)-245(complex,)-262(then)-245(the)-245(usual)-245(con)28(v)28(e)-1(n)28(tion)-245(app)1(lie)-1(s,)-262(i.e.)-415(the)-245(conjugate)]TJ 0 -11.955 Td [(transp)-28(ose)-323(of)]TJ/F11 9.9626 Tf 55.836 0 Td [(x)]TJ/F8 9.9626 Tf 8.913 0 Td [(is)-323(used.)-441(If)]TJ/F11 9.9626 Tf 46.366 0 Td [(x)]TJ/F8 9.9626 Tf 8.913 0 Td [(and)]TJ/F11 9.9626 Tf 19.269 0 Td [(y)]TJ/F8 9.9626 Tf 8.461 0 Td [(are)-323(of)-323(rank)-323(one,)-325(then)]TJ/F11 9.9626 Tf 94.212 0 Td [(r)-28(es)]TJ/F8 9.9626 Tf 17.299 0 Td [(is)-323(a)-323(scalar,)-325(else)-324(it)-323(is)]TJ -259.269 -11.955 Td [(a)-333(rank)-334(one)-333(arra)28(y)83(.)]TJ +/F8 9.9626 Tf 78.386 0 Td [(is)-333(the)-334(dot)-333(pro)-28(duct)-333(of)-333(sub)28(v)27(ectors)]TJ/F11 9.9626 Tf 142.189 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(and)]TJ/F11 9.9626 Tf 19.372 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -229.298 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.167 0 Td [(global)]TJ/F8 9.9626 Tf 32.653 0 Td [(unless)-291(the)-291(option)1(a)-1(l)-290(v)55(ariable)]TJ/F30 9.9626 Tf 121.039 0 Td [(global=.false.)]TJ/F8 9.9626 Tf 76.121 0 Td [(as)-291(b)-28(een)-290(sp)-28(ec-)]TJ -261.98 -11.955 Td [(i\014ed)]TJ 0 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(n)28(um)28(b)-28(er)-333(of)-334(the)-333(data)-333(t)27(yp)-27(e)-334(indicated)-333(in)-333(T)83(able)]TJ +0 0 1 rg 0 0 1 RG + [-333(2)]TJ 0 g 0 G + [(.)]TJ 0 g 0 G -/F30 9.9626 Tf 0 -18.175 Td [(call)-525(psb_gedots\050res,)-525(x,)-525(y,)-525(desc_a,)-525(info\051)]TJ +/F27 9.9626 Tf -24.906 -19.925 Td [(info)]TJ 0 g 0 G +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.956 Td [(An)-333(in)28(te)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ/F16 11.9552 Tf -24.906 -21.917 Td [(Notes)]TJ 0 g 0 G +/F8 9.9626 Tf 12.176 -19.926 Td [(1.)]TJ 0 g 0 G + [-500(The)-241(computation)-240(of)-241(a)-241(gl)1(obal)-241(result)-241(requires)-240(a)-241(global)-241(comm)28(unication,)-259(whic)28(h)]TJ 12.73 -11.955 Td [(en)28(tails)-421(a)-420(s)-1(i)1(gni\014can)27(t)-420(o)28(v)27(erhead.)-706(It)-420(ma)27(y)-420(b)-28(e)-421(necessary)-420(and/or)-421(advisable)-420(to)]TJ 0 -11.955 Td [(compute)-265(m)27(ultiple)-265(dot)-265(pro)-28(ducts)-265(at)-266(the)-265(same)-266(time;)-288(in)-265(this)-265(case,)-279(it)-266(is)-265(p)-28(ossible)]TJ 0 -11.955 Td [(to)-333(impro)27(v)28(e)-333(the)-333(run)27(time)-333(e\016ciency)-333(b)27(y)-333(using)-333(the)-334(f)1(o)-1(l)1(lo)27(wing)-333(sc)28(heme:)]TJ 25.19 -17.933 Td [(v)-128(r)-129(e)-128(s)-259(\050)-130(1)-131(\051)-642(=)-625(p)-115(s)-114(b)]TJ ET q -1 0 0 1 177.988 586.966 cm -[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S -Q -BT -/F11 9.9626 Tf 183.966 578.398 Td [(r)-28(es)]TJ/F8 9.9626 Tf 14.08 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(y)]TJ/F27 9.9626 Tf 88.459 0 Td [(Subroutine)]TJ -ET -q -1 0 0 1 177.988 574.612 cm -[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S -Q -BT -/F8 9.9626 Tf 183.966 566.045 Td [(Short)-333(Precision)-333(R)-1(eal)-3102(psb)]TJ -ET -q -1 0 0 1 319.972 566.244 cm +1 0 0 1 279.461 443.314 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 322.961 566.045 Td [(gedots)]TJ -138.995 -11.956 Td [(Long)-333(Precision)-334(Real)-3314(p)1(s)-1(b)]TJ +/F8 9.9626 Tf 283.591 443.115 Td [(g)-115(e)-114(d)-115(o)-114(t)-220(\050)-149(x)-43(1)-247(,)-204(y)-43(1)-248(,)-273(d)-113(e)-113(s)-112(c)]TJ ET q -1 0 0 1 319.972 554.289 cm +1 0 0 1 379.47 443.314 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 322.961 554.089 Td [(gedots)]TJ -138.995 -11.955 Td [(Short)-333(Precision)-333(C)-1(omplex)-1200(p)1(s)-1(b)]TJ +/F8 9.9626 Tf 383.581 443.115 Td [(a)-386(,)-288(i)-127(n)-127(f)-127(o)-415(,)-302(g)-141(l)-142(o)-141(b)-141(a)-141(l)-190(=)-48(.)]TJ/F27 9.9626 Tf 92.224 0 Td [(f)-132(a)-131(l)-132(s)-131(e)]TJ/F8 9.9626 Tf 30.348 0 Td [(.)-178(\051)]TJ -305.352 -11.955 Td [(v)-128(r)-129(e)-128(s)-259(\050)-130(2)-131(\051)-642(=)-625(p)-115(s)-114(b)]TJ ET q -1 0 0 1 319.972 542.333 cm +1 0 0 1 279.461 431.359 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 322.961 542.134 Td [(gedots)]TJ -138.995 -11.955 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ +/F8 9.9626 Tf 283.591 431.16 Td [(g)-115(e)-114(d)-115(o)-114(t)-220(\050)-149(x)-43(2)-247(,)-204(y)-43(2)-248(,)-273(d)-113(e)-113(s)-112(c)]TJ ET q -1 0 0 1 319.972 530.378 cm +1 0 0 1 379.47 431.359 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 322.961 530.179 Td [(gedots)]TJ -ET -q -1 0 0 1 177.988 526.393 cm -[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S -Q -0 g 0 G -BT -/F8 9.9626 Tf 228.067 498.354 Td [(T)83(able)-333(3:)-444(Data)-334(t)28(yp)-28(es)]TJ -0 g 0 G -0 g 0 G -0 g 0 G -/F27 9.9626 Tf -128.172 -28.356 Td [(T)32(yp)-32(e:)]TJ -0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ -0 g 0 G -/F27 9.9626 Tf -33.797 -18.428 Td [(On)-383(En)32(try)]TJ -0 g 0 G -0 g 0 G - 0 -18.429 Td [(x)]TJ -0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -167.933 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-55(jec)-1(t)-254(of)-255(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 244.743 0 Td [(psb)]TJ +/F8 9.9626 Tf 383.581 431.16 Td [(a)-386(,)-288(i)-127(n)-127(f)-127(o)-415(,)-302(g)-141(l)-142(o)-141(b)-141(a)-141(l)-190(=)-48(.)]TJ/F27 9.9626 Tf 92.224 0 Td [(f)-132(a)-131(l)-132(s)-131(e)]TJ/F8 9.9626 Tf 30.348 0 Td [(.)-178(\051)]TJ -305.352 -11.955 Td [(v)-128(r)-129(e)-128(s)-259(\050)-130(3)-131(\051)-642(=)-625(p)-115(s)-114(b)]TJ ET q -1 0 0 1 385.864 385.52 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 279.461 419.404 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F30 9.9626 Tf 389.002 385.321 Td [(T)]TJ +/F8 9.9626 Tf 283.591 419.205 Td [(g)-115(e)-114(d)-115(o)-114(t)-220(\050)-149(x)-43(3)-247(,)-204(y)-43(3)-248(,)-273(d)-113(e)-113(s)-112(c)]TJ ET q -1 0 0 1 394.86 385.52 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 379.47 419.404 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F30 9.9626 Tf 397.998 385.321 Td [(vect)]TJ +/F8 9.9626 Tf 383.581 419.205 Td [(a)-386(,)-288(i)-127(n)-127(f)-127(o)-415(,)-302(g)-141(l)-142(o)-141(b)-141(a)-141(l)-190(=)-48(.)]TJ/F27 9.9626 Tf 92.224 0 Td [(f)-132(a)-131(l)-132(s)-131(e)]TJ/F8 9.9626 Tf 30.348 0 Td [(.)-178(\051)]TJ/F27 9.9626 Tf -305.254 -11.955 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.198 0 Td [(p)-69(s)-69(b)]TJ ET q -1 0 0 1 419.547 385.52 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 247.753 407.449 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F30 9.9626 Tf 422.685 385.321 Td [(type)]TJ +/F8 9.9626 Tf 251.428 407.25 Td [(s)-69(u)-69(m)-174(\050)-245(i)-139(c)-139(t)-138(x)-139(t)-439(,)-290(v)-128(r)-128(e)-129(s)-293(\050)-165(1)-165(:)-165(3)-165(\051)-165(\051)]TJ 0 g 0 G -/F8 9.9626 Tf -297.883 -11.955 Td [(con)28(taining)-375(n)27(u)1(m)27(b)-27(e)-1(r)1(s)-376(of)-375(t)28(yp)-28(e)-375(sp)-28(eci\014ed)-375(in)-375(T)83(able)]TJ -0 0 1 rg 0 0 1 RG - [-375(3)]TJ 0 g 0 G - [(.)-570(The)-376(rank)-375(of)]TJ/F11 9.9626 Tf 274.03 0 Td [(x)]TJ/F8 9.9626 Tf 9.432 0 Td [(m)28(ust)-376(b)-27(e)]TJ -283.462 -11.956 Td [(the)-333(same)-334(of)]TJ/F11 9.9626 Tf 53.466 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ + -75.817 -21.918 Td [(In)-354(th)1(is)-354(w)28(a)28(y)-354(the)-353(global)-354(comm)28(unication,)-359(whic)28(h)-353(for)-354(small)-353(size)-1(s)-353(is)-354(a)-353(latency-)]TJ 0 -11.955 Td [(b)-28(ound)-333(op)-28(eration,)-333(is)-333(in)27(v)28(ok)28(ed)-333(only)-334(once.)]TJ 0 g 0 G -/F27 9.9626 Tf -83.615 -18.428 Td [(y)]TJ -0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -167.481 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-55(jec)-1(t)-254(of)-255(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 244.743 0 Td [(psb)]TJ -ET -q -1 0 0 1 385.864 295.361 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 389.002 295.162 Td [(T)]TJ -ET -q -1 0 0 1 394.86 295.361 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 397.998 295.162 Td [(vect)]TJ -ET -q -1 0 0 1 419.547 295.361 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 422.685 295.162 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf -297.883 -11.955 Td [(con)28(taining)-378(n)27(um)28(b)-28(ers)-378(of)-378(t)28(yp)-28(e)-378(sp)-28(eci\014ed)-378(in)-379(T)84(able)]TJ -0 0 1 rg 0 0 1 RG - [-378(3)]TJ -0 g 0 G - [(.)-580(The)-378(rank)-378(of)]TJ/F11 9.9626 Tf 274.422 0 Td [(y)]TJ/F8 9.9626 Tf 9.01 0 Td [(m)28(ust)-379(b)-27(e)]TJ -283.432 -11.956 Td [(the)-333(same)-334(of)]TJ/F11 9.9626 Tf 53.466 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -84.067 -18.428 Td [(desc)]TJ -ET -q -1 0 0 1 121.81 253.022 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 125.247 252.823 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(con)28(tains)-334(d)1(ata)-334(structures)-333(for)-333(com)-1(m)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 135.658 0 Td [(psb)]TJ -ET -q -1 0 0 1 276.779 205.202 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 279.917 205.003 Td [(desc)]TJ -ET -q -1 0 0 1 301.466 205.202 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 304.604 205.003 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -225.631 -18.429 Td [(On)-383(Return)]TJ -0 g 0 G -0 g 0 G - 0 -18.428 Td [(res)]TJ -0 g 0 G -/F8 9.9626 Tf 19.47 0 Td [(is)-333(the)-334(dot)-333(pro)-28(duct)-333(of)-333(sub)28(v)27(ectors)]TJ/F11 9.9626 Tf 142.19 0 Td [(x)]TJ/F8 9.9626 Tf 9.014 0 Td [(and)]TJ/F11 9.9626 Tf 19.372 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -170.381 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-357(as)-1(:)-493(a)-357(n)27(um)28(b)-28(er)-357(or)-358(a)-358(rank-one)-358(ar)1(ra)27(y)-357(of)-358(the)-358(data)-358(t)28(yp)-27(e)-358(indicated)-358(in)]TJ 0 -11.955 Td [(T)83(able)]TJ -0 0 1 rg 0 0 1 RG - [-333(2)]TJ -0 g 0 G - [(.)]TJ -0 g 0 G - 141.968 -29.888 Td [(33)]TJ + 141.968 -282.939 Td [(32)]TJ 0 g 0 G ET endstream endobj -912 0 obj +913 0 obj << /Type /ObjStm /N 100 -/First 886 -/Length 10464 +/First 888 +/Length 10167 >> stream -911 0 119 57 123 114 127 170 908 227 914 319 916 433 131 489 135 545 913 601 -919 693 921 807 139 864 143 920 918 976 923 1068 925 1182 147 1238 151 1294 922 1350 -927 1442 929 1556 155 1613 159 1670 163 1727 926 1784 933 1876 930 2018 931 2165 935 2311 -167 2367 171 2423 936 2479 932 2536 939 2641 941 2755 937 2812 175 2869 179 2926 183 2983 -187 3040 938 3097 945 3189 942 3331 943 3476 947 3621 191 3677 944 3733 953 3825 950 3967 -951 4113 955 4260 195 4317 199 4374 956 4430 958 4487 204 4544 952 4601 960 4719 962 4833 -959 4889 964 4968 966 5082 208 5139 963 5196 975 5275 967 5449 968 5594 969 5737 970 5882 -971 6027 972 6170 977 6315 212 6371 949 6427 974 6483 981 6614 973 6764 978 6910 979 7052 -983 7197 980 7254 991 7359 984 7533 985 7676 986 7821 987 7964 988 8109 989 8255 993 8399 -216 8455 994 8511 990 8568 997 8712 999 8826 996 8883 1007 8962 1000 9145 1001 9289 1002 9434 -% 911 0 obj +115 0 908 56 915 148 917 262 119 319 123 376 127 432 914 489 919 581 921 695 +131 751 135 807 918 863 924 955 926 1069 139 1126 143 1182 923 1238 928 1330 930 1444 +147 1500 151 1556 927 1612 932 1704 934 1818 155 1875 159 1932 163 1989 931 2046 938 2138 +935 2280 936 2427 940 2573 167 2629 171 2685 941 2741 937 2798 944 2903 946 3017 942 3074 +175 3131 179 3188 183 3245 187 3302 943 3359 950 3451 947 3593 948 3738 952 3883 191 3939 +949 3995 958 4087 955 4229 956 4375 960 4522 195 4579 199 4636 961 4692 963 4749 204 4806 +957 4863 965 4981 967 5095 964 5151 969 5230 971 5344 208 5401 968 5458 980 5537 972 5711 +973 5856 974 5999 975 6144 976 6289 977 6432 982 6577 212 6633 954 6689 979 6745 986 6876 +978 7026 983 7172 984 7314 988 7459 985 7516 995 7621 989 7787 990 7929 991 8074 992 8216 +993 8360 997 8505 216 8561 998 8617 994 8674 1002 8818 1000 8956 1004 9102 1005 9161 1006 9220 +% 115 0 obj +<< +/D [909 0 R /XYZ 99.895 279.894 null] +>> +% 908 0 obj +<< +/Font << /F27 560 0 R /F30 769 0 R /F8 561 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 915 0 obj << -/D [909 0 R /XYZ 149.705 753.953 null] +/Type /Page +/Contents 916 0 R +/Resources 914 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 887 0 R +>> +% 917 0 obj +<< +/D [915 0 R /XYZ 149.705 753.953 null] >> % 119 0 obj << -/D [909 0 R /XYZ 150.705 718.084 null] +/D [915 0 R /XYZ 150.705 718.084 null] >> % 123 0 obj << -/D [909 0 R /XYZ 150.705 538.16 null] +/D [915 0 R /XYZ 150.705 538.16 null] >> % 127 0 obj << -/D [909 0 R /XYZ 150.705 334.326 null] +/D [915 0 R /XYZ 150.705 334.326 null] >> -% 908 0 obj +% 914 0 obj << -/Font << /F27 556 0 R /F30 764 0 R /F8 557 0 R >> +/Font << /F27 560 0 R /F30 769 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 914 0 obj +% 919 0 obj << /Type /Page -/Contents 915 0 R -/Resources 913 0 R +/Contents 920 0 R +/Resources 918 0 R /MediaBox [0 0 595.276 841.89] -/Parent 917 0 R +/Parent 922 0 R >> -% 916 0 obj +% 921 0 obj << -/D [914 0 R /XYZ 98.895 753.953 null] +/D [919 0 R /XYZ 98.895 753.953 null] >> % 131 0 obj << -/D [914 0 R /XYZ 99.895 718.084 null] +/D [919 0 R /XYZ 99.895 718.084 null] >> % 135 0 obj << -/D [914 0 R /XYZ 99.895 363.788 null] +/D [919 0 R /XYZ 99.895 363.788 null] >> -% 913 0 obj +% 918 0 obj << -/Font << /F27 556 0 R /F30 764 0 R /F8 557 0 R >> +/Font << /F27 560 0 R /F30 769 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 919 0 obj +% 924 0 obj << /Type /Page -/Contents 920 0 R -/Resources 918 0 R +/Contents 925 0 R +/Resources 923 0 R /MediaBox [0 0 595.276 841.89] -/Parent 917 0 R +/Parent 922 0 R >> -% 921 0 obj +% 926 0 obj << -/D [919 0 R /XYZ 149.705 753.953 null] +/D [924 0 R /XYZ 149.705 753.953 null] >> % 139 0 obj << -/D [919 0 R /XYZ 150.705 652.99 null] +/D [924 0 R /XYZ 150.705 652.99 null] >> % 143 0 obj << -/D [919 0 R /XYZ 150.705 364.65 null] +/D [924 0 R /XYZ 150.705 364.65 null] >> -% 918 0 obj +% 923 0 obj << -/Font << /F27 556 0 R /F8 557 0 R /F30 764 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 923 0 obj +% 928 0 obj << /Type /Page -/Contents 924 0 R -/Resources 922 0 R +/Contents 929 0 R +/Resources 927 0 R /MediaBox [0 0 595.276 841.89] -/Parent 917 0 R +/Parent 922 0 R >> -% 925 0 obj +% 930 0 obj << -/D [923 0 R /XYZ 98.895 753.953 null] +/D [928 0 R /XYZ 98.895 753.953 null] >> % 147 0 obj << -/D [923 0 R /XYZ 99.895 718.084 null] +/D [928 0 R /XYZ 99.895 718.084 null] >> % 151 0 obj << -/D [923 0 R /XYZ 99.895 487.217 null] +/D [928 0 R /XYZ 99.895 487.217 null] >> -% 922 0 obj +% 927 0 obj << -/Font << /F27 556 0 R /F30 764 0 R /F8 557 0 R >> +/Font << /F27 560 0 R /F30 769 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 927 0 obj +% 932 0 obj << /Type /Page -/Contents 928 0 R -/Resources 926 0 R +/Contents 933 0 R +/Resources 931 0 R /MediaBox [0 0 595.276 841.89] -/Parent 917 0 R +/Parent 922 0 R >> -% 929 0 obj +% 934 0 obj << -/D [927 0 R /XYZ 149.705 753.953 null] +/D [932 0 R /XYZ 149.705 753.953 null] >> % 155 0 obj << -/D [927 0 R /XYZ 150.705 718.084 null] +/D [932 0 R /XYZ 150.705 718.084 null] >> % 159 0 obj << -/D [927 0 R /XYZ 150.705 325.491 null] +/D [932 0 R /XYZ 150.705 325.491 null] >> % 163 0 obj << -/D [927 0 R /XYZ 150.705 193.501 null] +/D [932 0 R /XYZ 150.705 193.501 null] >> -% 926 0 obj +% 931 0 obj << -/Font << /F27 556 0 R /F30 764 0 R /F8 557 0 R >> +/Font << /F27 560 0 R /F30 769 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 933 0 obj +% 938 0 obj << /Type /Page -/Contents 934 0 R -/Resources 932 0 R +/Contents 939 0 R +/Resources 937 0 R /MediaBox [0 0 595.276 841.89] -/Parent 917 0 R -/Annots [ 930 0 R 931 0 R ] +/Parent 922 0 R +/Annots [ 935 0 R 936 0 R ] >> -% 930 0 obj +% 935 0 obj << /Type /Annot /Subtype /Link @@ -8592,7 +8485,7 @@ stream /Rect [199.382 344.354 206.356 355.203] /A << /S /GoTo /D (section.6) >> >> -% 931 0 obj +% 936 0 obj << /Type /Annot /Subtype /Link @@ -8600,74 +8493,74 @@ stream /Rect [292.368 307.977 299.342 318.825] /A << /S /GoTo /D (figure.5) >> >> -% 935 0 obj +% 940 0 obj << -/D [933 0 R /XYZ 98.895 753.953 null] +/D [938 0 R /XYZ 98.895 753.953 null] >> % 167 0 obj << -/D [933 0 R /XYZ 99.895 598.678 null] +/D [938 0 R /XYZ 99.895 598.678 null] >> % 171 0 obj << -/D [933 0 R /XYZ 99.895 414.464 null] +/D [938 0 R /XYZ 99.895 414.464 null] >> -% 936 0 obj +% 941 0 obj << -/D [933 0 R /XYZ 121.151 383.153 null] +/D [938 0 R /XYZ 121.151 383.153 null] >> -% 932 0 obj +% 937 0 obj << -/Font << /F27 556 0 R /F8 557 0 R /F16 554 0 R /F30 764 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F16 558 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 939 0 obj +% 944 0 obj << /Type /Page -/Contents 940 0 R -/Resources 938 0 R +/Contents 945 0 R +/Resources 943 0 R /MediaBox [0 0 595.276 841.89] -/Parent 917 0 R +/Parent 922 0 R >> -% 941 0 obj +% 946 0 obj << -/D [939 0 R /XYZ 149.705 753.953 null] +/D [944 0 R /XYZ 149.705 753.953 null] >> -% 937 0 obj +% 942 0 obj << -/D [939 0 R /XYZ 208.488 610.432 null] +/D [944 0 R /XYZ 208.488 610.432 null] >> % 175 0 obj << -/D [939 0 R /XYZ 150.705 576.609 null] +/D [944 0 R /XYZ 150.705 576.609 null] >> % 179 0 obj << -/D [939 0 R /XYZ 150.705 560.207 null] +/D [944 0 R /XYZ 150.705 560.207 null] >> % 183 0 obj << -/D [939 0 R /XYZ 150.705 388.328 null] +/D [944 0 R /XYZ 150.705 388.328 null] >> % 187 0 obj << -/D [939 0 R /XYZ 150.705 216.449 null] +/D [944 0 R /XYZ 150.705 216.449 null] >> -% 938 0 obj +% 943 0 obj << -/Font << /F30 764 0 R /F8 557 0 R /F27 556 0 R >> +/Font << /F30 769 0 R /F8 561 0 R /F27 560 0 R >> /ProcSet [ /PDF /Text ] >> -% 945 0 obj +% 950 0 obj << /Type /Page -/Contents 946 0 R -/Resources 944 0 R +/Contents 951 0 R +/Resources 949 0 R /MediaBox [0 0 595.276 841.89] -/Parent 948 0 R -/Annots [ 942 0 R 943 0 R ] +/Parent 953 0 R +/Annots [ 947 0 R 948 0 R ] >> -% 942 0 obj +% 947 0 obj << /Type /Annot /Subtype /Link @@ -8675,7 +8568,7 @@ stream /Rect [382.088 606.388 389.062 617.237] /A << /S /GoTo /D (table.1) >> >> -% 943 0 obj +% 948 0 obj << /Type /Annot /Subtype /Link @@ -8683,29 +8576,29 @@ stream /Rect [382.088 460.595 389.062 471.443] /A << /S /GoTo /D (table.1) >> >> -% 947 0 obj +% 952 0 obj << -/D [945 0 R /XYZ 98.895 753.953 null] +/D [950 0 R /XYZ 98.895 753.953 null] >> % 191 0 obj << -/D [945 0 R /XYZ 99.895 315.722 null] +/D [950 0 R /XYZ 99.895 315.722 null] >> -% 944 0 obj +% 949 0 obj << -/Font << /F27 556 0 R /F8 557 0 R /F30 764 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 953 0 obj +% 958 0 obj << /Type /Page -/Contents 954 0 R -/Resources 952 0 R +/Contents 959 0 R +/Resources 957 0 R /MediaBox [0 0 595.276 841.89] -/Parent 948 0 R -/Annots [ 950 0 R 951 0 R ] +/Parent 953 0 R +/Annots [ 955 0 R 956 0 R ] >> -% 950 0 obj +% 955 0 obj << /Type /Annot /Subtype /Link @@ -8713,7 +8606,7 @@ stream /Rect [177.685 453.572 184.659 464.697] /A << /S /GoTo /D (figure.6) >> >> -% 951 0 obj +% 956 0 obj << /Type /Annot /Subtype /Link @@ -8721,83 +8614,83 @@ stream /Rect [297.652 273.706 304.626 284.554] /A << /S /GoTo /D (section.6) >> >> -% 955 0 obj +% 960 0 obj << -/D [953 0 R /XYZ 149.705 753.953 null] +/D [958 0 R /XYZ 149.705 753.953 null] >> % 195 0 obj << -/D [953 0 R /XYZ 150.705 718.084 null] +/D [958 0 R /XYZ 150.705 718.084 null] >> % 199 0 obj << -/D [953 0 R /XYZ 150.705 525.15 null] +/D [958 0 R /XYZ 150.705 525.15 null] >> -% 956 0 obj +% 961 0 obj << -/D [953 0 R /XYZ 308.372 468.737 null] +/D [958 0 R /XYZ 308.372 468.737 null] >> -% 958 0 obj +% 963 0 obj << -/D [953 0 R /XYZ 206.288 347.218 null] +/D [958 0 R /XYZ 206.288 347.218 null] >> % 204 0 obj << -/D [953 0 R /XYZ 150.705 307.161 null] +/D [958 0 R /XYZ 150.705 307.161 null] >> -% 952 0 obj +% 957 0 obj << -/Font << /F27 556 0 R /F30 764 0 R /F8 557 0 R /F16 554 0 R /F47 957 0 R >> +/Font << /F27 560 0 R /F30 769 0 R /F8 561 0 R /F16 558 0 R /F47 962 0 R >> /ProcSet [ /PDF /Text ] >> -% 960 0 obj +% 965 0 obj << /Type /Page -/Contents 961 0 R -/Resources 959 0 R +/Contents 966 0 R +/Resources 964 0 R /MediaBox [0 0 595.276 841.89] -/Parent 948 0 R +/Parent 953 0 R >> -% 962 0 obj +% 967 0 obj << -/D [960 0 R /XYZ 98.895 753.953 null] +/D [965 0 R /XYZ 98.895 753.953 null] >> -% 959 0 obj +% 964 0 obj << -/Font << /F27 556 0 R /F8 557 0 R >> +/Font << /F27 560 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 964 0 obj +% 969 0 obj << /Type /Page -/Contents 965 0 R -/Resources 963 0 R +/Contents 970 0 R +/Resources 968 0 R /MediaBox [0 0 595.276 841.89] -/Parent 948 0 R +/Parent 953 0 R >> -% 966 0 obj +% 971 0 obj << -/D [964 0 R /XYZ 149.705 753.953 null] +/D [969 0 R /XYZ 149.705 753.953 null] >> % 208 0 obj << -/D [964 0 R /XYZ 150.705 716.092 null] +/D [969 0 R /XYZ 150.705 716.092 null] >> -% 963 0 obj +% 968 0 obj << -/Font << /F16 554 0 R /F8 557 0 R >> +/Font << /F16 558 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 975 0 obj +% 980 0 obj << /Type /Page -/Contents 976 0 R -/Resources 974 0 R +/Contents 981 0 R +/Resources 979 0 R /MediaBox [0 0 595.276 841.89] -/Parent 948 0 R -/Annots [ 967 0 R 968 0 R 969 0 R 970 0 R 971 0 R 972 0 R ] +/Parent 953 0 R +/Annots [ 972 0 R 973 0 R 974 0 R 975 0 R 976 0 R 977 0 R ] >> -% 967 0 obj +% 972 0 obj << /Type /Annot /Subtype /Link @@ -8805,7 +8698,7 @@ stream /Rect [382.088 401.949 389.062 412.798] /A << /S /GoTo /D (table.1) >> >> -% 968 0 obj +% 973 0 obj << /Type /Annot /Subtype /Link @@ -8813,7 +8706,7 @@ stream /Rect [368.549 333.522 444.603 344.647] /A << /S /GoTo /D (vdata) >> >> -% 969 0 obj +% 974 0 obj << /Type /Annot /Subtype /Link @@ -8821,7 +8714,7 @@ stream /Rect [328.333 321.844 335.307 332.692] /A << /S /GoTo /D (table.1) >> >> -% 970 0 obj +% 975 0 obj << /Type /Annot /Subtype /Link @@ -8829,7 +8722,7 @@ stream /Rect [382.088 241.738 389.062 252.586] /A << /S /GoTo /D (table.1) >> >> -% 971 0 obj +% 976 0 obj << /Type /Annot /Subtype /Link @@ -8837,7 +8730,7 @@ stream /Rect [368.549 173.311 444.603 184.436] /A << /S /GoTo /D (vdata) >> >> -% 972 0 obj +% 977 0 obj << /Type /Annot /Subtype /Link @@ -8845,33 +8738,33 @@ stream /Rect [345.625 161.632 352.599 172.481] /A << /S /GoTo /D (table.1) >> >> -% 977 0 obj +% 982 0 obj << -/D [975 0 R /XYZ 98.895 753.953 null] +/D [980 0 R /XYZ 98.895 753.953 null] >> % 212 0 obj << -/D [975 0 R /XYZ 99.895 720.077 null] +/D [980 0 R /XYZ 99.895 720.077 null] >> -% 949 0 obj +% 954 0 obj << -/D [975 0 R /XYZ 267.641 539.42 null] +/D [980 0 R /XYZ 267.641 539.42 null] >> -% 974 0 obj +% 979 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F11 750 0 R /F14 767 0 R /F30 764 0 R /F27 556 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F11 755 0 R /F14 772 0 R /F30 769 0 R /F27 560 0 R >> /ProcSet [ /PDF /Text ] >> -% 981 0 obj +% 986 0 obj << /Type /Page -/Contents 982 0 R -/Resources 980 0 R +/Contents 987 0 R +/Resources 985 0 R /MediaBox [0 0 595.276 841.89] -/Parent 948 0 R -/Annots [ 973 0 R 978 0 R 979 0 R ] +/Parent 953 0 R +/Annots [ 978 0 R 983 0 R 984 0 R ] >> -% 973 0 obj +% 978 0 obj << /Type /Annot /Subtype /Link @@ -8879,7 +8772,7 @@ stream /Rect [310.273 679.008 377.331 690.133] /A << /S /GoTo /D (descdata) >> >> -% 978 0 obj +% 983 0 obj << /Type /Annot /Subtype /Link @@ -8887,7 +8780,7 @@ stream /Rect [419.358 589.345 495.412 600.47] /A << /S /GoTo /D (vdata) >> >> -% 979 0 obj +% 984 0 obj << /Type /Annot /Subtype /Link @@ -8895,164 +8788,116 @@ stream /Rect [396.367 577.666 403.341 588.514] /A << /S /GoTo /D (table.1) >> >> -% 983 0 obj +% 988 0 obj << -/D [981 0 R /XYZ 149.705 753.953 null] +/D [986 0 R /XYZ 149.705 753.953 null] >> -% 980 0 obj +% 985 0 obj << -/Font << /F8 557 0 R /F27 556 0 R /F30 764 0 R /F11 750 0 R >> +/Font << /F8 561 0 R /F27 560 0 R /F30 769 0 R /F11 755 0 R >> /ProcSet [ /PDF /Text ] >> -% 991 0 obj +% 995 0 obj << /Type /Page -/Contents 992 0 R -/Resources 990 0 R +/Contents 996 0 R +/Resources 994 0 R /MediaBox [0 0 595.276 841.89] -/Parent 995 0 R -/Annots [ 984 0 R 985 0 R 986 0 R 987 0 R 988 0 R 989 0 R ] +/Parent 999 0 R +/Annots [ 989 0 R 990 0 R 991 0 R 992 0 R 993 0 R ] >> -% 984 0 obj +% 989 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [368.549 361.842 444.603 372.967] +/Rect [368.549 355.465 444.603 366.59] /A << /S /GoTo /D (vdata) >> >> -% 985 0 obj +% 990 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [328.333 350.163 335.307 361.011] +/Rect [328.333 343.787 335.307 354.635] /A << /S /GoTo /D (table.2) >> >> -% 986 0 obj +% 991 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [368.549 270.772 444.603 281.897] +/Rect [368.549 264.06 444.603 275.185] /A << /S /GoTo /D (vdata) >> >> -% 987 0 obj +% 992 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [328.544 259.094 335.518 269.942] +/Rect [328.544 252.382 335.518 263.23] /A << /S /GoTo /D (table.2) >> >> -% 988 0 obj +% 993 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [259.464 179.703 326.522 190.828] +/Rect [259.464 172.655 326.522 183.78] /A << /S /GoTo /D (descdata) >> >> -% 989 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [382.088 117.392 389.062 128.24] -/A << /S /GoTo /D (table.2) >> ->> -% 993 0 obj +% 997 0 obj << -/D [991 0 R /XYZ 98.895 753.953 null] +/D [995 0 R /XYZ 98.895 753.953 null] >> % 216 0 obj << -/D [991 0 R /XYZ 99.895 720.077 null] +/D [995 0 R /XYZ 99.895 720.077 null] >> -% 994 0 obj -<< -/D [991 0 R /XYZ 267.641 495.047 null] ->> -% 990 0 obj -<< -/Font << /F16 554 0 R /F8 557 0 R /F11 750 0 R /F14 767 0 R /F10 766 0 R /F30 764 0 R /F27 556 0 R >> -/ProcSet [ /PDF /Text ] ->> -% 997 0 obj +% 998 0 obj << -/Type /Page -/Contents 998 0 R -/Resources 996 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 995 0 R ->> -% 999 0 obj -<< -/D [997 0 R /XYZ 149.705 753.953 null] +/D [995 0 R /XYZ 267.641 490.516 null] >> -% 996 0 obj +% 994 0 obj << -/Font << /F27 556 0 R /F8 557 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F11 755 0 R /F14 772 0 R /F10 771 0 R /F30 769 0 R /F27 560 0 R >> /ProcSet [ /PDF /Text ] >> -% 1007 0 obj +% 1002 0 obj << /Type /Page -/Contents 1008 0 R -/Resources 1006 0 R +/Contents 1003 0 R +/Resources 1001 0 R /MediaBox [0 0 595.276 841.89] -/Parent 995 0 R -/Annots [ 1000 0 R 1001 0 R 1002 0 R 1003 0 R 1004 0 R 1005 0 R ] +/Parent 999 0 R +/Annots [ 1000 0 R ] >> % 1000 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [368.549 382.111 444.603 393.236] -/A << /S /GoTo /D (vdata) >> +/Rect [432.897 603.569 439.871 614.417] +/A << /S /GoTo /D (table.2) >> >> -% 1001 0 obj +% 1004 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [328.333 370.432 335.307 381.28] -/A << /S /GoTo /D (table.3) >> +/D [1002 0 R /XYZ 149.705 753.953 null] >> -% 1002 0 obj +% 1005 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [368.549 291.951 444.603 303.076] -/A << /S /GoTo /D (vdata) >> +/D [1002 0 R /XYZ 150.705 512.854 null] >> - -endstream -endobj -1014 0 obj +% 1006 0 obj << -/Length 625 +/D [1002 0 R /XYZ 150.705 453.133 null] >> -stream -0 g 0 G -0 g 0 G -0 g 0 G -BT -/F27 9.9626 Tf 150.705 706.129 Td [(info)]TJ -0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ -0 g 0 G - 141.968 -567.87 Td [(34)]TJ -0 g 0 G -ET endstream endobj -1021 0 obj +1020 0 obj << -/Length 7088 +/Length 8468 >> stream 0 g 0 G @@ -9065,316 +8910,443 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(normi)-375(|)-375(In\014nit)31(y-Norm)-375(of)-375(V)94(ector)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-333(function)-334(computes)-333(the)-333(in\014nit)28(y-norm)-334(of)-333(a)-333(v)27(ector)]TJ/F11 9.9626 Tf 233.182 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -238.876 -11.956 Td [(If)]TJ/F11 9.9626 Tf 9.963 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(is)-333(a)-334(real)-333(v)28(ector)-334(it)-333(computes)-333(in\014nit)28(y)-334(norm)-333(as:)]TJ/F11 9.9626 Tf 115.269 -21.138 Td [(amax)]TJ/F14 9.9626 Tf 27.741 0 Td [(\040)]TJ/F8 9.9626 Tf 12.73 0 Td [(max)]TJ/F10 6.9738 Tf 7.861 -6.275 Td [(i)]TJ/F14 9.9626 Tf 12.341 6.275 Td [(j)]TJ/F11 9.9626 Tf 2.767 0 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.495 Td [(i)]TJ/F14 9.9626 Tf 3.317 1.495 Td [(j)]TJ/F8 9.9626 Tf -206.698 -24.37 Td [(else)-333(if)]TJ/F11 9.9626 Tf 28.007 0 Td [(x)]TJ/F8 9.9626 Tf 9.014 0 Td [(is)-333(a)-334(complex)-333(v)28(ector)-334(then)-333(it)-333(computes)-334(the)-333(in\014nit)28(y-norm)-333(as:)]TJ/F11 9.9626 Tf 61.447 -21.138 Td [(amax)]TJ/F14 9.9626 Tf 27.74 0 Td [(\040)]TJ/F8 9.9626 Tf 12.73 0 Td [(max)]TJ/F10 6.9738 Tf 7.862 -6.275 Td [(i)]TJ/F8 9.9626 Tf 12.34 6.275 Td [(\050)]TJ/F14 9.9626 Tf 3.875 0 Td [(j)]TJ/F11 9.9626 Tf 2.767 0 Td [(r)-28(e)]TJ/F8 9.9626 Tf 9.411 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.495 Td [(i)]TJ/F8 9.9626 Tf 3.317 1.495 Td [(\051)]TJ/F14 9.9626 Tf 3.874 0 Td [(j)]TJ/F8 9.9626 Tf 4.981 0 Td [(+)]TJ/F14 9.9626 Tf 9.963 0 Td [(j)]TJ/F11 9.9626 Tf 2.767 0 Td [(im)]TJ/F8 9.9626 Tf 12.18 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.495 Td [(i)]TJ/F8 9.9626 Tf 3.317 1.495 Td [(\051)]TJ/F14 9.9626 Tf 3.874 0 Td [(j)]TJ/F8 9.9626 Tf 2.768 0 Td [(\051)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(gedots)-375(|)-375(Generalized)-375(Dot)-375(Pro)-31(duct)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-392(subroutine)-392(computes)-392(a)-392(series)-392(of)-391(dot)-392(pro)-28(ducts)-392(among)-392(the)-392(columns)-392(of)-391(t)27(w)28(o)]TJ 0 -11.956 Td [(dense)-333(matrices)]TJ/F11 9.9626 Tf 67.11 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(and)]TJ/F11 9.9626 Tf 19.372 0 Td [(y)]TJ/F8 9.9626 Tf 5.241 0 Td [(:)]TJ/F11 9.9626 Tf 23.756 -11.955 Td [(r)-28(es)]TJ/F8 9.9626 Tf 14.081 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)]TJ/F14 9.9626 Tf 6.642 0 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(\050:)]TJ/F11 9.9626 Tf 6.642 0 Td [(;)-167(i)]TJ/F8 9.9626 Tf 7.86 0 Td [(\051)]TJ/F10 6.9738 Tf 3.874 4.114 Td [(T)]TJ/F11 9.9626 Tf 6.276 -4.114 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(\050:)]TJ/F11 9.9626 Tf 6.642 0 Td [(;)-167(i)]TJ/F8 9.9626 Tf 7.86 0 Td [(\051)]TJ -215.343 -15.687 Td [(If)-245(the)-245(matrices)-245(are)-245(complex,)-262(then)-245(the)-245(usual)-245(con)28(v)28(e)-1(n)28(tion)-245(app)1(lie)-1(s,)-262(i.e.)-415(the)-245(conjugate)]TJ 0 -11.955 Td [(transp)-28(ose)-323(of)]TJ/F11 9.9626 Tf 55.836 0 Td [(x)]TJ/F8 9.9626 Tf 8.913 0 Td [(is)-323(used.)-441(If)]TJ/F11 9.9626 Tf 46.366 0 Td [(x)]TJ/F8 9.9626 Tf 8.913 0 Td [(and)]TJ/F11 9.9626 Tf 19.269 0 Td [(y)]TJ/F8 9.9626 Tf 8.461 0 Td [(are)-323(of)-323(rank)-323(one,)-325(then)]TJ/F11 9.9626 Tf 94.212 0 Td [(r)-28(es)]TJ/F8 9.9626 Tf 17.299 0 Td [(is)-323(a)-323(scalar,)-325(else)-324(it)-323(is)]TJ -259.269 -11.955 Td [(a)-333(rank)-334(one)-333(arra)28(y)83(.)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -241.37 -24.37 Td [(psb_geamax\050x,)-525(desc_a,)-525(info\051)]TJ 0 -11.955 Td [(psb_normi\050x,)-525(desc_a,)-525(info\051)]TJ +/F30 9.9626 Tf 0 -18.175 Td [(call)-525(psb_gedots\050res,)-525(x,)-525(y,)-525(desc_a,)-525(info\051)]TJ 0 g 0 G 0 g 0 G 0 g 0 G ET q -1 0 0 1 129.083 549.573 cm -[]0 d 0 J 0.398 w 0 0 m 285.336 0 l S +1 0 0 1 177.988 586.966 cm +[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S Q BT -/F11 9.9626 Tf 135.06 541.005 Td [(amax)-7677(x)]TJ/F27 9.9626 Tf 221.863 0 Td [(F)96(unction)]TJ +/F11 9.9626 Tf 183.966 578.398 Td [(r)-28(es)]TJ/F8 9.9626 Tf 14.08 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(y)]TJ/F27 9.9626 Tf 88.459 0 Td [(Subroutine)]TJ ET q -1 0 0 1 129.083 537.219 cm -[]0 d 0 J 0.398 w 0 0 m 285.336 0 l S +1 0 0 1 177.988 574.612 cm +[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S Q BT -/F8 9.9626 Tf 135.06 528.651 Td [(Short)-333(Precision)-334(Real)-1200(Short)-333(Precision)-333(Real)-3103(psb)]TJ +/F8 9.9626 Tf 183.966 566.045 Td [(Short)-333(Precision)-333(R)-1(eal)-3102(psb)]TJ ET q -1 0 0 1 372.52 528.851 cm +1 0 0 1 319.972 566.244 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 375.509 528.651 Td [(geamax)]TJ -240.449 -11.955 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Re)-1(al)-3313(psb)]TJ +/F8 9.9626 Tf 322.961 566.045 Td [(gedots)]TJ -138.995 -11.956 Td [(Long)-333(Precision)-334(Real)-3314(p)1(s)-1(b)]TJ ET q -1 0 0 1 372.52 516.895 cm +1 0 0 1 319.972 554.289 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 375.509 516.696 Td [(geamax)]TJ -240.449 -11.955 Td [(Short)-333(Precision)-334(Real)-1200(Short)-333(Precision)-333(Complex)-1200(psb)]TJ +/F8 9.9626 Tf 322.961 554.089 Td [(gedots)]TJ -138.995 -11.955 Td [(Short)-333(Precision)-333(C)-1(omplex)-1200(p)1(s)-1(b)]TJ ET q -1 0 0 1 372.52 504.94 cm +1 0 0 1 319.972 542.333 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 375.509 504.741 Td [(geamax)]TJ -240.449 -11.955 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Com)-1(p)1(lex)-1412(psb)]TJ +/F8 9.9626 Tf 322.961 542.134 Td [(gedots)]TJ -138.995 -11.955 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ ET q -1 0 0 1 372.52 492.985 cm +1 0 0 1 319.972 530.378 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 375.509 492.786 Td [(geamax)]TJ +/F8 9.9626 Tf 322.961 530.179 Td [(gedots)]TJ ET q -1 0 0 1 129.083 489 cm -[]0 d 0 J 0.398 w 0 0 m 285.336 0 l S +1 0 0 1 177.988 526.393 cm +[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S Q 0 g 0 G BT -/F8 9.9626 Tf 228.067 460.961 Td [(T)83(able)-333(4:)-444(Data)-334(t)28(yp)-28(es)]TJ +/F8 9.9626 Tf 228.067 498.354 Td [(T)83(able)-333(3:)-444(Data)-334(t)28(yp)-28(es)]TJ 0 g 0 G 0 g 0 G 0 g 0 G -/F27 9.9626 Tf -128.172 -32.506 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf -128.172 -28.356 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.613 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -33.797 -18.428 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.614 Td [(x)]TJ + 0 -18.429 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -167.933 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-55(jec)-1(t)-254(of)-255(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -167.933 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-55(jec)-1(t)-254(of)-255(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 244.743 0 Td [(psb)]TJ ET q -1 0 0 1 385.864 341.607 cm +1 0 0 1 385.864 385.52 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 389.002 341.407 Td [(T)]TJ +/F30 9.9626 Tf 389.002 385.321 Td [(T)]TJ ET q -1 0 0 1 394.86 341.607 cm +1 0 0 1 394.86 385.52 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 397.998 341.407 Td [(vect)]TJ +/F30 9.9626 Tf 397.998 385.321 Td [(vect)]TJ ET q -1 0 0 1 419.547 341.607 cm +1 0 0 1 419.547 385.52 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 422.685 341.407 Td [(type)]TJ +/F30 9.9626 Tf 422.685 385.321 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf -297.883 -11.955 Td [(con)28(taining)-333(n)27(um)28(b)-28(ers)-333(of)-333(t)28(yp)-28(e)-334(sp)-27(eci\014ed)-334(in)-333(T)83(able)]TJ +/F8 9.9626 Tf -297.883 -11.955 Td [(con)28(taining)-375(n)27(u)1(m)27(b)-27(e)-1(r)1(s)-376(of)-375(t)28(yp)-28(e)-375(sp)-28(eci\014ed)-375(in)-375(T)83(able)]TJ 0 0 1 rg 0 0 1 RG - [-333(4)]TJ + [-375(3)]TJ 0 g 0 G - [(.)]TJ + [(.)-570(The)-376(rank)-375(of)]TJ/F11 9.9626 Tf 274.03 0 Td [(x)]TJ/F8 9.9626 Tf 9.432 0 Td [(m)28(ust)-376(b)-27(e)]TJ -283.462 -11.956 Td [(the)-333(same)-334(of)]TJ/F11 9.9626 Tf 53.466 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -83.615 -18.428 Td [(y)]TJ +0 g 0 G +/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -167.481 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-55(jec)-1(t)-254(of)-255(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 244.743 0 Td [(psb)]TJ +ET +q +1 0 0 1 385.864 295.361 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 389.002 295.162 Td [(T)]TJ +ET +q +1 0 0 1 394.86 295.361 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 397.998 295.162 Td [(vect)]TJ +ET +q +1 0 0 1 419.547 295.361 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 422.685 295.162 Td [(type)]TJ +0 g 0 G +/F8 9.9626 Tf -297.883 -11.955 Td [(con)28(taining)-378(n)27(um)28(b)-28(ers)-378(of)-378(t)28(yp)-28(e)-378(sp)-28(eci\014ed)-378(in)-379(T)84(able)]TJ +0 0 1 rg 0 0 1 RG + [-378(3)]TJ +0 g 0 G + [(.)-580(The)-378(rank)-378(of)]TJ/F11 9.9626 Tf 274.422 0 Td [(y)]TJ/F8 9.9626 Tf 9.01 0 Td [(m)28(ust)-379(b)-27(e)]TJ -283.432 -11.956 Td [(the)-333(same)-334(of)]TJ/F11 9.9626 Tf 53.466 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.613 Td [(desc)]TJ +/F27 9.9626 Tf -84.067 -18.428 Td [(desc)]TJ ET q -1 0 0 1 121.81 310.038 cm +1 0 0 1 121.81 253.022 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 125.247 309.839 Td [(a)]TJ +/F27 9.9626 Tf 125.247 252.823 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(con)28(tains)-334(d)1(ata)-334(structures)-333(for)-333(com)-1(m)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.551 0 Td [(con)28(tains)-334(d)1(ata)-334(structures)-333(for)-333(com)-1(m)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 135.658 0 Td [(psb)]TJ ET q -1 0 0 1 276.779 262.217 cm +1 0 0 1 276.779 205.202 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 279.917 262.018 Td [(desc)]TJ +/F30 9.9626 Tf 279.917 205.003 Td [(desc)]TJ ET q -1 0 0 1 301.466 262.217 cm +1 0 0 1 301.466 205.202 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 304.604 262.018 Td [(type)]TJ +/F30 9.9626 Tf 304.604 205.003 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -225.631 -19.614 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf -225.631 -18.429 Td [(On)-383(Return)]TJ +0 g 0 G 0 g 0 G + 0 -18.428 Td [(res)]TJ 0 g 0 G - 0 -19.613 Td [(F)96(unction)-384(v)64(alue)]TJ +/F8 9.9626 Tf 19.47 0 Td [(is)-333(the)-334(dot)-333(pro)-28(duct)-333(of)-333(sub)28(v)27(ectors)]TJ/F11 9.9626 Tf 142.19 0 Td [(x)]TJ/F8 9.9626 Tf 9.014 0 Td [(and)]TJ/F11 9.9626 Tf 19.372 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -170.381 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-357(as)-1(:)-493(a)-357(n)27(um)28(b)-28(er)-357(or)-358(a)-358(rank-one)-358(ar)1(ra)27(y)-357(of)-358(the)-358(data)-358(t)28(yp)-27(e)-358(indicated)-358(in)]TJ 0 -11.955 Td [(T)83(able)]TJ +0 0 1 rg 0 0 1 RG + [-333(2)]TJ 0 g 0 G -/F8 9.9626 Tf 78.387 0 Td [(is)-333(the)-334(in\014ni)1(t)27(y)-333(norm)-333(of)-334(sub)28(v)28(ector)]TJ/F11 9.9626 Tf 143.517 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -202.691 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(long)-333(precision)-333(real)-334(n)28(um)28(b)-28(er.)]TJ + [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.614 Td [(info)]TJ + 141.968 -29.888 Td [(33)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ +ET + +endstream +endobj +1025 0 obj +<< +/Length 625 +>> +stream +0 g 0 G +0 g 0 G +0 g 0 G +BT +/F27 9.9626 Tf 150.705 706.129 Td [(info)]TJ +0 g 0 G +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ 0 g 0 G - 141.968 -41.008 Td [(35)]TJ + 141.968 -567.87 Td [(34)]TJ 0 g 0 G ET endstream endobj -1029 0 obj +1032 0 obj << -/Length 6310 +/Length 6858 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ +/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ ET q -1 0 0 1 171.761 706.328 cm +1 0 0 1 120.951 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(geamaxs)-375(|)-375(Generalized)-375(In\014nit)31(y)-375(Norm)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-359(subroutine)-359(computes)-360(a)-359(series)-359(of)-359(in\014nit)28(y)-359(norms)-360(on)-359(the)-359(columns)-359(of)-359(a)-359(dense)]TJ 0 -11.956 Td [(matrix)]TJ/F11 9.9626 Tf 32.406 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(:)]TJ/F11 9.9626 Tf 87.106 -11.955 Td [(r)-28(es)]TJ/F8 9.9626 Tf 14.08 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)]TJ/F14 9.9626 Tf 6.642 0 Td [(\040)]TJ/F8 9.9626 Tf 12.73 0 Td [(max)]TJ/F10 6.9738 Tf 7.069 -6.503 Td [(k)]TJ/F14 9.9626 Tf 13.133 6.503 Td [(j)]TJ/F11 9.9626 Tf 2.767 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(k)-31(;)-167(i)]TJ/F8 9.9626 Tf 13.36 0 Td [(\051)]TJ/F14 9.9626 Tf 3.874 0 Td [(j)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(normi)-375(|)-375(In\014nit)31(y-Norm)-375(of)-375(V)94(ector)]TJ/F8 9.9626 Tf -25.091 -19.477 Td [(This)-333(function)-334(computes)-333(the)-333(in\014nit)28(y-norm)-334(of)-333(a)-333(v)27(ector)]TJ/F11 9.9626 Tf 233.182 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -238.876 -11.955 Td [(If)]TJ/F11 9.9626 Tf 9.963 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(is)-333(a)-334(real)-333(v)28(ector)-334(it)-333(computes)-333(in\014nit)28(y)-334(norm)-333(as:)]TJ/F11 9.9626 Tf 115.269 -23.087 Td [(amax)]TJ/F14 9.9626 Tf 27.741 0 Td [(\040)]TJ/F8 9.9626 Tf 12.73 0 Td [(max)]TJ/F10 6.9738 Tf 7.861 -6.275 Td [(i)]TJ/F14 9.9626 Tf 12.341 6.275 Td [(j)]TJ/F11 9.9626 Tf 2.767 0 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.494 Td [(i)]TJ/F14 9.9626 Tf 3.317 1.494 Td [(j)]TJ/F8 9.9626 Tf -206.698 -26.317 Td [(else)-333(if)]TJ/F11 9.9626 Tf 28.007 0 Td [(x)]TJ/F8 9.9626 Tf 9.014 0 Td [(is)-333(a)-334(complex)-333(v)28(ector)-334(then)-333(it)-333(computes)-334(the)-333(in\014nit)28(y-norm)-333(as:)]TJ/F11 9.9626 Tf 61.447 -23.087 Td [(amax)]TJ/F14 9.9626 Tf 27.74 0 Td [(\040)]TJ/F8 9.9626 Tf 12.73 0 Td [(max)]TJ/F10 6.9738 Tf 7.862 -6.275 Td [(i)]TJ/F8 9.9626 Tf 12.34 6.275 Td [(\050)]TJ/F14 9.9626 Tf 3.875 0 Td [(j)]TJ/F11 9.9626 Tf 2.767 0 Td [(r)-28(e)]TJ/F8 9.9626 Tf 9.411 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.494 Td [(i)]TJ/F8 9.9626 Tf 3.317 1.494 Td [(\051)]TJ/F14 9.9626 Tf 3.874 0 Td [(j)]TJ/F8 9.9626 Tf 4.981 0 Td [(+)]TJ/F14 9.9626 Tf 9.963 0 Td [(j)]TJ/F11 9.9626 Tf 2.767 0 Td [(im)]TJ/F8 9.9626 Tf 12.18 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.494 Td [(i)]TJ/F8 9.9626 Tf 3.317 1.494 Td [(\051)]TJ/F14 9.9626 Tf 3.874 0 Td [(j)]TJ/F8 9.9626 Tf 2.768 0 Td [(\051)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -215.737 -25.377 Td [(call)-525(psb_geamaxs\050res,)-525(x,)-525(desc_a,)-525(info\051)]TJ +/F30 9.9626 Tf -241.37 -26.901 Td [(psb_geamax\050x,)-525(desc_a,)-525(info)-525([,global]\051)]TJ 0 -11.956 Td [(psb_normi\050x,)-525(desc_a,)-525(info)-525([,global]\051)]TJ 0 g 0 G 0 g 0 G 0 g 0 G ET q -1 0 0 1 177.927 614.121 cm -[]0 d 0 J 0.398 w 0 0 m 289.266 0 l S +1 0 0 1 129.083 536.097 cm +[]0 d 0 J 0.398 w 0 0 m 285.336 0 l S Q BT -/F11 9.9626 Tf 183.905 605.553 Td [(r)-28(es)-8770(x)]TJ/F27 9.9626 Tf 221.863 0 Td [(Subroutine)]TJ +/F11 9.9626 Tf 135.06 527.529 Td [(amax)-7677(x)]TJ/F27 9.9626 Tf 221.863 0 Td [(F)96(unction)]TJ ET q -1 0 0 1 177.927 601.768 cm -[]0 d 0 J 0.398 w 0 0 m 289.266 0 l S +1 0 0 1 129.083 523.743 cm +[]0 d 0 J 0.398 w 0 0 m 285.336 0 l S Q BT -/F8 9.9626 Tf 183.905 593.2 Td [(Short)-333(Precision)-334(Real)-1200(Shor)1(t)-334(Precision)-333(Real)-3103(psb)]TJ +/F8 9.9626 Tf 135.06 515.175 Td [(Short)-333(Precision)-334(Real)-1200(Short)-333(Precision)-333(Real)-3103(psb)]TJ ET q -1 0 0 1 421.365 593.399 cm +1 0 0 1 372.52 515.374 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 424.354 593.2 Td [(geamaxs)]TJ -240.449 -11.956 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Real)-3314(psb)]TJ +/F8 9.9626 Tf 375.509 515.175 Td [(geamax)]TJ -240.449 -11.955 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Re)-1(al)-3313(psb)]TJ ET q -1 0 0 1 421.365 581.444 cm +1 0 0 1 372.52 503.419 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 424.354 581.244 Td [(geamaxs)]TJ -240.449 -11.955 Td [(Short)-333(Precision)-334(Real)-1200(Shor)1(t)-334(Precision)-333(Complex)-1200(psb)]TJ +/F8 9.9626 Tf 375.509 503.22 Td [(geamax)]TJ -240.449 -11.955 Td [(Short)-333(Precision)-334(Real)-1200(Short)-333(Precision)-333(Complex)-1200(psb)]TJ ET q -1 0 0 1 421.365 569.489 cm +1 0 0 1 372.52 491.464 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 424.354 569.289 Td [(geamaxs)]TJ -240.449 -11.955 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Complex)-1412(psb)]TJ +/F8 9.9626 Tf 375.509 491.265 Td [(geamax)]TJ -240.449 -11.955 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Com)-1(p)1(lex)-1412(psb)]TJ ET q -1 0 0 1 421.365 557.533 cm +1 0 0 1 372.52 479.509 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 424.354 557.334 Td [(geamaxs)]TJ +/F8 9.9626 Tf 375.509 479.31 Td [(geamax)]TJ ET q -1 0 0 1 177.927 553.548 cm -[]0 d 0 J 0.398 w 0 0 m 289.266 0 l S +1 0 0 1 129.083 475.524 cm +[]0 d 0 J 0.398 w 0 0 m 285.336 0 l S Q 0 g 0 G BT -/F8 9.9626 Tf 278.877 525.509 Td [(T)83(able)-333(5:)-444(Data)-334(t)28(yp)-28(es)]TJ +/F8 9.9626 Tf 228.067 447.485 Td [(T)83(able)-333(4:)-444(Data)-334(t)28(yp)-28(es)]TJ 0 g 0 G 0 g 0 G 0 g 0 G -/F27 9.9626 Tf -128.172 -33.596 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf -128.172 -36.518 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -33.797 -22.263 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.926 Td [(x)]TJ + 0 -22.263 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -167.933 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)28(o)-255(arra)28(y)-255(or)-255(an)-255(ob)-55(ject)-255(of)-255(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -167.933 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-55(jec)-1(t)-254(of)-255(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 244.742 0 Td [(psb)]TJ +/F30 9.9626 Tf 244.743 0 Td [(psb)]TJ ET q -1 0 0 1 436.673 404.441 cm +1 0 0 1 385.864 318.82 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 439.811 404.242 Td [(T)]TJ +/F30 9.9626 Tf 389.002 318.621 Td [(T)]TJ ET q -1 0 0 1 445.669 404.441 cm +1 0 0 1 394.86 318.82 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 448.807 404.242 Td [(vect)]TJ +/F30 9.9626 Tf 397.998 318.621 Td [(vect)]TJ ET q -1 0 0 1 470.356 404.441 cm +1 0 0 1 419.547 318.82 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 473.495 404.242 Td [(type)]TJ +/F30 9.9626 Tf 422.685 318.621 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf -297.884 -11.956 Td [(con)28(taining)-333(n)27(um)28(b)-28(ers)-333(of)-333(t)27(yp)-27(e)-334(sp)-27(ec)-1(i)1(\014ed)-334(in)-333(T)83(able)]TJ +/F8 9.9626 Tf -297.883 -11.956 Td [(con)28(taining)-333(n)27(um)28(b)-28(ers)-333(of)-333(t)28(yp)-28(e)-334(sp)-27(eci\014ed)-334(in)-333(T)83(able)]TJ 0 0 1 rg 0 0 1 RG - [-333(5)]TJ + [-333(4)]TJ 0 g 0 G [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -19.925 Td [(desc)]TJ +/F27 9.9626 Tf -24.907 -22.262 Td [(desc)]TJ ET q -1 0 0 1 172.619 372.56 cm +1 0 0 1 121.81 284.602 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 176.057 372.361 Td [(a)]TJ +/F27 9.9626 Tf 125.247 284.403 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.55 0 Td [(con)28(tains)-334(data)-333(structures)-333(for)-333(c)-1(omm)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.551 0 Td [(con)28(tains)-334(d)1(ata)-334(structures)-333(for)-333(com)-1(m)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 135.659 0 Td [(psb)]TJ +/F30 9.9626 Tf 135.658 0 Td [(psb)]TJ ET q -1 0 0 1 327.588 324.74 cm +1 0 0 1 276.779 236.781 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 330.727 324.54 Td [(desc)]TJ +/F30 9.9626 Tf 279.917 236.582 Td [(desc)]TJ ET q -1 0 0 1 352.275 324.74 cm +1 0 0 1 301.466 236.781 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 355.414 324.54 Td [(type)]TJ +/F30 9.9626 Tf 304.604 236.582 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +/F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -225.63 -19.925 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf -225.631 -22.263 Td [(global)]TJ 0 g 0 G +/F8 9.9626 Tf 34.738 0 Td [(Sp)-28(eci\014es)-357(whether)-357(the)-357(computation)-358(shoul)1(d)-358(include)-357(the)-357(global)-357(reduction)]TJ -9.831 -11.955 Td [(across)-333(all)-334(pro)-27(ce)-1(sses.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(logical)-333(scalar.)-445(Default:)]TJ/F30 9.9626 Tf 168.812 0 Td [(global=.true.)]TJ 0 g 0 G - 0 -19.925 Td [(res)]TJ +/F27 9.9626 Tf -193.719 -34.217 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G +/F8 9.9626 Tf 166.875 -29.888 Td [(35)]TJ +0 g 0 G +ET + +endstream +endobj +1037 0 obj +<< +/Length 4565 +>> +stream +0 g 0 G +0 g 0 G +0 g 0 G +BT +/F27 9.9626 Tf 150.705 706.129 Td [(F)96(unction)-384(v)64(alue)]TJ 0 g 0 G -/F8 9.9626 Tf 19.47 0 Td [(is)-333(the)-334(in\014nit)28(y)-333(norm)-333(of)-334(the)-333(columns)-333(of)]TJ/F11 9.9626 Tf 166.183 0 Td [(x)]TJ/F8 9.9626 Tf 5.693 0 Td [(.)]TJ -166.44 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.956 Td [(Sp)-28(eci\014ed)-289(as:)-422(a)-289(n)28(um)28(b)-28(er)-289(or)-289(a)-289(rank)1(-)-1(on)1(e)-289(arra)27(y)-288(of)-289(long)-289(precision)-289(real)-289(n)28(um)28(b)-28(ers.)]TJ +/F8 9.9626 Tf 78.386 0 Td [(is)-333(the)-334(in\014nit)28(y)-333(norm)-333(of)-334(sub)28(v)28(ector)]TJ/F11 9.9626 Tf 143.518 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -202.692 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.167 0 Td [(global)]TJ/F8 9.9626 Tf 32.653 0 Td [(unless)-291(the)-291(optional)-290(v)55(ariable)]TJ/F30 9.9626 Tf 121.039 0 Td [(global=.false.)]TJ/F8 9.9626 Tf 76.121 0 Td [(as)-291(b)-28(een)-290(sp)-28(ec-)]TJ -261.98 -11.955 Td [(i\014ed)]TJ 0 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(long)-333(precision)-334(r)1(e)-1(al)-333(n)28(um)28(b)-28(er.)]TJ 0 g 0 G /F27 9.9626 Tf -24.906 -19.925 Td [(info)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.956 Td [(An)-333(in)28(te)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.956 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ/F16 11.9552 Tf -24.906 -21.917 Td [(Notes)]TJ +0 g 0 G +/F8 9.9626 Tf 12.176 -19.926 Td [(1.)]TJ +0 g 0 G + [-500(The)-241(computation)-240(of)-241(a)-241(gl)1(obal)-241(result)-241(requires)-240(a)-241(global)-241(comm)28(unication,)-259(whic)28(h)]TJ 12.73 -11.955 Td [(en)28(tails)-421(a)-420(s)-1(i)1(gni\014can)27(t)-420(o)28(v)27(erhead.)-706(It)-420(ma)27(y)-420(b)-28(e)-421(necessary)-420(and/or)-421(advisable)-420(to)]TJ 0 -11.955 Td [(compute)-395(m)28(ultiple)-395(norms)-395(at)-395(the)-395(same)-395(time;)-426(in)-395(this)-395(case,)-410(it)-395(is)-395(p)-28(ossible)-395(to)]TJ 0 -11.955 Td [(impro)28(v)28(e)-334(the)-333(run)28(time)-334(e\016ciency)-333(b)28(y)-334(using)-333(the)-333(follo)28(wing)-334(sc)28(heme:)]TJ 25.19 -17.933 Td [(v)-128(r)-129(e)-128(s)-259(\050)-130(1)-131(\051)-642(=)-586(p)-75(s)-76(b)]TJ +ET +q +1 0 0 1 277.899 507.075 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 281.638 506.876 Td [(g)-75(e)-76(a)-75(m)-76(a)-75(x)-181(\050)-148(x)-43(1)-248(,)-273(d)-113(e)-113(s)-112(c)]TJ +ET +q +1 0 0 1 367.515 507.075 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 371.626 506.876 Td [(a)-386(,)-288(i)-127(n)-127(f)-127(o)-415(,)-302(g)-141(l)-142(o)-141(b)-141(a)-141(l)-190(=)-48(.)]TJ/F27 9.9626 Tf 92.223 0 Td [(f)-132(a)-131(l)-132(s)-131(e)]TJ/F8 9.9626 Tf 30.349 0 Td [(.)-178(\051)]TJ -293.397 -11.955 Td [(v)-128(r)-129(e)-128(s)-259(\050)-130(2)-131(\051)-642(=)-586(p)-75(s)-76(b)]TJ +ET +q +1 0 0 1 277.899 495.12 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 281.638 494.921 Td [(g)-75(e)-76(a)-75(m)-76(a)-75(x)-181(\050)-148(x)-43(2)-248(,)-273(d)-113(e)-113(s)-112(c)]TJ +ET +q +1 0 0 1 367.515 495.12 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 371.626 494.921 Td [(a)-386(,)-288(i)-127(n)-127(f)-127(o)-415(,)-302(g)-141(l)-142(o)-141(b)-141(a)-141(l)-190(=)-48(.)]TJ/F27 9.9626 Tf 92.223 0 Td [(f)-132(a)-131(l)-132(s)-131(e)]TJ/F8 9.9626 Tf 30.349 0 Td [(.)-178(\051)]TJ -293.397 -11.955 Td [(v)-128(r)-129(e)-128(s)-259(\050)-130(3)-131(\051)-642(=)-586(p)-75(s)-76(b)]TJ +ET +q +1 0 0 1 277.899 483.165 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 281.638 482.966 Td [(g)-75(e)-76(a)-75(m)-76(a)-75(x)-181(\050)-148(x)-43(3)-248(,)-273(d)-113(e)-113(s)-112(c)]TJ +ET +q +1 0 0 1 367.515 483.165 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 371.626 482.966 Td [(a)-386(,)-288(i)-127(n)-127(f)-127(o)-415(,)-302(g)-141(l)-142(o)-141(b)-141(a)-141(l)-190(=)-48(.)]TJ/F27 9.9626 Tf 92.223 0 Td [(f)-132(a)-131(l)-132(s)-131(e)]TJ/F8 9.9626 Tf 30.349 0 Td [(.)-178(\051)]TJ/F27 9.9626 Tf -293.299 -11.955 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.101 0 Td [(p)-59(s)-59(b)]TJ +ET +q +1 0 0 1 247.365 471.21 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 250.944 471.011 Td [(a)-59(m)-59(x)-165(\050)-245(i)-138(c)-139(t)-139(x)-139(t)-439(,)-289(v)-129(r)-128(e)-128(s)-294(\050)-165(1)-165(:)-165(3)-165(\051)-165(\051)]TJ +0 g 0 G 0 g 0 G - 141.968 -90.64 Td [(36)]TJ + -75.333 -21.918 Td [(In)-354(th)1(is)-354(w)28(a)28(y)-354(the)-353(global)-354(comm)28(unication,)-359(whic)28(h)-353(for)-354(small)-353(size)-1(s)-353(is)-354(a)-353(latency-)]TJ 0 -11.955 Td [(b)-28(ound)-333(op)-28(eration,)-333(is)-333(in)27(v)28(ok)28(ed)-333(only)-334(once.)]TJ +0 g 0 G + 141.968 -346.7 Td [(36)]TJ 0 g 0 G ET endstream endobj -1037 0 obj +1050 0 obj << -/Length 6740 +/Length 6326 >> stream 0 g 0 G @@ -9387,155 +9359,155 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(norm1)-375(|)-375(1-Norm)-375(of)-375(V)94(ector)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-333(function)-334(computes)-333(the)-333(1-norm)-334(of)-333(a)-333(v)27(ector)]TJ/F11 9.9626 Tf 207.168 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -212.862 -11.956 Td [(If)]TJ/F11 9.9626 Tf 9.963 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(is)-333(a)-334(real)-333(v)28(ector)-334(it)-333(computes)-333(1-norm)-334(as:)]TJ/F11 9.9626 Tf 123.449 -21.772 Td [(asum)]TJ/F14 9.9626 Tf 27.154 0 Td [(\040)-278(k)]TJ/F11 9.9626 Tf 17.711 0 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.494 Td [(i)]TJ/F14 9.9626 Tf 3.317 1.494 Td [(k)]TJ/F8 9.9626 Tf -196.303 -21.772 Td [(else)-333(if)]TJ/F11 9.9626 Tf 28.006 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(is)-333(a)-334(complex)-333(v)28(ector)-334(then)-333(it)-333(computes)-334(1-norm)-333(as:)]TJ/F11 9.9626 Tf 70.135 -21.772 Td [(asum)]TJ/F14 9.9626 Tf 27.154 0 Td [(\040)-278(k)]TJ/F11 9.9626 Tf 17.711 0 Td [(r)-28(e)]TJ/F8 9.9626 Tf 9.411 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(\051)]TJ/F14 9.9626 Tf 3.874 0 Td [(k)]TJ/F7 6.9738 Tf 4.982 -1.494 Td [(1)]TJ/F8 9.9626 Tf 6.683 1.494 Td [(+)]TJ/F14 9.9626 Tf 9.962 0 Td [(k)]TJ/F11 9.9626 Tf 4.982 0 Td [(im)]TJ/F8 9.9626 Tf 12.179 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(\051)]TJ/F14 9.9626 Tf 3.874 0 Td [(k)]TJ/F7 6.9738 Tf 4.981 -1.494 Td [(1)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(geamaxs)-375(|)-375(Generalized)-375(In\014nit)31(y)-375(Norm)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-359(subroutine)-359(computes)-360(a)-359(series)-359(of)-359(in\014nit)28(y)-359(norms)-360(on)-359(the)-359(columns)-359(of)-359(a)-360(d)1(e)-1(n)1(s)-1(e)]TJ 0 -11.956 Td [(matrix)]TJ/F11 9.9626 Tf 32.407 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(:)]TJ/F11 9.9626 Tf 87.106 -11.955 Td [(r)-28(es)]TJ/F8 9.9626 Tf 14.08 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.433 0 Td [(\051)]TJ/F14 9.9626 Tf 6.641 0 Td [(\040)]TJ/F8 9.9626 Tf 12.73 0 Td [(max)]TJ/F10 6.9738 Tf 7.069 -6.503 Td [(k)]TJ/F14 9.9626 Tf 13.133 6.503 Td [(j)]TJ/F11 9.9626 Tf 2.768 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(k)-31(;)-167(i)]TJ/F8 9.9626 Tf 13.36 0 Td [(\051)]TJ/F14 9.9626 Tf 3.875 0 Td [(j)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -232.086 -20.278 Td [(psb_geasum\050x,)-525(desc_a,)-525(info\051)]TJ 0 -11.955 Td [(psb_norm1\050x,)-525(desc_a,)-525(info\051)]TJ +/F30 9.9626 Tf -215.738 -25.377 Td [(call)-525(psb_geamaxs\050res,)-525(x,)-525(desc_a,)-525(info\051)]TJ 0 g 0 G 0 g 0 G 0 g 0 G ET q -1 0 0 1 129.47 552.614 cm -[]0 d 0 J 0.398 w 0 0 m 284.561 0 l S +1 0 0 1 127.118 614.121 cm +[]0 d 0 J 0.398 w 0 0 m 289.266 0 l S Q BT -/F11 9.9626 Tf 135.448 544.046 Td [(asum)-7735(x)]TJ/F27 9.9626 Tf 221.863 0 Td [(F)96(unction)]TJ +/F11 9.9626 Tf 133.096 605.553 Td [(r)-28(es)-8770(x)]TJ/F27 9.9626 Tf 221.862 0 Td [(Subroutine)]TJ ET q -1 0 0 1 129.47 540.26 cm -[]0 d 0 J 0.398 w 0 0 m 284.561 0 l S +1 0 0 1 127.118 601.768 cm +[]0 d 0 J 0.398 w 0 0 m 289.266 0 l S Q BT -/F8 9.9626 Tf 135.448 531.692 Td [(Short)-333(Precision)-334(Real)-1200(Sh)1(o)-1(r)1(t)-334(Precision)-333(Real)-3103(psb)]TJ +/F8 9.9626 Tf 133.096 593.2 Td [(Short)-333(Precision)-334(Real)-1200(Sh)1(ort)-334(Precision)-333(Real)-3103(psb)]TJ ET q -1 0 0 1 372.908 531.891 cm +1 0 0 1 370.556 593.399 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 375.897 531.692 Td [(geasum)]TJ -240.449 -11.955 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Real)-3314(psb)]TJ +/F8 9.9626 Tf 373.544 593.2 Td [(geamaxs)]TJ -240.448 -11.956 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Real)-3314(psb)]TJ ET q -1 0 0 1 372.908 519.936 cm +1 0 0 1 370.556 581.444 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 375.897 519.737 Td [(geasum)]TJ -240.449 -11.955 Td [(Short)-333(Precision)-334(Real)-1200(Sh)1(o)-1(r)1(t)-334(Precision)-333(Complex)-1200(psb)]TJ +/F8 9.9626 Tf 373.544 581.244 Td [(geamaxs)]TJ -240.448 -11.955 Td [(Short)-333(Precision)-334(Real)-1200(Sh)1(ort)-334(Precision)-333(Complex)-1200(psb)]TJ ET q -1 0 0 1 372.908 507.981 cm +1 0 0 1 370.556 569.489 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 375.897 507.782 Td [(geasum)]TJ -240.449 -11.955 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Complex)-1412(psb)]TJ +/F8 9.9626 Tf 373.544 569.289 Td [(geamaxs)]TJ -240.448 -11.955 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Complex)-1412(p)1(s)-1(b)]TJ ET q -1 0 0 1 372.908 496.026 cm +1 0 0 1 370.556 557.533 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 375.897 495.827 Td [(geasum)]TJ +/F8 9.9626 Tf 373.544 557.334 Td [(geamaxs)]TJ ET q -1 0 0 1 129.47 492.041 cm -[]0 d 0 J 0.398 w 0 0 m 284.561 0 l S +1 0 0 1 127.118 553.548 cm +[]0 d 0 J 0.398 w 0 0 m 289.266 0 l S Q 0 g 0 G BT -/F8 9.9626 Tf 228.067 464.002 Td [(T)83(able)-333(6:)-444(Data)-334(t)28(yp)-28(es)]TJ +/F8 9.9626 Tf 228.067 525.509 Td [(T)83(able)-333(5:)-444(Data)-334(t)28(yp)-28(es)]TJ 0 g 0 G 0 g 0 G 0 g 0 G -/F27 9.9626 Tf -128.172 -33.393 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf -128.172 -33.596 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.867 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.867 Td [(x)]TJ + 0 -19.926 Td [(x)]TJ 0 g 0 G /F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -167.933 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-55(jec)-1(t)-254(of)-255(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 244.743 0 Td [(psb)]TJ ET q -1 0 0 1 385.864 343.254 cm +1 0 0 1 385.864 404.441 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 389.002 343.055 Td [(T)]TJ +/F30 9.9626 Tf 389.002 404.242 Td [(T)]TJ ET q -1 0 0 1 394.86 343.254 cm +1 0 0 1 394.86 404.441 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 397.998 343.055 Td [(vect)]TJ +/F30 9.9626 Tf 397.998 404.242 Td [(vect)]TJ ET q -1 0 0 1 419.547 343.254 cm +1 0 0 1 419.547 404.441 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 422.685 343.055 Td [(type)]TJ +/F30 9.9626 Tf 422.685 404.242 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf -297.883 -11.956 Td [(con)28(taining)-333(n)27(um)28(b)-28(ers)-333(of)-333(t)28(yp)-28(e)-334(sp)-27(eci\014ed)-334(in)-333(T)83(able)]TJ 0 0 1 rg 0 0 1 RG - [-333(6)]TJ + [-333(5)]TJ 0 g 0 G [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.867 Td [(desc)]TJ +/F27 9.9626 Tf -24.907 -19.925 Td [(desc)]TJ ET q -1 0 0 1 121.81 311.432 cm +1 0 0 1 121.81 372.56 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 125.247 311.232 Td [(a)]TJ +/F27 9.9626 Tf 125.247 372.361 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(con)28(tains)-334(d)1(ata)-334(structures)-333(for)-333(com)-1(m)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.551 0 Td [(con)28(tains)-334(d)1(ata)-334(structures)-333(for)-333(com)-1(m)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 135.658 0 Td [(psb)]TJ ET q -1 0 0 1 276.779 263.611 cm +1 0 0 1 276.779 324.74 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 279.917 263.412 Td [(desc)]TJ +/F30 9.9626 Tf 279.917 324.54 Td [(desc)]TJ ET q -1 0 0 1 301.466 263.611 cm +1 0 0 1 301.466 324.74 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 304.604 263.412 Td [(type)]TJ +/F30 9.9626 Tf 304.604 324.54 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -225.631 -19.867 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf -225.631 -19.925 Td [(On)-383(Return)]TJ 0 g 0 G 0 g 0 G - 0 -19.867 Td [(F)96(unction)-384(v)64(alue)]TJ + 0 -19.925 Td [(res)]TJ 0 g 0 G -/F8 9.9626 Tf 78.387 0 Td [(is)-333(the)-334(1-norm)-333(of)-333(v)28(e)-1(ctor)]TJ/F11 9.9626 Tf 102.781 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -161.955 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(long)-333(precision)-333(real)-334(n)28(um)28(b)-28(er.)]TJ +/F8 9.9626 Tf 19.47 0 Td [(is)-333(the)-334(in\014nit)28(y)-333(norm)-333(of)-334(the)-333(columns)-333(of)]TJ/F11 9.9626 Tf 166.183 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -166.44 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.956 Td [(Sp)-28(eci\014ed)-289(as:)-422(a)-289(n)28(um)28(b)-28(er)-289(or)-289(a)-289(ran)1(k-one)-289(arra)27(y)-288(of)-289(long)-289(precision)-289(real)-289(n)28(um)28(b)-28(ers.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.867 Td [(info)]TJ +/F27 9.9626 Tf -24.907 -19.925 Td [(info)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.956 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ 0 g 0 G - 141.968 -41.642 Td [(37)]TJ + 141.968 -90.64 Td [(37)]TJ 0 g 0 G ET endstream endobj -1046 0 obj +1059 0 obj << -/Length 7351 +/Length 7149 >> stream 0 g 0 G @@ -9548,141 +9520,145 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(geasums)-375(|)-375(Generalized)-375(1-Norm)-375(of)-375(V)94(ector)]TJ/F8 9.9626 Tf -25.091 -19.22 Td [(This)-310(subroutine)-310(computes)-309(a)-310(series)-310(of)-310(1-norms)-310(on)-310(the)-309(c)-1(olu)1(m)-1(n)1(s)-310(of)-310(a)-310(dense)-310(matrix)]TJ/F11 9.9626 Tf 0 -11.955 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(:)]TJ/F11 9.9626 Tf 119.512 -13.293 Td [(r)-28(es)]TJ/F8 9.9626 Tf 14.081 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)]TJ/F14 9.9626 Tf 6.642 0 Td [(\040)]TJ/F8 9.9626 Tf 12.73 0 Td [(max)]TJ/F10 6.9738 Tf 7.069 -6.503 Td [(k)]TJ/F14 9.9626 Tf 13.133 6.503 Td [(j)]TJ/F11 9.9626 Tf 2.767 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(k)-31(;)-167(i)]TJ/F8 9.9626 Tf 13.36 0 Td [(\051)]TJ/F14 9.9626 Tf 3.874 0 Td [(j)]TJ/F8 9.9626 Tf -215.737 -22.73 Td [(This)-333(function)-334(computes)-333(the)-333(1-norm)-334(of)-333(a)-333(v)28(ec)-1(tor)]TJ/F11 9.9626 Tf 207.168 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -212.862 -11.955 Td [(If)]TJ/F11 9.9626 Tf 9.963 0 Td [(x)]TJ/F8 9.9626 Tf 9.014 0 Td [(is)-333(a)-334(real)-333(v)28(ector)-334(it)-333(computes)-333(1-norm)-334(as:)]TJ/F11 9.9626 Tf 123.012 -22.81 Td [(r)-28(es)]TJ/F8 9.9626 Tf 14.081 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)]TJ/F14 9.9626 Tf 6.642 0 Td [(\040)-278(k)]TJ/F11 9.9626 Tf 17.711 0 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.495 Td [(i)]TJ/F14 9.9626 Tf 3.317 1.495 Td [(k)]TJ/F8 9.9626 Tf -196.74 -22.81 Td [(else)-333(if)]TJ/F11 9.9626 Tf 28.006 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(is)-333(a)-334(complex)-333(v)28(ector)-334(then)-333(it)-333(computes)-334(1-norm)-333(as:)]TJ/F11 9.9626 Tf 69.697 -22.81 Td [(r)-28(es)]TJ/F8 9.9626 Tf 14.081 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)]TJ/F14 9.9626 Tf 6.642 0 Td [(\040)-278(k)]TJ/F11 9.9626 Tf 17.711 0 Td [(r)-28(e)]TJ/F8 9.9626 Tf 9.411 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(\051)]TJ/F14 9.9626 Tf 3.874 0 Td [(k)]TJ/F7 6.9738 Tf 4.982 -1.494 Td [(1)]TJ/F8 9.9626 Tf 6.683 1.494 Td [(+)]TJ/F14 9.9626 Tf 9.962 0 Td [(k)]TJ/F11 9.9626 Tf 4.982 0 Td [(im)]TJ/F8 9.9626 Tf 12.179 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(\051)]TJ/F14 9.9626 Tf 3.874 0 Td [(k)]TJ/F7 6.9738 Tf 4.981 -1.494 Td [(1)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(norm1)-375(|)-375(1-Norm)-375(of)-375(V)94(ector)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-333(function)-334(computes)-333(the)-333(1-norm)-334(of)-333(a)-333(v)28(ec)-1(tor)]TJ/F11 9.9626 Tf 207.168 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -212.862 -11.956 Td [(If)]TJ/F11 9.9626 Tf 9.963 0 Td [(x)]TJ/F8 9.9626 Tf 9.014 0 Td [(is)-333(a)-334(real)-333(v)28(ector)-334(it)-333(computes)-333(1-norm)-334(as:)]TJ/F11 9.9626 Tf 123.45 -19.151 Td [(asum)]TJ/F14 9.9626 Tf 27.154 0 Td [(\040)-278(k)]TJ/F11 9.9626 Tf 17.711 0 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.494 Td [(i)]TJ/F14 9.9626 Tf 3.317 1.494 Td [(k)]TJ/F8 9.9626 Tf -196.303 -19.151 Td [(else)-333(if)]TJ/F11 9.9626 Tf 28.006 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(is)-333(a)-334(complex)-333(v)28(ector)-334(then)-333(it)-333(computes)-334(1-norm)-333(as:)]TJ/F11 9.9626 Tf 70.135 -19.152 Td [(asum)]TJ/F14 9.9626 Tf 27.154 0 Td [(\040)-278(k)]TJ/F11 9.9626 Tf 17.711 0 Td [(r)-28(e)]TJ/F8 9.9626 Tf 9.41 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(\051)]TJ/F14 9.9626 Tf 3.874 0 Td [(k)]TJ/F7 6.9738 Tf 4.981 -1.494 Td [(1)]TJ/F8 9.9626 Tf 6.683 1.494 Td [(+)]TJ/F14 9.9626 Tf 9.963 0 Td [(k)]TJ/F11 9.9626 Tf 4.981 0 Td [(im)]TJ/F8 9.9626 Tf 12.18 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(\051)]TJ/F14 9.9626 Tf 3.875 0 Td [(k)]TJ/F7 6.9738 Tf 4.981 -1.494 Td [(1)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -232.523 -21.762 Td [(call)-525(psb_geasums\050res,)-525(x,)-525(desc_a,)-525(info\051)]TJ +/F30 9.9626 Tf -232.086 -17.657 Td [(psb_geasum\050x,)-525(desc_a,)-525(info)-525([,global]\051)]TJ 0 -11.955 Td [(psb_norm1\050x,)-525(desc_a,)-525(info)-525([,global]\051)]TJ 0 g 0 G 0 g 0 G 0 g 0 G ET q -1 0 0 1 178.071 508.729 cm -[]0 d 0 J 0.398 w 0 0 m 288.979 0 l S +1 0 0 1 180.28 566.766 cm +[]0 d 0 J 0.398 w 0 0 m 284.561 0 l S Q BT -/F11 9.9626 Tf 184.049 500.161 Td [(r)-28(es)-8770(x)]TJ/F27 9.9626 Tf 221.862 0 Td [(Subroutine)]TJ +/F11 9.9626 Tf 186.257 558.198 Td [(asum)-7736(x)]TJ/F27 9.9626 Tf 221.863 0 Td [(F)96(unction)]TJ ET q -1 0 0 1 178.071 496.375 cm -[]0 d 0 J 0.398 w 0 0 m 288.979 0 l S +1 0 0 1 180.28 554.412 cm +[]0 d 0 J 0.398 w 0 0 m 284.561 0 l S Q BT -/F8 9.9626 Tf 184.049 487.807 Td [(Short)-333(Precision)-333(R)-1(eal)-1200(S)1(hort)-334(Precision)-333(Real)-3103(psb)]TJ +/F8 9.9626 Tf 186.257 545.845 Td [(Short)-333(Precision)-334(Real)-1200(Short)-333(Precision)-333(Real)-3103(psb)]TJ ET q -1 0 0 1 421.508 488.007 cm +1 0 0 1 423.717 546.044 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 424.497 487.807 Td [(geasums)]TJ -240.448 -11.955 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Real)-3314(psb)]TJ +/F8 9.9626 Tf 426.706 545.845 Td [(geasum)]TJ -240.449 -11.956 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Real)-3314(psb)]TJ ET q -1 0 0 1 421.508 476.051 cm +1 0 0 1 423.717 534.089 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 424.497 475.852 Td [(geasums)]TJ -240.448 -11.955 Td [(Short)-333(Precision)-333(R)-1(eal)-1200(S)1(hort)-334(Precision)-333(Complex)-1200(psb)]TJ +/F8 9.9626 Tf 426.706 533.889 Td [(geasum)]TJ -240.449 -11.955 Td [(Short)-333(Precision)-334(Real)-1200(Short)-333(Precision)-333(Complex)-1200(psb)]TJ ET q -1 0 0 1 421.508 464.096 cm +1 0 0 1 423.717 522.133 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 424.497 463.897 Td [(geasums)]TJ -240.448 -11.955 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Complex)-1412(p)1(s)-1(b)]TJ +/F8 9.9626 Tf 426.706 521.934 Td [(geasum)]TJ -240.449 -11.955 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Com)-1(p)1(lex)-1412(psb)]TJ ET q -1 0 0 1 421.508 452.141 cm +1 0 0 1 423.717 510.178 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 424.497 451.942 Td [(geasums)]TJ +/F8 9.9626 Tf 426.706 509.979 Td [(geasum)]TJ ET q -1 0 0 1 178.071 448.156 cm -[]0 d 0 J 0.398 w 0 0 m 288.979 0 l S +1 0 0 1 180.28 506.193 cm +[]0 d 0 J 0.398 w 0 0 m 284.561 0 l S Q 0 g 0 G BT -/F8 9.9626 Tf 278.877 420.117 Td [(T)83(able)-333(7:)-444(Data)-334(t)28(yp)-28(es)]TJ +/F8 9.9626 Tf 278.877 478.154 Td [(T)83(able)-333(6:)-444(Data)-334(t)28(yp)-28(es)]TJ 0 g 0 G 0 g 0 G 0 g 0 G -/F27 9.9626 Tf -128.172 -35.827 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf -128.172 -29.723 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -21.709 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -33.797 -18.819 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -21.71 Td [(x)]TJ + 0 -18.819 Td [(x)]TJ 0 g 0 G /F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -167.933 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)28(o)-255(arra)28(y)-255(or)-255(an)-255(ob)-55(ject)-255(of)-255(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 244.742 0 Td [(psb)]TJ ET q -1 0 0 1 436.673 293.25 cm +1 0 0 1 436.673 363.172 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 439.811 293.051 Td [(T)]TJ +/F30 9.9626 Tf 439.811 362.973 Td [(T)]TJ ET q -1 0 0 1 445.669 293.25 cm +1 0 0 1 445.669 363.172 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 448.807 293.051 Td [(vect)]TJ +/F30 9.9626 Tf 448.807 362.973 Td [(vect)]TJ ET q -1 0 0 1 470.356 293.25 cm +1 0 0 1 470.356 363.172 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 473.495 293.051 Td [(type)]TJ +/F30 9.9626 Tf 473.495 362.973 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf -297.884 -11.956 Td [(con)28(taining)-333(n)27(um)28(b)-28(ers)-333(of)-333(t)27(yp)-27(e)-334(sp)-27(ec)-1(i)1(\014ed)-334(in)-333(T)83(able)]TJ +/F8 9.9626 Tf -297.884 -11.955 Td [(con)28(taining)-333(n)27(um)28(b)-28(ers)-333(of)-333(t)27(yp)-27(e)-334(sp)-27(ec)-1(i)1(\014ed)-334(in)-333(T)83(able)]TJ 0 0 1 rg 0 0 1 RG - [-333(7)]TJ + [-333(6)]TJ 0 g 0 G [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -21.709 Td [(desc)]TJ +/F27 9.9626 Tf -24.906 -18.819 Td [(desc)]TJ ET q -1 0 0 1 172.619 259.585 cm +1 0 0 1 172.619 332.398 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 176.057 259.386 Td [(a)]TJ +/F27 9.9626 Tf 176.057 332.199 Td [(a)]TJ 0 g 0 G /F8 9.9626 Tf 10.55 0 Td [(con)28(tains)-334(data)-333(structures)-333(for)-333(c)-1(omm)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 135.659 0 Td [(psb)]TJ ET q -1 0 0 1 327.588 211.765 cm +1 0 0 1 327.588 284.577 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 330.727 211.565 Td [(desc)]TJ +/F30 9.9626 Tf 330.727 284.378 Td [(desc)]TJ ET q -1 0 0 1 352.275 211.765 cm +1 0 0 1 352.275 284.577 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 355.414 211.565 Td [(type)]TJ +/F30 9.9626 Tf 355.414 284.378 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -225.63 -21.709 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf -225.63 -18.818 Td [(global)]TJ 0 g 0 G +/F8 9.9626 Tf 34.737 0 Td [(Sp)-28(eci\014es)-357(whether)-357(the)-357(co)-1(mpu)1(tation)-358(should)-357(include)-357(the)-357(global)-357(reduction)]TJ -9.831 -11.956 Td [(across)-333(all)-334(pro)-27(c)-1(esses.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf 40.576 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(logical)-333(scalar.)-445(Default:)]TJ/F30 9.9626 Tf 168.812 0 Td [(global=.true.)]TJ 0 g 0 G - 0 -21.71 Td [(res)]TJ +/F27 9.9626 Tf -193.718 -30.774 Td [(On)-383(Return)]TJ 0 g 0 G -/F8 9.9626 Tf 19.47 0 Td [(con)28(tains)-334(th)1(e)-334(1-norm)-333(of)-333(\050the)-334(columns)-333(of)-78(\051)]TJ/F11 9.9626 Tf 177.75 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -178.008 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Short)-324(as:)-440(a)-324(long)-324(precision)-325(r)1(e)-1(al)-324(n)28(um)28(b)-28(er.)-441(Sp)-28(eci\014ed)-324(as:)-440(a)-324(long)-324(precision)-325(real)]TJ 0 -11.955 Td [(n)28(um)28(b)-28(er.)]TJ +0 g 0 G + 0 -18.819 Td [(F)96(unction)-384(v)64(alue)]TJ +0 g 0 G +/F8 9.9626 Tf 78.386 0 Td [(is)-333(the)-334(1-norm)-333(of)-333(v)27(ector)]TJ/F11 9.9626 Tf 102.781 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -161.955 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.167 0 Td [(global)]TJ/F8 9.9626 Tf 32.653 0 Td [(unless)-291(the)-291(option)1(al)-291(v)55(ariable)]TJ/F30 9.9626 Tf 121.039 0 Td [(global=.false.)]TJ/F8 9.9626 Tf 76.121 0 Td [(as)-291(b)-28(een)-290(sp)-28(ec-)]TJ -261.98 -11.955 Td [(i\014ed)]TJ 0 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(long)-333(precision)-334(r)1(e)-1(al)-333(n)28(um)28(b)-28(er.)]TJ 0 g 0 G 141.968 -29.888 Td [(38)]TJ 0 g 0 G @@ -9690,9 +9666,9 @@ ET endstream endobj -1051 0 obj +1064 0 obj << -/Length 624 +/Length 3878 >> stream 0 g 0 G @@ -9701,353 +9677,249 @@ stream BT /F27 9.9626 Tf 99.895 706.129 Td [(info)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ 0 g 0 G - 141.968 -567.87 Td [(39)]TJ +/F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ 0 g 0 G -ET - -endstream -endobj -1058 0 obj -<< -/Length 6754 ->> -stream -0 g 0 G -0 g 0 G -BT -/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ -ET -q -1 0 0 1 171.761 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 175.796 706.129 Td [(norm2)-375(|)-375(2-Norm)-375(of)-375(V)94(ector)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-333(function)-334(computes)-333(the)-333(2-norm)-334(of)-333(a)-333(v)28(ec)-1(tor)]TJ/F11 9.9626 Tf 207.168 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -212.862 -11.956 Td [(If)]TJ/F11 9.9626 Tf 9.963 0 Td [(x)]TJ/F8 9.9626 Tf 9.014 0 Td [(is)-333(a)-334(real)-333(v)28(ector)-334(it)-333(computes)-333(2-norm)-334(as:)]TJ/F11 9.9626 Tf 119.907 -21.496 Td [(nr)-28(m)]TJ/F8 9.9626 Tf 19.498 0 Td [(2)]TJ/F14 9.9626 Tf 7.749 0 Td [(\040)]TJ 12.73 9.34 Td [(p)]TJ -ET -q -1 0 0 1 337.868 663.827 cm -[]0 d 0 J 0.398 w 0 0 m 17.664 0 l S -Q -BT -/F11 9.9626 Tf 337.868 654.288 Td [(x)]TJ/F10 6.9738 Tf 5.694 2.878 Td [(T)]TJ/F11 9.9626 Tf 6.276 -2.878 Td [(x)]TJ/F8 9.9626 Tf -199.133 -20.381 Td [(else)-333(if)]TJ/F11 9.9626 Tf 28.006 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(is)-333(a)-334(complex)-333(v)28(ector)-334(then)-333(it)-333(computes)-334(2-norm)-333(as:)]TJ/F11 9.9626 Tf 101.222 -21.496 Td [(nr)-28(m)]TJ/F8 9.9626 Tf 19.499 0 Td [(2)]TJ/F14 9.9626 Tf 7.749 0 Td [(\040)]TJ 12.73 9.339 Td [(p)]TJ -ET -q -1 0 0 1 337.228 621.949 cm -[]0 d 0 J 0.398 w 0 0 m 18.944 0 l S -Q -BT -/F11 9.9626 Tf 337.228 612.411 Td [(x)]TJ/F10 6.9738 Tf 5.694 2.878 Td [(H)]TJ/F11 9.9626 Tf 7.556 -2.878 Td [(x)]TJ -0 g 0 G -0 g 0 G -0 g 0 G -ET -q -1 0 0 1 180.294 592.22 cm -[]0 d 0 J 0.398 w 0 0 m 284.534 0 l S -Q -BT -/F11 9.9626 Tf 186.271 583.652 Td [(nr)-28(m)]TJ/F8 9.9626 Tf 19.499 0 Td [(2)]TJ/F11 9.9626 Tf 81.954 0 Td [(x)]TJ/F27 9.9626 Tf 120.41 0 Td [(F)96(unction)]TJ -ET -q -1 0 0 1 180.294 579.866 cm -[]0 d 0 J 0.398 w 0 0 m 284.534 0 l S -Q -BT -/F8 9.9626 Tf 186.271 571.298 Td [(Short)-333(Precision)-334(Real)-1200(Shor)1(t)-334(Precision)-333(Real)-3103(psb)]TJ + [-500(The)-241(computation)-240(of)-241(a)-240(global)-241(result)-241(requires)-240(a)-241(global)-241(comm)28(unication,)-259(whic)28(h)]TJ 12.73 -11.955 Td [(en)28(tails)-421(a)-420(signi\014can)27(t)-420(o)28(v)27(erhead.)-706(It)-420(ma)27(y)-420(b)-28(e)-421(necessary)-420(and/or)-421(advisable)-420(to)]TJ 0 -11.955 Td [(compute)-395(m)28(ultiple)-395(norms)-395(at)-395(the)-395(same)-395(time;)-426(in)-395(this)-395(case,)-410(it)-395(is)-395(p)-28(ossible)-395(to)]TJ 0 -11.955 Td [(impro)28(v)28(e)-334(the)-333(run)28(time)-334(e\016ciency)-333(b)28(y)-334(using)-333(the)-333(follo)28(wing)-334(sc)28(heme:)]TJ 25.189 -17.933 Td [(v)-128(r)-129(e)-128(s)-259(\050)-131(1)-130(\051)-642(=)-593(p)-83(s)-82(b)]TJ ET q -1 0 0 1 423.731 571.497 cm +1 0 0 1 227.371 562.866 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 426.72 571.298 Td [(genrm2)]TJ -240.449 -11.955 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Real)-3314(psb)]TJ +/F8 9.9626 Tf 231.181 562.667 Td [(g)-82(e)-83(a)-82(s)-83(u)-82(m)-188(\050)-149(x)-43(1)-247(,)-274(d)-112(e)-113(s)-113(c)]TJ ET q -1 0 0 1 423.731 559.542 cm +1 0 0 1 316.705 562.866 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 426.72 559.343 Td [(genrm2)]TJ -240.449 -11.955 Td [(Short)-333(Precision)-334(Real)-1200(Short)-333(Precision)-333(Complex)-1200(psb)]TJ +/F8 9.9626 Tf 320.816 562.667 Td [(a)-386(,)-288(i)-127(n)-127(f)-127(o)-415(,)-302(g)-141(l)-142(o)-141(b)-141(a)-141(l)-190(=)-48(.)]TJ/F27 9.9626 Tf 92.224 0 Td [(f)-132(a)-131(l)-132(s)-131(e)]TJ/F8 9.9626 Tf 30.348 0 Td [(.)-178(\051)]TJ -293.397 -11.955 Td [(v)-128(r)-129(e)-128(s)-259(\050)-131(2)-130(\051)-642(=)-593(p)-83(s)-82(b)]TJ ET q -1 0 0 1 423.731 547.587 cm +1 0 0 1 227.371 550.911 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 426.72 547.388 Td [(genrm2)]TJ -240.449 -11.955 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Complex)-1412(psb)]TJ +/F8 9.9626 Tf 231.181 550.712 Td [(g)-82(e)-83(a)-82(s)-83(u)-82(m)-188(\050)-149(x)-43(2)-247(,)-274(d)-112(e)-113(s)-113(c)]TJ ET q -1 0 0 1 423.731 535.632 cm +1 0 0 1 316.705 550.911 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 426.72 535.433 Td [(genrm2)]TJ -ET -q -1 0 0 1 180.294 531.647 cm -[]0 d 0 J 0.398 w 0 0 m 284.534 0 l S -Q -0 g 0 G -BT -/F8 9.9626 Tf 278.877 503.608 Td [(T)83(able)-333(8:)-444(Data)-334(t)28(yp)-28(es)]TJ -0 g 0 G -0 g 0 G -0 g 0 G -0 g 0 G -/F30 9.9626 Tf -128.172 -33.435 Td [(psb_genrm2\050x,)-525(desc_a,)-525(info\051)]TJ 0 -11.955 Td [(psb_norm2\050x,)-525(desc_a,)-525(info\051)]TJ -0 g 0 G -/F27 9.9626 Tf 0 -20.382 Td [(T)32(yp)-32(e:)]TJ -0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ -0 g 0 G -/F27 9.9626 Tf -33.797 -19.31 Td [(On)-383(En)32(try)]TJ -0 g 0 G -0 g 0 G - 0 -19.311 Td [(x)]TJ -0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -167.933 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)28(o)-255(arra)28(y)-255(or)-255(an)-255(ob)-55(ject)-255(of)-255(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 244.742 0 Td [(psb)]TJ -ET -q -1 0 0 1 436.673 351.593 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 439.811 351.394 Td [(T)]TJ -ET -q -1 0 0 1 445.669 351.593 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 448.807 351.394 Td [(vect)]TJ -ET -q -1 0 0 1 470.356 351.593 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 473.495 351.394 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf -297.884 -11.955 Td [(con)28(taining)-333(n)27(um)28(b)-28(ers)-333(of)-333(t)27(yp)-27(e)-334(sp)-27(ec)-1(i)1(\014ed)-334(in)-333(T)83(able)]TJ -0 0 1 rg 0 0 1 RG - [-333(8)]TJ -0 g 0 G - [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.906 -19.311 Td [(desc)]TJ +/F8 9.9626 Tf 320.816 550.712 Td [(a)-386(,)-288(i)-127(n)-127(f)-127(o)-415(,)-302(g)-141(l)-142(o)-141(b)-141(a)-141(l)-190(=)-48(.)]TJ/F27 9.9626 Tf 92.224 0 Td [(f)-132(a)-131(l)-132(s)-131(e)]TJ/F8 9.9626 Tf 30.348 0 Td [(.)-178(\051)]TJ -293.397 -11.955 Td [(v)-128(r)-129(e)-128(s)-259(\050)-131(3)-130(\051)-642(=)-593(p)-83(s)-82(b)]TJ ET q -1 0 0 1 172.619 320.328 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +1 0 0 1 227.371 538.956 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F27 9.9626 Tf 176.057 320.128 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.55 0 Td [(con)28(tains)-334(data)-333(structures)-333(for)-333(c)-1(omm)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 135.659 0 Td [(psb)]TJ +/F8 9.9626 Tf 231.181 538.757 Td [(g)-82(e)-83(a)-82(s)-83(u)-82(m)-188(\050)-149(x)-43(3)-247(,)-274(d)-112(e)-113(s)-113(c)]TJ ET q -1 0 0 1 327.588 272.507 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 316.705 538.956 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F30 9.9626 Tf 330.727 272.308 Td [(desc)]TJ +/F8 9.9626 Tf 320.816 538.757 Td [(a)-386(,)-288(i)-127(n)-127(f)-127(o)-415(,)-302(g)-141(l)-142(o)-141(b)-141(a)-141(l)-190(=)-48(.)]TJ/F27 9.9626 Tf 92.224 0 Td [(f)-132(a)-131(l)-132(s)-131(e)]TJ/F8 9.9626 Tf 30.348 0 Td [(.)-178(\051)]TJ/F27 9.9626 Tf -293.299 -11.956 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.198 0 Td [(p)-69(s)-69(b)]TJ ET q -1 0 0 1 352.275 272.507 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 196.943 527.001 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F30 9.9626 Tf 355.414 272.308 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -225.63 -19.311 Td [(On)-383(Return)]TJ +/F8 9.9626 Tf 200.618 526.801 Td [(s)-69(u)-69(m)-174(\050)-245(i)-139(c)-139(t)-138(x)-139(t)-439(,)-290(v)-128(r)-128(e)-129(s)-293(\050)-165(1)-165(:)-165(3)-165(\051)-166(\051)]TJ 0 g 0 G 0 g 0 G - 0 -19.311 Td [(F)96(unction)-384(V)96(alue)]TJ + -75.816 -21.917 Td [(In)-353(this)-354(w)28(a)28(y)-354(the)-353(global)-354(comm)28(unication,)-359(whic)28(h)-353(for)-354(small)-353(sizes)-354(is)-354(a)-353(latency-)]TJ 0 -11.956 Td [(b)-28(ound)-333(op)-28(eration,)-333(is)-333(in)28(v)27(ok)28(ed)-333(only)-333(onc)-1(e.)]TJ 0 g 0 G -/F8 9.9626 Tf 80.683 0 Td [(is)-333(the)-334(2-norm)-333(of)-333(sub)27(v)28(ector)]TJ/F11 9.9626 Tf 117.504 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -178.974 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-334(long)-333(precision)-333(real)-334(n)28(um)28(b)-28(er.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -19.311 Td [(info)]TJ -0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.034 -11.955 Td [(An)-333(in)28(teger)-334(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detected.)]TJ -0 g 0 G - 141.967 -40.251 Td [(40)]TJ + 141.968 -402.49 Td [(39)]TJ 0 g 0 G ET endstream endobj -1066 0 obj +1077 0 obj << -/Length 6130 +/Length 7351 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ +/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ ET q -1 0 0 1 120.951 706.328 cm +1 0 0 1 171.761 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(genrm2s)-375(|)-375(Generalized)-375(2-Norm)-375(of)-375(V)94(ector)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-310(subroutine)-310(computes)-309(a)-310(series)-310(of)-310(2-norms)-310(on)-310(the)-310(columns)-309(of)-310(a)-310(dense)-310(matrix)]TJ/F11 9.9626 Tf 0 -11.956 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(:)]TJ/F11 9.9626 Tf 126.531 -11.955 Td [(r)-28(es)]TJ/F8 9.9626 Tf 14.081 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)]TJ/F14 9.9626 Tf 6.642 0 Td [(\040)-278(k)]TJ/F11 9.9626 Tf 17.711 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(\050:)]TJ/F11 9.9626 Tf 6.642 0 Td [(;)-167(i)]TJ/F8 9.9626 Tf 7.86 0 Td [(\051)]TJ/F14 9.9626 Tf 3.875 0 Td [(k)]TJ/F7 6.9738 Tf 4.981 -1.494 Td [(2)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(geasums)-375(|)-375(Generalized)-375(1-Norm)-375(of)-375(V)94(ector)]TJ/F8 9.9626 Tf -25.091 -19.22 Td [(This)-310(subroutine)-310(computes)-309(a)-310(series)-310(of)-310(1-norms)-310(on)-310(the)-309(c)-1(olu)1(m)-1(n)1(s)-310(of)-310(a)-310(dense)-310(matrix)]TJ/F11 9.9626 Tf 0 -11.955 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(:)]TJ/F11 9.9626 Tf 119.512 -13.293 Td [(r)-28(es)]TJ/F8 9.9626 Tf 14.081 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)]TJ/F14 9.9626 Tf 6.642 0 Td [(\040)]TJ/F8 9.9626 Tf 12.73 0 Td [(max)]TJ/F10 6.9738 Tf 7.069 -6.503 Td [(k)]TJ/F14 9.9626 Tf 13.133 6.503 Td [(j)]TJ/F11 9.9626 Tf 2.767 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(k)-31(;)-167(i)]TJ/F8 9.9626 Tf 13.36 0 Td [(\051)]TJ/F14 9.9626 Tf 3.874 0 Td [(j)]TJ/F8 9.9626 Tf -215.737 -22.73 Td [(This)-333(function)-334(computes)-333(the)-333(1-norm)-334(of)-333(a)-333(v)28(ec)-1(tor)]TJ/F11 9.9626 Tf 207.168 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -212.862 -11.955 Td [(If)]TJ/F11 9.9626 Tf 9.963 0 Td [(x)]TJ/F8 9.9626 Tf 9.014 0 Td [(is)-333(a)-334(real)-333(v)28(ector)-334(it)-333(computes)-333(1-norm)-334(as:)]TJ/F11 9.9626 Tf 123.012 -22.81 Td [(r)-28(es)]TJ/F8 9.9626 Tf 14.081 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)]TJ/F14 9.9626 Tf 6.642 0 Td [(\040)-278(k)]TJ/F11 9.9626 Tf 17.711 0 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.495 Td [(i)]TJ/F14 9.9626 Tf 3.317 1.495 Td [(k)]TJ/F8 9.9626 Tf -196.74 -22.81 Td [(else)-333(if)]TJ/F11 9.9626 Tf 28.006 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(is)-333(a)-334(complex)-333(v)28(ector)-334(then)-333(it)-333(computes)-334(1-norm)-333(as:)]TJ/F11 9.9626 Tf 69.697 -22.81 Td [(r)-28(es)]TJ/F8 9.9626 Tf 14.081 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)]TJ/F14 9.9626 Tf 6.642 0 Td [(\040)-278(k)]TJ/F11 9.9626 Tf 17.711 0 Td [(r)-28(e)]TJ/F8 9.9626 Tf 9.411 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(\051)]TJ/F14 9.9626 Tf 3.874 0 Td [(k)]TJ/F7 6.9738 Tf 4.982 -1.494 Td [(1)]TJ/F8 9.9626 Tf 6.683 1.494 Td [(+)]TJ/F14 9.9626 Tf 9.962 0 Td [(k)]TJ/F11 9.9626 Tf 4.982 0 Td [(im)]TJ/F8 9.9626 Tf 12.179 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(\051)]TJ/F14 9.9626 Tf 3.874 0 Td [(k)]TJ/F7 6.9738 Tf 4.981 -1.494 Td [(1)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -207.017 -20.424 Td [(call)-525(psb_genrm2s\050res,)-525(x,)-525(desc_a,)-525(info\051)]TJ +/F30 9.9626 Tf -232.523 -21.762 Td [(call)-525(psb_geasums\050res,)-525(x,)-525(desc_a,)-525(info\051)]TJ 0 g 0 G 0 g 0 G 0 g 0 G ET q -1 0 0 1 127.261 617.58 cm +1 0 0 1 178.071 508.729 cm []0 d 0 J 0.398 w 0 0 m 288.979 0 l S Q BT -/F11 9.9626 Tf 133.239 609.013 Td [(r)-28(es)-8770(x)]TJ/F27 9.9626 Tf 221.863 0 Td [(Subroutine)]TJ +/F11 9.9626 Tf 184.049 500.161 Td [(r)-28(es)-8770(x)]TJ/F27 9.9626 Tf 221.862 0 Td [(Subroutine)]TJ ET q -1 0 0 1 127.261 605.227 cm +1 0 0 1 178.071 496.375 cm []0 d 0 J 0.398 w 0 0 m 288.979 0 l S Q BT -/F8 9.9626 Tf 133.239 596.659 Td [(Short)-333(Precision)-334(Real)-1200(Shor)1(t)-334(Precision)-333(Real)-3103(psb)]TJ +/F8 9.9626 Tf 184.049 487.807 Td [(Short)-333(Precision)-333(R)-1(eal)-1200(S)1(hort)-334(Precision)-333(Real)-3103(psb)]TJ ET q -1 0 0 1 370.699 596.858 cm +1 0 0 1 421.508 488.007 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 373.688 596.659 Td [(genrm2s)]TJ -240.449 -11.955 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Real)-3314(psb)]TJ +/F8 9.9626 Tf 424.497 487.807 Td [(geasums)]TJ -240.448 -11.955 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Real)-3314(psb)]TJ ET q -1 0 0 1 370.699 584.903 cm +1 0 0 1 421.508 476.051 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 373.688 584.704 Td [(genrm2s)]TJ -240.449 -11.955 Td [(Short)-333(Precision)-334(Real)-1200(Shor)1(t)-334(Precision)-333(Complex)-1200(psb)]TJ +/F8 9.9626 Tf 424.497 475.852 Td [(geasums)]TJ -240.448 -11.955 Td [(Short)-333(Precision)-333(R)-1(eal)-1200(S)1(hort)-334(Precision)-333(Complex)-1200(psb)]TJ ET q -1 0 0 1 370.699 572.948 cm +1 0 0 1 421.508 464.096 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 373.688 572.749 Td [(genrm2s)]TJ -240.449 -11.956 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Complex)-1412(psb)]TJ +/F8 9.9626 Tf 424.497 463.897 Td [(geasums)]TJ -240.448 -11.955 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Complex)-1412(p)1(s)-1(b)]TJ ET q -1 0 0 1 370.699 560.993 cm +1 0 0 1 421.508 452.141 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 373.688 560.793 Td [(genrm2s)]TJ +/F8 9.9626 Tf 424.497 451.942 Td [(geasums)]TJ ET q -1 0 0 1 127.261 557.008 cm +1 0 0 1 178.071 448.156 cm []0 d 0 J 0.398 w 0 0 m 288.979 0 l S Q 0 g 0 G BT -/F8 9.9626 Tf 228.067 528.968 Td [(T)83(able)-333(9:)-444(Data)-334(t)28(yp)-28(es)]TJ +/F8 9.9626 Tf 278.877 420.117 Td [(T)83(able)-333(7:)-444(Data)-334(t)28(yp)-28(es)]TJ 0 g 0 G 0 g 0 G 0 g 0 G -/F27 9.9626 Tf -128.172 -33.596 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf -128.172 -35.827 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -33.797 -21.709 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.926 Td [(x)]TJ + 0 -21.71 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -167.933 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-55(jec)-1(t)-254(of)-255(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -167.933 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)28(o)-255(arra)28(y)-255(or)-255(an)-255(ob)-55(ject)-255(of)-255(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 244.743 0 Td [(psb)]TJ +/F30 9.9626 Tf 244.742 0 Td [(psb)]TJ ET q -1 0 0 1 385.864 407.9 cm +1 0 0 1 436.673 293.25 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 389.002 407.701 Td [(T)]TJ +/F30 9.9626 Tf 439.811 293.051 Td [(T)]TJ ET q -1 0 0 1 394.86 407.9 cm +1 0 0 1 445.669 293.25 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 397.998 407.701 Td [(vect)]TJ +/F30 9.9626 Tf 448.807 293.051 Td [(vect)]TJ ET q -1 0 0 1 419.547 407.9 cm +1 0 0 1 470.356 293.25 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 422.685 407.701 Td [(type)]TJ +/F30 9.9626 Tf 473.495 293.051 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf -297.883 -11.955 Td [(con)28(taining)-333(n)27(um)28(b)-28(ers)-333(of)-333(t)28(yp)-28(e)-334(sp)-27(eci\014ed)-334(in)-333(T)83(able)]TJ +/F8 9.9626 Tf -297.884 -11.956 Td [(con)28(taining)-333(n)27(um)28(b)-28(ers)-333(of)-333(t)27(yp)-27(e)-334(sp)-27(ec)-1(i)1(\014ed)-334(in)-333(T)83(able)]TJ 0 0 1 rg 0 0 1 RG - [-333(9)]TJ + [-333(7)]TJ 0 g 0 G [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.926 Td [(desc)]TJ +/F27 9.9626 Tf -24.906 -21.709 Td [(desc)]TJ ET q -1 0 0 1 121.81 376.02 cm +1 0 0 1 172.619 259.585 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 125.247 375.82 Td [(a)]TJ +/F27 9.9626 Tf 176.057 259.386 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(con)28(tains)-334(d)1(ata)-334(structures)-333(for)-333(com)-1(m)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.55 0 Td [(con)28(tains)-334(data)-333(structures)-333(for)-333(c)-1(omm)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 135.658 0 Td [(psb)]TJ +/F30 9.9626 Tf 135.659 0 Td [(psb)]TJ ET q -1 0 0 1 276.779 328.199 cm +1 0 0 1 327.588 211.765 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 279.917 328 Td [(desc)]TJ +/F30 9.9626 Tf 330.727 211.565 Td [(desc)]TJ ET q -1 0 0 1 301.466 328.199 cm +1 0 0 1 352.275 211.765 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 304.604 328 Td [(type)]TJ +/F30 9.9626 Tf 355.414 211.565 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(.)]TJ +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -225.631 -19.926 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf -225.63 -21.709 Td [(On)-383(Return)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(res)]TJ + 0 -21.71 Td [(res)]TJ 0 g 0 G -/F8 9.9626 Tf 19.47 0 Td [(con)28(tains)-334(the)-333(1-norm)-333(of)-334(\050th)1(e)-334(columns)-333(of)-78(\051)]TJ/F11 9.9626 Tf 177.751 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -178.008 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(long)-333(precision)-333(real)-334(n)28(um)28(b)-28(er.)]TJ +/F8 9.9626 Tf 19.47 0 Td [(con)28(tains)-334(th)1(e)-334(1-norm)-333(of)-333(\050the)-334(columns)-333(of)-78(\051)]TJ/F11 9.9626 Tf 177.75 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -178.008 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Short)-324(as:)-440(a)-324(long)-324(precision)-325(r)1(e)-1(al)-324(n)28(um)28(b)-28(er.)-441(Sp)-28(eci\014ed)-324(as:)-440(a)-324(long)-324(precision)-325(real)]TJ 0 -11.955 Td [(n)28(um)28(b)-28(er.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.926 Td [(info)]TJ + 141.968 -29.888 Td [(40)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ +ET + +endstream +endobj +1082 0 obj +<< +/Length 624 +>> +stream +0 g 0 G +0 g 0 G +0 g 0 G +BT +/F27 9.9626 Tf 99.895 706.129 Td [(info)]TJ 0 g 0 G - 141.968 -94.1 Td [(41)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ +0 g 0 G + 141.968 -567.87 Td [(41)]TJ 0 g 0 G ET endstream endobj -1073 0 obj +1089 0 obj << -/Length 5509 +/Length 6462 >> stream 0 g 0 G @@ -10060,735 +9932,629 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(norm1)-375(|)-375(1-Norm)-375(of)-375(Sparse)-375(Matrix)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-333(function)-334(computes)-333(the)-333(1-norm)-334(of)-333(a)-333(matrix)]TJ/F11 9.9626 Tf 209.658 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(:)]TJ/F11 9.9626 Tf -76.215 -33.873 Td [(nr)-28(m)]TJ/F8 9.9626 Tf 19.498 0 Td [(1)]TJ/F14 9.9626 Tf 7.749 0 Td [(\040)-278(k)]TJ/F11 9.9626 Tf 17.711 0 Td [(A)]TJ/F14 9.9626 Tf 7.472 0 Td [(k)]TJ/F7 6.9738 Tf 4.982 -1.495 Td [(1)]TJ/F8 9.9626 Tf -198.327 -20.423 Td [(where:)]TJ -0 g 0 G -/F11 9.9626 Tf 0 -19.926 Td [(A)]TJ -0 g 0 G -/F8 9.9626 Tf 12.453 0 Td [(represen)28(ts)-334(the)-333(global)-333(matrix)]TJ/F11 9.9626 Tf 125.834 0 Td [(A)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(norm2)-375(|)-375(2-Norm)-375(of)-375(V)94(ector)]TJ/F8 9.9626 Tf -25.091 -19.67 Td [(This)-333(function)-334(computes)-333(the)-333(2-norm)-334(of)-333(a)-333(v)28(ec)-1(tor)]TJ/F11 9.9626 Tf 207.168 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -212.862 -11.955 Td [(If)]TJ/F11 9.9626 Tf 9.963 0 Td [(x)]TJ/F8 9.9626 Tf 9.014 0 Td [(is)-333(a)-334(real)-333(v)28(ector)-334(it)-333(computes)-333(2-norm)-334(as:)]TJ/F11 9.9626 Tf 119.907 -24.408 Td [(nr)-28(m)]TJ/F8 9.9626 Tf 19.498 0 Td [(2)]TJ/F14 9.9626 Tf 7.749 0 Td [(\040)]TJ 12.73 9.339 Td [(p)]TJ +ET +q +1 0 0 1 337.868 659.634 cm +[]0 d 0 J 0.398 w 0 0 m 17.664 0 l S +Q +BT +/F11 9.9626 Tf 337.868 650.096 Td [(x)]TJ/F10 6.9738 Tf 5.694 2.878 Td [(T)]TJ/F11 9.9626 Tf 6.276 -2.878 Td [(x)]TJ/F8 9.9626 Tf -199.133 -23.294 Td [(else)-333(if)]TJ/F11 9.9626 Tf 28.006 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(is)-333(a)-334(complex)-333(v)28(ector)-334(then)-333(it)-333(computes)-334(2-norm)-333(as:)]TJ/F11 9.9626 Tf 101.222 -24.408 Td [(nr)-28(m)]TJ/F8 9.9626 Tf 19.499 0 Td [(2)]TJ/F14 9.9626 Tf 7.749 0 Td [(\040)]TJ 12.73 9.339 Td [(p)]TJ +ET +q +1 0 0 1 337.228 611.932 cm +[]0 d 0 J 0.398 w 0 0 m 18.944 0 l S +Q +BT +/F11 9.9626 Tf 337.228 602.394 Td [(x)]TJ/F10 6.9738 Tf 5.694 2.878 Td [(H)]TJ/F11 9.9626 Tf 7.556 -2.878 Td [(x)]TJ 0 g 0 G 0 g 0 G 0 g 0 G ET q -1 0 0 1 230.992 589.962 cm -[]0 d 0 J 0.398 w 0 0 m 183.136 0 l S +1 0 0 1 180.294 577.3 cm +[]0 d 0 J 0.398 w 0 0 m 284.534 0 l S Q BT -/F11 9.9626 Tf 236.97 581.394 Td [(A)]TJ/F27 9.9626 Tf 120.41 0 Td [(F)96(unction)]TJ +/F11 9.9626 Tf 186.271 568.732 Td [(nr)-28(m)]TJ/F8 9.9626 Tf 19.499 0 Td [(2)]TJ/F11 9.9626 Tf 81.954 0 Td [(x)]TJ/F27 9.9626 Tf 120.41 0 Td [(F)96(unction)]TJ ET q -1 0 0 1 230.992 577.608 cm -[]0 d 0 J 0.398 w 0 0 m 183.136 0 l S +1 0 0 1 180.294 564.947 cm +[]0 d 0 J 0.398 w 0 0 m 284.534 0 l S Q BT -/F8 9.9626 Tf 236.97 569.04 Td [(Short)-333(Precision)-334(Real)-3102(psb)]TJ +/F8 9.9626 Tf 186.271 556.379 Td [(Short)-333(Precision)-334(Real)-1200(Shor)1(t)-334(Precision)-333(Real)-3103(psb)]TJ ET q -1 0 0 1 372.977 569.24 cm +1 0 0 1 423.731 556.578 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 375.966 569.04 Td [(spnrm1)]TJ -138.996 -11.955 Td [(Long)-333(Precision)-334(Real)-3314(psb)]TJ +/F8 9.9626 Tf 426.72 556.379 Td [(genrm2)]TJ -240.449 -11.955 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Real)-3314(psb)]TJ ET q -1 0 0 1 372.977 557.284 cm +1 0 0 1 423.731 544.623 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 375.966 557.085 Td [(spnrm1)]TJ -138.996 -11.955 Td [(Short)-333(Precision)-334(Complex)-1200(psb)]TJ +/F8 9.9626 Tf 426.72 544.424 Td [(genrm2)]TJ -240.449 -11.956 Td [(Short)-333(Precision)-334(Real)-1200(Short)-333(Precision)-333(Complex)-1200(psb)]TJ ET q -1 0 0 1 372.977 545.329 cm +1 0 0 1 423.731 532.668 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 375.966 545.13 Td [(spnrm1)]TJ -138.996 -11.955 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ +/F8 9.9626 Tf 426.72 532.468 Td [(genrm2)]TJ -240.449 -11.955 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Complex)-1412(psb)]TJ ET q -1 0 0 1 372.977 533.374 cm +1 0 0 1 423.731 520.713 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 375.966 533.175 Td [(spnrm1)]TJ +/F8 9.9626 Tf 426.72 520.513 Td [(genrm2)]TJ ET q -1 0 0 1 230.992 529.389 cm -[]0 d 0 J 0.398 w 0 0 m 183.136 0 l S +1 0 0 1 180.294 516.727 cm +[]0 d 0 J 0.398 w 0 0 m 284.534 0 l S Q 0 g 0 G BT -/F8 9.9626 Tf 276.386 501.35 Td [(T)83(able)-333(10:)-444(Data)-334(t)28(yp)-28(es)]TJ +/F8 9.9626 Tf 278.877 488.688 Td [(T)83(able)-333(8:)-444(Data)-334(t)28(yp)-28(es)]TJ 0 g 0 G 0 g 0 G 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -125.681 -33.873 Td [(psb_spnrm1\050A,)-525(desc_a,)-525(info\051)]TJ 0 -11.956 Td [(psb_norm1\050A,)-525(desc_a,)-525(info\051)]TJ +/F30 9.9626 Tf -128.172 -39.713 Td [(psb_genrm2\050x,)-525(desc_a,)-525(info)-525([,global]\051)]TJ 0 -11.955 Td [(psb_norm2\050x,)-525(desc_a,)-525(info)-525([,global]\051)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -21.917 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf 0 -23.982 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -33.797 -22.677 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(a)]TJ + 0 -22.677 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(the)-333(global)-333(sparse)-334(matrix)]TJ/F11 9.9626 Tf 196.126 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(.)]TJ -189.242 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -167.933 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)28(o)-255(arra)28(y)-255(or)-255(an)-255(ob)-55(ject)-255(of)-255(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 135.658 0 Td [(psb)]TJ +/F30 9.9626 Tf 244.742 0 Td [(psb)]TJ ET q -1 0 0 1 327.588 346.132 cm +1 0 0 1 436.673 320.063 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 330.727 345.932 Td [(Tspmat)]TJ +/F30 9.9626 Tf 439.811 319.864 Td [(T)]TJ ET q -1 0 0 1 362.736 346.132 cm +1 0 0 1 445.669 320.063 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 365.874 345.932 Td [(type)]TJ +/F30 9.9626 Tf 448.807 319.864 Td [(vect)]TJ +ET +q +1 0 0 1 470.356 320.063 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 473.495 319.864 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(.)]TJ +/F8 9.9626 Tf -297.884 -11.956 Td [(con)28(taining)-333(n)27(um)28(b)-28(ers)-333(of)-333(t)27(yp)-27(e)-334(sp)-27(ec)-1(i)1(\014ed)-334(in)-333(T)83(able)]TJ +0 0 1 rg 0 0 1 RG + [-333(8)]TJ 0 g 0 G -/F27 9.9626 Tf -236.091 -19.925 Td [(desc)]TJ + [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.906 -22.677 Td [(desc)]TJ ET q -1 0 0 1 172.619 326.206 cm +1 0 0 1 172.619 285.431 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 176.057 326.007 Td [(a)]TJ +/F27 9.9626 Tf 176.057 285.231 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.55 0 Td [(con)28(tains)-334(data)-333(structures)-333(for)-333(c)-1(omm)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.55 0 Td [(con)28(tains)-334(data)-333(structures)-333(for)-333(c)-1(omm)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 135.659 0 Td [(psb)]TJ ET q -1 0 0 1 327.588 278.386 cm +1 0 0 1 327.588 237.61 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 330.727 278.186 Td [(desc)]TJ +/F30 9.9626 Tf 330.727 237.411 Td [(desc)]TJ ET q -1 0 0 1 352.275 278.386 cm +1 0 0 1 352.275 237.61 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 355.414 278.186 Td [(type)]TJ +/F30 9.9626 Tf 355.414 237.411 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -225.63 -19.925 Td [(On)-383(Return)]TJ -0 g 0 G -0 g 0 G - 0 -19.925 Td [(F)96(unction)-384(v)64(alue)]TJ +/F27 9.9626 Tf -225.63 -22.677 Td [(global)]TJ 0 g 0 G -/F8 9.9626 Tf 78.386 0 Td [(is)-333(the)-334(1-norm)-333(of)-333(sparse)-334(submatrix)]TJ/F11 9.9626 Tf 150.298 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(.)]TJ -211.25 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(long)-333(precision)-334(r)1(e)-1(al)-333(n)28(um)28(b)-28(er.)]TJ +/F8 9.9626 Tf 34.737 0 Td [(Sp)-28(eci\014es)-357(whether)-357(the)-357(co)-1(mpu)1(tation)-358(should)-357(include)-357(the)-357(global)-357(reduction)]TJ -9.831 -11.955 Td [(across)-333(all)-334(pro)-27(c)-1(esses.)]TJ 0 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf 40.576 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(logical)-333(scalar.)-445(Default:)]TJ/F30 9.9626 Tf 168.812 0 Td [(global=.true.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -19.926 Td [(info)]TJ +/F27 9.9626 Tf -193.718 -34.632 Td [(On)-383(Return)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ 0 g 0 G - 141.968 -56.242 Td [(42)]TJ +/F8 9.9626 Tf 166.874 -29.888 Td [(42)]TJ 0 g 0 G ET endstream endobj -1080 0 obj +1094 0 obj << -/Length 5546 +/Length 4631 >> stream 0 g 0 G 0 g 0 G +0 g 0 G BT -/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ -ET -q -1 0 0 1 120.951 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 124.986 706.129 Td [(normi)-375(|)-375(In\014nit)31(y)-375(Norm)-375(of)-375(Sparse)-375(Matrix)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-333(function)-334(computes)-333(the)-333(in\014nit)28(y-norm)-334(of)-333(a)-333(matrix)]TJ/F11 9.9626 Tf 235.673 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(:)]TJ/F11 9.9626 Tf -103.441 -33.873 Td [(nr)-28(mi)]TJ/F14 9.9626 Tf 25.698 0 Td [(\040)-278(k)]TJ/F11 9.9626 Tf 17.712 0 Td [(A)]TJ/F14 9.9626 Tf 7.472 0 Td [(k)]TJ/F13 6.9738 Tf 4.981 -1.495 Td [(1)]TJ/F8 9.9626 Tf -195.567 -20.423 Td [(where:)]TJ +/F27 9.9626 Tf 99.895 706.129 Td [(F)96(unction)-384(V)96(alue)]TJ 0 g 0 G -/F11 9.9626 Tf 0 -19.926 Td [(A)]TJ +/F8 9.9626 Tf 80.684 0 Td [(is)-333(the)-334(2-norm)-333(of)-333(sub)28(v)27(ector)]TJ/F11 9.9626 Tf 117.503 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -178.974 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.167 0 Td [(global)]TJ/F8 9.9626 Tf 32.653 0 Td [(unless)-291(the)-291(opti)1(onal)-291(v)55(ariable)]TJ/F30 9.9626 Tf 121.038 0 Td [(global=.false.)]TJ/F8 9.9626 Tf 76.122 0 Td [(as)-291(b)-28(een)-290(sp)-28(ec-)]TJ -261.98 -11.955 Td [(i\014ed)]TJ 0 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(long)-333(precision)-333(real)-334(n)28(um)28(b)-28(er.)]TJ 0 g 0 G -/F8 9.9626 Tf 12.454 0 Td [(represen)28(ts)-334(the)-333(global)-333(matrix)]TJ/F11 9.9626 Tf 125.834 0 Td [(A)]TJ +/F27 9.9626 Tf -24.907 -19.925 Td [(info)]TJ 0 g 0 G +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ 0 g 0 G +/F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ 0 g 0 G + [-500(The)-241(computation)-240(of)-241(a)-240(global)-241(result)-241(requires)-240(a)-241(global)-241(comm)28(unication,)-259(whic)28(h)]TJ 12.73 -11.955 Td [(en)28(tails)-421(a)-420(signi\014can)27(t)-420(o)28(v)27(erhead.)-706(It)-420(ma)27(y)-420(b)-28(e)-421(necessary)-420(and/or)-421(advisable)-420(to)]TJ 0 -11.955 Td [(compute)-395(m)28(ultiple)-395(norms)-395(at)-395(the)-395(same)-395(time;)-426(in)-395(this)-395(case,)-410(it)-395(is)-395(p)-28(ossible)-395(to)]TJ 0 -11.955 Td [(impro)28(v)28(e)-334(the)-333(run)28(time)-334(e\016ciency)-333(b)28(y)-334(using)-333(the)-333(follo)28(wing)-334(sc)28(heme:)]TJ 25.189 -17.933 Td [(v)-128(r)-129(e)-128(s)-259(\050)-131(1)-130(\051)-642(=)-594(p)-82(s)-83(b)]TJ ET q -1 0 0 1 181.29 589.962 cm -[]0 d 0 J 0.398 w 0 0 m 180.922 0 l S +1 0 0 1 227.381 495.12 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F11 9.9626 Tf 187.268 581.394 Td [(A)]TJ/F27 9.9626 Tf 120.409 0 Td [(F)96(unction)]TJ +/F8 9.9626 Tf 231.194 494.921 Td [(g)-83(e)-82(n)-83(r)-83(m)-82(2)-189(\050)-148(x)-43(1)-248(,)-273(d)-113(e)-113(s)-112(c)]TJ ET q -1 0 0 1 181.29 577.608 cm -[]0 d 0 J 0.398 w 0 0 m 180.922 0 l S +1 0 0 1 316.705 495.12 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 187.268 569.04 Td [(Short)-333(Precision)-333(R)-1(eal)-3102(psb)]TJ +/F8 9.9626 Tf 320.816 494.921 Td [(a)-386(,)-288(i)-127(n)-127(f)-127(o)-415(,)-302(g)-141(l)-142(o)-141(b)-141(a)-141(l)-190(=)-48(.)]TJ/F27 9.9626 Tf 92.224 0 Td [(f)-132(a)-131(l)-132(s)-131(e)]TJ/F8 9.9626 Tf 30.348 0 Td [(.)-178(\051)]TJ -293.397 -11.955 Td [(v)-128(r)-129(e)-128(s)-259(\050)-131(2)-130(\051)-642(=)-594(p)-82(s)-83(b)]TJ ET q -1 0 0 1 323.274 569.24 cm +1 0 0 1 227.381 483.165 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 326.263 569.04 Td [(spnrmi)]TJ -138.995 -11.955 Td [(Long)-333(Precision)-334(Real)-3314(p)1(s)-1(b)]TJ +/F8 9.9626 Tf 231.194 482.966 Td [(g)-83(e)-82(n)-83(r)-83(m)-82(2)-189(\050)-148(x)-43(2)-248(,)-273(d)-113(e)-113(s)-112(c)]TJ ET q -1 0 0 1 323.274 557.284 cm +1 0 0 1 316.705 483.165 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 326.263 557.085 Td [(spnrmi)]TJ -138.995 -11.955 Td [(Short)-333(Precision)-333(C)-1(omplex)-1200(p)1(s)-1(b)]TJ +/F8 9.9626 Tf 320.816 482.966 Td [(a)-386(,)-288(i)-127(n)-127(f)-127(o)-415(,)-302(g)-141(l)-142(o)-141(b)-141(a)-141(l)-190(=)-48(.)]TJ/F27 9.9626 Tf 92.224 0 Td [(f)-132(a)-131(l)-132(s)-131(e)]TJ/F8 9.9626 Tf 30.348 0 Td [(.)-178(\051)]TJ -293.397 -11.955 Td [(v)-128(r)-129(e)-128(s)-259(\050)-131(3)-130(\051)-642(=)-594(p)-82(s)-83(b)]TJ ET q -1 0 0 1 323.274 545.329 cm +1 0 0 1 227.381 471.21 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 326.263 545.13 Td [(spnrmi)]TJ -138.995 -11.955 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ +/F8 9.9626 Tf 231.194 471.011 Td [(g)-83(e)-82(n)-83(r)-83(m)-82(2)-189(\050)-148(x)-43(3)-248(,)-273(d)-113(e)-113(s)-112(c)]TJ ET q -1 0 0 1 323.274 533.374 cm +1 0 0 1 316.705 471.21 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 326.263 533.175 Td [(spnrmi)]TJ +/F8 9.9626 Tf 320.816 471.011 Td [(a)-386(,)-288(i)-127(n)-127(f)-127(o)-415(,)-302(g)-141(l)-142(o)-141(b)-141(a)-141(l)-190(=)-48(.)]TJ/F27 9.9626 Tf 92.224 0 Td [(f)-132(a)-131(l)-132(s)-131(e)]TJ/F8 9.9626 Tf 30.348 0 Td [(.)-178(\051)]TJ/F27 9.9626 Tf -293.299 -11.956 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.236 0 Td [(p)-73(s)-72(b)]TJ ET q -1 0 0 1 181.29 529.389 cm -[]0 d 0 J 0.398 w 0 0 m 180.922 0 l S +1 0 0 1 197.093 459.255 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q -0 g 0 G BT -/F8 9.9626 Tf 225.577 501.35 Td [(T)83(able)-333(11:)-444(Data)-334(t)28(yp)-28(es)]TJ +/F8 9.9626 Tf 200.806 459.055 Td [(n)-73(r)-72(m)-73(2)-178(\050)-245(i)-138(c)-139(t)-139(x)-139(t)-439(,)-290(v)-128(r)-128(e)-129(s)-293(\050)-165(1)-165(:)-165(3)-165(\051)-165(\051)]TJ 0 g 0 G 0 g 0 G + -76.004 -21.917 Td [(In)-353(this)-354(w)28(a)28(y)-354(the)-353(global)-354(comm)28(unication,)-359(whic)28(h)-353(for)-354(small)-353(sizes)-354(is)-354(a)-353(latency-)]TJ 0 -11.956 Td [(b)-28(ound)-333(op)-28(eration,)-333(is)-333(in)28(v)27(ok)28(ed)-333(only)-333(onc)-1(e.)]TJ 0 g 0 G + 141.968 -334.744 Td [(43)]TJ 0 g 0 G -/F30 9.9626 Tf -125.682 -33.873 Td [(psb_spnrmi\050A,)-525(desc_a,)-525(info\051)]TJ 0 -11.956 Td [(psb_normi\050A,)-525(desc_a,)-525(info\051)]TJ +ET + +endstream +endobj +1108 0 obj +<< +/Length 6162 +>> +stream 0 g 0 G -/F27 9.9626 Tf 0 -21.917 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ +BT +/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ +ET +q +1 0 0 1 171.761 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 175.796 706.129 Td [(genrm2s)-375(|)-375(Generalized)-375(2-Norm)-375(of)-375(V)94(ector)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-310(subroutine)-310(computes)-309(a)-310(series)-310(of)-310(2-norms)-310(on)-310(the)-309(c)-1(olu)1(m)-1(n)1(s)-310(of)-310(a)-310(dense)-310(matrix)]TJ/F11 9.9626 Tf 0 -11.956 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(:)]TJ/F11 9.9626 Tf 126.531 -11.955 Td [(r)-28(es)]TJ/F8 9.9626 Tf 14.08 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)]TJ/F14 9.9626 Tf 6.642 0 Td [(\040)-278(k)]TJ/F11 9.9626 Tf 17.711 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(\050:)]TJ/F11 9.9626 Tf 6.642 0 Td [(;)-167(i)]TJ/F8 9.9626 Tf 7.86 0 Td [(\051)]TJ/F14 9.9626 Tf 3.874 0 Td [(k)]TJ/F7 6.9738 Tf 4.981 -1.494 Td [(2)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ 0 g 0 G -0 g 0 G - 0 -19.925 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(the)-333(global)-333(sparse)-334(matrix)]TJ/F11 9.9626 Tf 196.126 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(.)]TJ -189.242 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 135.658 0 Td [(psb)]TJ -ET -q -1 0 0 1 276.779 346.132 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 279.917 345.932 Td [(Tspmat)]TJ -ET -q -1 0 0 1 311.927 346.132 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 315.065 345.932 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -236.091 -19.925 Td [(desc)]TJ -ET -q -1 0 0 1 121.81 326.206 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 125.247 326.007 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(con)28(tains)-334(d)1(ata)-334(structures)-333(for)-333(com)-1(m)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 135.658 0 Td [(psb)]TJ -ET -q -1 0 0 1 276.779 278.386 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 279.917 278.186 Td [(desc)]TJ -ET -q -1 0 0 1 301.466 278.386 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 304.604 278.186 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -225.631 -19.925 Td [(On)-383(Return)]TJ -0 g 0 G -0 g 0 G - 0 -19.925 Td [(F)96(unction)-384(v)64(alue)]TJ -0 g 0 G -/F8 9.9626 Tf 78.387 0 Td [(is)-333(the)-334(in\014ni)1(t)27(y-norm)-333(of)-333(sparse)-334(submatrix)]TJ/F11 9.9626 Tf 176.311 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(.)]TJ -237.263 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(long)-333(precision)-333(real)-334(n)28(um)28(b)-28(er.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -19.926 Td [(info)]TJ -0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ -0 g 0 G - 141.968 -56.242 Td [(43)]TJ -0 g 0 G -ET - -endstream -endobj -1092 0 obj -<< -/Length 7300 ->> -stream -0 g 0 G -0 g 0 G -BT -/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ -ET -q -1 0 0 1 171.761 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 175.796 706.129 Td [(spmm)-375(|)-375(Sparse)-375(Matrix)-375(b)31(y)-375(Dense)-375(Matrix)-375(Pro)-31(duct)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-333(subroutine)-334(computes)-333(the)-333(Sparse)-334(Matrix)-333(b)28(y)-333(Dense)-334(Matrix)-333(Pro)-28(duct:)]TJ/F11 9.9626 Tf 139.908 -23.911 Td [(y)]TJ/F14 9.9626 Tf 8.009 0 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(\013)-4(Ax)]TJ/F8 9.9626 Tf 21.79 0 Td [(+)]TJ/F11 9.9626 Tf 9.963 0 Td [(\014)-53(y)]TJ -0 g 0 G -/F8 9.9626 Tf 138.581 0 Td [(\0501\051)]TJ -0 g 0 G -/F11 9.9626 Tf -194.211 -17.408 Td [(y)]TJ/F14 9.9626 Tf 8.009 0 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(\013)-4(A)]TJ/F10 6.9738 Tf 13.882 4.113 Td [(T)]TJ/F11 9.9626 Tf 6.276 -4.113 Td [(x)]TJ/F8 9.9626 Tf 7.908 0 Td [(+)]TJ/F11 9.9626 Tf 9.963 0 Td [(\014)-53(y)]TJ -0 g 0 G -/F8 9.9626 Tf 135.443 0 Td [(\0502\051)]TJ -0 g 0 G -/F11 9.9626 Tf -194.851 -17.408 Td [(y)]TJ/F14 9.9626 Tf 8.009 0 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(\013)-4(A)]TJ/F10 6.9738 Tf 13.882 4.113 Td [(H)]TJ/F11 9.9626 Tf 7.557 -4.113 Td [(x)]TJ/F8 9.9626 Tf 7.907 0 Td [(+)]TJ/F11 9.9626 Tf 9.963 0 Td [(\014)-53(y)]TJ -0 g 0 G -/F8 9.9626 Tf 134.803 0 Td [(\0503\051)]TJ -0 g 0 G - -316.037 -17.408 Td [(where:)]TJ -0 g 0 G -/F11 9.9626 Tf -14.944 -19.226 Td [(x)]TJ -0 g 0 G -/F8 9.9626 Tf 10.675 0 Td [(is)-333(the)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 116.093 0 Td [(x)]TJ/F7 6.9738 Tf 5.694 -1.495 Td [(:)]TJ/F10 6.9738 Tf 2.255 0 Td [(;)]TJ/F7 6.9738 Tf 2.366 0 Td [(:)]TJ -0 g 0 G -/F11 9.9626 Tf -137.083 -18.081 Td [(y)]TJ -0 g 0 G -/F8 9.9626 Tf 10.223 0 Td [(is)-333(the)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 116.093 0 Td [(y)]TJ/F7 6.9738 Tf 4.884 -1.494 Td [(:)]TJ/F10 6.9738 Tf 2.256 0 Td [(;)]TJ/F7 6.9738 Tf 2.366 0 Td [(:)]TJ -0 g 0 G -/F11 9.9626 Tf -135.822 -18.081 Td [(A)]TJ -0 g 0 G -/F8 9.9626 Tf 12.453 0 Td [(is)-333(the)-334(global)-333(sparse)-333(matrix)]TJ/F11 9.9626 Tf 118.943 0 Td [(A)]TJ +/F30 9.9626 Tf -207.016 -20.424 Td [(call)-525(psb_genrm2s\050res,)-525(x,)-525(desc_a,)-525(info\051)]TJ 0 g 0 G 0 g 0 G 0 g 0 G ET q -1 0 0 1 228.797 532.215 cm -[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S +1 0 0 1 178.071 617.58 cm +[]0 d 0 J 0.398 w 0 0 m 288.979 0 l S Q BT -/F11 9.9626 Tf 234.775 523.647 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(,)]TJ/F11 9.9626 Tf 6.089 0 Td [(\013)]TJ/F8 9.9626 Tf 6.41 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(\014)]TJ/F27 9.9626 Tf 71.239 0 Td [(Subroutine)]TJ +/F11 9.9626 Tf 184.049 609.013 Td [(r)-28(es)-8770(x)]TJ/F27 9.9626 Tf 221.862 0 Td [(Subroutine)]TJ ET q -1 0 0 1 228.797 519.862 cm -[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S +1 0 0 1 178.071 605.227 cm +[]0 d 0 J 0.398 w 0 0 m 288.979 0 l S Q BT -/F8 9.9626 Tf 234.775 511.294 Td [(Short)-333(Precision)-334(Real)-3102(psb)]TJ +/F8 9.9626 Tf 184.049 596.659 Td [(Short)-333(Precision)-333(R)-1(eal)-1200(S)1(hort)-334(Precision)-333(Real)-3103(psb)]TJ ET q -1 0 0 1 370.782 511.493 cm +1 0 0 1 421.508 596.858 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 373.771 511.294 Td [(spmm)]TJ -138.996 -11.956 Td [(Long)-333(Precision)-334(Real)-3314(psb)]TJ +/F8 9.9626 Tf 424.497 596.659 Td [(genrm2s)]TJ -240.448 -11.955 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Real)-3314(psb)]TJ ET q -1 0 0 1 370.782 499.538 cm +1 0 0 1 421.508 584.903 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 373.771 499.338 Td [(spmm)]TJ -138.996 -11.955 Td [(Short)-333(Precision)-334(Complex)-1200(psb)]TJ +/F8 9.9626 Tf 424.497 584.704 Td [(genrm2s)]TJ -240.448 -11.955 Td [(Short)-333(Precision)-333(R)-1(eal)-1200(S)1(hort)-334(Precision)-333(Complex)-1200(psb)]TJ ET q -1 0 0 1 370.782 487.583 cm +1 0 0 1 421.508 572.948 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 373.771 487.383 Td [(spmm)]TJ -138.996 -11.955 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ +/F8 9.9626 Tf 424.497 572.749 Td [(genrm2s)]TJ -240.448 -11.956 Td [(Long)-333(Precision)-334(Real)-1411(Long)-333(Precision)-333(Complex)-1412(p)1(s)-1(b)]TJ ET q -1 0 0 1 370.782 475.627 cm +1 0 0 1 421.508 560.993 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 373.771 475.428 Td [(spmm)]TJ +/F8 9.9626 Tf 424.497 560.793 Td [(genrm2s)]TJ ET q -1 0 0 1 228.797 471.642 cm -[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S +1 0 0 1 178.071 557.008 cm +[]0 d 0 J 0.398 w 0 0 m 288.979 0 l S Q 0 g 0 G BT -/F8 9.9626 Tf 276.386 443.603 Td [(T)83(able)-333(12:)-444(Data)-334(t)28(yp)-28(es)]TJ -0 g 0 G +/F8 9.9626 Tf 278.877 528.968 Td [(T)83(able)-333(9:)-444(Data)-334(t)28(yp)-28(es)]TJ 0 g 0 G 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -125.681 -32.649 Td [(call)-525(psb_spmm\050alpha,)-525(a,)-525(x,)-525(beta,)-525(y,)-525(desc_a,)-525(info\051)]TJ 0 -11.955 Td [(call)-525(psb_spmm\050alpha,)-525(a,)-525(x,)-525(beta,)-525(y,desc_a,)-525(info,)-525(&)]TJ 67.994 -11.955 Td [(&)-525(trans,)-525(work\051)]TJ -0 g 0 G -/F27 9.9626 Tf -67.994 -21.044 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf -128.172 -33.596 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.575 Td [(On)-383(En)32(try)]TJ -0 g 0 G -0 g 0 G - 0 -19.576 Td [(alpha)]TJ -0 g 0 G -/F8 9.9626 Tf 32.032 0 Td [(the)-333(scalar)]TJ/F11 9.9626 Tf 45.469 0 Td [(\013)]TJ/F8 9.9626 Tf 6.41 0 Td [(.)]TJ -59.005 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(n)28(um)28(b)-28(er)-333(of)-334(the)-333(data)-333(t)27(yp)-27(e)-334(indicated)-333(in)-333(T)83(able)]TJ -0 0 1 rg 0 0 1 RG - [-333(12)]TJ -0 g 0 G - [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.906 -19.575 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.55 0 Td [(the)-333(lo)-28(cal)-334(p)-27(ortion)-333(of)-334(the)-333(sparse)-334(matri)1(x)]TJ/F11 9.9626 Tf 166.792 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(.)]TJ -159.908 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 135.659 0 Td [(psb)]TJ -ET -q -1 0 0 1 327.588 211.831 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 330.727 211.632 Td [(Tspmat)]TJ -ET -q -1 0 0 1 362.736 211.831 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 365.874 211.632 Td [(type)]TJ +/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -236.091 -19.575 Td [(x)]TJ + 0 -19.926 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -167.933 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)28(o)-255(arra)28(y)-255(or)-255(an)-255(ob)-55(ject)-255(of)-255(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -167.933 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)28(o)-255(arra)28(y)-255(or)-255(an)-255(ob)-55(ject)-255(of)-255(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 244.742 0 Td [(psb)]TJ ET q -1 0 0 1 436.673 144.435 cm +1 0 0 1 436.673 407.9 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 439.811 144.236 Td [(T)]TJ +/F30 9.9626 Tf 439.811 407.701 Td [(T)]TJ ET q -1 0 0 1 445.669 144.435 cm +1 0 0 1 445.669 407.9 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 448.807 144.236 Td [(vect)]TJ +/F30 9.9626 Tf 448.807 407.701 Td [(vect)]TJ ET q -1 0 0 1 470.356 144.435 cm +1 0 0 1 470.356 407.9 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 473.495 144.236 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf -297.884 -11.955 Td [(con)28(taining)-342(n)28(um)28(b)-28(ers)-342(of)-342(t)28(yp)-28(e)-342(sp)-28(eci\014ed)-342(in)-341(T)83(able)]TJ -0 0 1 rg 0 0 1 RG - [-342(12)]TJ -0 g 0 G - [(.)-470(The)-342(rank)-342(of)]TJ/F11 9.9626 Tf 274.695 0 Td [(x)]TJ/F8 9.9626 Tf 9.1 0 Td [(m)28(ust)-342(b)-28(e)]TJ -283.795 -11.955 Td [(the)-333(same)-334(of)]TJ/F11 9.9626 Tf 53.467 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -0 g 0 G - 83.259 -29.888 Td [(44)]TJ -0 g 0 G -ET - -endstream -endobj -1107 0 obj -<< -/Length 6992 ->> -stream -0 g 0 G -0 g 0 G -0 g 0 G -BT -/F27 9.9626 Tf 99.895 706.129 Td [(b)-32(eta)]TJ +/F30 9.9626 Tf 473.495 407.701 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 26.941 0 Td [(the)-333(scalar)]TJ/F11 9.9626 Tf 45.468 0 Td [(\014)]TJ/F8 9.9626 Tf 6.161 0 Td [(.)]TJ -53.663 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(n)28(um)28(b)-28(er)-333(of)-334(the)-333(data)-333(t)28(yp)-28(e)-334(ind)1(ic)-1(ated)-333(in)-333(T)83(able)]TJ +/F8 9.9626 Tf -297.884 -11.955 Td [(con)28(taining)-333(n)27(um)28(b)-28(ers)-333(of)-333(t)27(yp)-27(e)-334(sp)-27(ec)-1(i)1(\014ed)-334(in)-333(T)83(able)]TJ 0 0 1 rg 0 0 1 RG - [-333(12)]TJ + [-333(9)]TJ 0 g 0 G [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -18.453 Td [(y)]TJ -0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -167.481 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-55(jec)-1(t)-254(of)-255(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 244.743 0 Td [(psb)]TJ -ET -q -1 0 0 1 385.864 592.233 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 389.002 592.034 Td [(T)]TJ -ET -q -1 0 0 1 394.86 592.233 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 397.998 592.034 Td [(vect)]TJ -ET -q -1 0 0 1 419.547 592.233 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 422.685 592.034 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf -297.883 -11.955 Td [(con)28(taining)-345(n)28(um)28(b)-28(ers)-345(of)-345(t)28(yp)-28(e)-345(sp)-28(eci\014ed)-345(in)-345(T)84(able)]TJ -0 0 1 rg 0 0 1 RG - [-345(12)]TJ -0 g 0 G - [(.)-479(The)-345(rank)-345(of)]TJ/F11 9.9626 Tf 275.086 0 Td [(y)]TJ/F8 9.9626 Tf 8.678 0 Td [(m)28(ust)-345(b)-28(e)]TJ -283.764 -11.955 Td [(the)-333(same)-334(of)]TJ/F11 9.9626 Tf 53.466 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -84.067 -18.454 Td [(desc)]TJ +/F27 9.9626 Tf -24.906 -19.926 Td [(desc)]TJ ET q -1 0 0 1 121.81 549.87 cm +1 0 0 1 172.619 376.02 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 125.247 549.67 Td [(a)]TJ +/F27 9.9626 Tf 176.057 375.82 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(con)28(tains)-334(d)1(ata)-334(structures)-333(for)-333(com)-1(m)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.55 0 Td [(con)28(tains)-334(data)-333(structures)-333(for)-333(c)-1(omm)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 135.658 0 Td [(psb)]TJ +/F30 9.9626 Tf 135.659 0 Td [(psb)]TJ ET q -1 0 0 1 276.779 502.049 cm +1 0 0 1 327.588 328.199 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 279.917 501.85 Td [(desc)]TJ +/F30 9.9626 Tf 330.727 328 Td [(desc)]TJ ET q -1 0 0 1 301.466 502.049 cm +1 0 0 1 352.275 328.199 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 304.604 501.85 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -225.631 -18.454 Td [(trans)]TJ -0 g 0 G -/F8 9.9626 Tf 30.609 0 Td [(indicates)-333(what)-334(kind)-333(of)-333(op)-28(eration)-333(to)-334(p)-27(erform.)]TJ -0 g 0 G -/F27 9.9626 Tf -5.702 -18.453 Td [(trans)-383(=)-384(N)]TJ -0 g 0 G -/F8 9.9626 Tf 56.124 0 Td [(the)-333(op)-28(eration)-333(is)-334(sp)-27(e)-1(ci\014ed)-333(b)28(y)-333(equation)]TJ -0 0 1 rg 0 0 1 RG - [-334(1)]TJ -0 g 0 G +/F30 9.9626 Tf 355.414 328 Td [(type)]TJ 0 g 0 G -/F27 9.9626 Tf -56.124 -14.469 Td [(trans)-383(=)-384(T)]TJ -0 g 0 G -/F8 9.9626 Tf 55.128 0 Td [(the)-333(op)-28(eration)-333(is)-334(sp)-27(e)-1(ci\014)1(e)-1(d)-333(b)28(y)-333(equation)]TJ -0 0 1 rg 0 0 1 RG - [-334(2)]TJ -0 g 0 G -0 g 0 G -/F27 9.9626 Tf -55.128 -14.468 Td [(trans)-383(=)-384(C)]TJ -0 g 0 G -/F8 9.9626 Tf 55.432 0 Td [(the)-333(op)-28(eration)-333(is)-334(sp)-28(eci\014ed)-333(b)28(y)-333(equation)]TJ -0 0 1 rg 0 0 1 RG - [-334(3)]TJ -0 g 0 G - -55.432 -18.453 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Default:)]TJ/F11 9.9626 Tf 39.436 0 Td [(tr)-28(ans)]TJ/F8 9.9626 Tf 27.052 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(N)]TJ/F8 9.9626 Tf -77.004 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(c)28(haracter)-333(v)55(ariable.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -18.454 Td [(w)32(ork)]TJ -0 g 0 G -/F8 9.9626 Tf 29.432 0 Td [(w)28(ork)-333(arra)27(y)84(.)]TJ -4.525 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-487(as:)-753(a)-487(rank)-488(one)-487(arra)28(y)-488(of)-487(the)-488(same)-487(t)27(yp)-27(e)-488(of)]TJ/F11 9.9626 Tf 239.183 0 Td [(x)]TJ/F8 9.9626 Tf 10.55 0 Td [(and)]TJ/F11 9.9626 Tf 20.908 0 Td [(y)]TJ/F8 9.9626 Tf 10.098 0 Td [(with)-487(the)]TJ -280.739 -11.955 Td [(T)83(AR)28(GET)-333(attribute.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -18.454 Td [(On)-383(Return)]TJ +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G +/F27 9.9626 Tf -225.63 -19.926 Td [(On)-383(Return)]TJ 0 g 0 G - 0 -18.453 Td [(y)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(result)-333(matrix)]TJ/F11 9.9626 Tf 147.365 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -138.728 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-474(as:)-727(an)-475(arra)28(y)-474(of)-475(rank)-475(on)1(e)-475(or)-475(t)28(w)28(o)-475(con)28(taining)-474(n)27(u)1(m)27(b)-27(e)-1(r)1(s)-475(of)-475(t)28(yp)-28(e)]TJ 0 -11.955 Td [(sp)-28(eci\014ed)-333(in)-333(T)83(able)]TJ -0 0 1 rg 0 0 1 RG - [-333(12)]TJ + 0 -19.925 Td [(res)]TJ 0 g 0 G - [(.)]TJ +/F8 9.9626 Tf 19.47 0 Td [(con)28(tains)-334(th)1(e)-334(1-norm)-333(of)-333(\050the)-334(columns)-333(of)-78(\051)]TJ/F11 9.9626 Tf 177.75 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -178.008 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(long)-333(precision)-334(r)1(e)-1(al)-333(n)28(um)28(b)-28(er.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -18.454 Td [(info)]TJ +/F27 9.9626 Tf -24.906 -19.926 Td [(info)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(te)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ 0 g 0 G - 141.968 -38.108 Td [(45)]TJ + 141.968 -94.1 Td [(44)]TJ 0 g 0 G ET endstream endobj -1113 0 obj +1115 0 obj << -/Length 6772 +/Length 5516 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ +/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ ET q -1 0 0 1 171.761 706.328 cm +1 0 0 1 120.951 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(spsm)-375(|)-375(T)94(riangular)-375(System)-375(Solv)31(e)]TJ/F8 9.9626 Tf -25.091 -19.095 Td [(This)-333(subroutine)-334(computes)-333(the)-333(T)83(riangular)-333(System)-334(S)1(o)-1(l)1(v)27(e:)]TJ/F11 9.9626 Tf 121.692 -35.01 Td [(y)]TJ/F14 9.9626 Tf 15.205 0 Td [(\040)]TJ/F11 9.9626 Tf 19.925 0 Td [(\013)-4(T)]TJ/F13 6.9738 Tf 13.616 4.113 Td [(\000)]TJ/F7 6.9738 Tf 6.226 0 Td [(1)]TJ/F11 9.9626 Tf 4.47 -4.113 Td [(x)]TJ/F8 9.9626 Tf 7.907 0 Td [(+)]TJ/F11 9.9626 Tf 9.963 0 Td [(\014)-53(y)]TJ -77.312 -14.944 Td [(y)]TJ/F14 9.9626 Tf 15.205 0 Td [(\040)]TJ/F11 9.9626 Tf 19.925 0 Td [(\013)-4(D)-27(T)]TJ/F13 6.9738 Tf 22.141 4.113 Td [(\000)]TJ/F7 6.9738 Tf 6.226 0 Td [(1)]TJ/F11 9.9626 Tf 4.47 -4.113 Td [(x)]TJ/F8 9.9626 Tf 7.907 0 Td [(+)]TJ/F11 9.9626 Tf 9.963 0 Td [(\014)-53(y)]TJ -85.837 -14.944 Td [(y)]TJ/F14 9.9626 Tf 15.205 0 Td [(\040)]TJ/F11 9.9626 Tf 19.925 0 Td [(\013)-4(T)]TJ/F13 6.9738 Tf 13.616 4.113 Td [(\000)]TJ/F7 6.9738 Tf 6.226 0 Td [(1)]TJ/F11 9.9626 Tf 4.47 -4.113 Td [(D)-28(x)]TJ/F8 9.9626 Tf 16.432 0 Td [(+)]TJ/F11 9.9626 Tf 9.963 0 Td [(\014)-53(y)]TJ -85.837 -14.944 Td [(y)]TJ/F14 9.9626 Tf 15.205 0 Td [(\040)]TJ/F11 9.9626 Tf 19.925 0 Td [(\013)-4(T)]TJ/F13 6.9738 Tf 13.616 4.113 Td [(\000)]TJ/F10 6.9738 Tf 6.226 0 Td [(T)]TJ/F11 9.9626 Tf 6.276 -4.113 Td [(x)]TJ/F8 9.9626 Tf 7.908 0 Td [(+)]TJ/F11 9.9626 Tf 9.963 0 Td [(\014)-53(y)]TJ -79.119 -14.944 Td [(y)]TJ/F14 9.9626 Tf 15.205 0 Td [(\040)]TJ/F11 9.9626 Tf 19.925 0 Td [(\013)-4(D)-27(T)]TJ/F13 6.9738 Tf 22.141 4.113 Td [(\000)]TJ/F10 6.9738 Tf 6.226 0 Td [(T)]TJ/F11 9.9626 Tf 6.276 -4.113 Td [(x)]TJ/F8 9.9626 Tf 7.908 0 Td [(+)]TJ/F11 9.9626 Tf 9.963 0 Td [(\014)-53(y)]TJ -87.644 -14.944 Td [(y)]TJ/F14 9.9626 Tf 15.205 0 Td [(\040)]TJ/F11 9.9626 Tf 19.925 0 Td [(\013)-4(T)]TJ/F13 6.9738 Tf 13.616 4.113 Td [(\000)]TJ/F10 6.9738 Tf 6.226 0 Td [(T)]TJ/F11 9.9626 Tf 6.276 -4.113 Td [(D)-28(x)]TJ/F8 9.9626 Tf 16.433 0 Td [(+)]TJ/F11 9.9626 Tf 9.963 0 Td [(\014)-53(y)]TJ -87.644 -14.944 Td [(y)]TJ/F14 9.9626 Tf 15.205 0 Td [(\040)]TJ/F11 9.9626 Tf 19.925 0 Td [(\013)-4(T)]TJ/F13 6.9738 Tf 13.616 4.113 Td [(\000)]TJ/F10 6.9738 Tf 6.226 0 Td [(H)]TJ/F11 9.9626 Tf 7.557 -4.113 Td [(x)]TJ/F8 9.9626 Tf 7.907 0 Td [(+)]TJ/F11 9.9626 Tf 9.963 0 Td [(\014)-53(y)]TJ -80.399 -14.944 Td [(y)]TJ/F14 9.9626 Tf 15.205 0 Td [(\040)]TJ/F11 9.9626 Tf 19.925 0 Td [(\013)-4(D)-27(T)]TJ/F13 6.9738 Tf 22.141 4.113 Td [(\000)]TJ/F10 6.9738 Tf 6.226 0 Td [(H)]TJ/F11 9.9626 Tf 7.557 -4.113 Td [(x)]TJ/F8 9.9626 Tf 7.907 0 Td [(+)]TJ/F11 9.9626 Tf 9.963 0 Td [(\014)-53(y)]TJ -88.924 -14.944 Td [(y)]TJ/F14 9.9626 Tf 15.205 0 Td [(\040)]TJ/F11 9.9626 Tf 19.925 0 Td [(\013)-4(T)]TJ/F13 6.9738 Tf 13.616 4.113 Td [(\000)]TJ/F10 6.9738 Tf 6.226 0 Td [(H)]TJ/F11 9.9626 Tf 7.557 -4.113 Td [(D)-28(x)]TJ/F8 9.9626 Tf 16.432 0 Td [(+)]TJ/F11 9.9626 Tf 9.963 0 Td [(\014)-53(y)]TJ/F8 9.9626 Tf -195.672 -37.999 Td [(where:)]TJ -0 g 0 G -/F11 9.9626 Tf -14.944 -21.063 Td [(x)]TJ -0 g 0 G -/F8 9.9626 Tf 10.675 0 Td [(is)-333(the)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 116.093 0 Td [(x)]TJ/F7 6.9738 Tf 5.694 -1.494 Td [(:)]TJ/F10 6.9738 Tf 2.255 0 Td [(;)]TJ/F7 6.9738 Tf 2.366 0 Td [(:)]TJ -0 g 0 G -/F11 9.9626 Tf -137.083 -19.948 Td [(y)]TJ -0 g 0 G -/F8 9.9626 Tf 10.223 0 Td [(is)-333(the)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 116.093 0 Td [(y)]TJ/F7 6.9738 Tf 4.884 -1.494 Td [(:)]TJ/F10 6.9738 Tf 2.256 0 Td [(;)]TJ/F7 6.9738 Tf 2.366 0 Td [(:)]TJ -0 g 0 G -/F11 9.9626 Tf -135.822 -19.948 Td [(T)]TJ -0 g 0 G -/F8 9.9626 Tf 12.187 0 Td [(is)-333(the)-334(global)-333(sparse)-333(blo)-28(c)28(k)-334(triangul)1(a)-1(r)-333(submatrix)]TJ/F11 9.9626 Tf 206.78 0 Td [(T)]TJ -0 g 0 G - -218.967 -21.441 Td [(D)]TJ -0 g 0 G -/F8 9.9626 Tf 13.506 0 Td [(is)-333(the)-334(scaling)-333(diagonal)-333(matrix.)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(norm1)-375(|)-375(1-Norm)-375(of)-375(Sparse)-375(Matrix)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-333(function)-334(computes)-333(the)-333(1-norm)-334(of)-333(a)-333(matrix)]TJ/F11 9.9626 Tf 209.659 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(:)]TJ/F11 9.9626 Tf -76.216 -33.873 Td [(nr)-28(m)]TJ/F8 9.9626 Tf 19.499 0 Td [(1)]TJ/F14 9.9626 Tf 7.749 0 Td [(\040)-278(k)]TJ/F11 9.9626 Tf 17.711 0 Td [(A)]TJ/F14 9.9626 Tf 7.472 0 Td [(k)]TJ/F7 6.9738 Tf 4.981 -1.495 Td [(1)]TJ/F8 9.9626 Tf -198.327 -20.423 Td [(where:)]TJ 0 g 0 G +/F11 9.9626 Tf 0 -19.926 Td [(A)]TJ 0 g 0 G -/F30 9.9626 Tf -13.506 -23.814 Td [(call)-525(psb_spsm\050alpha,)-525(t,)-525(x,)-525(beta,)-525(y,)-525(desc_a,)-525(info\051)]TJ 0 -11.955 Td [(call)-525(psb_spsm\050alpha,)-525(t,)-525(x,)-525(beta,)-525(y,)-525(desc_a,)-525(info,&)]TJ 67.994 -11.955 Td [(&)-525(trans,)-525(unit,)-525(choice,)-525(diag,)-525(work\051)]TJ +/F8 9.9626 Tf 12.454 0 Td [(represen)28(ts)-334(the)-333(global)-333(matrix)]TJ/F11 9.9626 Tf 125.834 0 Td [(A)]TJ 0 g 0 G 0 g 0 G 0 g 0 G ET q -1 0 0 1 228.797 335.134 cm -[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S +1 0 0 1 180.183 589.962 cm +[]0 d 0 J 0.398 w 0 0 m 183.136 0 l S Q BT -/F11 9.9626 Tf 234.775 326.566 Td [(T)]TJ/F8 9.9626 Tf 7.206 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(D)]TJ/F8 9.9626 Tf 8.525 0 Td [(,)]TJ/F11 9.9626 Tf 6.089 0 Td [(\013)]TJ/F8 9.9626 Tf 6.41 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(\014)]TJ/F27 9.9626 Tf 56.892 0 Td [(Subroutine)]TJ +/F11 9.9626 Tf 186.161 581.394 Td [(A)]TJ/F27 9.9626 Tf 120.409 0 Td [(F)96(unction)]TJ ET q -1 0 0 1 228.797 322.78 cm -[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S +1 0 0 1 180.183 577.608 cm +[]0 d 0 J 0.398 w 0 0 m 183.136 0 l S Q BT -/F8 9.9626 Tf 234.775 314.213 Td [(Short)-333(Precision)-334(Real)-3102(psb)]TJ +/F8 9.9626 Tf 186.161 569.04 Td [(Short)-333(Precision)-334(Real)-3102(psb)]TJ ET q -1 0 0 1 370.782 314.412 cm +1 0 0 1 322.167 569.24 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 373.771 314.213 Td [(spsm)]TJ -138.996 -11.956 Td [(Long)-333(Precision)-334(Real)-3314(psb)]TJ +/F8 9.9626 Tf 325.156 569.04 Td [(spnrm1)]TJ -138.995 -11.955 Td [(Long)-333(Precision)-334(Real)-3314(p)1(s)-1(b)]TJ ET q -1 0 0 1 370.782 302.457 cm +1 0 0 1 322.167 557.284 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 373.771 302.257 Td [(spsm)]TJ -138.996 -11.955 Td [(Short)-333(Precision)-334(Complex)-1200(psb)]TJ +/F8 9.9626 Tf 325.156 557.085 Td [(spnrm1)]TJ -138.995 -11.955 Td [(Short)-333(Precision)-334(Complex)-1200(psb)]TJ ET q -1 0 0 1 370.782 290.501 cm +1 0 0 1 322.167 545.329 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 373.771 290.302 Td [(spsm)]TJ -138.996 -11.955 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ +/F8 9.9626 Tf 325.156 545.13 Td [(spnrm1)]TJ -138.995 -11.955 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ ET q -1 0 0 1 370.782 278.546 cm +1 0 0 1 322.167 533.374 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 373.771 278.347 Td [(spsm)]TJ +/F8 9.9626 Tf 325.156 533.175 Td [(spnrm1)]TJ ET q -1 0 0 1 228.797 274.561 cm -[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S +1 0 0 1 180.183 529.389 cm +[]0 d 0 J 0.398 w 0 0 m 183.136 0 l S Q 0 g 0 G BT -/F8 9.9626 Tf 276.386 246.522 Td [(T)83(able)-333(13:)-444(Data)-334(t)28(yp)-28(es)]TJ +/F8 9.9626 Tf 225.577 501.35 Td [(T)83(able)-333(10:)-444(Data)-334(t)28(yp)-28(es)]TJ 0 g 0 G 0 g 0 G 0 g 0 G -/F27 9.9626 Tf -125.681 -35.492 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ -0 g 0 G -/F27 9.9626 Tf -33.797 -21.442 Td [(On)-383(En)32(try)]TJ +/F30 9.9626 Tf -125.682 -33.873 Td [(psb_spnrm1\050A,)-525(desc_a,)-525(info\051)]TJ 0 -11.956 Td [(psb_norm1\050A,)-525(desc_a,)-525(info\051)]TJ 0 g 0 G +/F27 9.9626 Tf 0 -21.917 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G - 0 -21.442 Td [(alpha)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G -/F8 9.9626 Tf 32.032 0 Td [(the)-333(scalar)]TJ/F11 9.9626 Tf 45.469 0 Td [(\013)]TJ/F8 9.9626 Tf 6.41 0 Td [(.)]TJ -59.005 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(n)28(um)28(b)-28(er)-333(of)-334(the)-333(data)-333(t)27(yp)-27(e)-334(indicated)-333(in)-333(T)83(able)]TJ -0 0 1 rg 0 0 1 RG - [-333(13)]TJ +/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ 0 g 0 G - [(.)]TJ 0 g 0 G - 141.968 -29.888 Td [(46)]TJ + 0 -19.925 Td [(a)]TJ 0 g 0 G +/F8 9.9626 Tf 10.551 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(the)-333(global)-333(sparse)-334(matrix)]TJ/F11 9.9626 Tf 196.126 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(.)]TJ -189.242 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 135.658 0 Td [(psb)]TJ ET - -endstream -endobj -1011 0 obj -<< -/Type /ObjStm +q +1 0 0 1 276.779 346.132 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 279.917 345.932 Td [(Tspmat)]TJ +ET +q +1 0 0 1 311.927 346.132 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 315.065 345.932 Td [(type)]TJ +0 g 0 G +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -236.091 -19.925 Td [(desc)]TJ +ET +q +1 0 0 1 121.81 326.206 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 125.247 326.007 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.551 0 Td [(con)28(tains)-334(d)1(ata)-334(structures)-333(for)-333(com)-1(m)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 135.658 0 Td [(psb)]TJ +ET +q +1 0 0 1 276.779 278.386 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 279.917 278.186 Td [(desc)]TJ +ET +q +1 0 0 1 301.466 278.386 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 304.604 278.186 Td [(type)]TJ +0 g 0 G +/F8 9.9626 Tf 20.922 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -225.631 -19.925 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(F)96(unction)-384(v)64(alue)]TJ +0 g 0 G +/F8 9.9626 Tf 78.387 0 Td [(is)-333(the)-334(1-norm)-333(of)-333(sparse)-334(submatrix)]TJ/F11 9.9626 Tf 150.297 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(.)]TJ -211.249 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(long)-333(precision)-333(real)-334(n)28(um)28(b)-28(er.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.926 Td [(info)]TJ +0 g 0 G +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ +0 g 0 G + 141.968 -56.242 Td [(45)]TJ +0 g 0 G +ET + +endstream +endobj +1011 0 obj +<< +/Type /ObjStm /N 100 -/First 988 -/Length 12372 +/First 980 +/Length 11075 >> stream -1003 0 1004 146 1005 293 1009 438 220 496 1010 553 1006 612 1013 757 1015 874 1012 933 -1020 1013 1016 1169 1017 1313 1018 1459 1022 1606 224 1664 1023 1721 1019 1780 1028 1925 1024 2081 -1025 2225 1026 2371 1030 2517 228 2576 1031 2634 1027 2693 1036 2838 1032 2995 1033 3139 1034 3285 -1038 3432 232 3490 1039 3547 1035 3606 1045 3763 1041 3920 1042 4063 1043 4208 1047 4354 236 4413 -1048 4471 1044 4530 1050 4687 1052 4805 1049 4863 1057 4943 1053 5100 1054 5244 1055 5390 1059 5537 -240 5596 1060 5654 1056 5713 1065 5858 1061 6015 1062 6159 1063 6304 1067 6451 244 6509 1068 6566 -1064 6625 1072 6769 1069 6917 1070 7062 1074 7209 248 7268 1075 7326 1071 7385 1079 7529 1076 7677 -1077 7822 1081 7969 252 8027 1083 8084 1078 8143 1091 8289 1085 8455 1086 8602 1087 8747 1088 8891 -1093 9038 256 9097 1094 9155 1095 9214 1096 9273 1097 9332 1090 9391 1106 9548 1089 9750 1098 9897 -1099 10041 1100 10188 1101 10335 1102 10486 1103 10637 1104 10788 1108 10935 1105 10993 1112 11099 1109 11238 -% 1003 0 obj +1007 0 1008 58 1009 117 1010 175 1001 234 1019 353 1012 536 1013 680 1014 825 1015 969 +1016 1115 1017 1262 1021 1407 220 1465 1022 1522 1018 1581 1024 1726 1026 1843 1023 1902 1031 1982 +1027 2138 1028 2281 1029 2426 1033 2573 224 2631 1034 2688 1030 2746 1036 2891 1038 3008 1039 3067 +1040 3126 1041 3185 1042 3244 1043 3303 1044 3362 1035 3421 1049 3540 1045 3697 1046 3841 1047 3987 +1051 4133 228 4191 1052 4248 1048 4307 1058 4452 1054 4609 1055 4753 1056 4899 1060 5046 232 5105 +1061 5163 1057 5222 1063 5379 1065 5497 1066 5555 1067 5613 1068 5671 1069 5730 1070 5789 1071 5848 +1062 5907 1076 6000 1072 6157 1073 6300 1074 6445 1078 6591 236 6650 1079 6708 1075 6767 1081 6924 +1083 7042 1080 7100 1088 7180 1084 7337 1085 7481 1086 7627 1090 7774 240 7833 1091 7891 1087 7950 +1093 8095 1095 8213 1096 8271 1097 8329 1098 8387 1099 8446 1100 8505 1101 8564 1092 8623 1107 8742 +1103 8899 1104 9043 1105 9188 1109 9335 244 9394 1110 9452 1106 9511 1114 9655 1111 9803 1112 9948 +% 1007 0 obj +<< +/D [1002 0 R /XYZ 175.611 455.07 null] +>> +% 1008 0 obj +<< +/D [1002 0 R /XYZ 175.611 443.115 null] +>> +% 1009 0 obj +<< +/D [1002 0 R /XYZ 175.611 431.16 null] +>> +% 1010 0 obj +<< +/D [1002 0 R /XYZ 175.611 419.205 null] +>> +% 1001 0 obj +<< +/Font << /F8 561 0 R /F27 560 0 R /F30 769 0 R /F11 755 0 R /F16 558 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1019 0 obj +<< +/Type /Page +/Contents 1020 0 R +/Resources 1018 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 999 0 R +/Annots [ 1012 0 R 1013 0 R 1014 0 R 1015 0 R 1016 0 R 1017 0 R ] +>> +% 1012 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [368.549 382.111 444.603 393.236] +/A << /S /GoTo /D (vdata) >> +>> +% 1013 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [328.333 370.432 335.307 381.28] +/A << /S /GoTo /D (table.3) >> +>> +% 1014 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [368.549 291.951 444.603 303.076] +/A << /S /GoTo /D (vdata) >> +>> +% 1015 0 obj << /Type /Annot /Subtype /Link @@ -10796,7 +10562,7 @@ stream /Rect [328.544 280.273 335.518 291.121] /A << /S /GoTo /D (table.3) >> >> -% 1004 0 obj +% 1016 0 obj << /Type /Annot /Subtype /Link @@ -10804,7 +10570,7 @@ stream /Rect [259.464 201.792 326.522 212.917] /A << /S /GoTo /D (descdata) >> >> -% 1005 0 obj +% 1017 0 obj << /Type /Annot /Subtype /Link @@ -10812,200 +10578,282 @@ stream /Rect [151.203 119.329 158.177 128.24] /A << /S /GoTo /D (table.2) >> >> -% 1009 0 obj +% 1021 0 obj << -/D [1007 0 R /XYZ 98.895 753.953 null] +/D [1019 0 R /XYZ 98.895 753.953 null] >> % 220 0 obj << -/D [1007 0 R /XYZ 99.895 720.077 null] +/D [1019 0 R /XYZ 99.895 720.077 null] >> -% 1010 0 obj +% 1022 0 obj << -/D [1007 0 R /XYZ 267.641 510.309 null] +/D [1019 0 R /XYZ 267.641 510.309 null] >> -% 1006 0 obj +% 1018 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F11 750 0 R /F14 767 0 R /F10 766 0 R /F30 764 0 R /F27 556 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F11 755 0 R /F14 772 0 R /F10 771 0 R /F30 769 0 R /F27 560 0 R >> /ProcSet [ /PDF /Text ] >> -% 1013 0 obj +% 1024 0 obj << /Type /Page -/Contents 1014 0 R -/Resources 1012 0 R +/Contents 1025 0 R +/Resources 1023 0 R /MediaBox [0 0 595.276 841.89] -/Parent 995 0 R +/Parent 999 0 R >> -% 1015 0 obj +% 1026 0 obj << -/D [1013 0 R /XYZ 149.705 753.953 null] +/D [1024 0 R /XYZ 149.705 753.953 null] >> -% 1012 0 obj +% 1023 0 obj << -/Font << /F27 556 0 R /F8 557 0 R >> +/Font << /F27 560 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 1020 0 obj +% 1031 0 obj << /Type /Page -/Contents 1021 0 R -/Resources 1019 0 R +/Contents 1032 0 R +/Resources 1030 0 R /MediaBox [0 0 595.276 841.89] -/Parent 995 0 R -/Annots [ 1016 0 R 1017 0 R 1018 0 R ] +/Parent 999 0 R +/Annots [ 1027 0 R 1028 0 R 1029 0 R ] >> -% 1016 0 obj +% 1027 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [368.549 338.197 444.603 349.322] +/Rect [368.549 315.41 444.603 326.535] /A << /S /GoTo /D (vdata) >> >> -% 1017 0 obj +% 1028 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [325.411 326.519 332.385 337.367] +/Rect [325.411 303.732 332.385 314.58] /A << /S /GoTo /D (table.4) >> >> -% 1018 0 obj +% 1029 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [259.464 258.808 326.522 269.933] +/Rect [259.464 233.372 326.522 244.497] /A << /S /GoTo /D (descdata) >> >> -% 1022 0 obj +% 1033 0 obj << -/D [1020 0 R /XYZ 98.895 753.953 null] +/D [1031 0 R /XYZ 98.895 753.953 null] >> % 224 0 obj << -/D [1020 0 R /XYZ 99.895 720.077 null] +/D [1031 0 R /XYZ 99.895 720.077 null] >> -% 1023 0 obj +% 1034 0 obj << -/D [1020 0 R /XYZ 267.641 472.916 null] +/D [1031 0 R /XYZ 267.641 459.44 null] >> -% 1019 0 obj +% 1030 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F11 750 0 R /F14 767 0 R /F10 766 0 R /F30 764 0 R /F27 556 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F11 755 0 R /F14 772 0 R /F10 771 0 R /F30 769 0 R /F27 560 0 R >> /ProcSet [ /PDF /Text ] >> -% 1028 0 obj +% 1036 0 obj << /Type /Page -/Contents 1029 0 R -/Resources 1027 0 R +/Contents 1037 0 R +/Resources 1035 0 R /MediaBox [0 0 595.276 841.89] -/Parent 995 0 R -/Annots [ 1024 0 R 1025 0 R 1026 0 R ] +/Parent 999 0 R >> -% 1024 0 obj +% 1038 0 obj +<< +/D [1036 0 R /XYZ 149.705 753.953 null] +>> +% 1039 0 obj +<< +/D [1036 0 R /XYZ 150.705 576.615 null] +>> +% 1040 0 obj +<< +/D [1036 0 R /XYZ 150.705 516.894 null] +>> +% 1041 0 obj +<< +/D [1036 0 R /XYZ 175.611 518.831 null] +>> +% 1042 0 obj +<< +/D [1036 0 R /XYZ 175.611 506.876 null] +>> +% 1043 0 obj +<< +/D [1036 0 R /XYZ 175.611 494.921 null] +>> +% 1044 0 obj +<< +/D [1036 0 R /XYZ 175.611 482.966 null] +>> +% 1035 0 obj +<< +/Font << /F27 560 0 R /F8 561 0 R /F11 755 0 R /F30 769 0 R /F16 558 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1049 0 obj +<< +/Type /Page +/Contents 1050 0 R +/Resources 1048 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1053 0 R +/Annots [ 1045 0 R 1046 0 R 1047 0 R ] +>> +% 1045 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [419.358 401.031 495.412 412.156] +/Rect [368.549 401.031 444.603 412.156] /A << /S /GoTo /D (vdata) >> >> -% 1025 0 obj +% 1046 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [376.221 389.353 383.195 400.201] +/Rect [325.411 389.353 332.385 400.201] /A << /S /GoTo /D (table.5) >> >> -% 1026 0 obj +% 1047 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [310.273 321.33 377.331 332.455] +/Rect [259.464 321.33 326.522 332.455] /A << /S /GoTo /D (descdata) >> >> -% 1030 0 obj +% 1051 0 obj << -/D [1028 0 R /XYZ 149.705 753.953 null] +/D [1049 0 R /XYZ 98.895 753.953 null] >> % 228 0 obj << -/D [1028 0 R /XYZ 150.705 720.077 null] +/D [1049 0 R /XYZ 99.895 720.077 null] >> -% 1031 0 obj +% 1052 0 obj << -/D [1028 0 R /XYZ 318.451 537.464 null] +/D [1049 0 R /XYZ 267.641 537.464 null] >> -% 1027 0 obj +% 1048 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F11 750 0 R /F14 767 0 R /F10 766 0 R /F30 764 0 R /F27 556 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F11 755 0 R /F14 772 0 R /F10 771 0 R /F30 769 0 R /F27 560 0 R >> /ProcSet [ /PDF /Text ] >> -% 1036 0 obj +% 1058 0 obj << /Type /Page -/Contents 1037 0 R -/Resources 1035 0 R +/Contents 1059 0 R +/Resources 1057 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1040 0 R -/Annots [ 1032 0 R 1033 0 R 1034 0 R ] +/Parent 1053 0 R +/Annots [ 1054 0 R 1055 0 R 1056 0 R ] >> -% 1032 0 obj +% 1054 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [368.549 339.844 444.603 350.969] +/Rect [419.358 359.763 495.412 370.887] /A << /S /GoTo /D (vdata) >> >> -% 1033 0 obj +% 1055 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [325.411 328.166 332.385 339.014] +/Rect [376.221 348.084 383.195 358.932] /A << /S /GoTo /D (table.6) >> >> -% 1034 0 obj +% 1056 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [259.464 260.202 326.522 271.327] +/Rect [310.273 281.168 377.331 292.293] /A << /S /GoTo /D (descdata) >> >> -% 1038 0 obj +% 1060 0 obj << -/D [1036 0 R /XYZ 98.895 753.953 null] +/D [1058 0 R /XYZ 149.705 753.953 null] >> % 232 0 obj << -/D [1036 0 R /XYZ 99.895 720.077 null] +/D [1058 0 R /XYZ 150.705 720.077 null] >> -% 1039 0 obj +% 1061 0 obj << -/D [1036 0 R /XYZ 267.641 475.957 null] +/D [1058 0 R /XYZ 318.451 490.109 null] >> -% 1035 0 obj +% 1057 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F11 750 0 R /F14 767 0 R /F10 766 0 R /F7 765 0 R /F30 764 0 R /F27 556 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F11 755 0 R /F14 772 0 R /F10 771 0 R /F7 770 0 R /F30 769 0 R /F27 560 0 R >> /ProcSet [ /PDF /Text ] >> -% 1045 0 obj +% 1063 0 obj << /Type /Page -/Contents 1046 0 R -/Resources 1044 0 R +/Contents 1064 0 R +/Resources 1062 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1040 0 R -/Annots [ 1041 0 R 1042 0 R 1043 0 R ] +/Parent 1053 0 R >> -% 1041 0 obj +% 1065 0 obj +<< +/D [1063 0 R /XYZ 98.895 753.953 null] +>> +% 1066 0 obj +<< +/D [1063 0 R /XYZ 99.895 632.405 null] +>> +% 1067 0 obj +<< +/D [1063 0 R /XYZ 99.895 572.685 null] +>> +% 1068 0 obj +<< +/D [1063 0 R /XYZ 124.802 574.622 null] +>> +% 1069 0 obj +<< +/D [1063 0 R /XYZ 124.802 562.667 null] +>> +% 1070 0 obj +<< +/D [1063 0 R /XYZ 124.802 550.712 null] +>> +% 1071 0 obj +<< +/D [1063 0 R /XYZ 124.802 538.757 null] +>> +% 1062 0 obj +<< +/Font << /F27 560 0 R /F8 561 0 R /F16 558 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1076 0 obj +<< +/Type /Page +/Contents 1077 0 R +/Resources 1075 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1053 0 R +/Annots [ 1072 0 R 1073 0 R 1074 0 R ] +>> +% 1072 0 obj << /Type /Annot /Subtype /Link @@ -11013,7 +10861,7 @@ stream /Rect [419.358 289.84 495.412 300.965] /A << /S /GoTo /D (vdata) >> >> -% 1042 0 obj +% 1073 0 obj << /Type /Annot /Subtype /Link @@ -11021,7 +10869,7 @@ stream /Rect [376.221 278.162 383.195 289.01] /A << /S /GoTo /D (table.7) >> >> -% 1043 0 obj +% 1074 0 obj << /Type /Annot /Subtype /Link @@ -11029,1063 +10877,671 @@ stream /Rect [310.273 208.355 377.331 219.48] /A << /S /GoTo /D (descdata) >> >> -% 1047 0 obj +% 1078 0 obj << -/D [1045 0 R /XYZ 149.705 753.953 null] +/D [1076 0 R /XYZ 149.705 753.953 null] >> % 236 0 obj << -/D [1045 0 R /XYZ 150.705 720.077 null] +/D [1076 0 R /XYZ 150.705 720.077 null] >> -% 1048 0 obj +% 1079 0 obj << -/D [1045 0 R /XYZ 318.451 432.072 null] +/D [1076 0 R /XYZ 318.451 432.072 null] >> -% 1044 0 obj +% 1075 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F11 750 0 R /F14 767 0 R /F10 766 0 R /F7 765 0 R /F30 764 0 R /F27 556 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F11 755 0 R /F14 772 0 R /F10 771 0 R /F7 770 0 R /F30 769 0 R /F27 560 0 R >> /ProcSet [ /PDF /Text ] >> -% 1050 0 obj +% 1081 0 obj << /Type /Page -/Contents 1051 0 R -/Resources 1049 0 R +/Contents 1082 0 R +/Resources 1080 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1040 0 R +/Parent 1053 0 R >> -% 1052 0 obj +% 1083 0 obj << -/D [1050 0 R /XYZ 98.895 753.953 null] +/D [1081 0 R /XYZ 98.895 753.953 null] >> -% 1049 0 obj +% 1080 0 obj << -/Font << /F27 556 0 R /F8 557 0 R >> +/Font << /F27 560 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 1057 0 obj +% 1088 0 obj << /Type /Page -/Contents 1058 0 R -/Resources 1056 0 R +/Contents 1089 0 R +/Resources 1087 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1040 0 R -/Annots [ 1053 0 R 1054 0 R 1055 0 R ] +/Parent 1053 0 R +/Annots [ 1084 0 R 1085 0 R 1086 0 R ] >> -% 1053 0 obj +% 1084 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [419.358 348.184 495.412 359.309] +/Rect [419.358 316.653 495.412 327.778] /A << /S /GoTo /D (vdata) >> >> -% 1054 0 obj +% 1085 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [376.221 336.506 383.195 347.354] +/Rect [376.221 304.975 383.195 315.823] /A << /S /GoTo /D (table.8) >> >> -% 1055 0 obj +% 1086 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [310.273 269.097 377.331 280.222] +/Rect [310.273 234.201 377.331 245.325] /A << /S /GoTo /D (descdata) >> >> -% 1059 0 obj +% 1090 0 obj << -/D [1057 0 R /XYZ 149.705 753.953 null] +/D [1088 0 R /XYZ 149.705 753.953 null] >> % 240 0 obj << -/D [1057 0 R /XYZ 150.705 720.077 null] +/D [1088 0 R /XYZ 150.705 720.077 null] >> -% 1060 0 obj +% 1091 0 obj << -/D [1057 0 R /XYZ 318.451 515.563 null] +/D [1088 0 R /XYZ 318.451 500.643 null] >> -% 1056 0 obj +% 1087 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F11 750 0 R /F14 767 0 R /F10 766 0 R /F27 556 0 R /F30 764 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F11 755 0 R /F14 772 0 R /F10 771 0 R /F27 560 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 1065 0 obj +% 1093 0 obj << /Type /Page -/Contents 1066 0 R -/Resources 1064 0 R +/Contents 1094 0 R +/Resources 1092 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1040 0 R -/Annots [ 1061 0 R 1062 0 R 1063 0 R ] +/Parent 1102 0 R >> -% 1061 0 obj +% 1095 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [368.549 404.491 444.603 415.616] -/A << /S /GoTo /D (vdata) >> ->> -% 1062 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [325.411 392.812 332.385 403.66] -/A << /S /GoTo /D (table.9) >> ->> -% 1063 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [259.464 324.789 326.522 335.914] -/A << /S /GoTo /D (descdata) >> ->> -% 1067 0 obj -<< -/D [1065 0 R /XYZ 98.895 753.953 null] ->> -% 244 0 obj -<< -/D [1065 0 R /XYZ 99.895 720.077 null] ->> -% 1068 0 obj -<< -/D [1065 0 R /XYZ 267.641 540.923 null] ->> -% 1064 0 obj -<< -/Font << /F16 554 0 R /F8 557 0 R /F11 750 0 R /F14 767 0 R /F7 765 0 R /F30 764 0 R /F27 556 0 R >> -/ProcSet [ /PDF /Text ] ->> -% 1072 0 obj -<< -/Type /Page -/Contents 1073 0 R -/Resources 1071 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1040 0 R -/Annots [ 1069 0 R 1070 0 R ] ->> -% 1069 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [310.273 342.722 387.792 353.847] -/A << /S /GoTo /D (spdata) >> ->> -% 1070 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [310.273 274.976 377.331 286.101] -/A << /S /GoTo /D (descdata) >> ->> -% 1074 0 obj -<< -/D [1072 0 R /XYZ 149.705 753.953 null] ->> -% 248 0 obj -<< -/D [1072 0 R /XYZ 150.705 720.077 null] ->> -% 1075 0 obj -<< -/D [1072 0 R /XYZ 320.941 513.305 null] ->> -% 1071 0 obj -<< -/Font << /F16 554 0 R /F8 557 0 R /F11 750 0 R /F14 767 0 R /F7 765 0 R /F27 556 0 R /F30 764 0 R >> -/ProcSet [ /PDF /Text ] +/D [1093 0 R /XYZ 98.895 753.953 null] >> -% 1079 0 obj +% 1096 0 obj << -/Type /Page -/Contents 1080 0 R -/Resources 1078 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1084 0 R -/Annots [ 1076 0 R 1077 0 R ] +/D [1093 0 R /XYZ 99.895 564.659 null] >> -% 1076 0 obj +% 1097 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [259.464 342.722 336.983 353.847] -/A << /S /GoTo /D (spdata) >> +/D [1093 0 R /XYZ 99.895 504.939 null] >> -% 1077 0 obj +% 1098 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [259.464 274.976 326.522 286.101] -/A << /S /GoTo /D (descdata) >> +/D [1093 0 R /XYZ 124.802 506.876 null] >> -% 1081 0 obj +% 1099 0 obj << -/D [1079 0 R /XYZ 98.895 753.953 null] +/D [1093 0 R /XYZ 124.802 494.921 null] >> -% 252 0 obj +% 1100 0 obj << -/D [1079 0 R /XYZ 99.895 720.077 null] +/D [1093 0 R /XYZ 124.802 482.966 null] >> -% 1083 0 obj +% 1101 0 obj << -/D [1079 0 R /XYZ 270.132 513.305 null] +/D [1093 0 R /XYZ 124.802 471.011 null] >> -% 1078 0 obj +% 1092 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F11 750 0 R /F14 767 0 R /F13 1082 0 R /F27 556 0 R /F30 764 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F11 755 0 R /F30 769 0 R /F16 558 0 R >> /ProcSet [ /PDF /Text ] >> -% 1091 0 obj +% 1107 0 obj << /Type /Page -/Contents 1092 0 R -/Resources 1090 0 R +/Contents 1108 0 R +/Resources 1106 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1084 0 R -/Annots [ 1085 0 R 1086 0 R 1087 0 R 1088 0 R ] ->> -% 1085 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [432.897 276.095 444.852 286.943] -/A << /S /GoTo /D (table.12) >> +/Parent 1102 0 R +/Annots [ 1103 0 R 1104 0 R 1105 0 R ] >> -% 1086 0 obj +% 1103 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [310.273 208.422 387.792 219.547] -/A << /S /GoTo /D (spdata) >> +/Rect [419.358 404.491 495.412 415.616] +/A << /S /GoTo /D (vdata) >> >> -% 1087 0 obj +% 1104 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [419.358 141.026 495.412 152.151] -/A << /S /GoTo /D (vdata) >> +/Rect [376.221 392.812 383.195 403.66] +/A << /S /GoTo /D (table.9) >> >> -% 1088 0 obj +% 1105 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [376.818 129.347 388.773 140.196] -/A << /S /GoTo /D (table.12) >> ->> -% 1093 0 obj -<< -/D [1091 0 R /XYZ 149.705 753.953 null] ->> -% 256 0 obj -<< -/D [1091 0 R /XYZ 150.705 720.077 null] ->> -% 1094 0 obj -<< -/D [1091 0 R /XYZ 290.613 675.784 null] +/Rect [310.273 324.789 377.331 335.914] +/A << /S /GoTo /D (descdata) >> >> -% 1095 0 obj +% 1109 0 obj << -/D [1091 0 R /XYZ 287.475 658.376 null] +/D [1107 0 R /XYZ 149.705 753.953 null] >> -% 1096 0 obj +% 244 0 obj << -/D [1091 0 R /XYZ 286.835 640.968 null] +/D [1107 0 R /XYZ 150.705 720.077 null] >> -% 1097 0 obj +% 1110 0 obj << -/D [1091 0 R /XYZ 320.941 455.558 null] +/D [1107 0 R /XYZ 318.451 540.923 null] >> -% 1090 0 obj +% 1106 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F11 750 0 R /F14 767 0 R /F10 766 0 R /F7 765 0 R /F27 556 0 R /F30 764 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F11 755 0 R /F14 772 0 R /F7 770 0 R /F30 769 0 R /F27 560 0 R >> /ProcSet [ /PDF /Text ] >> -% 1106 0 obj +% 1114 0 obj << /Type /Page -/Contents 1107 0 R -/Resources 1105 0 R +/Contents 1115 0 R +/Resources 1113 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1084 0 R -/Annots [ 1089 0 R 1098 0 R 1099 0 R 1100 0 R 1101 0 R 1102 0 R 1103 0 R 1104 0 R ] ->> -% 1089 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [382.088 655.375 394.043 666.223] -/A << /S /GoTo /D (table.12) >> ->> -% 1098 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [368.549 588.824 444.603 599.949] -/A << /S /GoTo /D (vdata) >> ->> -% 1099 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [326.219 577.145 338.174 587.994] -/A << /S /GoTo /D (table.12) >> ->> -% 1100 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [259.464 498.639 326.522 509.764] -/A << /S /GoTo /D (descdata) >> ->> -% 1101 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [346.389 462.009 353.363 472.858] -/A << /S /GoTo /D (equation.4.1) >> ->> -% 1102 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.393 447.541 352.367 458.389] -/A << /S /GoTo /D (equation.4.2) >> ->> -% 1103 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.697 433.073 352.671 443.921] -/A << /S /GoTo /D (equation.4.3) >> +/Parent 1102 0 R +/Annots [ 1111 0 R 1112 0 R ] >> -% 1104 0 obj +% 1111 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [203.009 191.887 214.964 202.735] -/A << /S /GoTo /D (table.12) >> ->> -% 1108 0 obj -<< -/D [1106 0 R /XYZ 98.895 753.953 null] ->> -% 1105 0 obj -<< -/Font << /F27 556 0 R /F8 557 0 R /F11 750 0 R /F30 764 0 R >> -/ProcSet [ /PDF /Text ] +/Rect [259.464 342.722 336.983 353.847] +/A << /S /GoTo /D (spdata) >> >> % 1112 0 obj << -/Type /Page -/Contents 1113 0 R -/Resources 1111 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1084 0 R -/Annots [ 1109 0 R ] ->> -% 1109 0 obj -<< /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [432.897 117.392 444.852 128.24] -/A << /S /GoTo /D (table.13) >> +/Rect [259.464 274.976 326.522 286.101] +/A << /S /GoTo /D (descdata) >> >> endstream endobj -1125 0 obj +1123 0 obj << -/Length 7790 +/Length 5523 >> stream 0 g 0 G 0 g 0 G -0 g 0 G BT -/F27 9.9626 Tf 99.895 706.129 Td [(t)]TJ -0 g 0 G -/F8 9.9626 Tf 9.437 0 Td [(the)-333(global)-334(p)-27(ortion)-334(of)-333(the)-333(sparse)-334(matrix)]TJ/F11 9.9626 Tf 172.603 0 Td [(T)]TJ/F8 9.9626 Tf 7.206 0 Td [(.)]TJ -164.339 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(t)28(yp)-28(e)-333(sp)-28(eci\014ed)-333(in)]TJ/F14 9.9626 Tf 176.118 0 Td [(x)]TJ -0 0 1 rg 0 0 1 RG -/F8 9.9626 Tf 7.748 0 Td [(3)]TJ -0 g 0 G - [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -208.773 -20.65 Td [(x)]TJ -0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -167.933 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-55(jec)-1(t)-254(of)-255(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 244.743 0 Td [(psb)]TJ -ET -q -1 0 0 1 385.864 590.037 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 389.002 589.838 Td [(T)]TJ -ET -q -1 0 0 1 394.86 590.037 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 397.998 589.838 Td [(vect)]TJ +/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ ET q -1 0 0 1 419.547 590.037 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 171.761 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F30 9.9626 Tf 422.685 589.838 Td [(type)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(normi)-375(|)-375(In\014nit)31(y)-375(Norm)-375(of)-375(Sparse)-375(Matrix)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-333(function)-334(computes)-333(the)-333(in\014nit)28(y-norm)-334(of)-333(a)-333(matrix)]TJ/F11 9.9626 Tf 235.672 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(:)]TJ/F11 9.9626 Tf -103.44 -33.873 Td [(nr)-28(mi)]TJ/F14 9.9626 Tf 25.698 0 Td [(\040)-278(k)]TJ/F11 9.9626 Tf 17.711 0 Td [(A)]TJ/F14 9.9626 Tf 7.472 0 Td [(k)]TJ/F13 6.9738 Tf 4.982 -1.495 Td [(1)]TJ/F8 9.9626 Tf -195.567 -20.423 Td [(where:)]TJ 0 g 0 G -/F8 9.9626 Tf -297.883 -11.955 Td [(con)28(taining)-342(n)28(um)28(b)-28(ers)-342(of)-342(t)28(yp)-28(e)-342(sp)-28(eci\014ed)-342(in)-341(T)83(able)]TJ -0 0 1 rg 0 0 1 RG - [-342(13)]TJ -0 g 0 G - [(.)-470(The)-342(rank)-342(of)]TJ/F11 9.9626 Tf 274.694 0 Td [(x)]TJ/F8 9.9626 Tf 9.101 0 Td [(m)28(ust)-342(b)-28(e)]TJ -283.795 -11.956 Td [(the)-333(same)-334(of)]TJ/F11 9.9626 Tf 53.466 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -83.615 -20.649 Td [(b)-32(eta)]TJ +/F11 9.9626 Tf 0 -19.926 Td [(A)]TJ 0 g 0 G -/F8 9.9626 Tf 26.941 0 Td [(the)-333(scalar)]TJ/F11 9.9626 Tf 45.468 0 Td [(\014)]TJ/F8 9.9626 Tf 6.161 0 Td [(.)]TJ -53.663 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(n)28(um)28(b)-28(er)-333(of)-334(the)-333(data)-333(t)28(yp)-28(e)-334(ind)1(ic)-1(ated)-333(in)-333(T)83(able)]TJ -0 0 1 rg 0 0 1 RG - [-333(13)]TJ +/F8 9.9626 Tf 12.453 0 Td [(represen)28(ts)-334(the)-333(global)-333(matrix)]TJ/F11 9.9626 Tf 125.834 0 Td [(A)]TJ 0 g 0 G - [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -20.65 Td [(y)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -167.481 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-55(jec)-1(t)-254(of)-255(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 244.743 0 Td [(psb)]TJ ET q -1 0 0 1 385.864 429.186 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 232.099 589.962 cm +[]0 d 0 J 0.398 w 0 0 m 180.922 0 l S Q BT -/F30 9.9626 Tf 389.002 428.986 Td [(T)]TJ +/F11 9.9626 Tf 238.077 581.394 Td [(A)]TJ/F27 9.9626 Tf 120.41 0 Td [(F)96(unction)]TJ ET q -1 0 0 1 394.86 429.186 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 232.099 577.608 cm +[]0 d 0 J 0.398 w 0 0 m 180.922 0 l S Q BT -/F30 9.9626 Tf 397.998 428.986 Td [(vect)]TJ +/F8 9.9626 Tf 238.077 569.04 Td [(Short)-333(Precision)-334(Real)-3102(psb)]TJ ET q -1 0 0 1 419.547 429.186 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 374.084 569.24 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F30 9.9626 Tf 422.685 428.986 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf -297.883 -11.955 Td [(con)28(taining)-345(n)28(um)28(b)-28(ers)-345(of)-345(t)28(yp)-28(e)-345(sp)-28(eci\014ed)-345(in)-345(T)84(able)]TJ -0 0 1 rg 0 0 1 RG - [-345(13)]TJ -0 g 0 G - [(.)-479(The)-345(rank)-345(of)]TJ/F11 9.9626 Tf 275.086 0 Td [(y)]TJ/F8 9.9626 Tf 8.678 0 Td [(m)28(ust)-345(b)-28(e)]TJ -283.764 -11.955 Td [(the)-333(same)-334(of)]TJ/F11 9.9626 Tf 53.466 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -84.067 -20.65 Td [(desc)]TJ +/F8 9.9626 Tf 377.073 569.04 Td [(spnrmi)]TJ -138.996 -11.955 Td [(Long)-333(Precision)-334(Real)-3314(psb)]TJ ET q -1 0 0 1 121.81 384.625 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +1 0 0 1 374.084 557.284 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F27 9.9626 Tf 125.247 384.426 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(con)28(tains)-334(d)1(ata)-334(structures)-333(for)-333(com)-1(m)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 135.658 0 Td [(psb)]TJ +/F8 9.9626 Tf 377.073 557.085 Td [(spnrmi)]TJ -138.996 -11.955 Td [(Short)-333(Precision)-334(Complex)-1200(psb)]TJ ET q -1 0 0 1 276.779 336.805 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 374.084 545.329 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F30 9.9626 Tf 279.917 336.605 Td [(desc)]TJ +/F8 9.9626 Tf 377.073 545.13 Td [(spnrmi)]TJ -138.996 -11.955 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ ET q -1 0 0 1 301.466 336.805 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 374.084 533.374 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F30 9.9626 Tf 304.604 336.605 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -225.631 -20.649 Td [(trans)]TJ -0 g 0 G -/F8 9.9626 Tf 30.609 0 Td [(sp)-28(ecify)-333(with)]TJ/F17 9.9626 Tf 55.68 0 Td [(unitd)]TJ/F8 9.9626 Tf 25.726 0 Td [(the)-333(op)-28(eration)-333(to)-334(p)-27(erform.)]TJ -0 g 0 G -/F27 9.9626 Tf -87.108 -20.65 Td [(trans)-383(=)-384('N')]TJ -0 g 0 G -/F8 9.9626 Tf 62.489 0 Td [(the)-333(op)-28(eration)-333(is)-334(with)-333(no)-333(transp)-28(osed)-333(matrix)]TJ -0 g 0 G -/F27 9.9626 Tf -62.489 -16.303 Td [(trans)-383(=)-384('T')]TJ -0 g 0 G -/F8 9.9626 Tf 61.493 0 Td [(the)-333(op)-28(eration)-333(is)-334(with)-333(transp)-28(osed)-333(matrix.)]TJ -0 g 0 G -/F27 9.9626 Tf -61.493 -16.302 Td [(trans)-383(=)-384('C')]TJ -0 g 0 G -/F8 9.9626 Tf 61.797 0 Td [(the)-333(op)-28(eration)-333(is)-334(with)-333(conjugate)-333(transp)-28(osed)-333(matrix.)]TJ -61.797 -20.65 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Default:)]TJ/F11 9.9626 Tf 39.436 0 Td [(tr)-28(ans)]TJ/F8 9.9626 Tf 27.052 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(N)]TJ/F8 9.9626 Tf -77.004 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(c)28(haracter)-333(v)55(ariable.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -20.65 Td [(unitd)]TJ -0 g 0 G -/F8 9.9626 Tf 31.715 0 Td [(sp)-28(ecify)-333(with)]TJ/F17 9.9626 Tf 55.68 0 Td [(tr)51(ans)]TJ/F8 9.9626 Tf 25.089 0 Td [(the)-333(op)-28(eration)-333(to)-334(p)-27(erform.)]TJ -0 g 0 G -/F27 9.9626 Tf -87.577 -20.649 Td [(unitd)-383(=)-384('U')]TJ -0 g 0 G -/F8 9.9626 Tf 63.442 0 Td [(the)-333(op)-28(eration)-333(is)-334(with)-333(no)-333(scaling)]TJ -0 g 0 G -/F27 9.9626 Tf -63.442 -16.303 Td [(unitd)-383(=)-384('L')]TJ -0 g 0 G -/F8 9.9626 Tf 61.519 0 Td [(the)-333(op)-28(eration)-333(is)-334(with)-333(left)-333(scaling)]TJ -0 g 0 G -/F27 9.9626 Tf -61.519 -16.302 Td [(unitd)-383(=)-384('R')]TJ -0 g 0 G -/F8 9.9626 Tf 63.221 0 Td [(the)-333(op)-28(eration)-333(is)-334(with)-333(righ)28(t)-333(s)-1(calin)1(g.)]TJ -0 g 0 G - 78.747 -29.888 Td [(47)]TJ -0 g 0 G -ET - -endstream -endobj -1131 0 obj -<< -/Length 4678 ->> -stream -0 g 0 G +/F8 9.9626 Tf 377.073 533.175 Td [(spnrmi)]TJ +ET +q +1 0 0 1 232.099 529.389 cm +[]0 d 0 J 0.398 w 0 0 m 180.922 0 l S +Q 0 g 0 G BT -/F8 9.9626 Tf 175.611 706.129 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Default:)]TJ/F11 9.9626 Tf 39.436 0 Td [(unitd)]TJ/F8 9.9626 Tf 26.666 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(U)]TJ/F8 9.9626 Tf -76.618 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(c)28(haracter)-334(v)56(ariable.)]TJ +/F8 9.9626 Tf 276.386 501.35 Td [(T)83(able)-333(11:)-444(Data)-334(t)28(yp)-28(es)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -19.925 Td [(c)32(hoice)]TJ 0 g 0 G -/F8 9.9626 Tf 35.374 0 Td [(sp)-28(eci\014es)-333(the)-334(up)-27(date)-334(of)-333(o)28(v)28(erlap)-334(elemen)28(ts)-333(to)-334(b)-27(e)-334(p)-28(erf)1(orme)-1(d)-333(on)-333(exit:)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -5.486 -19.925 Td [(psb_none_)]TJ -0 g 0 G -0 g 0 G - 0 -15.941 Td [(psb_sum_)]TJ +/F30 9.9626 Tf -125.681 -33.873 Td [(psb_spnrmi\050A,)-525(desc_a,)-525(info\051)]TJ 0 -11.956 Td [(psb_normi\050A,)-525(desc_a,)-525(info\051)]TJ 0 g 0 G +/F27 9.9626 Tf 0 -21.917 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G - 0 -15.94 Td [(psb_avg_)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G +/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ 0 g 0 G - 0 -15.94 Td [(psb_square_root_)]TJ/F8 9.9626 Tf -4.982 -19.925 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Default:)]TJ/F30 9.9626 Tf 39.436 0 Td [(psb_avg_)]TJ/F8 9.9626 Tf -39.436 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -19.925 Td [(diag)]TJ + 0 -19.925 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 25.826 0 Td [(the)-333(diagonal)-334(scaling)-333(matrix.)]TJ -0.92 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Default:)]TJ/F11 9.9626 Tf 39.436 0 Td [(diag)]TJ/F8 9.9626 Tf 18.993 0 Td [(\0501\051)-278(=)-278(1\050)]TJ/F11 9.9626 Tf 34.869 0 Td [(noscal)-20(ing)]TJ/F8 9.9626 Tf 42.747 0 Td [(\051)]TJ -136.045 -11.955 Td [(Sp)-28(eci\014ed)-382(as:)-543(a)-382(rank)-383(on)1(e)-383(arra)28(y)-382(c)-1(on)28(taining)-382(n)28(um)28(b)-28(ers)-383(of)-382(the)-382(t)27(yp)-27(e)-383(indicated)]TJ 0 -11.955 Td [(in)-333(T)83(able)]TJ +/F8 9.9626 Tf 10.551 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(the)-333(global)-333(sparse)-334(matrix)]TJ/F11 9.9626 Tf 196.126 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(.)]TJ -189.242 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG - [-333(13)]TJ -0 g 0 G - [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.906 -19.926 Td [(w)32(ork)]TJ -0 g 0 G -/F8 9.9626 Tf 29.431 0 Td [(a)-333(w)27(ork)-333(arra)28(y)83(.)]TJ -4.525 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-377(as:)-531(a)-377(rank)-377(on)1(e)-377(arra)28(y)-377(of)-377(the)-377(same)-377(t)28(yp)-28(e)-377(of)]TJ/F11 9.9626 Tf 225.953 0 Td [(x)]TJ/F8 9.9626 Tf 9.448 0 Td [(with)-377(the)-377(T)84(AR)28(G)-1(E)1(T)]TJ -235.401 -11.955 Td [(attribute.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.906 -19.926 Td [(On)-383(Return)]TJ +/F30 9.9626 Tf 135.658 0 Td [(psb)]TJ +ET +q +1 0 0 1 327.588 346.132 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 330.727 345.932 Td [(Tspmat)]TJ +ET +q +1 0 0 1 362.736 346.132 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 365.874 345.932 Td [(type)]TJ 0 g 0 G +/F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G - 0 -19.925 Td [(y)]TJ +/F27 9.9626 Tf -236.091 -19.925 Td [(desc)]TJ +ET +q +1 0 0 1 172.619 326.206 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 176.057 326.007 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(y)]TJ/F8 9.9626 Tf 5.241 0 Td [(.)]TJ -167.481 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-474(as:)-727(an)-475(arra)28(y)-475(of)-474(rank)-475(one)-474(or)-475(t)28(w)28(o)-475(con)28(taining)-474(n)27(um)28(b)-28(ers)-474(of)-475(t)28(yp)-28(e)]TJ 0 -11.955 Td [(sp)-28(eci\014ed)-333(in)-333(T)83(able)]TJ +/F8 9.9626 Tf 10.55 0 Td [(con)28(tains)-334(data)-333(structures)-333(for)-333(c)-1(omm)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG - [-333(13)]TJ -0 g 0 G - [(.)]TJ +/F30 9.9626 Tf 135.659 0 Td [(psb)]TJ +ET +q +1 0 0 1 327.588 278.386 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 330.727 278.186 Td [(desc)]TJ +ET +q +1 0 0 1 352.275 278.386 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 355.414 278.186 Td [(type)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -19.925 Td [(info)]TJ +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(te)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(t)1(e)-1(d)1(.)]TJ +/F27 9.9626 Tf -225.63 -19.925 Td [(On)-383(Return)]TJ 0 g 0 G - 141.968 -73.723 Td [(48)]TJ 0 g 0 G -ET - -endstream -endobj -1136 0 obj -<< -/Length 632 ->> -stream + 0 -19.925 Td [(F)96(unction)-384(v)64(alue)]TJ 0 g 0 G +/F8 9.9626 Tf 78.386 0 Td [(is)-333(the)-334(in\014nit)28(y-norm)-333(of)-333(sparse)-334(submatrix)]TJ/F11 9.9626 Tf 176.311 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(.)]TJ -237.263 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(long)-333(precision)-334(r)1(e)-1(al)-333(n)28(um)28(b)-28(er.)]TJ 0 g 0 G -BT -/F16 14.3462 Tf 99.895 706.129 Td [(5)-1125(Comm)31(unication)-375(routines)]TJ/F8 9.9626 Tf 0 -21.821 Td [(The)-283(routines)-283(in)-283(this)-283(c)28(hapter)-283(implemen)28(t)-283(v)55(arious)-283(global)-283(comm)28(unication)-283(op)-28(erators)]TJ 0 -11.955 Td [(on)-344(v)28(ectors)-344(asso)-28(ciated)-343(with)-344(a)-344(discretization)-343(mesh.)-476(F)84(or)-344(auxiliary)-344(comm)28(unication)]TJ 0 -11.955 Td [(routines)-333(not)-334(tied)-333(to)-333(a)-334(discretization)-333(space)-333(see)]TJ -0 0 1 rg 0 0 1 RG - [-334(6)]TJ +/F27 9.9626 Tf -24.906 -19.926 Td [(info)]TJ 0 g 0 G - [(.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(te)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ 0 g 0 G - 166.875 -569.96 Td [(49)]TJ + 141.968 -56.242 Td [(46)]TJ 0 g 0 G ET endstream endobj -1145 0 obj +1134 0 obj << -/Length 7227 +/Length 7328 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ +/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ ET q -1 0 0 1 171.761 706.328 cm +1 0 0 1 120.951 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(halo)-375(|)-375(Halo)-375(Data)-375(Comm)31(unication)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(These)-333(subroutines)-334(gathers)-333(the)-333(v)55(alues)-333(of)-333(the)-334(halo)-333(elemen)28(ts:)]TJ/F11 9.9626 Tf 158.413 -23.188 Td [(x)]TJ/F14 9.9626 Tf 8.461 0 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(x)]TJ/F8 9.9626 Tf -179.604 -21.251 Td [(where:)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(spmm)-375(|)-375(Sparse)-375(Matrix)-375(b)31(y)-375(Dense)-375(Matrix)-375(Pro)-31(duct)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-333(subroutine)-334(computes)-333(the)-333(Sparse)-334(Matrix)-333(b)28(y)-333(Dense)-334(Matrix)-333(Pro)-28(duct:)]TJ/F11 9.9626 Tf 139.909 -23.911 Td [(y)]TJ/F14 9.9626 Tf 8.009 0 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(\013)-4(Ax)]TJ/F8 9.9626 Tf 21.79 0 Td [(+)]TJ/F11 9.9626 Tf 9.962 0 Td [(\014)-53(y)]TJ 0 g 0 G -/F11 9.9626 Tf 0 -19.391 Td [(x)]TJ +/F8 9.9626 Tf 138.581 0 Td [(\0501\051)]TJ +0 g 0 G +/F11 9.9626 Tf -194.21 -17.408 Td [(y)]TJ/F14 9.9626 Tf 8.009 0 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(\013)-4(A)]TJ/F10 6.9738 Tf 13.882 4.113 Td [(T)]TJ/F11 9.9626 Tf 6.276 -4.113 Td [(x)]TJ/F8 9.9626 Tf 7.908 0 Td [(+)]TJ/F11 9.9626 Tf 9.962 0 Td [(\014)-53(y)]TJ +0 g 0 G +/F8 9.9626 Tf 135.443 0 Td [(\0502\051)]TJ +0 g 0 G +/F11 9.9626 Tf -194.851 -17.408 Td [(y)]TJ/F14 9.9626 Tf 8.01 0 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(\013)-4(A)]TJ/F10 6.9738 Tf 13.882 4.113 Td [(H)]TJ/F11 9.9626 Tf 7.556 -4.113 Td [(x)]TJ/F8 9.9626 Tf 7.908 0 Td [(+)]TJ/F11 9.9626 Tf 9.963 0 Td [(\014)-53(y)]TJ +0 g 0 G +/F8 9.9626 Tf 134.802 0 Td [(\0503\051)]TJ +0 g 0 G + -316.037 -17.408 Td [(where:)]TJ +0 g 0 G +/F11 9.9626 Tf -14.944 -19.226 Td [(x)]TJ +0 g 0 G +/F8 9.9626 Tf 10.676 0 Td [(is)-333(the)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 116.092 0 Td [(x)]TJ/F7 6.9738 Tf 5.694 -1.495 Td [(:)]TJ/F10 6.9738 Tf 2.256 0 Td [(;)]TJ/F7 6.9738 Tf 2.366 0 Td [(:)]TJ +0 g 0 G +/F11 9.9626 Tf -137.084 -18.081 Td [(y)]TJ 0 g 0 G -/F8 9.9626 Tf 10.675 0 Td [(is)-333(a)-334(global)-333(dense)-333(submatrix.)]TJ +/F8 9.9626 Tf 10.224 0 Td [(is)-333(the)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 116.092 0 Td [(y)]TJ/F7 6.9738 Tf 4.885 -1.494 Td [(:)]TJ/F10 6.9738 Tf 2.255 0 Td [(;)]TJ/F7 6.9738 Tf 2.366 0 Td [(:)]TJ +0 g 0 G +/F11 9.9626 Tf -135.822 -18.081 Td [(A)]TJ +0 g 0 G +/F8 9.9626 Tf 12.454 0 Td [(is)-333(the)-334(global)-333(sparse)-333(matrix)]TJ/F11 9.9626 Tf 118.943 0 Td [(A)]TJ 0 g 0 G 0 g 0 G 0 g 0 G ET q -1 0 0 1 228.797 602.649 cm +1 0 0 1 177.988 532.215 cm []0 d 0 J 0.398 w 0 0 m 187.526 0 l S Q BT -/F11 9.9626 Tf 234.775 594.081 Td [(\013)]TJ/F8 9.9626 Tf 6.41 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(x)]TJ/F27 9.9626 Tf 107.912 0 Td [(Subroutine)]TJ +/F11 9.9626 Tf 183.966 523.647 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(\013)]TJ/F8 9.9626 Tf 6.41 0 Td [(,)]TJ/F11 9.9626 Tf 6.089 0 Td [(\014)]TJ/F27 9.9626 Tf 71.238 0 Td [(Subroutine)]TJ ET q -1 0 0 1 228.797 590.295 cm +1 0 0 1 177.988 519.862 cm []0 d 0 J 0.398 w 0 0 m 187.526 0 l S Q BT -/F8 9.9626 Tf 234.775 581.727 Td [(In)28(teger)-9028(psb)]TJ -ET -q -1 0 0 1 370.782 581.926 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F8 9.9626 Tf 373.771 581.727 Td [(halo)]TJ -138.996 -11.955 Td [(Short)-333(Precision)-334(Real)-3102(psb)]TJ +/F8 9.9626 Tf 183.966 511.294 Td [(Short)-333(Precision)-333(R)-1(eal)-3102(psb)]TJ ET q -1 0 0 1 370.782 569.971 cm +1 0 0 1 319.972 511.493 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 373.771 569.772 Td [(halo)]TJ -138.996 -11.955 Td [(Long)-333(Precision)-334(Real)-3314(psb)]TJ +/F8 9.9626 Tf 322.961 511.294 Td [(spmm)]TJ -138.995 -11.956 Td [(Long)-333(Precision)-334(Real)-3314(p)1(s)-1(b)]TJ ET q -1 0 0 1 370.782 558.016 cm +1 0 0 1 319.972 499.538 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 373.771 557.817 Td [(halo)]TJ -138.996 -11.955 Td [(Short)-333(Precision)-334(Complex)-1200(psb)]TJ +/F8 9.9626 Tf 322.961 499.338 Td [(spmm)]TJ -138.995 -11.955 Td [(Short)-333(Precision)-333(C)-1(omplex)-1200(p)1(s)-1(b)]TJ ET q -1 0 0 1 370.782 546.061 cm +1 0 0 1 319.972 487.583 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 373.771 545.862 Td [(halo)]TJ -138.996 -11.956 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ +/F8 9.9626 Tf 322.961 487.383 Td [(spmm)]TJ -138.995 -11.955 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ ET q -1 0 0 1 370.782 534.106 cm +1 0 0 1 319.972 475.627 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 373.771 533.906 Td [(halo)]TJ +/F8 9.9626 Tf 322.961 475.428 Td [(spmm)]TJ ET q -1 0 0 1 228.797 530.121 cm +1 0 0 1 177.988 471.642 cm []0 d 0 J 0.398 w 0 0 m 187.526 0 l S Q 0 g 0 G BT -/F8 9.9626 Tf 276.386 502.081 Td [(T)83(able)-333(14:)-444(Data)-334(t)28(yp)-28(es)]TJ +/F8 9.9626 Tf 225.577 443.603 Td [(T)83(able)-333(12:)-444(Data)-334(t)28(yp)-28(es)]TJ +0 g 0 G +0 g 0 G +0 g 0 G +0 g 0 G +/F30 9.9626 Tf -125.682 -32.649 Td [(call)-525(psb_spmm\050alpha,)-525(a,)-525(x,)-525(beta,)-525(y,)-525(desc_a,)-525(info\051)]TJ 0 -11.955 Td [(call)-525(psb_spmm\050alpha,)-525(a,)-525(x,)-525(beta,)-525(y,desc_a,)-525(info,)-525(&)]TJ 67.995 -11.955 Td [(&)-525(trans,)-525(work\051)]TJ +0 g 0 G +/F27 9.9626 Tf -67.995 -21.044 Td [(T)32(yp)-32(e:)]TJ +0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ +0 g 0 G +/F27 9.9626 Tf -33.797 -19.575 Td [(On)-383(En)32(try)]TJ +0 g 0 G +0 g 0 G + 0 -19.576 Td [(alpha)]TJ +0 g 0 G +/F8 9.9626 Tf 32.033 0 Td [(the)-333(scalar)]TJ/F11 9.9626 Tf 45.468 0 Td [(\013)]TJ/F8 9.9626 Tf 6.41 0 Td [(.)]TJ -59.004 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(n)28(um)28(b)-28(er)-333(of)-334(the)-333(data)-333(t)28(yp)-28(e)-334(ind)1(ic)-1(ated)-333(in)-333(T)83(able)]TJ +0 0 1 rg 0 0 1 RG + [-333(12)]TJ +0 g 0 G + [(.)]TJ 0 g 0 G +/F27 9.9626 Tf -24.907 -19.575 Td [(a)]TJ 0 g 0 G -/F27 9.9626 Tf -124.304 -29.354 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.73 0 Td [(p)-122(s)-123(b)]TJ +/F8 9.9626 Tf 10.551 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(the)-333(sparse)-333(matrix)]TJ/F11 9.9626 Tf 166.792 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(.)]TJ -159.908 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 135.658 0 Td [(psb)]TJ ET q -1 0 0 1 201.066 472.926 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 276.779 211.831 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F8 9.9626 Tf 205.274 472.727 Td [(h)-122(a)-123(l)-122(o)-228(\050)-129(x)-210(,)-873(d)-113(e)-113(s)-112(c)]TJ +/F30 9.9626 Tf 279.917 211.632 Td [(Tspmat)]TJ ET q -1 0 0 1 276.854 472.926 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 311.927 211.831 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 315.065 211.632 Td [(type)]TJ +0 g 0 G +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -236.091 -19.575 Td [(x)]TJ +0 g 0 G +/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -167.933 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-55(jec)-1(t)-254(of)-255(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 244.743 0 Td [(psb)]TJ +ET +q +1 0 0 1 385.864 144.435 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F8 9.9626 Tf 280.965 472.727 Td [(a)-386(,)-914(i)-152(n)-152(f)-152(o)-258(\051)]TJ/F27 9.9626 Tf -128.883 -11.955 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.73 0 Td [(p)-122(s)-123(b)]TJ +/F30 9.9626 Tf 389.002 144.236 Td [(T)]TJ ET q -1 0 0 1 201.066 460.971 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 394.86 144.435 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F8 9.9626 Tf 205.274 460.772 Td [(h)-122(a)-123(l)-122(o)-228(\050)-129(x)-210(,)-873(d)-113(e)-113(s)-112(c)]TJ +/F30 9.9626 Tf 397.998 144.236 Td [(vect)]TJ ET q -1 0 0 1 276.854 460.971 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 419.547 144.435 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F8 9.9626 Tf 280.965 460.772 Td [(a)-386(,)-888(i)-127(n)-127(f)-127(o)-415(,)-804(w)-43(o)-43(r)-43(k)-247(,)]TJ/F27 9.9626 Tf 91.303 0 Td [(d)-39(a)-39(t)-40(a)]TJ/F8 9.9626 Tf 24.572 0 Td [(\051)]TJ +/F30 9.9626 Tf 422.685 144.236 Td [(type)]TJ 0 g 0 G +/F8 9.9626 Tf -297.883 -11.955 Td [(con)28(taining)-342(n)28(um)28(b)-28(ers)-342(of)-342(t)28(yp)-28(e)-342(sp)-28(eci\014ed)-342(in)-341(T)83(able)]TJ +0 0 1 rg 0 0 1 RG + [-342(12)]TJ 0 g 0 G + [(.)-470(The)-342(rank)-342(of)]TJ/F11 9.9626 Tf 274.694 0 Td [(x)]TJ/F8 9.9626 Tf 9.101 0 Td [(m)28(ust)-342(b)-28(e)]TJ -283.795 -11.955 Td [(the)-333(same)-334(of)]TJ/F11 9.9626 Tf 53.466 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -246.135 -26.961 Td [(T)32(yp)-32(e:)]TJ + 83.26 -29.888 Td [(47)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ +ET + +endstream +endobj +1149 0 obj +<< +/Length 6975 +>> +stream 0 g 0 G -/F27 9.9626 Tf -33.797 -19.659 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.658 Td [(x)]TJ +BT +/F27 9.9626 Tf 150.705 706.129 Td [(b)-32(eta)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(global)-333(dense)-334(matrix)]TJ/F11 9.9626 Tf 88.917 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -80.732 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)28(o)-255(arra)28(y)-255(or)-255(an)-255(ob)-55(ject)-255(of)-255(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 26.94 0 Td [(the)-333(scalar)]TJ/F11 9.9626 Tf 45.469 0 Td [(\014)]TJ/F8 9.9626 Tf 6.161 0 Td [(.)]TJ -53.664 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(n)28(um)28(b)-28(er)-333(of)-334(the)-333(data)-333(t)27(yp)-27(e)-334(indicated)-333(in)-333(T)83(able)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 244.742 0 Td [(psb)]TJ + [-333(12)]TJ +0 g 0 G + [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.906 -18.453 Td [(y)]TJ +0 g 0 G +/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -167.482 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-56(j)1(e)-1(ct)-254(of)-255(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 244.743 0 Td [(psb)]TJ ET q -1 0 0 1 436.673 346.872 cm +1 0 0 1 436.673 592.233 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 439.811 346.673 Td [(T)]TJ +/F30 9.9626 Tf 439.811 592.034 Td [(T)]TJ ET q -1 0 0 1 445.669 346.872 cm +1 0 0 1 445.669 592.233 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 448.807 346.673 Td [(vect)]TJ +/F30 9.9626 Tf 448.807 592.034 Td [(vect)]TJ ET q -1 0 0 1 470.356 346.872 cm +1 0 0 1 470.356 592.233 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 473.495 346.673 Td [(type)]TJ +/F30 9.9626 Tf 473.495 592.034 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf -297.884 -11.955 Td [(con)28(taining)-333(n)27(um)28(b)-28(ers)-333(of)-333(t)27(yp)-27(e)-334(sp)-27(ec)-1(i)1(\014ed)-334(in)-333(T)83(able)]TJ +/F8 9.9626 Tf -297.884 -11.955 Td [(con)28(taining)-345(n)28(um)28(b)-28(ers)-345(of)-345(t)28(yp)-28(e)-345(sp)-28(eci\014ed)-345(in)-345(T)84(able)]TJ 0 0 1 rg 0 0 1 RG - [-333(14)]TJ + [-345(12)]TJ 0 g 0 G - [(.)]TJ + [(.)-479(The)-345(rank)-345(of)]TJ/F11 9.9626 Tf 275.087 0 Td [(y)]TJ/F8 9.9626 Tf 8.678 0 Td [(m)28(ust)-345(b)-28(e)]TJ -283.765 -11.955 Td [(the)-333(same)-334(of)]TJ/F11 9.9626 Tf 53.467 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -19.658 Td [(desc)]TJ +/F27 9.9626 Tf -84.067 -18.454 Td [(desc)]TJ ET q -1 0 0 1 172.619 315.259 cm +1 0 0 1 172.619 549.87 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 176.057 315.06 Td [(a)]TJ +/F27 9.9626 Tf 176.057 549.67 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.55 0 Td [(con)28(tains)-334(data)-333(structures)-333(for)-333(c)-1(omm)28(unications.)]TJ -10.996 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.55 0 Td [(con)28(tains)-334(data)-333(structures)-333(for)-333(c)-1(omm)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ +/F30 9.9626 Tf 135.659 0 Td [(psb)]TJ ET q -1 0 0 1 362.845 267.438 cm +1 0 0 1 327.588 502.049 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 365.983 267.239 Td [(desc)]TJ +/F30 9.9626 Tf 330.727 501.85 Td [(desc)]TJ ET q -1 0 0 1 387.532 267.438 cm +1 0 0 1 352.275 502.049 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 390.67 267.239 Td [(type)]TJ +/F30 9.9626 Tf 355.414 501.85 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -260.887 -19.658 Td [(w)32(ork)]TJ -0 g 0 G -/F8 9.9626 Tf 29.431 0 Td [(the)-333(w)27(ork)-333(arra)28(y)83(.)]TJ -4.525 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-334(ar)1(ra)27(y)-333(of)-333(the)-334(same)-333(t)28(yp)-28(e)-333(of)]TJ/F11 9.9626 Tf 220.756 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -251.356 -19.659 Td [(data)]TJ +/F27 9.9626 Tf -225.63 -18.454 Td [(trans)]TJ 0 g 0 G -/F8 9.9626 Tf 26.94 0 Td [(index)-333(list)-334(selector.)]TJ -2.034 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(Sp)-28(eci\014ed)-222(as:)-389(an)-222(in)28(teger.)-408(V)84(alues:)]TJ/F30 9.9626 Tf 136.48 0 Td [(psb_comm_halo_)]TJ/F8 9.9626 Tf 73.224 0 Td [(,)]TJ/F30 9.9626 Tf 2.768 0 Td [(psb_comm_mov_)]TJ/F8 9.9626 Tf 67.994 0 Td [(,)]TJ/F30 9.9626 Tf 5.203 0 Td [(psb_comm_ext_)]TJ/F8 9.9626 Tf 67.994 0 Td [(,)]TJ -353.663 -11.955 Td [(default:)]TJ/F30 9.9626 Tf 39.089 0 Td [(psb_comm_halo_)]TJ/F8 9.9626 Tf 73.225 0 Td [(.)-705(Cho)-27(ose)-1(s)-420(the)-420(index)-420(list)-420(on)-420(whic)28(h)-420(to)-420(base)-420(the)]TJ -112.314 -11.955 Td [(data)-333(exc)27(hange.)]TJ +/F8 9.9626 Tf 30.609 0 Td [(indicates)-333(what)-334(kind)-333(of)-333(op)-28(eration)-333(to)-333(p)-28(erform.)]TJ 0 g 0 G - 141.968 -29.888 Td [(50)]TJ +/F27 9.9626 Tf -5.703 -18.453 Td [(trans)-383(=)-384(N)]TJ 0 g 0 G -ET - -endstream -endobj -1155 0 obj -<< -/Length 3199 ->> -stream +/F8 9.9626 Tf 56.124 0 Td [(the)-333(op)-28(eration)-333(is)-334(sp)-28(eci\014ed)-333(b)28(y)-333(equation)]TJ +0 0 1 rg 0 0 1 RG + [-334(1)]TJ 0 g 0 G 0 g 0 G +/F27 9.9626 Tf -56.124 -14.469 Td [(trans)-383(=)-384(T)]TJ 0 g 0 G -BT -/F27 9.9626 Tf 99.895 706.129 Td [(On)-383(Return)]TJ +/F8 9.9626 Tf 55.128 0 Td [(the)-333(op)-28(eration)-333(is)-334(sp)-28(eci\014ed)-333(b)28(y)-333(equation)]TJ +0 0 1 rg 0 0 1 RG + [-334(2)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(x)]TJ +/F27 9.9626 Tf -55.128 -14.468 Td [(trans)-383(=)-384(C)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(global)-333(dense)-334(result)-333(matrix)]TJ/F11 9.9626 Tf 116.674 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -108.489 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Returned)-271(as:)-414(a)-271(rank)-271(one)-271(or)-272(t)28(w)28(o)-271(arra)28(y)-272(con)28(taining)-271(n)28(um)28(b)-28(ers)-271(of)-272(t)28(yp)-28(e)-271(sp)-28(eci\014ed)]TJ 0 -11.955 Td [(in)-333(T)83(able)]TJ +/F8 9.9626 Tf 55.433 0 Td [(the)-333(op)-28(eration)-333(is)-334(sp)-27(ec)-1(i\014)1(e)-1(d)-333(b)28(y)-333(equation)]TJ 0 0 1 rg 0 0 1 RG - [-333(14)]TJ + [-334(3)]TJ 0 g 0 G - [(.)]TJ + -55.433 -18.453 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Default:)]TJ/F11 9.9626 Tf 39.436 0 Td [(tr)-28(ans)]TJ/F8 9.9626 Tf 27.052 0 Td [(=)]TJ/F11 9.9626 Tf 10.517 0 Td [(N)]TJ/F8 9.9626 Tf -77.005 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(c)28(haracter)-334(v)56(ariable.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.926 Td [(info)]TJ +/F27 9.9626 Tf -24.906 -18.454 Td [(w)32(ork)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(result)-333(submatrix)]TJ/F11 9.9626 Tf 162.364 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -166.457 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue)-334(that)-333(con)28(tains)-333(an)-334(error)-333(co)-28(de.)]TJ +/F8 9.9626 Tf 29.431 0 Td [(w)28(ork)-334(arr)1(a)27(y)84(.)]TJ -4.525 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-487(as:)-753(a)-487(rank)-488(one)-487(arra)28(y)-488(of)-487(the)-488(same)-487(t)27(yp)-27(e)-488(of)]TJ/F11 9.9626 Tf 239.183 0 Td [(x)]TJ/F8 9.9626 Tf 10.551 0 Td [(and)]TJ/F11 9.9626 Tf 20.907 0 Td [(y)]TJ/F8 9.9626 Tf 10.099 0 Td [(with)-487(the)]TJ -280.74 -11.955 Td [(T)83(AR)28(GET)-333(attribute.)]TJ 0 g 0 G +/F27 9.9626 Tf -24.906 -18.454 Td [(On)-383(Return)]TJ 0 g 0 G 0 g 0 G -ET -1 0 0 1 159.702 337.279 cm -q -.45 0 0 .45 0 0 cm -q -1 0 0 1 0 0 cm -/Im3 Do -Q -Q + 0 -18.453 Td [(y)]TJ 0 g 0 G -1 0 0 1 -159.702 -337.279 cm -BT -/F8 9.9626 Tf 189.268 305.398 Td [(Figure)-333(7:)-445(Sample)-333(discretization)-333(mes)-1(h)1(.)]TJ +/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(result)-333(matrix)]TJ/F11 9.9626 Tf 147.364 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -138.728 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-474(as:)-727(an)-475(arra)28(y)-475(of)-474(rank)-475(one)-474(or)-475(t)28(w)28(o)-475(con)28(taining)-474(n)27(um)28(b)-28(ers)-474(of)-475(t)28(yp)-28(e)]TJ 0 -11.955 Td [(sp)-28(eci\014ed)-333(in)-333(T)83(able)]TJ +0 0 1 rg 0 0 1 RG + [-333(12)]TJ 0 g 0 G + [(.)]TJ 0 g 0 G -/F16 11.9552 Tf -89.373 -23.91 Td [(Usage)-381(Example)]TJ/F8 9.9626 Tf 93.981 0 Td [(Consider)-338(the)-339(discretization)-338(mesh)-339(depicted)-338(in)-338(\014g.)]TJ -0 0 1 rg 0 0 1 RG - [-339(7)]TJ +/F27 9.9626 Tf -24.906 -18.454 Td [(info)]TJ 0 g 0 G - [(,)-339(parti-)]TJ -93.981 -11.955 Td [(tioned)-334(among)-334(t)27(w)28(o)-334(pro)-28(cesses)-334(as)-335(sho)28(wn)-334(b)28(y)-334(the)-335(dashed)-334(line;)-334(the)-335(data)-334(distribution)]TJ 0 -11.955 Td [(is)-422(suc)28(h)-422(that)-422(eac)28(h)-422(pro)-28(cess)-422(will)-421(o)27(wn)-422(32)-421(en)27(tries)-422(in)-421(the)-422(index)-422(space,)-444(with)-422(a)-422(halo)]TJ 0 -11.956 Td [(made)-340(of)-341(8)-340(en)28(tries)-341(placed)-340(at)-340(lo)-28(cal)-341(ind)1(ice)-1(s)-340(33)-340(through)-341(40.)-465(If)-340(pro)-28(cess)-341(0)-340(assigns)-340(an)]TJ 0 -11.955 Td [(initial)-423(v)55(alue)-423(of)-424(1)-423(to)-424(its)-423(en)28(tries)-424(in)-423(the)]TJ/F11 9.9626 Tf 169.006 0 Td [(x)]TJ/F8 9.9626 Tf 9.913 0 Td [(v)28(ector,)-446(and)-424(pr)1(o)-28(cess)-424(1)-423(assigns)-424(a)-423(v)55(alue)]TJ -178.919 -11.955 Td [(of)-349(2,)-353(then)-349(after)-349(a)-349(call)-349(to)]TJ/F30 9.9626 Tf 108.539 0 Td [(psb_halo)]TJ/F8 9.9626 Tf 45.32 0 Td [(the)-349(con)28(ten)27(ts)-349(of)-349(the)-349(lo)-27(c)-1(al)-349(v)28(ectors)-349(will)-349(b)-28(e)-349(the)]TJ -153.859 -11.955 Td [(follo)28(wing:)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(te)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(t)1(e)-1(d.)]TJ 0 g 0 G - 166.875 -119.319 Td [(51)]TJ + 141.968 -38.108 Td [(48)]TJ 0 g 0 G ET endstream endobj -1151 0 obj +1155 0 obj << -/Type /XObject -/Subtype /Form -/FormType 1 -/PTEX.FileName (./figures/try8x8.pdf) -/PTEX.PageNumber 1 -/PTEX.InfoDict 1158 0 R -/BBox [0 0 498 439] -/Resources << -/ProcSet [ /PDF /Text ] -/ExtGState << -/R7 1159 0 R ->>/Font << /R8 1160 0 R/R10 1161 0 R>> ->> -/Length 3349 -/Filter /FlateDecode ->> -stream -x]$~tkXtjY}-qWWfDFr$ɬo1d%gro}=1s<h^ٽ}cVz_=>⩽ǎ'!w ;\)nBBZ!-$5=OztRZHLk/DX=&cZ  b!r+@x 1d-G5G||7|+_@dn@-Edk ИD-^ {Ldkc"{ˑ=&q@@>Cq)YD>E3 [@>E3iyaeMx f-Z-8Z=e9M>yݜF@l#mH?Kihy1ҎFb+ԑ |c3F9F#7F##ƌcH1!̥#gƈ1H=cę9>1RD9󍹍+-fs3Gnf3F9F#Ƭ"cC+?ߘlq0cĘcĘ9r3k1b1b1fsX(,m;V(7P?#z_q"mw`z|ÚwM,f~F~:Z?kFE5, ]`͌f c/4k4RU|$3.vsohSaAB~h~ǎFhִz~ d2-Eb%4kEGkmh}tE4n5M|=aB;hcb(4k:@wE/}3^<1satε۳>I`A&GR0wIؿOQu}N5h=u |z|OcdgXy۶ -;,_0 7k3M༿Dz,ٷqž<|d8lͺM༿Dzp?,pw SpeV.<cB`jg%cp0>x|$8,vf_NFp_"=Ve/,Wn`\mqeqς0H CH&3xp-,[&d.fe1,j07Ʃؕ@!Lqu a\FT7 fJݎ+M/޷"wZh!A?C/A~iY 1 <qVƢ4",YIsCk1#0B3 -U1\o{Wl}J뭴\Z!Ybnج_O;'7wӛs[i"]|_O'7wS"VZ .-W9p=YV<檶VZ .'6]/ʜֆp.yI|t=*:煮>?6T5|t1oS`$>6׻Ei9P+j#,7:煮N}0 qև[̓I|ONGdJ0|'aem,J#g\OMzFSl M}vp=U_^KW_FClpfx+M;V\﵇%%h1v7H>o'j۴c^Ly_RehxfyvI|6X9/p=YI剢5b?8p=vI|6Xq"jxT(Z!^_FCa7M;b$K_?9-3cR]bf!} 6mdeזՋon&t17T7[*fBKx Z]-rSkCyԌN.x'vWU.t+:煮>P]GCyMU0ȟz܊p -6ɖOWbzSE 0ˮΨxܳ>PU|h>^yԎX<Af\dy׎X<v4U3ڱz?Tjm~/[}:~<ωק/ߟvvݾkeo]{??~Cޟ#aYaX)'Wk3{ο*{ -endstream -endobj -1164 0 obj -<< -/Filter /FlateDecode -/Subtype /Type1C -/Length 13073 ->> -stream -xwxW?laό rG5hB'ZBL1`pø˶$KeK%Yr-˽w L% $$$m{Ȗ<<~4ss>s -o%!)&c攤}7#-VyR/<1cNc~G8fA>~<ެ5onݼ &.II'KO:mh4&#!.yIV̡Ԥď/<~sL\}Dsݧ<*wjM}~___;bd,`|< -) 'G;?̷с'7ɏ=, c|?1;nkc]4vƍ-p+ -|ApQg ͿؿĿɿӿI0`I@x2 0$TՀ d_ |#p]`Z`f5.b? ~򠸠 ڠ栎A烾 67P('|S8[ppp0Gh -&aGxE ! O^*8|=q?wʇRSsJjOTUBPT'uI=L&%"E0KDSEDEDEE[D"HdEuI% m}WE#!CD!lĐi!C, Y1$2$>Db ) q4t9r!Ð!C~- -S+F~*hb8PoJ)R2dV8ܪ&\YR)z%-V p;qFߦldz3n'-ڵVZX箷mF;k(5:'[2 4i<o ?3[pP ?ϦP8^AQ:̮4 AF%ɖGkgN'vuLB@Q8t{`;'Pp',\8.0O5 -C -bc}{C}¡F΁3bt񪝻O[w -v2RcpmIjk4Ϸ@wؗ/:/>ڱ##*z#Z<{)2mbи߀A0gvN)' £V.<x8M9sc_À%dM$ p`iɩnp}E}*]E|%<$v*'PN¢݇kV0y,!o2LAXpTE&¸1/wg@7jKvYr7%Ptw⣹}im`̬4j -M|B_k6u.$.a>H Z8 /흴3k_ٝ`B(HG4f[Jm{/ e{ ֓]qH'1e_LZ٭ -rĀifeŦruɈah~F/%-&O-yn-7>m|f]5 tySs9Pa:bϝn>y9rc1$bLNg3-%%"AۛK(U3ya1!9b<ᵈ|yzaK#_ޛBJ|b{ʇV>p$x Ka]hc*IfTYt|JQJ у|pz (E g1ǣݨ.$v8O$:@IU*+X0W"ђ8%ף{MNe'!F0K?y ӾwO>Y췋2N{F?Qp [`8&-h3& oysø߈Adl3JR@y{HwE҅ĽjU!wߚ[a8GS#U\cx@?7Rgkf2.'"B>*=K=Ŝ# D6Z55A‡iȪbJU.%Z5 ' 7K 9#kziΒ?JVP@Q*ldžΟ:5%P=Iqq1m}m,`6ˍ}ap-ǣ VEo) -sh,:8?_fdJX;&mm-0T09^1`,/r"g6Qh>N߬ K*rSe.͍`G㶢y|?S-vVpv3ՠ5RU_c9~ K{]5([OSS _ erG-S?fV( -Cs]e tFqM3ߝ+U^WqzE";ՙh5[>#!-&%."W;'3P7`°$W@"A YhDM}].NTv.FC?ӠЋê}lNcnšz~mky1giE{:I^R_HÉkwNy&PPrX_ -;ӸFd4L퓋=w%1l(/Ϸbgz '}`g(ď w -GCv nJH{/p#'n2#FBgE*iuJVeYtb<5Sz6\B>nP8YjقL$B 9R\*g*]8(|Wyjܳ .=IMG+Ih ifqZPχ=72Ǒn$ 3D>bDFϚ$ؤAWveY BoI[a+.J5,JtƤ!Y ̀'5qCPZZd+4rwsÑX"XJEѵaDgH̃\q{O?߾Y#W+wk`Um-OƱ* c8n8G$蠟-\T#oiutXX]憚tcmslbڙqd,$#$ح@AK25,*YYk|,e[e9D?c%TbZZbbsZgGssggZ!?Rö6Z[/Pؒ8Q,_40|b>?G} Spk\ojXZM|8;X 2 `a+^3xSD.Bj= ?5xXVLZpjU!A4>:DWEC ;vQI8Q$p8A$Тz<8`k'hGhvnsK)D㐆+!μ|.*4 -Wb]r$H,kV:SSyLJgˣ9YKhGMCDduRW3Mrl]Kɒb2IYA{$؟_Yg՚909R+y:b>MZ -m~ޙ>y&nڙel}4+*}&|$z#( -fr1.wrl8 ;h+(EvDb7]FqCf(nH#"Kn)(ͨ5Xi{T{'Z/:dWY1칛Yt}džO\E~)h@)ʣ4Elyy!{ ȯŀj R%ߐ I5h2Ujdb@͗T;U̎CҦeiJZf(3<+TJJe^ljmsV72]qlRt^n<%H<B.֞憓Ȃg?"!pQ kp=e , O)1ŵYׁej{h4#܁FZ$rso;#V$dr&e;yf( $AJHP/`䵛UE,q. J$Z5gŞ8voua ~rk22reఄ pR|}R)%rv7BM7'&Q#qbw@?{0@=7HQgHۮwQk:!ym' - F)[+ncіG>?)NCi -!:+V`OLۣ߰L@'LG?wze;HhGFxpv(Hu"(r3(OI.Iw8&(|f|N_CZO%R -;ʪaN{0<8\|Q_ei۶̓ X/2R PQMyTPk?9nWHBՂƸ߮/L1/)%9limo#SYTLZ@b[N,E@wQu`_v+j_1p};DN่Ūq||-ogRiJ2pVCqbB1|A9v8__n{CByCw8}ǃ|+͹yn@H(,^?'AQ4ō}[5 -xⒹg7z±⏮gDŽt0̡yd=Q"G3:֪^ɜWaVAA`)h{aqm_鋂O^8۠tf'1ǒW~Z=~a|/c\@y5|$I5@p }| <3 k<8]M? p .<<o;*£߮`-2v]w>?H;Y5߇LشU3 @1}$$s*7,u/|IxeLb2QN=9Zn x=`g}8 [Edkcֲ-p>pZ3E꫓KP u`wvlu]Gi-=w<[9O15V^0$_J5e`G[ \-㥗_BSW&?"8ooqQQ䃺ÌKq//~bZ9k{9~ko~*b8g*DLHpg.9z,f!hb^ϩ|FD|+uͬL˽`f^㏰G_h>ڲ/'.4ZFu!pfOK5=NJᾩ%Q_CA1{ϜoL8G=az<ê'6'>_Q>ld9:P`F+b*9h/JN°VZ` TUme0 -'+d,kj3fY:f,O5>Gx8,M;77ڷc~~R?E~Ncq|4._⅄& -¿0z?运D6|J `&X*1pCY}#EDBCƅzȄ^sGJ@6G -]"H]sh!tWTVީ.wOJ>&zeģ?M-ly` UYyg||[-eєCf8:0^^WDdpW-]VaUh : XE=M%NWl322 Fr9 - zԊ8Z7y yodVޯ4\ëxN~oHyB t1wfBO\>GNw]6̨dV_AO(50RYl+KKѓ-9ÃlZFV:0,+SgflO;+`Ϗr_\deUm5gV]=-`;[:خVg)qA 툘v?ԝʍ۴¦onj(ufm{rkfER5S__{]?2% u8q87(x|'rQ`^GRYop oN2'^oE_8%gۓӚe:ynɱ3*Esa+ 6oG_,CW\'ų ȕxgu~NQWeFm%Lrڏ'Vͅ5yđ1"di;cz!&]%SѺ|o.[s ,`G[γpgbegyY% dJ&sv*fr\.GM+-6%[k#3Жuu1S(1 8GI [xelzm/o.:pLtԮI_eӖzK()[0%0a -SXEJ°(_'%UU{PH?xl蔌R_1K yTjYD\fzO!۟VjbؒL,Ru kGv\4sOʊybD= }eZj[/aױi$hw@Ray!F( C dѪ:Rb/ZbUYgGjJsN2fGN5Y5]Y})Kvqqlxf*\CXJMt aXvnm\+g%|?RMH=1zgw!MɭI*0D?E\*5328y Sz` 9񵖼2м#'6o",0Wtg*I#[Uu>X=. -4r5Д)d\۫+H쳦; 2g1M ˵kPN |*G~PV-E5b_#>6f;,\;/[|o0W8|I59);HJOOLnJohnlHkNbvV^yFނ_8a,g؇ @|Phb̥&B3$p\Uo`D9_Cn$zQ)gBN;n[F]bTF_gj,֕6uu zWmz^-R0ƢCIiZ]6xr6ls7ĽڴT,.ˤ -g$$_N—zDUVŽqiɺ⫳LDlIc׎ޢ6.}  +Q{Pݫ+çh4 -]{b/C%PZ ?\b@q=U3B>6{cM|&}ZnStBl1^e:!!G"eFYɧ|>DYq.z̵bސ+`tΨlJcQ;ZZ*a5(\QAԕiBZâhgDZ S "ÔF x)2 C)Tk ',&LuMpQ!Δ&meh&OJ?+ᔬOF<З͋ɼyќRnLJ溿=vyXK62bKvlOH-p3xj-[X-r# N"`>ސvm!;OU&2g˙ځ@ 82ē㤶Ə0x}n}v3"ī 䄥([%QG^v$0,ld+(7p?ǏO6-c.°4?oOxxCۯ¯"Q/,QWa4;HFbmC6ddY- KRS^7`^5&=+5*DkͣSI}=-lc!-we2Sh$W/W0sQ,O⺊#A;ح/.>$a@Fj{d.&;.?@wpj~~-aHڔYQt9BOsk͑~񅸳;ƽmoӻQRSÕnPl?[cE zc;mk'TfE9,`Vk&[:"RMGRzW+*ԟz~Vn¼e:XU\E -GP2}Z\*c\o06dY^<6NMZj" "\ث7$[9*ZPpc4SU@hW6A"PI?ْzY6IJ7J|oOPCzkyAK) l)Np,z+a+cV;|# r &%JVĬdQaj Nxsg ޜqDJ)jJ ,~V n&ڕmFA&>:(_trd?JSMZGSFfJS &]>W@փOJ x֏j< ʚGvn޼ ( &i:=+A|3+m(zФ.3iPvAs[_˞ S"$_"A7>h9L:5xd1 fm&}Ʃ2WKKe.iL.UTMs̀m6W ™=x3_xޢ0AH\(6Ψ6FIxELU6T^ΩSc*PZzVoY2ߜOgd5(:|pљZѐÂTR%]G1X*0ph"(*lۿXG~Aygҳh @ gPPu=,Iy,P=G޴<ǧ{H!A -= -B]9n6Ym1,PK8K;o76OCӿJ~ݑ&nkό=8'?U\gAK|cK\CA" -\mIU Vi[)Huܪb'aE5q9ӽ%ݕ}[! W~`dw U-mOY#d'@5t;,<-זQO8ykP,nTd+_1yoI*!Q070 8JMv(R*s/Ϧv&Rp!HHFɃ]W$g]Q y%Nԭ UOC\un_~C *%4vܢ%‰كl0^2F~ 996=/ `/v pć0e4:G*,-%| 4Ttuu$5ۇ+J\fo[qC +E'l>h,@[hZBAMr eJ}xsi@B`_)y`mqGz۽bM| tZ) ŽuNcpMSWo3r#]a5Ϳ+Wy{?q*>;^Z9 yƇŒp'\h"ղkpxتTR)oǤp!UK͝Q,K -endstream -endobj -1165 0 obj -<< -/Filter /FlateDecode -/Subtype /Type1C -/Length 11578 ->> -stream -xzwxT/C؅IfF&X* -dLI&d&I2BHB Б*"ǂ~krV< Ͻ̓{wWwI&MqxØtttt4I*͑vJ9Nv9.s\x11ɱƱG:N38-rZ:NNNeN>!N8}r,u~Yty^gogssssMϝs ¹個K%%%եĥe.w\|Df/s͒-mԲYTfʮnޗ}"RDW?TTW7˽Apy<^"7ȫ->o?fv1clj465El9[625c"{'>wKNYER}Џ C7#i׹ "̦b3|E&!/M20,+=? s6Th8<p*NRpXAb8AԒG]5#W@V1 6ZX*|@D&<4?|!%HtP -b˛ Buc*+`ha49ȌVU&=A(+-B0h)((=_?Gg%U!\zFI!h E[)P<rAhh2u= N=UV֞Gn<Mvg(ZeBr@F6 u >3D'_0#m4՛co1336Ӣo|KďdW+jˊ[ TTsvAV8f&33A4%~ pN,ҍ<$ {yˎ[=~B~aQ=N'DW-dcyQQ)WX)SFR۸7r`)qS[SjiiNk ^40B3'i_L_+B+J}n98.]c+Y"ɮW!QC;=L-uӓr**%@XЗ*So -PkKuhx6}mآ"}=k[_HVOZ"?X:-^N9MawU -(l.*)Js3ijݙϡ}[OhĪXS=>R 7m0u2x(5.7x`f -= -M f| 4:G%čњ"0=/GqPÝj6^|f 1Y  ś;2{ss8sK2~yx^U*XPz?APg:HSm3x8߭nȠu%\Fa @ez:o8rl3|DKK(xk cٵ9tAn~V"--!5U@r$'Ѯhꄾ:7Љ0SGs4$&wHAԩR2)Yz!jTjv~E`mQ< -SyEPjB1j#8mIT=- ?)9!.,)Ca^A>U=7i - xk\_O -Ou/1I`<O`O('[[O ߨ6ѰWwyDy]tJ~a|Ӯ%a(| -C"tFI""od'iWd>&SEq෺7+^P/ gB.Mŀ1~weHAH,"+}% -\ېZ:_RhV"*;^WXk#DE6$n0% o`z+(c݀Swѫ9yE)ƚҼrо}T`leib=BgznzšIٯO.ZAmSIog\~ʜp&/VSYq!N|K|G᧊RjRLqBXsFAx>+{a/դV -rxtc2Ful]$B[{y -Gdo z_Ag!%6bz.zΓ87QV >dƜL. 6s]zD 125V˵m"°~6HS {GHx:%<8+۲k4\ ?O - ~n\ef -YL4"G^~U^i#UuH%<W'1Y4US8]ZuFsK}~y.*n8r&7=\f29mVQqd>ǢDR1h/K`v`Α}_`A߲Qmb}<;;;:Ei!` KQ}Ikmv%zW -{X!*X^1Ǝ?1L&8+@#(xt6U'M(V;(F漮/4i)Z9#62 sRh45U4r]08ᡞ!pGx'r;P?/Ql5 0Q)&CGj{ߛ4(nzMQ) -4vE`K.,bmspFjMFU]o[#h֗dF)Eʠ&ڀ:x(OVo9*ԟ(鹪^b\`Ʊe -|p ?25,)ͭO񅍌hiiijjiiABz qtwi`?3% 뛹J@' - i:~B,)8'@y>'"*p1QVkS-BҖ+4 S"H0 ՝ܩ(/-S3NiDtQ]4I42&ǁV*/ϱI@Ep)8汣 a@ 6-El%;!ARyyZ _d/ -݈}:kx ݢγ\_Shǃ$R>upB| -(i|էzU I1m+(,,,((/.~Rb(+-(wx7<;lI2,+gO79rM[n.NmєWlR5n}b1L\ ?!WkTUHQЛP::y Sӧ~,f01Ig s H L:5p^jO/n}}}_8Lr f99R>vw;K'II*Z^F*͕JWwHpwtr|U}3O;sxs_^rdp:4tOӿ9s^fg/`XTR&=?tхp2ez.]]]]]Z]κuw-fȞ=/[#-E2dYZ 땝ݐ#'J?#V%+u=C Z&ϒeZyM%ߒ$$^>Nb3Lv}]ƾbAl沥l-{gϰ٫m=dWu닮]_wuWo`XWkkkEkc{,I?n{sj9[uʼn '2:rҰ,i8 9j!\4Ӆ铳Onײ>,7\bkyHu<4<|h>ހ>o"䇎 -F,` Hé"d҈\}6YR+*H1G;+5BzYnQdVy!:-TMI="R;s+|hvtKEL] !쭓Z]qt@au*,0 qZ+ wZ(G?V56tOIc[B򲻳ٷO0]&#@Dl .pR+iaikƲrCWR] ȁ -ˏ.U ApٽwbDSR|Y4Zӑ"J2(b[: u:783G*{BF#^_OnKx*\ 'רCChcp;m:kD~n*vnݓS7d*} -l3Y]\>e'yŌ<M8JPbN> єhʏ>b )ES%4;#+k,3{2dp֗豳fKx]\w<{^yVp~}o~Ux‡o,~Cߏp?\o>-B^zZM;Vxm!ՇMbilAJ?{ё Iуe/ЍpxN jk+yz*2m؇h%附IW2NZ:q~qk"aryEݙZA=h@GIi\No溛[{:RFm:*~DSS&:6iޙ8p0`L -(:8F5 T:FgxU: ݆q?i -H/ ,"tETBRËt2ژYBe֟Egtְ`?t5Tbzsi~eILg?CZLle#,J; t5^E+, -QU_;8Vp3F,^E~SfGϢnS?,x]ۆ,BlUNș\9uFwz<ҹ'UKBo" ݢ<4op*CH~S"\lGh_, _Oh#*7fxh^Cm -Z;Uő5{`A~.L6 55-B RW9qm;4 _¶h -s|h S &+Qͺ+B)(}@Ý '>R@zmz]NvUq]ߑCt"[?bj+:uxISQ1::8sƖKD*MQ`@3<pMֶ5@kh&ԙG=[" N/ -}JU'3Ss҄T7kTe[ӑu rB$q}"`_)d\xAeVUs{֮b|us8 ###G$:]yr(J]CӽVp@>jYhtQ"$ - ű - q𙞓gl{SK$S'N#h!| ݧ#kh-V`xXNr tEƶQ`|́1!q]Yb_A_#<s=ZV (Ĵ(CyVh:b7GtI?\c@@`i{jeqBR=H@G -m_&K - yn߇Ē1"@[EbK9Z{Y?j&:hZf% S5ݡ҉Pݡt]&c}eMg/pHBד'ugD>&FW0Q2z=KWL=Ksn߾mجKTW-WtG+D`s21;{x@^(q?HC_j;|BO:6# r{ByGq.6 Ck -ʄlGUWZmL:`"2?5.,_2:dzj̸<,Vz;m\ҋ +5@;L p63I+LK| y`3XC[*?zmĹYy,Aq}GESl(cx[3a_b)q!vSSPP?GD)D٥o)pCJ# 8x!A?ޜ4oJs[BxLt]U p6|ɧmy&`a6 tpz'פ|Q 1oYb ZWDjcQea)r|?nMĆh9ZQ \VC{?[d y[K0yEGV+߄C|3H42ju#?K=cў p>db HnMl%:HQûz!F\DB,hjŔ5) h Pvܥ>' [ -e@<щP.8+r9|Lh02+cb=]s:ַߜ={\{x}sV='фna;/?d9qt]QfыC -,xC; N 2kܶjPңdֱC~ M\THr`AM} esXnS?=tG[G>w=0aK6nogm7ڣxo[|=:w≯gCXUtrf47jH2 )=-KO.({(BA")Jah y4/p6@S ;`#ёjn:0={aәx P]Q9:7gw:@I> -stream -0 g 0 G -0 g 0 G -0 g 0 G -0 g 0 G -0 g 0 G -BT -/F46 8.9664 Tf 256.776 645.656 Td [(Pro)-28(cess)-343(0)-8224(Pro)-28(cess)-343(1)]TJ -33.967 -10.959 Td [(I)-1333(GLOB\050I\051)-1334(X)1(\050I\051)-4657(I)-1334(GL)1(OB\050I\051)-1334(X\050I\051)]TJ -1.282 -10.959 Td [(1)-4966(1)-1961(1.0)-4514(1)-4452(33)-1961(2.0)]TJ 0 -10.959 Td [(2)-4966(2)-1961(1.0)-4514(2)-4452(34)-1961(2.0)]TJ 0 -10.959 Td [(3)-4966(3)-1961(1.0)-4514(3)-4452(35)-1961(2.0)]TJ 0 -10.959 Td [(4)-4966(4)-1961(1.0)-4514(4)-4452(36)-1961(2.0)]TJ 0 -10.959 Td [(5)-4966(5)-1961(1.0)-4514(5)-4452(37)-1961(2.0)]TJ 0 -10.959 Td [(6)-4966(6)-1961(1.0)-4514(6)-4452(38)-1961(2.0)]TJ 0 -10.959 Td [(7)-4966(7)-1961(1.0)-4514(7)-4452(39)-1961(2.0)]TJ 0 -10.958 Td [(8)-4966(8)-1961(1.0)-4514(8)-4452(40)-1961(2.0)]TJ 0 -10.959 Td [(9)-4966(9)-1961(1.0)-4514(9)-4452(41)-1961(2.0)]TJ -4.607 -10.959 Td [(10)-4452(10)-1961(1.0)-4000(10)-4452(42)-1961(2.0)]TJ 0 -10.959 Td [(11)-4452(11)-1961(1.0)-4000(11)-4452(43)-1961(2.0)]TJ 0 -10.959 Td [(12)-4452(12)-1961(1.0)-4000(12)-4452(44)-1961(2.0)]TJ 0 -10.959 Td [(13)-4452(13)-1961(1.0)-4000(13)-4452(45)-1961(2.0)]TJ 0 -10.959 Td [(14)-4452(14)-1961(1.0)-4000(14)-4452(46)-1961(2.0)]TJ 0 -10.959 Td [(15)-4452(15)-1961(1.0)-4000(15)-4452(47)-1961(2.0)]TJ 0 -10.959 Td [(16)-4452(16)-1961(1.0)-4000(16)-4452(48)-1961(2.0)]TJ 0 -10.959 Td [(17)-4452(17)-1961(1.0)-4000(17)-4452(49)-1961(2.0)]TJ 0 -10.958 Td [(18)-4452(18)-1961(1.0)-4000(18)-4452(50)-1961(2.0)]TJ 0 -10.959 Td [(19)-4452(19)-1961(1.0)-4000(19)-4452(51)-1961(2.0)]TJ 0 -10.959 Td [(20)-4452(20)-1961(1.0)-4000(20)-4452(52)-1961(2.0)]TJ 0 -10.959 Td [(21)-4452(21)-1961(1.0)-4000(21)-4452(53)-1961(2.0)]TJ 0 -10.959 Td [(22)-4452(22)-1961(1.0)-4000(22)-4452(54)-1961(2.0)]TJ 0 -10.959 Td [(23)-4452(23)-1961(1.0)-4000(23)-4452(55)-1961(2.0)]TJ 0 -10.959 Td [(24)-4452(24)-1961(1.0)-4000(24)-4452(56)-1961(2.0)]TJ 0 -10.959 Td [(25)-4452(25)-1961(1.0)-4000(25)-4452(57)-1961(2.0)]TJ 0 -10.959 Td [(26)-4452(26)-1961(1.0)-4000(26)-4452(58)-1961(2.0)]TJ 0 -10.959 Td [(27)-4452(27)-1961(1.0)-4000(27)-4452(59)-1961(2.0)]TJ 0 -10.958 Td [(28)-4452(28)-1961(1.0)-4000(28)-4452(60)-1961(2.0)]TJ 0 -10.959 Td [(29)-4452(29)-1961(1.0)-4000(29)-4452(61)-1961(2.0)]TJ 0 -10.959 Td [(30)-4452(30)-1961(1.0)-4000(30)-4452(62)-1961(2.0)]TJ 0 -10.959 Td [(31)-4452(31)-1961(1.0)-4000(31)-4452(63)-1961(2.0)]TJ 0 -10.959 Td [(32)-4452(32)-1961(1.0)-4000(32)-4452(64)-1961(2.0)]TJ 0 -10.959 Td [(33)-4452(33)-1961(2.0)-4000(33)-4452(25)-1961(1.0)]TJ 0 -10.959 Td [(34)-4452(34)-1961(2.0)-4000(34)-4452(26)-1961(1.0)]TJ 0 -10.959 Td [(35)-4452(35)-1961(2.0)-4000(35)-4452(27)-1961(1.0)]TJ 0 -10.959 Td [(36)-4452(36)-1961(2.0)-4000(36)-4452(28)-1961(1.0)]TJ 0 -10.959 Td [(37)-4452(37)-1961(2.0)-4000(37)-4452(29)-1961(1.0)]TJ 0 -10.958 Td [(38)-4452(38)-1961(2.0)-4000(38)-4452(30)-1961(1.0)]TJ 0 -10.959 Td [(39)-4452(39)-1961(2.0)-4000(39)-4452(31)-1961(1.0)]TJ 0 -10.959 Td [(40)-4452(40)-1961(2.0)-4000(40)-4452(32)-1961(1.0)]TJ -0 g 0 G -0 g 0 G -/F8 9.9626 Tf 100.659 -105.903 Td [(52)]TJ -0 g 0 G -ET - -endstream -endobj -1176 0 obj -<< -/Length 8516 +/Length 6787 >> stream 0 g 0 G @@ -12098,309 +11554,532 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(o)31(vrl)-375(|)-375(Ov)31(erlap)-375(Up)-31(date)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(These)-333(s)-1(u)1(broutines)-334(applies)-333(an)-333(o)27(v)28(erlap)-333(op)-28(erator)-333(to)-333(the)-334(input)-333(v)28(ector:)]TJ/F11 9.9626 Tf 154.475 -22.077 Td [(x)]TJ/F14 9.9626 Tf 8.462 0 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(Qx)]TJ/F8 9.9626 Tf -175.667 -20.14 Td [(where:)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(spsm)-375(|)-375(T)94(riangular)-375(System)-375(Solv)31(e)]TJ/F8 9.9626 Tf -25.091 -19.095 Td [(This)-333(subroutine)-334(computes)-333(the)-333(T)83(riangular)-333(System)-334(Solv)28(e:)]TJ/F11 9.9626 Tf 121.693 -35.01 Td [(y)]TJ/F14 9.9626 Tf 15.204 0 Td [(\040)]TJ/F11 9.9626 Tf 19.925 0 Td [(\013)-4(T)]TJ/F13 6.9738 Tf 13.616 4.113 Td [(\000)]TJ/F7 6.9738 Tf 6.227 0 Td [(1)]TJ/F11 9.9626 Tf 4.469 -4.113 Td [(x)]TJ/F8 9.9626 Tf 7.908 0 Td [(+)]TJ/F11 9.9626 Tf 9.962 0 Td [(\014)-53(y)]TJ -77.311 -14.944 Td [(y)]TJ/F14 9.9626 Tf 15.204 0 Td [(\040)]TJ/F11 9.9626 Tf 19.925 0 Td [(\013)-4(D)-28(T)]TJ/F13 6.9738 Tf 22.141 4.113 Td [(\000)]TJ/F7 6.9738 Tf 6.227 0 Td [(1)]TJ/F11 9.9626 Tf 4.469 -4.113 Td [(x)]TJ/F8 9.9626 Tf 7.908 0 Td [(+)]TJ/F11 9.9626 Tf 9.962 0 Td [(\014)-53(y)]TJ -85.836 -14.944 Td [(y)]TJ/F14 9.9626 Tf 15.204 0 Td [(\040)]TJ/F11 9.9626 Tf 19.925 0 Td [(\013)-4(T)]TJ/F13 6.9738 Tf 13.616 4.113 Td [(\000)]TJ/F7 6.9738 Tf 6.227 0 Td [(1)]TJ/F11 9.9626 Tf 4.469 -4.113 Td [(D)-28(x)]TJ/F8 9.9626 Tf 16.433 0 Td [(+)]TJ/F11 9.9626 Tf 9.962 0 Td [(\014)-53(y)]TJ -85.836 -14.944 Td [(y)]TJ/F14 9.9626 Tf 15.204 0 Td [(\040)]TJ/F11 9.9626 Tf 19.925 0 Td [(\013)-4(T)]TJ/F13 6.9738 Tf 13.616 4.113 Td [(\000)]TJ/F10 6.9738 Tf 6.227 0 Td [(T)]TJ/F11 9.9626 Tf 6.276 -4.113 Td [(x)]TJ/F8 9.9626 Tf 7.908 0 Td [(+)]TJ/F11 9.9626 Tf 9.962 0 Td [(\014)-53(y)]TJ -79.118 -14.944 Td [(y)]TJ/F14 9.9626 Tf 15.204 0 Td [(\040)]TJ/F11 9.9626 Tf 19.925 0 Td [(\013)-4(D)-28(T)]TJ/F13 6.9738 Tf 22.141 4.113 Td [(\000)]TJ/F10 6.9738 Tf 6.227 0 Td [(T)]TJ/F11 9.9626 Tf 6.276 -4.113 Td [(x)]TJ/F8 9.9626 Tf 7.908 0 Td [(+)]TJ/F11 9.9626 Tf 9.962 0 Td [(\014)-53(y)]TJ -87.643 -14.944 Td [(y)]TJ/F14 9.9626 Tf 15.204 0 Td [(\040)]TJ/F11 9.9626 Tf 19.925 0 Td [(\013)-4(T)]TJ/F13 6.9738 Tf 13.616 4.113 Td [(\000)]TJ/F10 6.9738 Tf 6.227 0 Td [(T)]TJ/F11 9.9626 Tf 6.276 -4.113 Td [(D)-28(x)]TJ/F8 9.9626 Tf 16.433 0 Td [(+)]TJ/F11 9.9626 Tf 9.962 0 Td [(\014)-53(y)]TJ -87.643 -14.944 Td [(y)]TJ/F14 9.9626 Tf 15.204 0 Td [(\040)]TJ/F11 9.9626 Tf 19.925 0 Td [(\013)-4(T)]TJ/F13 6.9738 Tf 13.616 4.113 Td [(\000)]TJ/F10 6.9738 Tf 6.227 0 Td [(H)]TJ/F11 9.9626 Tf 7.556 -4.113 Td [(x)]TJ/F8 9.9626 Tf 7.908 0 Td [(+)]TJ/F11 9.9626 Tf 9.962 0 Td [(\014)-53(y)]TJ -80.398 -14.944 Td [(y)]TJ/F14 9.9626 Tf 15.204 0 Td [(\040)]TJ/F11 9.9626 Tf 19.925 0 Td [(\013)-4(D)-28(T)]TJ/F13 6.9738 Tf 22.141 4.113 Td [(\000)]TJ/F10 6.9738 Tf 6.227 0 Td [(H)]TJ/F11 9.9626 Tf 7.556 -4.113 Td [(x)]TJ/F8 9.9626 Tf 7.908 0 Td [(+)]TJ/F11 9.9626 Tf 9.962 0 Td [(\014)-53(y)]TJ -88.923 -14.944 Td [(y)]TJ/F14 9.9626 Tf 15.204 0 Td [(\040)]TJ/F11 9.9626 Tf 19.925 0 Td [(\013)-4(T)]TJ/F13 6.9738 Tf 13.616 4.113 Td [(\000)]TJ/F10 6.9738 Tf 6.227 0 Td [(H)]TJ/F11 9.9626 Tf 7.556 -4.113 Td [(D)-28(x)]TJ/F8 9.9626 Tf 16.433 0 Td [(+)]TJ/F11 9.9626 Tf 9.962 0 Td [(\014)-53(y)]TJ/F8 9.9626 Tf -195.672 -37.999 Td [(where:)]TJ 0 g 0 G -/F11 9.9626 Tf 0 -18.503 Td [(x)]TJ +/F11 9.9626 Tf -14.944 -21.063 Td [(x)]TJ +0 g 0 G +/F8 9.9626 Tf 10.676 0 Td [(is)-333(the)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 116.092 0 Td [(x)]TJ/F7 6.9738 Tf 5.694 -1.494 Td [(:)]TJ/F10 6.9738 Tf 2.256 0 Td [(;)]TJ/F7 6.9738 Tf 2.366 0 Td [(:)]TJ +0 g 0 G +/F11 9.9626 Tf -137.084 -19.948 Td [(y)]TJ +0 g 0 G +/F8 9.9626 Tf 10.224 0 Td [(is)-333(the)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 116.092 0 Td [(y)]TJ/F7 6.9738 Tf 4.885 -1.494 Td [(:)]TJ/F10 6.9738 Tf 2.255 0 Td [(;)]TJ/F7 6.9738 Tf 2.366 0 Td [(:)]TJ +0 g 0 G +/F11 9.9626 Tf -135.822 -19.948 Td [(T)]TJ +0 g 0 G +/F8 9.9626 Tf 12.187 0 Td [(is)-333(the)-334(global)-333(sparse)-333(blo)-28(c)28(k)-334(triangular)-333(submatrix)]TJ/F11 9.9626 Tf 206.781 0 Td [(T)]TJ 0 g 0 G -/F8 9.9626 Tf 10.676 0 Td [(is)-333(the)-334(global)-333(dense)-333(submatrix)]TJ/F11 9.9626 Tf 131.092 0 Td [(x)]TJ + -218.968 -21.441 Td [(D)]TJ 0 g 0 G - -141.768 -19.214 Td [(Q)]TJ +/F8 9.9626 Tf 13.507 0 Td [(is)-333(the)-334(scaling)-333(diagonal)-333(matrix.)]TJ 0 g 0 G -/F8 9.9626 Tf 12.858 0 Td [(is)-333(the)-334(o)28(v)28(erlap)-333(op)-28(erator;)-333(it)-334(is)-333(the)-333(comp)-28(osition)-334(of)-333(t)28(w)28(o)-334(op)-27(erators)]TJ/F11 9.9626 Tf 271.842 0 Td [(P)]TJ/F10 6.9738 Tf 6.396 -1.494 Td [(a)]TJ/F8 9.9626 Tf 8.14 1.494 Td [(and)]TJ/F11 9.9626 Tf 19.372 0 Td [(P)]TJ/F10 6.9738 Tf 7.78 3.616 Td [(T)]TJ/F8 9.9626 Tf 6.276 -3.616 Td [(.)]TJ +0 g 0 G +/F30 9.9626 Tf -13.507 -23.814 Td [(call)-525(psb_spsm\050alpha,)-525(t,)-525(x,)-525(beta,)-525(y,)-525(desc_a,)-525(info\051)]TJ 0 -11.955 Td [(call)-525(psb_spsm\050alpha,)-525(t,)-525(x,)-525(beta,)-525(y,)-525(desc_a,)-525(info,&)]TJ 67.995 -11.955 Td [(&)-525(trans,)-525(unit,)-525(choice,)-525(diag,)-525(work\051)]TJ 0 g 0 G 0 g 0 G 0 g 0 G ET q -1 0 0 1 177.988 587.879 cm +1 0 0 1 177.988 335.134 cm []0 d 0 J 0.398 w 0 0 m 187.526 0 l S Q BT -/F11 9.9626 Tf 183.966 579.311 Td [(x)]TJ/F27 9.9626 Tf 120.409 0 Td [(Subroutine)]TJ +/F11 9.9626 Tf 183.966 326.566 Td [(T)]TJ/F8 9.9626 Tf 7.205 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(,)]TJ/F11 9.9626 Tf 6.089 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(D)]TJ/F8 9.9626 Tf 8.525 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(\013)]TJ/F8 9.9626 Tf 6.41 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(\014)]TJ/F27 9.9626 Tf 56.892 0 Td [(Subroutine)]TJ ET q -1 0 0 1 177.988 575.525 cm +1 0 0 1 177.988 322.78 cm []0 d 0 J 0.398 w 0 0 m 187.526 0 l S Q BT -/F8 9.9626 Tf 183.966 566.957 Td [(Short)-333(Precision)-333(R)-1(eal)-3102(psb)]TJ +/F8 9.9626 Tf 183.966 314.213 Td [(Short)-333(Precision)-333(R)-1(eal)-3102(psb)]TJ ET q -1 0 0 1 319.972 567.156 cm +1 0 0 1 319.972 314.412 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 322.961 566.957 Td [(o)28(vrl)]TJ -138.995 -11.955 Td [(Long)-333(Precision)-334(Real)-3314(p)1(s)-1(b)]TJ +/F8 9.9626 Tf 322.961 314.213 Td [(spsm)]TJ -138.995 -11.956 Td [(Long)-333(Precision)-334(Real)-3314(p)1(s)-1(b)]TJ ET q -1 0 0 1 319.972 555.201 cm +1 0 0 1 319.972 302.457 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 322.961 555.002 Td [(o)28(vrl)]TJ -138.995 -11.955 Td [(Short)-333(Precision)-333(C)-1(omplex)-1200(p)1(s)-1(b)]TJ +/F8 9.9626 Tf 322.961 302.257 Td [(spsm)]TJ -138.995 -11.955 Td [(Short)-333(Precision)-333(C)-1(omplex)-1200(p)1(s)-1(b)]TJ ET q -1 0 0 1 319.972 543.246 cm +1 0 0 1 319.972 290.501 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 322.961 543.047 Td [(o)28(vrl)]TJ -138.995 -11.956 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ +/F8 9.9626 Tf 322.961 290.302 Td [(spsm)]TJ -138.995 -11.955 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ ET q -1 0 0 1 319.972 531.291 cm +1 0 0 1 319.972 278.546 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 322.961 531.091 Td [(o)28(vrl)]TJ +/F8 9.9626 Tf 322.961 278.347 Td [(spsm)]TJ ET q -1 0 0 1 177.988 527.306 cm +1 0 0 1 177.988 274.561 cm []0 d 0 J 0.398 w 0 0 m 187.526 0 l S Q 0 g 0 G BT -/F8 9.9626 Tf 225.577 499.266 Td [(T)83(able)-333(15:)-444(Data)-334(t)28(yp)-28(es)]TJ +/F8 9.9626 Tf 225.577 246.522 Td [(T)83(able)-333(13:)-444(Data)-334(t)28(yp)-28(es)]TJ 0 g 0 G 0 g 0 G -/F27 9.9626 Tf -124.305 -28.465 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.881 0 Td [(p)-137(s)-138(b)]TJ -ET -q -1 0 0 1 150.859 471 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F8 9.9626 Tf 155.217 470.801 Td [(o)-138(v)-137(r)-137(l)-243(\050)-130(x)-209(,)-874(d)-113(e)-112(s)-113(c)]TJ +0 g 0 G +/F27 9.9626 Tf -125.682 -35.492 Td [(T)32(yp)-32(e:)]TJ +0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ +0 g 0 G +/F27 9.9626 Tf -33.797 -21.442 Td [(On)-383(En)32(try)]TJ +0 g 0 G +0 g 0 G + 0 -21.442 Td [(alpha)]TJ +0 g 0 G +/F8 9.9626 Tf 32.033 0 Td [(the)-333(scalar)]TJ/F11 9.9626 Tf 45.468 0 Td [(\013)]TJ/F8 9.9626 Tf 6.41 0 Td [(.)]TJ -59.004 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(n)28(um)28(b)-28(er)-333(of)-334(the)-333(data)-333(t)28(yp)-28(e)-334(ind)1(ic)-1(ated)-333(in)-333(T)83(able)]TJ +0 0 1 rg 0 0 1 RG + [-333(13)]TJ +0 g 0 G + [(.)]TJ +0 g 0 G + 141.968 -29.888 Td [(49)]TJ +0 g 0 G ET -q -1 0 0 1 226.044 471 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q + +endstream +endobj +1167 0 obj +<< +/Length 7789 +>> +stream +0 g 0 G +0 g 0 G +0 g 0 G BT -/F8 9.9626 Tf 230.155 470.801 Td [(a)-386(,)-914(i)-152(n)-152(f)-152(o)-258(\051)]TJ/F27 9.9626 Tf -128.883 -11.955 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.881 0 Td [(p)-137(s)-138(b)]TJ +/F27 9.9626 Tf 150.705 706.129 Td [(t)]TJ +0 g 0 G +/F8 9.9626 Tf 9.437 0 Td [(the)-333(global)-334(p)-27(ortion)-334(of)-333(the)-333(sparse)-334(matrix)]TJ/F11 9.9626 Tf 172.603 0 Td [(T)]TJ/F8 9.9626 Tf 7.205 0 Td [(.)]TJ -164.339 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(t)28(yp)-28(e)-333(sp)-28(eci\014ed)-333(in)]TJ/F14 9.9626 Tf 176.118 0 Td [(x)]TJ +0 0 1 rg 0 0 1 RG +/F8 9.9626 Tf 7.749 0 Td [(3)]TJ +0 g 0 G + [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -208.773 -20.65 Td [(x)]TJ +0 g 0 G +/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -167.934 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-56(j)1(e)-1(ct)-254(of)-255(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 244.743 0 Td [(psb)]TJ ET q -1 0 0 1 150.859 459.045 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 436.673 590.037 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F8 9.9626 Tf 155.217 458.846 Td [(o)-138(v)-137(r)-137(l)-243(\050)-130(x)-209(,)-874(d)-113(e)-112(s)-113(c)]TJ +/F30 9.9626 Tf 439.811 589.838 Td [(T)]TJ ET q -1 0 0 1 226.044 459.045 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 445.669 590.037 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F8 9.9626 Tf 230.155 458.846 Td [(a)-386(,)-888(i)-127(n)-127(f)-127(o)-415(,)-847(u)-85(p)-86(d)-86(a)-85(t)-86(e)3(=)-13(u)-102(p)-101(d)-102(a)-102(t)-102(e)]TJ +/F30 9.9626 Tf 448.807 589.838 Td [(vect)]TJ ET q -1 0 0 1 364.631 459.045 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 470.356 590.037 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F8 9.9626 Tf 368.634 458.846 Td [(t)-102(y)-102(p)-101(e)-365(,)-813(w)-52(o)-51(r)-52(k)37(=)38(w)-52(o)-52(r)-51(k)-158(\051)]TJ -0 g 0 G +/F30 9.9626 Tf 473.495 589.838 Td [(type)]TJ 0 g 0 G +/F8 9.9626 Tf -297.884 -11.955 Td [(con)28(taining)-342(n)28(um)28(b)-28(ers)-342(of)-342(t)28(yp)-28(e)-342(sp)-28(eci\014ed)-342(in)-341(T)83(able)]TJ +0 0 1 rg 0 0 1 RG + [-342(13)]TJ 0 g 0 G -/F27 9.9626 Tf -268.739 -25.406 Td [(T)32(yp)-32(e:)]TJ + [(.)-470(The)-342(rank)-342(of)]TJ/F11 9.9626 Tf 274.695 0 Td [(x)]TJ/F8 9.9626 Tf 9.1 0 Td [(m)28(ust)-342(b)-28(e)]TJ -283.795 -11.956 Td [(the)-333(same)-334(of)]TJ/F11 9.9626 Tf 53.467 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ +/F27 9.9626 Tf -83.615 -20.649 Td [(b)-32(eta)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.214 Td [(On)-383(En)32(try)]TJ +/F8 9.9626 Tf 26.94 0 Td [(the)-333(scalar)]TJ/F11 9.9626 Tf 45.469 0 Td [(\014)]TJ/F8 9.9626 Tf 6.161 0 Td [(.)]TJ -53.663 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-334(n)28(um)28(b)-28(er)-333(of)-334(the)-333(data)-333(t)28(yp)-28(e)-334(in)1(dicate)-1(d)-333(in)-333(T)83(able)]TJ +0 0 1 rg 0 0 1 RG + [-333(13)]TJ 0 g 0 G + [(.)]TJ 0 g 0 G - 0 -19.214 Td [(x)]TJ +/F27 9.9626 Tf -24.907 -20.65 Td [(y)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(global)-333(dense)-334(matrix)]TJ/F11 9.9626 Tf 88.917 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -80.732 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-55(jec)-1(t)-254(of)-255(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -167.481 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)28(o)-255(arra)28(y)-255(or)-255(an)-255(ob)-55(ject)-255(of)-255(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 244.743 0 Td [(psb)]TJ +/F30 9.9626 Tf 244.742 0 Td [(psb)]TJ ET q -1 0 0 1 385.864 347.39 cm +1 0 0 1 436.673 429.186 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 389.002 347.191 Td [(T)]TJ +/F30 9.9626 Tf 439.811 428.986 Td [(T)]TJ ET q -1 0 0 1 394.86 347.39 cm +1 0 0 1 445.669 429.186 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 397.998 347.191 Td [(vect)]TJ +/F30 9.9626 Tf 448.807 428.986 Td [(vect)]TJ ET q -1 0 0 1 419.547 347.39 cm +1 0 0 1 470.356 429.186 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 422.685 347.191 Td [(type)]TJ +/F30 9.9626 Tf 473.495 428.986 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf -297.883 -11.955 Td [(con)28(taining)-333(n)27(um)28(b)-28(ers)-333(of)-333(t)28(yp)-28(e)-334(sp)-27(eci\014ed)-334(in)-333(T)83(able)]TJ +/F8 9.9626 Tf -297.884 -11.955 Td [(con)28(taining)-345(n)28(um)28(b)-28(ers)-345(of)-345(t)28(yp)-28(e)-345(sp)-28(eci\014ed)-345(in)-345(T)84(able)]TJ 0 0 1 rg 0 0 1 RG - [-333(15)]TJ + [-345(13)]TJ 0 g 0 G - [(.)]TJ + [(.)-479(The)-345(rank)-345(of)]TJ/F11 9.9626 Tf 275.087 0 Td [(y)]TJ/F8 9.9626 Tf 8.678 0 Td [(m)28(ust)-345(b)-28(e)]TJ -283.765 -11.955 Td [(the)-333(same)-334(of)]TJ/F11 9.9626 Tf 53.467 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.214 Td [(desc)]TJ +/F27 9.9626 Tf -84.067 -20.65 Td [(desc)]TJ ET q -1 0 0 1 121.81 316.221 cm +1 0 0 1 172.619 384.625 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 125.247 316.022 Td [(a)]TJ +/F27 9.9626 Tf 176.057 384.426 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(con)28(tains)-334(d)1(ata)-334(structures)-333(for)-333(com)-1(m)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.55 0 Td [(con)28(tains)-334(data)-333(structures)-333(for)-333(c)-1(omm)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ +/F30 9.9626 Tf 135.659 0 Td [(psb)]TJ ET q -1 0 0 1 312.036 268.401 cm +1 0 0 1 327.588 336.805 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 315.174 268.201 Td [(desc)]TJ +/F30 9.9626 Tf 330.727 336.605 Td [(desc)]TJ ET q -1 0 0 1 336.723 268.401 cm +1 0 0 1 352.275 336.805 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 339.861 268.201 Td [(type)]TJ +/F30 9.9626 Tf 355.414 336.605 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -260.887 -19.214 Td [(up)-32(date)]TJ +/F27 9.9626 Tf -225.63 -20.649 Td [(trans)]TJ 0 g 0 G -/F8 9.9626 Tf 39.671 0 Td [(Up)-28(date)-333(op)-28(erator.)]TJ +/F8 9.9626 Tf 30.609 0 Td [(sp)-28(ecify)-333(with)]TJ/F17 9.9626 Tf 55.68 0 Td [(unitd)]TJ/F8 9.9626 Tf 25.725 0 Td [(the)-333(op)-28(eration)-333(to)-334(p)-27(e)-1(r)1(form.)]TJ 0 g 0 G -/F27 9.9626 Tf -14.764 -31.169 Td [(up)-32(date)-383(=)-384(psb)]TJ -ET -q -1 0 0 1 193.977 218.017 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 197.414 217.818 Td [(none)]TJ -ET -q -1 0 0 1 221.811 218.017 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q +/F27 9.9626 Tf -87.108 -20.65 Td [(trans)-383(=)-384('N')]TJ +0 g 0 G +/F8 9.9626 Tf 62.489 0 Td [(the)-333(op)-28(eration)-333(is)-334(with)-333(no)-333(transp)-28(osed)-333(matrix)]TJ +0 g 0 G +/F27 9.9626 Tf -62.489 -16.303 Td [(trans)-383(=)-384('T')]TJ +0 g 0 G +/F8 9.9626 Tf 61.493 0 Td [(the)-333(op)-28(eration)-333(is)-334(with)-333(transp)-28(osed)-333(matrix.)]TJ +0 g 0 G +/F27 9.9626 Tf -61.493 -16.302 Td [(trans)-383(=)-384('C')]TJ +0 g 0 G +/F8 9.9626 Tf 61.798 0 Td [(the)-333(op)-28(eration)-333(is)-334(with)-333(conjugate)-333(transp)-28(osed)-333(matrix.)]TJ -61.798 -20.65 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Default:)]TJ/F11 9.9626 Tf 39.436 0 Td [(tr)-28(ans)]TJ/F8 9.9626 Tf 27.052 0 Td [(=)]TJ/F11 9.9626 Tf 10.517 0 Td [(N)]TJ/F8 9.9626 Tf -77.005 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(c)28(haracter)-334(v)56(ariable.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.906 -20.65 Td [(unitd)]TJ +0 g 0 G +/F8 9.9626 Tf 31.714 0 Td [(sp)-28(ecify)-333(with)]TJ/F17 9.9626 Tf 55.68 0 Td [(tr)51(ans)]TJ/F8 9.9626 Tf 25.089 0 Td [(the)-333(op)-28(eration)-333(to)-334(p)-27(erform.)]TJ +0 g 0 G +/F27 9.9626 Tf -87.577 -20.649 Td [(unitd)-383(=)-384('U')]TJ +0 g 0 G +/F8 9.9626 Tf 63.443 0 Td [(the)-333(op)-28(eration)-333(is)-334(with)-333(no)-333(scaling)]TJ +0 g 0 G +/F27 9.9626 Tf -63.443 -16.303 Td [(unitd)-383(=)-384('L')]TJ +0 g 0 G +/F8 9.9626 Tf 61.519 0 Td [(the)-333(op)-28(eration)-333(is)-334(with)-333(left)-333(scaling)]TJ +0 g 0 G +/F27 9.9626 Tf -61.519 -16.302 Td [(unitd)-383(=)-384('R')]TJ +0 g 0 G +/F8 9.9626 Tf 63.221 0 Td [(the)-333(op)-28(eration)-333(is)-334(with)-333(righ)28(t)-333(s)-1(caling.)]TJ +0 g 0 G + 78.747 -29.888 Td [(50)]TJ +0 g 0 G +ET + +endstream +endobj +1173 0 obj +<< +/Length 4663 +>> +stream +0 g 0 G +0 g 0 G +BT +/F8 9.9626 Tf 124.802 706.129 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Default:)]TJ/F11 9.9626 Tf 39.436 0 Td [(unitd)]TJ/F8 9.9626 Tf 26.665 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(U)]TJ/F8 9.9626 Tf -76.617 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(c)28(haracter)-333(v)55(ariable.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.925 Td [(c)32(hoice)]TJ +0 g 0 G +/F8 9.9626 Tf 35.375 0 Td [(sp)-28(eci\014es)-333(the)-334(u)1(p)-28(date)-334(of)-333(o)28(v)28(erlap)-334(elemen)28(ts)-333(to)-334(b)-27(e)-334(p)-27(erformed)-334(on)-333(exit:)]TJ +0 g 0 G +0 g 0 G +/F30 9.9626 Tf -5.487 -19.925 Td [(psb_none_)]TJ +0 g 0 G +0 g 0 G + 0 -15.941 Td [(psb_sum_)]TJ +0 g 0 G +0 g 0 G + 0 -15.94 Td [(psb_avg_)]TJ +0 g 0 G +0 g 0 G + 0 -15.94 Td [(psb_square_root_)]TJ/F8 9.9626 Tf -4.981 -19.925 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Default:)]TJ/F30 9.9626 Tf 39.436 0 Td [(psb_avg_)]TJ/F8 9.9626 Tf -39.436 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.925 Td [(diag)]TJ +0 g 0 G +/F8 9.9626 Tf 25.827 0 Td [(the)-333(diagonal)-334(scaling)-333(matrix.)]TJ -0.92 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Default:)]TJ/F11 9.9626 Tf 39.436 0 Td [(diag)]TJ/F8 9.9626 Tf 18.993 0 Td [(\0501\051)-278(=)-277(1\050)]TJ/F11 9.9626 Tf 34.869 0 Td [(noscal)-20(ing)]TJ/F8 9.9626 Tf 42.747 0 Td [(\051)]TJ -136.045 -11.955 Td [(Sp)-28(eci\014ed)-382(as:)-543(a)-382(rank)-382(one)-383(arra)28(y)-382(con)27(taining)-382(n)28(um)28(b)-28(ers)-383(of)-382(the)-382(t)27(yp)-27(e)-383(indicated)]TJ 0 -11.955 Td [(in)-333(T)83(able)]TJ +0 0 1 rg 0 0 1 RG + [-333(13)]TJ +0 g 0 G + [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.926 Td [(w)32(ork)]TJ +0 g 0 G +/F8 9.9626 Tf 29.432 0 Td [(a)-333(w)27(ork)-333(arra)28(y)83(.)]TJ -4.525 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-377(as:)-531(a)-377(rank)-376(one)-377(arra)28(y)-377(of)-377(the)-377(same)-377(t)28(yp)-28(e)-377(of)]TJ/F11 9.9626 Tf 225.953 0 Td [(x)]TJ/F8 9.9626 Tf 9.448 0 Td [(with)-377(the)-377(T)84(AR)28(GET)]TJ -235.401 -11.955 Td [(attribute.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.926 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(y)]TJ +0 g 0 G +/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -167.481 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-474(as:)-727(an)-475(arra)28(y)-474(of)-475(rank)-475(on)1(e)-475(or)-475(t)28(w)28(o)-475(con)28(taining)-474(n)27(u)1(m)27(b)-27(e)-1(r)1(s)-475(of)-475(t)28(yp)-28(e)]TJ 0 -11.955 Td [(sp)-28(eci\014ed)-333(in)-333(T)83(able)]TJ +0 0 1 rg 0 0 1 RG + [-333(13)]TJ +0 g 0 G + [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.925 Td [(info)]TJ +0 g 0 G +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ +0 g 0 G + 141.968 -73.723 Td [(51)]TJ +0 g 0 G +ET + +endstream +endobj +1178 0 obj +<< +/Length 651 +>> +stream +0 g 0 G +0 g 0 G +BT +/F16 14.3462 Tf 150.705 706.129 Td [(5)-1125(Comm)31(unication)-375(routines)]TJ/F8 9.9626 Tf 0 -21.821 Td [(The)-283(routines)-283(in)-283(this)-283(c)28(hapter)-283(implemen)28(t)-283(v)55(arious)-283(global)-283(comm)28(unication)-283(op)-28(erators)]TJ 0 -11.955 Td [(on)-344(v)28(ectors)-344(asso)-27(c)-1(iated)-343(with)-344(a)-344(d)1(is)-1(cretization)-343(mesh.)-476(F)84(or)-344(auxiliary)-344(comm)28(unication)]TJ 0 -11.955 Td [(routines)-333(not)-334(tied)-333(to)-333(a)-334(d)1(is)-1(cretization)-333(space)-333(see)]TJ +0 0 1 rg 0 0 1 RG + [-334(6)]TJ +0 g 0 G + [(.)]TJ +0 g 0 G + 166.874 -569.96 Td [(52)]TJ +0 g 0 G +ET + +endstream +endobj +1186 0 obj +<< +/Length 7259 +>> +stream 0 g 0 G -BT -/F8 9.9626 Tf 230.229 217.818 Td [(Do)-333(nothing;)]TJ 0 g 0 G -/F27 9.9626 Tf -105.427 -15.229 Td [(up)-32(date)-383(=)-384(psb)]TJ -ET -q -1 0 0 1 193.977 202.789 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q BT -/F27 9.9626 Tf 197.414 202.589 Td [(add)]TJ +/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ ET q -1 0 0 1 216.4 202.789 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +1 0 0 1 120.951 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q -0 g 0 G BT -/F8 9.9626 Tf 224.819 202.589 Td [(Sum)-333(o)27(v)28(erlap)-333(en)28(tries,)-334(i.e.)-444(apply)]TJ/F11 9.9626 Tf 136.544 0 Td [(P)]TJ/F10 6.9738 Tf 7.78 3.616 Td [(T)]TJ/F8 9.9626 Tf 6.276 -3.616 Td [(;)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(halo)-375(|)-375(Halo)-375(Data)-375(Comm)31(unication)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(These)-333(s)-1(u)1(broutines)-334(gathers)-333(the)-333(v)55(alues)-333(of)-334(th)1(e)-334(halo)-333(elemen)28(ts:)]TJ/F11 9.9626 Tf 158.413 -23.188 Td [(x)]TJ/F14 9.9626 Tf 8.462 0 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(x)]TJ/F8 9.9626 Tf -179.605 -21.251 Td [(where:)]TJ +0 g 0 G +/F11 9.9626 Tf 0 -19.391 Td [(x)]TJ +0 g 0 G +/F8 9.9626 Tf 10.676 0 Td [(is)-333(a)-334(global)-333(dense)-333(submatrix.)]TJ +0 g 0 G +0 g 0 G 0 g 0 G -/F27 9.9626 Tf -250.617 -15.229 Td [(up)-32(date)-383(=)-384(psb)]TJ ET q -1 0 0 1 193.977 187.56 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +1 0 0 1 177.988 602.649 cm +[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S Q BT -/F27 9.9626 Tf 197.414 187.36 Td [(a)32(vg)]TJ +/F11 9.9626 Tf 183.966 594.081 Td [(\013)]TJ/F8 9.9626 Tf 6.41 0 Td [(,)]TJ/F11 9.9626 Tf 6.088 0 Td [(x)]TJ/F27 9.9626 Tf 107.911 0 Td [(Subroutine)]TJ ET q -1 0 0 1 215.127 187.56 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +1 0 0 1 177.988 590.295 cm +[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S Q -0 g 0 G BT -/F8 9.9626 Tf 223.546 187.36 Td [(Av)28(erage)-334(o)28(v)28(erlap)-333(en)27(tri)1(e)-1(s,)-333(i.e.)-444(apply)]TJ/F11 9.9626 Tf 152.345 0 Td [(P)]TJ/F10 6.9738 Tf 6.397 -1.494 Td [(a)]TJ/F11 9.9626 Tf 4.819 1.494 Td [(P)]TJ/F10 6.9738 Tf 7.78 3.616 Td [(T)]TJ/F8 9.9626 Tf 6.276 -3.616 Td [(;)]TJ -276.361 -19.214 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Default:)]TJ/F11 9.9626 Tf 39.436 0 Td [(update)]TJ +/F8 9.9626 Tf 183.966 581.727 Td [(In)28(teger)-9028(psb)]TJ ET q -1 0 0 1 194.239 144.435 cm +1 0 0 1 319.972 581.926 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F11 9.9626 Tf 197.228 144.236 Td [(ty)-36(pe)]TJ/F8 9.9626 Tf 21.258 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(psb)]TJ +/F8 9.9626 Tf 322.961 581.727 Td [(halo)]TJ -138.995 -11.955 Td [(Short)-333(Precision)-333(R)-1(eal)-3102(psb)]TJ ET q -1 0 0 1 243.558 144.435 cm +1 0 0 1 319.972 569.971 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F11 9.9626 Tf 246.547 144.236 Td [(av)-36(g)]TJ +/F8 9.9626 Tf 322.961 569.772 Td [(halo)]TJ -138.995 -11.955 Td [(Long)-333(Precision)-334(Real)-3314(p)1(s)-1(b)]TJ ET q -1 0 0 1 262.706 144.435 cm +1 0 0 1 319.972 558.016 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 124.802 132.281 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(in)28(teger)-333(v)55(ariable.)]TJ -0 g 0 G - 141.968 -29.888 Td [(53)]TJ -0 g 0 G +/F8 9.9626 Tf 322.961 557.817 Td [(halo)]TJ -138.995 -11.955 Td [(Short)-333(Precision)-333(C)-1(omplex)-1200(p)1(s)-1(b)]TJ ET - -endstream -endobj -1188 0 obj -<< -/Length 5872 ->> -stream +q +1 0 0 1 319.972 546.061 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 322.961 545.862 Td [(halo)]TJ -138.995 -11.956 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ +ET +q +1 0 0 1 319.972 534.106 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 322.961 533.906 Td [(halo)]TJ +ET +q +1 0 0 1 177.988 530.121 cm +[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S +Q 0 g 0 G +BT +/F8 9.9626 Tf 225.577 502.081 Td [(T)83(able)-333(14:)-444(Data)-334(t)28(yp)-28(es)]TJ 0 g 0 G 0 g 0 G +/F27 9.9626 Tf -124.305 -29.354 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.731 0 Td [(p)-122(s)-123(b)]TJ +ET +q +1 0 0 1 150.256 472.926 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 154.464 472.727 Td [(h)-122(a)-123(l)-122(o)-228(\050)-130(x)-209(,)-874(d)-112(e)-113(s)-113(c)]TJ +ET +q +1 0 0 1 226.044 472.926 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 230.155 472.727 Td [(a)-386(,)-914(i)-152(n)-152(f)-152(o)-258(\051)]TJ/F27 9.9626 Tf -128.883 -11.955 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.731 0 Td [(p)-122(s)-123(b)]TJ +ET +q +1 0 0 1 150.256 460.971 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 154.464 460.772 Td [(h)-122(a)-123(l)-122(o)-228(\050)-130(x)-209(,)-874(d)-112(e)-113(s)-113(c)]TJ +ET +q +1 0 0 1 226.044 460.971 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q BT -/F27 9.9626 Tf 150.705 706.129 Td [(w)32(ork)]TJ +/F8 9.9626 Tf 230.155 460.772 Td [(a)-386(,)-888(i)-127(n)-127(f)-127(o)-415(,)-804(w)-43(o)-43(r)-43(k)-247(,)]TJ/F27 9.9626 Tf 91.304 0 Td [(d)-39(a)-39(t)-40(a)]TJ/F8 9.9626 Tf 24.571 0 Td [(\051)]TJ 0 g 0 G -/F8 9.9626 Tf 29.431 0 Td [(the)-333(w)27(ork)-333(arra)28(y)83(.)]TJ -4.525 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(one)-333(dimensional)-334(arr)1(a)27(y)-333(of)-333(the)-334(same)-333(t)28(yp)-28(e)-333(of)]TJ/F11 9.9626 Tf 252.609 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -283.209 -19.925 Td [(On)-383(Return)]TJ 0 g 0 G +/F27 9.9626 Tf -246.135 -26.961 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G - 0 -19.925 Td [(x)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(global)-333(dense)-334(result)-333(matrix)]TJ/F11 9.9626 Tf 116.674 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -108.49 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-474(as:)-727(an)-475(arra)28(y)-475(of)-474(rank)-475(one)-474(or)-475(t)28(w)28(o)-475(con)28(taining)-474(n)27(um)28(b)-28(ers)-474(of)-475(t)28(yp)-28(e)]TJ 0 -11.955 Td [(sp)-28(eci\014ed)-333(in)-333(T)83(able)]TJ -0 0 1 rg 0 0 1 RG - [-333(15)]TJ +/F27 9.9626 Tf -33.797 -19.659 Td [(On)-383(En)32(try)]TJ 0 g 0 G - [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -19.926 Td [(info)]TJ + 0 -19.658 Td [(x)]TJ +0 g 0 G +/F8 9.9626 Tf 11.028 0 Td [(global)-333(dense)-334(matrix)]TJ/F11 9.9626 Tf 88.917 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -80.732 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-55(jec)-1(t)-254(of)-255(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 244.743 0 Td [(psb)]TJ +ET +q +1 0 0 1 385.864 346.872 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 389.002 346.673 Td [(T)]TJ +ET +q +1 0 0 1 394.86 346.872 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 397.998 346.673 Td [(vect)]TJ +ET +q +1 0 0 1 419.547 346.872 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 422.685 346.673 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(te)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(t)1(e)-1(d.)]TJ/F16 11.9552 Tf -24.906 -21.918 Td [(Notes)]TJ +/F8 9.9626 Tf -297.883 -11.955 Td [(con)28(taining)-333(n)27(um)28(b)-28(ers)-333(of)-333(t)28(yp)-28(e)-334(sp)-27(eci\014ed)-334(in)-333(T)83(able)]TJ +0 0 1 rg 0 0 1 RG + [-333(14)]TJ 0 g 0 G -/F8 9.9626 Tf 12.176 -19.925 Td [(1.)]TJ + [(.)]TJ 0 g 0 G - [-500(If)-316(there)-316(is)-317(no)-316(o)28(v)28(erlap)-316(in)-317(t)1(he)-317(data)-316(distribution)-316(asso)-28(ciated)-316(with)-316(the)-316(descrip-)]TJ 12.73 -11.955 Td [(tor,)-333(no)-334(op)-27(erations)-334(are)-333(p)-28(erformed;)]TJ +/F27 9.9626 Tf -24.907 -19.658 Td [(desc)]TJ +ET +q +1 0 0 1 121.81 315.259 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 125.247 315.06 Td [(a)]TJ 0 g 0 G - -12.73 -19.926 Td [(2.)]TJ +/F8 9.9626 Tf 10.551 0 Td [(con)28(tains)-334(d)1(ata)-334(structures)-333(for)-333(com)-1(m)28(unications.)]TJ -10.996 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ +ET +q +1 0 0 1 312.036 267.438 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 315.174 267.239 Td [(desc)]TJ +ET +q +1 0 0 1 336.723 267.438 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 339.861 267.239 Td [(type)]TJ 0 g 0 G - [-500(The)-351(op)-27(e)-1(r)1(ator)]TJ/F11 9.9626 Tf 73.738 0 Td [(P)]TJ/F10 6.9738 Tf 7.779 3.616 Td [(T)]TJ/F8 9.9626 Tf 9.77 -3.616 Td [(p)-28(erforms)-350(the)-351(reduction)-351(sum)-350(of)-351(o)28(v)27(erlap)-350(elemen)27(ts;)-359(it)-351(is)-350(a)]TJ -78.557 -11.955 Td [(\134prolongation")-365(op)-28(erator)]TJ/F11 9.9626 Tf 108.923 0 Td [(P)]TJ/F10 6.9738 Tf 7.78 3.615 Td [(T)]TJ/F8 9.9626 Tf 9.914 -3.615 Td [(that)-365(replicates)-365(o)27(v)28(erlap)-365(elemen)28(ts,)-373(accoun)27(ting)]TJ -126.617 -11.955 Td [(for)-333(the)-334(ph)28(ysical)-333(replication)-333(of)-334(data;)]TJ +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G - -12.73 -19.925 Td [(3.)]TJ +/F27 9.9626 Tf -260.887 -19.658 Td [(w)32(ork)]TJ 0 g 0 G - [-500(The)-256(op)-27(erator)]TJ/F11 9.9626 Tf 71.841 0 Td [(P)]TJ/F10 6.9738 Tf 6.396 -1.495 Td [(a)]TJ/F8 9.9626 Tf 7.365 1.495 Td [(p)-28(erforms)-255(a)-256(scaling)-255(on)-256(the)-255(o)28(v)27(erlap)-255(elemen)28(ts)-256(b)28(y)-256(th)1(e)-256(amoun)28(t)]TJ -72.872 -11.956 Td [(of)-290(repli)1(c)-1(ation)1(;)-305(th)28(us,)-298(when)-290(com)28(bined)-289(with)-290(the)-289(re)-1(d)1(uction)-290(op)-28(erator,)-298(it)-290(impl)1(e)-1(-)]TJ 0 -11.955 Td [(men)28(ts)-334(the)-333(a)28(v)28(erage)-334(of)-333(replicated)-333(ele)-1(men)28(ts)-333(o)28(v)27(er)-333(all)-333(of)-334(t)1(he)-1(i)1(r)-334(instances.)]TJ/F16 11.9552 Tf -24.906 -19.925 Td [(Example)-388(of)-387(us)-1(e)]TJ/F8 9.9626 Tf 93.468 0 Td [(Consider)-345(the)-344(discretization)-345(mesh)-345(d)1(e)-1(p)1(ic)-1(ted)-344(in)-345(\014g.)]TJ -0 0 1 rg 0 0 1 RG - [-344(8)]TJ +/F8 9.9626 Tf 29.432 0 Td [(the)-333(w)27(ork)-333(arra)28(y)83(.)]TJ -4.525 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-333(arra)27(y)-333(of)-333(the)-334(same)-333(t)28(yp)-28(e)-333(of)]TJ/F11 9.9626 Tf 220.756 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ 0 g 0 G - [(,)-348(parti-)]TJ -93.468 -11.955 Td [(tioned)-330(among)-330(t)28(w)27(o)-330(pro)-27(ce)-1(sses)-330(as)-330(sho)28(wn)-330(b)28(y)-331(th)1(e)-331(dashed)-330(lines,)-330(w)-1(i)1(th)-331(an)-330(o)28(v)28(erlap)-330(of)-330(1)]TJ 0 -11.955 Td [(extra)-360(la)28(y)28(er)-360(with)-359(resp)-28(ect)-360(to)-359(the)-360(partition)-359(of)-360(\014g.)]TJ -0 0 1 rg 0 0 1 RG - [-359(7)]TJ +/F27 9.9626 Tf -251.357 -19.659 Td [(data)]TJ 0 g 0 G - [(;)-373(the)-359(data)-360(distribution)-359(is)-360(suc)28(h)]TJ 0 -11.956 Td [(that)-351(eac)27(h)-351(pro)-28(cess)-351(will)-351(o)27(wn)-351(40)-351(en)27(tries)-351(in)-351(the)-352(index)-351(space,)-356(with)-351(an)-352(o)28(v)28(erlap)-351(of)-352(16)]TJ 0 -11.955 Td [(en)28(tries)-326(placed)-325(at)-326(lo)-28(cal)-325(indices)-326(25)-326(through)-325(40;)-328(the)-326(halo)-325(will)-326(run)-325(from)-326(lo)-28(cal)-325(index)]TJ 0 -11.955 Td [(41)-290(through)-291(lo)-27(cal)-291(index)-290(48..)-430(If)-291(pro)-27(cess)-291(0)-290(assigns)-291(an)-290(initial)-290(v)55(alue)-290(of)-291(1)-290(to)-290(its)-291(en)28(tries)]TJ 0 -11.955 Td [(in)-298(the)]TJ/F11 9.9626 Tf 28.078 0 Td [(x)]TJ/F8 9.9626 Tf 8.663 0 Td [(v)28(ector,)-305(and)-298(pro)-28(cess)-298(1)-298(ass)-1(i)1(gns)-299(a)-298(v)56(alue)-298(of)-298(2,)-305(then)-298(after)-298(a)-298(call)-298(to)]TJ/F30 9.9626 Tf 265.127 0 Td [(psb_ovrl)]TJ/F8 9.9626 Tf -301.868 -11.955 Td [(with)]TJ/F30 9.9626 Tf 22.4 0 Td [(psb_avg_)]TJ/F8 9.9626 Tf 44.871 0 Td [(and)-304(a)-304(call)-304(to)]TJ/F30 9.9626 Tf 56.945 0 Td [(psb_halo_)]TJ/F8 9.9626 Tf 50.102 0 Td [(the)-304(con)28(ten)28(ts)-304(of)-304(the)-304(lo)-28(cal)-304(v)28(ectors)-304(will)-304(b)-28(e)]TJ -174.318 -11.955 Td [(the)-333(follo)28(wing)-334(\050sho)28(wing)-333(a)-334(transition)-333(among)-333(the)-334(t)28(w)28(o)-333(sub)-28(domains\051)]TJ +/F8 9.9626 Tf 26.941 0 Td [(index)-333(list)-334(selector.)]TJ -2.034 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(Sp)-28(eci\014ed)-222(as:)-389(an)-222(in)28(teger.)-408(V)84(alues:)]TJ/F30 9.9626 Tf 136.479 0 Td [(psb_comm_halo_)]TJ/F8 9.9626 Tf 73.225 0 Td [(,)]TJ/F30 9.9626 Tf 2.767 0 Td [(psb_comm_mov_)]TJ/F8 9.9626 Tf 67.995 0 Td [(,)]TJ/F30 9.9626 Tf 5.202 0 Td [(psb_comm_ext_)]TJ/F8 9.9626 Tf 67.995 0 Td [(,)]TJ -353.663 -11.955 Td [(default:)]TJ/F30 9.9626 Tf 39.089 0 Td [(psb_comm_halo_)]TJ/F8 9.9626 Tf 73.224 0 Td [(.)-705(Cho)-27(os)-1(es)-420(the)-420(index)-420(list)-420(on)-420(whic)28(h)-420(to)-420(base)-420(the)]TJ -112.313 -11.955 Td [(data)-333(exc)27(hange.)]TJ 0 g 0 G - 166.874 -143.462 Td [(54)]TJ + 141.968 -29.888 Td [(53)]TJ 0 g 0 G ET @@ -12408,83 +12087,83 @@ endstream endobj 1196 0 obj << -/Length 3552 +/Length 3196 >> stream 0 g 0 G 0 g 0 G 0 g 0 G -0 g 0 G -0 g 0 G BT -/F31 7.9701 Tf 210.112 653.177 Td [(Pro)-29(cess)-355(0)-8986(Pro)-30(cess)-354(1)]TJ -33.382 -9.464 Td [(I)-1500(GLOB\050I\051)-1500(X\050I\051)-5180(I)-1500(GLOB\050I\051)-1500(X\050I\051)]TJ -1.184 -9.465 Td [(1)-5253(1)-2147(1.0)-5032(1)-4722(33)-2147(1.5)]TJ 0 -9.464 Td [(2)-5253(2)-2147(1.0)-5032(2)-4722(34)-2147(1.5)]TJ 0 -9.465 Td [(3)-5253(3)-2147(1.0)-5032(3)-4722(35)-2147(1.5)]TJ 0 -9.464 Td [(4)-5253(4)-2147(1.0)-5032(4)-4722(36)-2147(1.5)]TJ 0 -9.465 Td [(5)-5253(5)-2147(1.0)-5032(5)-4722(37)-2147(1.5)]TJ 0 -9.464 Td [(6)-5253(6)-2147(1.0)-5032(6)-4722(38)-2147(1.5)]TJ 0 -9.465 Td [(7)-5253(7)-2147(1.0)-5032(7)-4722(39)-2147(1.5)]TJ 0 -9.464 Td [(8)-5253(8)-2147(1.0)-5032(8)-4722(40)-2147(1.5)]TJ 0 -9.465 Td [(9)-5253(9)-2147(1.0)-5032(9)-4722(41)-2147(2.0)]TJ -4.235 -9.464 Td [(10)-4722(10)-2147(1.0)-4500(10)-4722(42)-2147(2.0)]TJ 0 -9.465 Td [(11)-4722(11)-2147(1.0)-4500(11)-4722(43)-2147(2.0)]TJ 0 -9.464 Td [(12)-4722(12)-2147(1.0)-4500(12)-4722(44)-2147(2.0)]TJ 0 -9.465 Td [(13)-4722(13)-2147(1.0)-4500(13)-4722(45)-2147(2.0)]TJ 0 -9.464 Td [(14)-4722(14)-2147(1.0)-4500(14)-4722(46)-2147(2.0)]TJ 0 -9.465 Td [(15)-4722(15)-2147(1.0)-4500(15)-4722(47)-2147(2.0)]TJ 0 -9.464 Td [(16)-4722(16)-2147(1.0)-4500(16)-4722(48)-2147(2.0)]TJ 0 -9.465 Td [(17)-4722(17)-2147(1.0)-4500(17)-4722(49)-2147(2.0)]TJ 0 -9.464 Td [(18)-4722(18)-2147(1.0)-4500(18)-4722(50)-2147(2.0)]TJ 0 -9.465 Td [(19)-4722(19)-2147(1.0)-4500(19)-4722(51)-2147(2.0)]TJ 0 -9.464 Td [(20)-4722(20)-2147(1.0)-4500(20)-4722(52)-2147(2.0)]TJ 0 -9.465 Td [(21)-4722(21)-2147(1.0)-4500(21)-4722(53)-2147(2.0)]TJ 0 -9.464 Td [(22)-4722(22)-2147(1.0)-4500(22)-4722(54)-2147(2.0)]TJ 0 -9.465 Td [(23)-4722(23)-2147(1.0)-4500(23)-4722(55)-2147(2.0)]TJ 0 -9.464 Td [(24)-4722(24)-2147(1.0)-4500(24)-4722(56)-2147(2.0)]TJ 0 -9.465 Td [(25)-4722(25)-2147(1.5)-4500(25)-4722(57)-2147(2.0)]TJ 0 -9.464 Td [(26)-4722(26)-2147(1.5)-4500(26)-4722(58)-2147(2.0)]TJ 0 -9.465 Td [(27)-4722(27)-2147(1.5)-4500(27)-4722(59)-2147(2.0)]TJ 0 -9.464 Td [(28)-4722(28)-2147(1.5)-4500(28)-4722(60)-2147(2.0)]TJ 0 -9.465 Td [(29)-4722(29)-2147(1.5)-4500(29)-4722(61)-2147(2.0)]TJ 0 -9.464 Td [(30)-4722(30)-2147(1.5)-4500(30)-4722(62)-2147(2.0)]TJ 0 -9.465 Td [(31)-4722(31)-2147(1.5)-4500(31)-4722(63)-2147(2.0)]TJ 0 -9.464 Td [(32)-4722(32)-2147(1.5)-4500(32)-4722(64)-2147(2.0)]TJ 0 -9.465 Td [(33)-4722(33)-2147(1.5)-4500(33)-4722(25)-2147(1.5)]TJ 0 -9.464 Td [(34)-4722(34)-2147(1.5)-4500(34)-4722(26)-2147(1.5)]TJ 0 -9.465 Td [(35)-4722(35)-2147(1.5)-4500(35)-4722(27)-2147(1.5)]TJ 0 -9.464 Td [(36)-4722(36)-2147(1.5)-4500(36)-4722(28)-2147(1.5)]TJ 0 -9.465 Td [(37)-4722(37)-2147(1.5)-4500(37)-4722(29)-2147(1.5)]TJ 0 -9.464 Td [(38)-4722(38)-2147(1.5)-4500(38)-4722(30)-2147(1.5)]TJ 0 -9.465 Td [(39)-4722(39)-2147(1.5)-4500(39)-4722(31)-2147(1.5)]TJ 0 -9.464 Td [(40)-4722(40)-2147(1.5)-4500(40)-4722(32)-2147(1.5)]TJ 0 -9.465 Td [(41)-4722(41)-2147(2.0)-4500(41)-4722(17)-2147(1.0)]TJ 0 -9.464 Td [(42)-4722(42)-2147(2.0)-4500(42)-4722(18)-2147(1.0)]TJ 0 -9.465 Td [(43)-4722(43)-2147(2.0)-4500(43)-4722(19)-2147(1.0)]TJ 0 -9.464 Td [(44)-4722(44)-2147(2.0)-4500(44)-4722(20)-2147(1.0)]TJ 0 -9.465 Td [(45)-4722(45)-2147(2.0)-4500(45)-4722(21)-2147(1.0)]TJ 0 -9.464 Td [(46)-4722(46)-2147(2.0)-4500(46)-4722(22)-2147(1.0)]TJ 0 -9.465 Td [(47)-4722(47)-2147(2.0)-4500(47)-4722(23)-2147(1.0)]TJ 0 -9.464 Td [(48)-4722(48)-2147(2.0)-4500(48)-4722(24)-2147(1.0)]TJ +/F27 9.9626 Tf 150.705 706.129 Td [(On)-383(Return)]TJ 0 g 0 G 0 g 0 G -/F8 9.9626 Tf 95.459 -98.979 Td [(55)]TJ + 0 -19.925 Td [(x)]TJ 0 g 0 G -ET - -endstream -endobj -1201 0 obj -<< -/Length 318 ->> -stream +/F8 9.9626 Tf 11.028 0 Td [(global)-333(dense)-334(result)-333(matrix)]TJ/F11 9.9626 Tf 116.674 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -108.49 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Returned)-271(as:)-414(a)-271(rank)-271(one)-271(or)-272(t)28(w)28(o)-271(arra)28(y)-272(con)28(taining)-271(n)28(um)28(b)-28(ers)-271(of)-272(t)28(yp)-28(e)-271(sp)-28(eci\014ed)]TJ 0 -11.955 Td [(in)-333(T)83(able)]TJ +0 0 1 rg 0 0 1 RG + [-333(14)]TJ +0 g 0 G + [(.)]TJ 0 g 0 G +/F27 9.9626 Tf -24.906 -19.926 Td [(info)]TJ 0 g 0 G +/F8 9.9626 Tf 23.758 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(result)-333(submatrix)]TJ/F11 9.9626 Tf 162.364 0 Td [(y)]TJ/F8 9.9626 Tf 5.241 0 Td [(.)]TJ -166.457 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(te)-1(ger)-333(v)56(alue)-334(that)-333(con)28(tains)-333(an)-334(error)-333(co)-28(de.)]TJ 0 g 0 G 0 g 0 G 0 g 0 G -1 0 0 1 154.862 292.444 cm +ET +1 0 0 1 210.511 337.279 cm q -.65 0 0 .65 0 0 cm +.45 0 0 .45 0 0 cm q 1 0 0 1 0 0 cm -/Im4 Do +/Im3 Do Q Q 0 g 0 G -1 0 0 1 -154.862 -292.444 cm +1 0 0 1 -210.511 -337.279 cm BT -/F8 9.9626 Tf 240.078 260.564 Td [(Figure)-333(8:)-445(Sample)-333(discretization)-333(mesh.)]TJ +/F8 9.9626 Tf 240.078 305.398 Td [(Figure)-333(7:)-445(Sample)-333(discretization)-333(mesh.)]TJ 0 g 0 G 0 g 0 G +/F16 11.9552 Tf -89.373 -23.91 Td [(Usage)-381(Example)]TJ/F8 9.9626 Tf 93.98 0 Td [(Consider)-338(the)-339(discretization)-338(mesh)-339(depicted)-338(in)-338(\014g.)]TJ +0 0 1 rg 0 0 1 RG + [-339(7)]TJ +0 g 0 G + [(,)-339(parti-)]TJ -93.98 -11.955 Td [(tioned)-334(among)-334(t)27(w)28(o)-334(pro)-28(cesses)-334(as)-335(sho)28(wn)-334(b)28(y)-334(the)-335(dashed)-334(line;)-334(the)-335(data)-334(distribution)]TJ 0 -11.955 Td [(is)-422(suc)28(h)-422(that)-422(eac)28(h)-422(pro)-28(cess)-422(will)-421(o)27(wn)-422(32)-421(en)27(tries)-421(in)-422(the)-422(index)-422(space,)-444(with)-422(a)-422(halo)]TJ 0 -11.956 Td [(made)-340(of)-341(8)-340(en)28(tries)-341(placed)-340(at)-340(lo)-28(cal)-341(in)1(dices)-341(33)-340(through)-340(40.)-466(If)-340(pro)-28(cess)-341(0)-340(assigns)-340(an)]TJ 0 -11.955 Td [(initial)-423(v)55(alue)-423(of)-424(1)-423(to)-424(its)-423(en)28(tries)-424(in)-423(the)]TJ/F11 9.9626 Tf 169.005 0 Td [(x)]TJ/F8 9.9626 Tf 9.913 0 Td [(v)28(ector,)-446(and)-424(pro)-27(cess)-424(1)-423(ass)-1(i)1(g)-1(n)1(s)-424(a)-423(v)55(alue)]TJ -178.918 -11.955 Td [(of)-349(2,)-353(then)-349(after)-349(a)-349(call)-349(to)]TJ/F30 9.9626 Tf 108.539 0 Td [(psb_halo)]TJ/F8 9.9626 Tf 45.32 0 Td [(the)-349(con)28(ten)27(t)1(s)-350(of)-349(the)-349(lo)-27(cal)-350(v)28(ectors)-349(will)-349(b)-28(e)-349(the)]TJ -153.859 -11.955 Td [(follo)28(wing:)]TJ 0 g 0 G - 77.501 -170.126 Td [(56)]TJ + 166.874 -119.319 Td [(54)]TJ 0 g 0 G ET endstream endobj -1183 0 obj +1192 0 obj << /Type /XObject /Subtype /Form /FormType 1 -/PTEX.FileName (./figures/try8x8_ov.pdf) +/PTEX.FileName (./figures/try8x8.pdf) /PTEX.PageNumber 1 -/PTEX.InfoDict 1203 0 R -/BBox [0 0 516 439] +/PTEX.InfoDict 1199 0 R +/BBox [0 0 498 439] /Resources << /ProcSet [ /PDF /Text ] /ExtGState << -/R7 1204 0 R ->>/Font << /R8 1205 0 R/R10 1206 0 R>> +/R7 1200 0 R +>>/Font << /R8 1201 0 R/R10 1202 0 R>> >> -/Length 3413 +/Length 3349 /Filter /FlateDecode >> stream -xA +8s^˒- Svҷj&{|I(m|%Zߟ[ynx?ף?lOgaV+_.=ݥM:߷ZKض[J'Ĵ8͞MTmi&v @%o3o{ lv #"6ف|lvD"@663_dl# Md9D.>}m= m|{DdF@6;.6CZ$ lm"nG6mdK33/ g#"\~>g#"\~N [363_dl# Md9D.>Мqht3L9.LC f4f :f 37fjL9.. ]f h33͙Z3ŌAnjAsyfALA ͠ -lA7b8tS!jq 33BĖ zG.á*jp pF.jo,*o)TwK٥[.Rr▂K-U[rC܎V8V]cz?Z+̣gD_6^=tjnf9 Y2& -\h6O`Ih]g4@h6!PN7#Cw*uAH MGۏ?>Eh!3h$Kh6!P̹mCD]jcf]Q)&2@AZ[YM -͆e|_Ŭ롾oƋ;2ї"F:#}]/~.%0Q&G@_v&a}wQU=}jj.3u˖: 2=ep?TwǕ%v>ʮm).=o|X"ȕ -כAC\Wh ]|ۚ_ܮ2/7k5Ln`1` ps%ks^Qo/ճ*׻ s[AW ]|ۚ_5U慪>ZU @oI|T=b~[ >Z k}o<@g~gU/n\nZ|S+3ع>\vTYqI;sutGD@33t'0smLFD%F푑0.zB.B"+Фz{^t[ާ@`[v ,]$>ȫjHqvEkCTi _']UWMݴ|/Z}\W_'\UkJʼ@g^*yj~œ&?n7 -> 7z3mW=򙿪Ok*#_e}0h;ׇĂUmxPyPp}gZz43cL̵1Y][Vέ5x]Oh5E_ZSYdUZR6Tl4^l]M׵6Nɋ&%ě)?'Q:V\ֆU n|œzC+wum_kC*\b[=?' G_ߙ8"*1L̵1Y=Ƣzځm,uZMuTYaU&[:ZGv_P=-F5louY*oX<M+7uys6cn:|oœԱzS7>Zj?|b+T|oœ}Ա2/P=P[1`z:b$>6uMWֆ}qwf-G>7u|M#_e^z䫬Zaꦓ9X?񶎏x0z~DDE]ׅaX!>do֫\̕w-/Iv!o'ȟ`[G. +x]$~tkXtjY}-qWWfDFr$ɬo1d%gro}=1s<h^ٽ}cVz_=>⩽ǎ'!w ;\)nBBZ!-$5=OztRZHLk/DX=&cZ  b!r+@x 1d-G5G||7|+_@dn@-Edk ИD-^ {Ldkc"{ˑ=&q@@>Cq)YD>E3 [@>E3iyaeMx f-Z-8Z=e9M>yݜF@l#mH?Kihy1ҎFb+ԑ |c3F9F#7F##ƌcH1!̥#gƈ1H=cę9>1RD9󍹍+-fs3Gnf3F9F#Ƭ"cC+?ߘlq0cĘcĘ9r3k1b1b1fsX(,m;V(7P?#z_q"mw`z|ÚwM,f~F~:Z?kFE5, ]`͌f c/4k4RU|$3.vsohSaAB~h~ǎFhִz~ d2-Eb%4kEGkmh}tE4n5M|=aB;hcb(4k:@wE/}3^<1satε۳>I`A&GR0wIؿOQu}N5h=u |z|OcdgXy۶ +;,_0 7k3M༿Dz,ٷqž<|d8lͺM༿Dzp?,pw SpeV.<cB`jg%cp0>x|$8,vf_NFp_"=Ve/,Wn`\mqeqς0H CH&3xp-,[&d.fe1,j07Ʃؕ@!Lqu a\FT7 fJݎ+M/޷"wZh!A?C/A~iY 1 <qVƢ4",YIsCk1#0B3 +U1\o{Wl}J뭴\Z!Ybnج_O;'7wӛs[i"]|_O'7wS"VZ .-W9p=YV<檶VZ .'6]/ʜֆp.yI|t=*:煮>?6T5|t1oS`$>6׻Ei9P+j#,7:煮N}0 qև[̓I|ONGdJ0|'aem,J#g\OMzFSl M}vp=U_^KW_FClpfx+M;V\﵇%%h1v7H>o'j۴c^Ly_RehxfyvI|6X9/p=YI剢5b?8p=vI|6Xq"jxT(Z!^_FCa7M;b$K_?9-3cR]bf!} 6mdeזՋon&t17T7[*fBKx Z]-rSkCyԌN.x'vWU.t+:煮>P]GCyMU0ȟz܊p +6ɖOWbzSE 0ˮΨxܳ>PU|h>^yԎX<Af\dy׎X<v4U3ڱz?Tjm~/[}:~<ωק/ߟvvݾkeo]{??~Cޟ#aYaX)'Wk3{ο*{ endstream endobj -1209 0 obj +1205 0 obj << /Filter /FlateDecode /Subtype /Type1C @@ -12543,7 +12222,7 @@ r ^Ƀ]W$g]Q y%Nԭ UOC\un_~C *%4vܢ%‰كl0^2F~ 996=/ `/v pć0e4:G*,-%| 4Ttuu$5ۇ+J\fo[qC +E'l>h,@[hZBAMr eJ}xsi@B`_)y`mqGz۽bM| tZ) ŽuNcpMSWo3r#]a5Ϳ+Wy{?q*>;^Z9 yƇŒp'\h"ղkpxتTR)oǤp!UK͝Q,K endstream endobj -1210 0 obj +1206 0 obj << /Filter /FlateDecode /Subtype /Type1C @@ -12616,790 +12295,836 @@ k OWk'T_Pi줮$1R(l?弣 endstream endobj -1216 0 obj +1209 0 obj << -/Length 9388 +/Length 3050 >> stream 0 g 0 G 0 g 0 G +0 g 0 G +0 g 0 G +0 g 0 G BT -/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ +/F46 8.9664 Tf 205.966 645.656 Td [(Pro)-29(cess)-342(0)-8224(Pro)-28(cess)-343(1)]TJ -33.967 -10.959 Td [(I)-1333(GLOB\050I\051)-1334(X\050I\051)-4656(I)-1334(GLOB\050I\051)-1333(X\050I\051)]TJ -1.281 -10.959 Td [(1)-4966(1)-1961(1.0)-4514(1)-4452(33)-1961(2.0)]TJ 0 -10.959 Td [(2)-4966(2)-1961(1.0)-4514(2)-4452(34)-1961(2.0)]TJ 0 -10.959 Td [(3)-4966(3)-1961(1.0)-4514(3)-4452(35)-1961(2.0)]TJ 0 -10.959 Td [(4)-4966(4)-1961(1.0)-4514(4)-4452(36)-1961(2.0)]TJ 0 -10.959 Td [(5)-4966(5)-1961(1.0)-4514(5)-4452(37)-1961(2.0)]TJ 0 -10.959 Td [(6)-4966(6)-1961(1.0)-4514(6)-4452(38)-1961(2.0)]TJ 0 -10.959 Td [(7)-4966(7)-1961(1.0)-4514(7)-4452(39)-1961(2.0)]TJ 0 -10.958 Td [(8)-4966(8)-1961(1.0)-4514(8)-4452(40)-1961(2.0)]TJ 0 -10.959 Td [(9)-4966(9)-1961(1.0)-4514(9)-4452(41)-1961(2.0)]TJ -4.608 -10.959 Td [(10)-4452(10)-1961(1.0)-4000(10)-4452(42)-1961(2.0)]TJ 0 -10.959 Td [(11)-4452(11)-1961(1.0)-4000(11)-4452(43)-1961(2.0)]TJ 0 -10.959 Td [(12)-4452(12)-1961(1.0)-4000(12)-4452(44)-1961(2.0)]TJ 0 -10.959 Td [(13)-4452(13)-1961(1.0)-4000(13)-4452(45)-1961(2.0)]TJ 0 -10.959 Td [(14)-4452(14)-1961(1.0)-4000(14)-4452(46)-1961(2.0)]TJ 0 -10.959 Td [(15)-4452(15)-1961(1.0)-4000(15)-4452(47)-1961(2.0)]TJ 0 -10.959 Td [(16)-4452(16)-1961(1.0)-4000(16)-4452(48)-1961(2.0)]TJ 0 -10.959 Td [(17)-4452(17)-1961(1.0)-4000(17)-4452(49)-1961(2.0)]TJ 0 -10.958 Td [(18)-4452(18)-1961(1.0)-4000(18)-4452(50)-1961(2.0)]TJ 0 -10.959 Td [(19)-4452(19)-1961(1.0)-4000(19)-4452(51)-1961(2.0)]TJ 0 -10.959 Td [(20)-4452(20)-1961(1.0)-4000(20)-4452(52)-1961(2.0)]TJ 0 -10.959 Td [(21)-4452(21)-1961(1.0)-4000(21)-4452(53)-1961(2.0)]TJ 0 -10.959 Td [(22)-4452(22)-1961(1.0)-4000(22)-4452(54)-1961(2.0)]TJ 0 -10.959 Td [(23)-4452(23)-1961(1.0)-4000(23)-4452(55)-1961(2.0)]TJ 0 -10.959 Td [(24)-4452(24)-1961(1.0)-4000(24)-4452(56)-1961(2.0)]TJ 0 -10.959 Td [(25)-4452(25)-1961(1.0)-4000(25)-4452(57)-1961(2.0)]TJ 0 -10.959 Td [(26)-4452(26)-1961(1.0)-4000(26)-4452(58)-1961(2.0)]TJ 0 -10.959 Td [(27)-4452(27)-1961(1.0)-4000(27)-4452(59)-1961(2.0)]TJ 0 -10.958 Td [(28)-4452(28)-1961(1.0)-4000(28)-4452(60)-1961(2.0)]TJ 0 -10.959 Td [(29)-4452(29)-1961(1.0)-4000(29)-4452(61)-1961(2.0)]TJ 0 -10.959 Td [(30)-4452(30)-1961(1.0)-4000(30)-4452(62)-1961(2.0)]TJ 0 -10.959 Td [(31)-4452(31)-1961(1.0)-4000(31)-4452(63)-1961(2.0)]TJ 0 -10.959 Td [(32)-4452(32)-1961(1.0)-4000(32)-4452(64)-1961(2.0)]TJ 0 -10.959 Td [(33)-4452(33)-1961(2.0)-4000(33)-4452(25)-1961(1.0)]TJ 0 -10.959 Td [(34)-4452(34)-1961(2.0)-4000(34)-4452(26)-1961(1.0)]TJ 0 -10.959 Td [(35)-4452(35)-1961(2.0)-4000(35)-4452(27)-1961(1.0)]TJ 0 -10.959 Td [(36)-4452(36)-1961(2.0)-4000(36)-4452(28)-1961(1.0)]TJ 0 -10.959 Td [(37)-4452(37)-1961(2.0)-4000(37)-4452(29)-1961(1.0)]TJ 0 -10.958 Td [(38)-4452(38)-1961(2.0)-4000(38)-4452(30)-1961(1.0)]TJ 0 -10.959 Td [(39)-4452(39)-1961(2.0)-4000(39)-4452(31)-1961(1.0)]TJ 0 -10.959 Td [(40)-4452(40)-1961(2.0)-4000(40)-4452(32)-1961(1.0)]TJ +0 g 0 G +0 g 0 G +/F8 9.9626 Tf 100.66 -105.903 Td [(55)]TJ +0 g 0 G ET -q -1 0 0 1 120.951 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 124.986 706.129 Td [(gather)-375(|)-375(Gather)-375(Global)-375(Dense)-375(Matrix)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(These)-384(subroutines)-384(collect)-385(the)-384(p)-28(orti)1(ons)-385(of)-384(global)-384(dense)-384(matrix)-384(distributed)-384(o)28(v)27(er)]TJ 0 -11.956 Td [(all)-333(pro)-28(cess)-334(in)28(to)-333(one)-333(single)-334(arra)28(y)-333(stored)-334(on)-333(one)-333(pro)-28(cess.)]TJ/F11 9.9626 Tf 120.435 -22.804 Td [(g)-36(l)-20(ob)]TJ -ET -q -1 0 0 1 238.311 653.179 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F11 9.9626 Tf 241.299 652.98 Td [(x)]TJ/F14 9.9626 Tf 8.462 0 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(col)-20(l)-19(ect)]TJ/F8 9.9626 Tf 28.025 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(l)-20(oc)]TJ -ET -q -1 0 0 1 307.298 653.179 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F11 9.9626 Tf 310.287 652.98 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.494 Td [(i)]TJ/F8 9.9626 Tf 3.316 1.494 Td [(\051)]TJ -219.402 -20.867 Td [(where:)]TJ + +endstream +endobj +1218 0 obj +<< +/Length 8482 +>> +stream 0 g 0 G -/F11 9.9626 Tf 0 -19.085 Td [(g)-36(l)-20(ob)]TJ -ET -q -1 0 0 1 117.965 613.227 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F11 9.9626 Tf 121.403 613.028 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 10.675 0 Td [(is)-333(the)-334(global)-333(submatrix)]TJ/F11 9.9626 Tf 103.916 0 Td [(g)-36(l)-20(ob)]TJ -ET -q -1 0 0 1 253.974 613.227 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q BT -/F11 9.9626 Tf 256.963 613.028 Td [(x)]TJ/F7 6.9738 Tf 5.694 -1.494 Td [(1:)]TJ/F10 6.9738 Tf 6.227 0 Td [(m;)]TJ/F7 6.9738 Tf 9.436 0 Td [(1:)]TJ/F10 6.9738 Tf 6.226 0 Td [(n)]TJ -0 g 0 G -/F11 9.9626 Tf -184.651 -18.011 Td [(l)-20(oc)]TJ +/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ ET q -1 0 0 1 112.892 593.722 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +1 0 0 1 171.761 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F11 9.9626 Tf 116.329 593.523 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.494 Td [(i)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(o)31(vrl)-375(|)-375(Ov)31(erlap)-375(Up)-31(date)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(These)-333(subroutines)-334(applies)-333(an)-333(o)27(v)28(erlap)-333(op)-28(erator)-333(to)-333(the)-334(input)-333(v)28(ector:)]TJ/F11 9.9626 Tf 154.475 -22.077 Td [(x)]TJ/F14 9.9626 Tf 8.461 0 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(Qx)]TJ/F8 9.9626 Tf -175.666 -20.14 Td [(where:)]TJ +0 g 0 G +/F11 9.9626 Tf 0 -18.503 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 8.298 1.494 Td [(is)-333(the)-334(lo)-27(c)-1(al)-333(p)-28(ortion)-333(of)-333(global)-333(dense)-334(matrix)-333(on)-333(pro)-28(cess)]TJ/F11 9.9626 Tf 234.704 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(.)]TJ +/F8 9.9626 Tf 10.675 0 Td [(is)-333(the)-334(global)-333(dense)-333(submatrix)]TJ/F11 9.9626 Tf 131.092 0 Td [(x)]TJ 0 g 0 G -/F11 9.9626 Tf -268.562 -19.505 Td [(col)-20(l)-19(ect)]TJ + -141.767 -19.214 Td [(Q)]TJ 0 g 0 G -/F8 9.9626 Tf 33.007 0 Td [(is)-333(the)-334(collect)-333(function.)]TJ +/F8 9.9626 Tf 12.857 0 Td [(is)-333(the)-334(o)28(v)28(erlap)-333(op)-28(erator;)-333(it)-334(is)-333(the)-333(co)-1(mp)-27(osition)-334(of)-333(t)28(w)28(o)-334(op)-27(erators)]TJ/F11 9.9626 Tf 271.842 0 Td [(P)]TJ/F10 6.9738 Tf 6.396 -1.494 Td [(a)]TJ/F8 9.9626 Tf 8.141 1.494 Td [(and)]TJ/F11 9.9626 Tf 19.372 0 Td [(P)]TJ/F10 6.9738 Tf 7.78 3.616 Td [(T)]TJ/F8 9.9626 Tf 6.276 -3.616 Td [(.)]TJ 0 g 0 G 0 g 0 G 0 g 0 G ET q -1 0 0 1 177.988 555.154 cm +1 0 0 1 228.797 587.879 cm []0 d 0 J 0.398 w 0 0 m 187.526 0 l S Q BT -/F11 9.9626 Tf 183.966 546.587 Td [(x)]TJ/F10 6.9738 Tf 5.693 -1.495 Td [(i)]TJ/F11 9.9626 Tf 3.317 1.495 Td [(;)-167(y)]TJ/F27 9.9626 Tf 111.399 0 Td [(Subroutine)]TJ +/F11 9.9626 Tf 234.775 579.311 Td [(x)]TJ/F27 9.9626 Tf 120.41 0 Td [(Subroutine)]TJ ET q -1 0 0 1 177.988 542.801 cm +1 0 0 1 228.797 575.525 cm []0 d 0 J 0.398 w 0 0 m 187.526 0 l S Q BT -/F8 9.9626 Tf 183.966 534.233 Td [(In)28(teger)-9028(psb)]TJ -ET -q -1 0 0 1 319.972 534.432 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F8 9.9626 Tf 322.961 534.233 Td [(gather)]TJ -138.995 -11.955 Td [(Short)-333(Precision)-333(R)-1(eal)-3102(psb)]TJ +/F8 9.9626 Tf 234.775 566.957 Td [(Short)-333(Precision)-334(Real)-3102(psb)]TJ ET q -1 0 0 1 319.972 522.477 cm +1 0 0 1 370.782 567.156 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 322.961 522.278 Td [(gather)]TJ -138.995 -11.955 Td [(Long)-333(Precision)-334(Real)-3314(p)1(s)-1(b)]TJ +/F8 9.9626 Tf 373.771 566.957 Td [(o)28(vrl)]TJ -138.996 -11.955 Td [(Long)-333(Precision)-334(Real)-3314(psb)]TJ ET q -1 0 0 1 319.972 510.522 cm +1 0 0 1 370.782 555.201 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 322.961 510.323 Td [(gather)]TJ -138.995 -11.956 Td [(Short)-333(Precision)-333(C)-1(omplex)-1200(p)1(s)-1(b)]TJ +/F8 9.9626 Tf 373.771 555.002 Td [(o)28(vrl)]TJ -138.996 -11.955 Td [(Short)-333(Precision)-334(Complex)-1200(psb)]TJ ET q -1 0 0 1 319.972 498.567 cm +1 0 0 1 370.782 543.246 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 322.961 498.367 Td [(gather)]TJ -138.995 -11.955 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ +/F8 9.9626 Tf 373.771 543.047 Td [(o)28(vrl)]TJ -138.996 -11.956 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ ET q -1 0 0 1 319.972 486.612 cm +1 0 0 1 370.782 531.291 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 322.961 486.412 Td [(gather)]TJ +/F8 9.9626 Tf 373.771 531.091 Td [(o)28(vrl)]TJ ET q -1 0 0 1 177.988 482.626 cm +1 0 0 1 228.797 527.306 cm []0 d 0 J 0.398 w 0 0 m 187.526 0 l S Q 0 g 0 G BT -/F8 9.9626 Tf 225.577 454.587 Td [(T)83(able)-333(16:)-444(Data)-334(t)28(yp)-28(es)]TJ +/F8 9.9626 Tf 276.386 499.266 Td [(T)83(able)-333(15:)-444(Data)-334(t)28(yp)-28(es)]TJ 0 g 0 G 0 g 0 G -/F27 9.9626 Tf -124.305 -30.984 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.738 0 Td [(p)-123(s)-123(b)]TJ -ET -q -1 0 0 1 150.286 423.802 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F8 9.9626 Tf 154.501 423.603 Td [(g)-123(a)-123(t)-123(h)-123(e)-123(r)-229(\050)-215(g)-110(l)-110(o)-110(b)]TJ -ET -q -1 0 0 1 219.873 423.802 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F8 9.9626 Tf 223.956 423.603 Td [(x)-381(,)-888(l)-127(o)-127(c)]TJ -ET -q -1 0 0 1 261.2 423.802 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F8 9.9626 Tf 265.456 423.603 Td [(x)-415(,)-874(d)-113(e)-112(s)-113(c)]TJ +/F27 9.9626 Tf -124.304 -28.465 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.881 0 Td [(p)-137(s)-138(b)]TJ ET q -1 0 0 1 309.731 423.802 cm +1 0 0 1 201.669 471 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 313.842 423.603 Td [(a)-386(,)-888(i)-127(n)-127(f)-127(o)-415(,)-885(r)-124(o)-123(o)-124(t)-230(\051)]TJ/F27 9.9626 Tf -212.57 -11.956 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.738 0 Td [(p)-123(s)-123(b)]TJ +/F8 9.9626 Tf 206.027 470.801 Td [(o)-137(v)-138(r)-137(l)-243(\050)-130(x)-209(,)-874(d)-113(e)-112(s)-113(c)]TJ ET q -1 0 0 1 150.286 411.847 cm +1 0 0 1 276.854 471 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 154.501 411.647 Td [(g)-123(a)-123(t)-123(h)-123(e)-123(r)-229(\050)-215(g)-110(l)-110(o)-110(b)]TJ +/F8 9.9626 Tf 280.965 470.801 Td [(a)-386(,)-914(i)-152(n)-152(f)-152(o)-258(\051)]TJ/F27 9.9626 Tf -128.883 -11.955 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.881 0 Td [(p)-137(s)-138(b)]TJ ET q -1 0 0 1 219.873 411.847 cm +1 0 0 1 201.669 459.045 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 223.956 411.647 Td [(x)-381(,)-888(l)-127(o)-127(c)]TJ +/F8 9.9626 Tf 206.027 458.846 Td [(o)-137(v)-138(r)-137(l)-243(\050)-130(x)-209(,)-874(d)-113(e)-112(s)-113(c)]TJ ET q -1 0 0 1 261.2 411.847 cm +1 0 0 1 276.854 459.045 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 265.456 411.647 Td [(x)-415(,)-874(d)-113(e)-112(s)-113(c)]TJ +/F8 9.9626 Tf 280.965 458.846 Td [(a)-386(,)-888(i)-127(n)-127(f)-127(o)-415(,)-846(u)-86(p)-86(d)-86(a)-85(t)-86(e)3(=)-13(u)-101(p)-102(d)-102(a)-102(t)-102(e)]TJ ET q -1 0 0 1 309.731 411.847 cm +1 0 0 1 415.44 459.045 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 313.842 411.647 Td [(a)-386(,)-888(i)-127(n)-127(f)-127(o)-415(,)-885(r)-124(o)-123(o)-124(t)-230(\051)]TJ +/F8 9.9626 Tf 419.443 458.846 Td [(t)-102(y)-102(p)-101(e)-365(,)-813(w)-52(o)-51(r)-52(k)37(=)38(w)-52(o)-52(r)-51(k)-158(\051)]TJ 0 g 0 G 0 g 0 G 0 g 0 G -/F27 9.9626 Tf -213.947 -26.424 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf -268.738 -25.406 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.505 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -33.797 -19.214 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.505 Td [(lo)-32(c)]TJ -ET -q -1 0 0 1 114.904 346.412 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 118.341 346.213 Td [(x)]TJ + 0 -19.214 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(g)-36(l)-19(o)-1(b)]TJ -ET -q -1 0 0 1 323.467 346.412 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F11 9.9626 Tf 326.456 346.213 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -207.348 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-55(jec)-1(t)-254(of)-255(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 11.028 0 Td [(global)-333(dense)-334(matrix)]TJ/F11 9.9626 Tf 88.917 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -80.732 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)28(o)-255(arra)28(y)-255(or)-255(an)-255(ob)-55(ject)-255(of)-255(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 244.743 0 Td [(psb)]TJ +/F30 9.9626 Tf 244.742 0 Td [(psb)]TJ ET q -1 0 0 1 385.864 298.592 cm +1 0 0 1 436.673 347.39 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 389.002 298.392 Td [(T)]TJ +/F30 9.9626 Tf 439.811 347.191 Td [(T)]TJ ET q -1 0 0 1 394.86 298.592 cm +1 0 0 1 445.669 347.39 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 397.998 298.392 Td [(vect)]TJ +/F30 9.9626 Tf 448.807 347.191 Td [(vect)]TJ ET q -1 0 0 1 419.547 298.592 cm +1 0 0 1 470.356 347.39 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 422.685 298.392 Td [(type)]TJ +/F30 9.9626 Tf 473.495 347.191 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf -297.883 -11.955 Td [(indicated)-333(in)-334(T)84(able)]TJ +/F8 9.9626 Tf -297.884 -11.955 Td [(con)28(taining)-333(n)27(um)28(b)-28(ers)-333(of)-333(t)27(yp)-27(e)-334(sp)-27(ec)-1(i)1(\014ed)-334(in)-333(T)83(able)]TJ 0 0 1 rg 0 0 1 RG - [-334(16)]TJ + [-333(15)]TJ 0 g 0 G [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.505 Td [(desc)]TJ +/F27 9.9626 Tf -24.906 -19.214 Td [(desc)]TJ ET q -1 0 0 1 121.81 267.131 cm +1 0 0 1 172.619 316.221 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 125.247 266.932 Td [(a)]TJ +/F27 9.9626 Tf 176.057 316.022 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(con)28(tains)-334(d)1(ata)-334(structures)-333(for)-333(com)-1(m)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.55 0 Td [(con)28(tains)-334(data)-333(structures)-333(for)-333(c)-1(omm)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 312.036 219.311 cm +1 0 0 1 362.845 268.401 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 315.174 219.111 Td [(desc)]TJ +/F30 9.9626 Tf 365.983 268.201 Td [(desc)]TJ ET q -1 0 0 1 336.723 219.311 cm +1 0 0 1 387.532 268.401 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 339.861 219.111 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -260.887 -19.505 Td [(ro)-32(ot)]TJ -0 g 0 G -/F8 9.9626 Tf 25.931 0 Td [(The)-291(pro)-28(cess)-291(that)-291(holds)-291(the)-291(global)-291(cop)28(y)83(.)-430(If)]TJ/F11 9.9626 Tf 182.522 0 Td [(r)-28(oot)]TJ/F8 9.9626 Tf 20.795 0 Td [(=)]TJ/F14 9.9626 Tf 10.516 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)-291(all)-291(the)-291(pro)-28(cesses)-291(will)]TJ -222.606 -11.955 Td [(ha)28(v)28(e)-334(a)-333(cop)28(y)-334(of)-333(the)-333(global)-334(v)28(ector.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable)]TJ/F14 9.9626 Tf 142.079 0 Td [(\000)]TJ/F8 9.9626 Tf 7.748 0 Td [(1)]TJ/F14 9.9626 Tf 7.749 0 Td [(\024)]TJ/F11 9.9626 Tf 10.516 0 Td [(r)-28(oot)]TJ/F14 9.9626 Tf 20.795 0 Td [(\024)]TJ/F11 9.9626 Tf 10.516 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.963 0 Td [(1,)-333(default)]TJ/F14 9.9626 Tf 44.555 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1.)]TJ -0 g 0 G -/F27 9.9626 Tf -299.783 -19.505 Td [(On)-383(Return)]TJ -0 g 0 G +/F30 9.9626 Tf 390.67 268.201 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 166.875 -29.888 Td [(57)]TJ -0 g 0 G -ET - -endstream -endobj -1224 0 obj -<< -/Length 1459 ->> -stream +/F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G +/F27 9.9626 Tf -260.887 -19.214 Td [(up)-32(date)]TJ 0 g 0 G +/F8 9.9626 Tf 39.67 0 Td [(Up)-28(date)-333(op)-28(erator.)]TJ 0 g 0 G -BT -/F27 9.9626 Tf 150.705 706.129 Td [(glob)]TJ +/F27 9.9626 Tf -14.764 -31.169 Td [(up)-32(date)-383(=)-384(psb)]TJ ET q -1 0 0 1 172.397 706.328 cm +1 0 0 1 244.786 218.017 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 175.834 706.129 Td [(x)]TJ -0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(The)-333(arra)27(y)-333(where)-333(the)-334(lo)-27(cal)-334(parts)-333(m)28(ust)-334(b)-27(e)-334(gathered.)]TJ -11.251 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-334(or)-333(t)28(w)28(o)-334(arra)28(y)-333(with)-333(the)]TJ/F30 9.9626 Tf 204.401 0 Td [(ALLOCATABLE)]TJ/F8 9.9626 Tf 60.855 0 Td [(attribute.)]TJ -0 g 0 G -/F27 9.9626 Tf -290.162 -19.925 Td [(info)]TJ -0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ -0 g 0 G - 141.968 -500.124 Td [(58)]TJ -0 g 0 G -ET - -endstream -endobj -1230 0 obj -<< -/Length 7828 ->> -stream -0 g 0 G -0 g 0 G -BT -/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ -ET -q -1 0 0 1 120.951 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 124.986 706.129 Td [(scatter)-375(|)-375(Scatter)-375(Global)-375(Dense)-375(Matrix)]TJ/F8 9.9626 Tf -25.091 -19.28 Td [(These)-315(subroutines)-315(scatters)-315(the)-315(p)-28(ortions)-315(of)-315(global)-315(dense)-315(matrix)-315(o)28(wned)-315(b)27(y)-315(a)-315(pro-)]TJ 0 -11.955 Td [(cess)-334(to)-333(all)-333(the)-334(p)1(ro)-28(cesses)-334(in)-333(the)-333(pro)-28(cesses)-334(grid.)]TJ/F11 9.9626 Tf 119.021 -25.291 Td [(l)-20(oc)]TJ -ET -q -1 0 0 1 231.823 649.802 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F11 9.9626 Tf 234.812 649.603 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.494 Td [(i)]TJ/F14 9.9626 Tf 6.084 1.494 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(scatter)]TJ/F8 9.9626 Tf 30.853 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(g)-36(l)-19(o)-1(b)]TJ -ET -q -1 0 0 1 312.028 649.802 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F11 9.9626 Tf 315.017 649.603 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(\051)]TJ -220.816 -22.875 Td [(where:)]TJ -0 g 0 G -/F11 9.9626 Tf 0 -21.361 Td [(g)-36(l)-20(ob)]TJ +/F27 9.9626 Tf 248.223 217.818 Td [(none)]TJ ET q -1 0 0 1 117.965 605.567 cm +1 0 0 1 272.62 218.017 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q -BT -/F11 9.9626 Tf 121.403 605.367 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 10.675 0 Td [(is)-333(the)-334(global)-333(matrix)]TJ/F11 9.9626 Tf 88.917 0 Td [(g)-36(l)-19(ob)]TJ -ET -q -1 0 0 1 238.975 605.567 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q BT -/F11 9.9626 Tf 241.964 605.367 Td [(x)]TJ/F7 6.9738 Tf 5.694 -1.494 Td [(1:)]TJ/F10 6.9738 Tf 6.227 0 Td [(m;)]TJ/F7 6.9738 Tf 9.435 0 Td [(1:)]TJ/F10 6.9738 Tf 6.227 0 Td [(n)]TJ +/F8 9.9626 Tf 281.039 217.818 Td [(Do)-333(nothing;)]TJ 0 g 0 G -/F11 9.9626 Tf -169.652 -20.345 Td [(l)-20(oc)]TJ +/F27 9.9626 Tf -105.428 -15.229 Td [(up)-32(date)-383(=)-384(psb)]TJ ET q -1 0 0 1 112.892 583.727 cm +1 0 0 1 244.786 202.789 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F11 9.9626 Tf 116.329 583.528 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.494 Td [(i)]TJ -0 g 0 G -/F8 9.9626 Tf 8.298 1.494 Td [(is)-333(the)-334(lo)-27(c)-1(al)-333(p)-28(ortion)-333(of)-333(global)-333(dense)-334(matrix)-333(on)-333(pro)-28(cess)]TJ/F11 9.9626 Tf 234.704 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(.)]TJ -0 g 0 G -/F11 9.9626 Tf -268.562 -21.839 Td [(scatter)]TJ -0 g 0 G -/F8 9.9626 Tf 35.835 0 Td [(is)-333(the)-334(scatter)-333(function.)]TJ -0 g 0 G -0 g 0 G -0 g 0 G -ET -q -1 0 0 1 177.988 539.65 cm -[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S -Q -BT -/F11 9.9626 Tf 183.966 531.082 Td [(x)]TJ/F10 6.9738 Tf 5.693 -1.494 Td [(i)]TJ/F11 9.9626 Tf 3.317 1.494 Td [(;)-167(y)]TJ/F27 9.9626 Tf 111.399 0 Td [(Subroutine)]TJ +/F27 9.9626 Tf 248.223 202.589 Td [(add)]TJ ET q -1 0 0 1 177.988 527.296 cm -[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S +1 0 0 1 267.21 202.789 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q +0 g 0 G BT -/F8 9.9626 Tf 183.966 518.729 Td [(In)28(teger)-9028(psb)]TJ +/F8 9.9626 Tf 275.628 202.589 Td [(Sum)-333(o)27(v)28(erlap)-333(en)28(tries,)-334(i.e.)-444(apply)]TJ/F11 9.9626 Tf 136.544 0 Td [(P)]TJ/F10 6.9738 Tf 7.78 3.616 Td [(T)]TJ/F8 9.9626 Tf 6.276 -3.616 Td [(;)]TJ +0 g 0 G +/F27 9.9626 Tf -250.617 -15.229 Td [(up)-32(date)-383(=)-384(psb)]TJ ET q -1 0 0 1 319.972 518.928 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 244.786 187.56 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F8 9.9626 Tf 322.961 518.729 Td [(scatter)]TJ -138.995 -11.956 Td [(Short)-333(Precision)-333(R)-1(eal)-3102(psb)]TJ +/F27 9.9626 Tf 248.223 187.36 Td [(a)32(vg)]TJ ET q -1 0 0 1 319.972 506.973 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 265.937 187.56 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q +0 g 0 G BT -/F8 9.9626 Tf 322.961 506.773 Td [(scatter)]TJ -138.995 -11.955 Td [(Long)-333(Precision)-334(Real)-3314(p)1(s)-1(b)]TJ +/F8 9.9626 Tf 274.355 187.36 Td [(Av)28(erage)-334(o)28(v)28(erlap)-333(en)27(tries,)-333(i.e.)-444(apply)]TJ/F11 9.9626 Tf 152.346 0 Td [(P)]TJ/F10 6.9738 Tf 6.396 -1.494 Td [(a)]TJ/F11 9.9626 Tf 4.82 1.494 Td [(P)]TJ/F10 6.9738 Tf 7.78 3.616 Td [(T)]TJ/F8 9.9626 Tf 6.276 -3.616 Td [(;)]TJ -276.362 -19.214 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Default:)]TJ/F11 9.9626 Tf 39.436 0 Td [(update)]TJ ET q -1 0 0 1 319.972 495.017 cm +1 0 0 1 245.048 144.435 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 322.961 494.818 Td [(scatter)]TJ -138.995 -11.955 Td [(Short)-333(Precision)-333(C)-1(omplex)-1200(p)1(s)-1(b)]TJ +/F11 9.9626 Tf 248.037 144.236 Td [(ty)-36(pe)]TJ/F8 9.9626 Tf 21.258 0 Td [(=)]TJ/F11 9.9626 Tf 10.517 0 Td [(psb)]TJ ET q -1 0 0 1 319.972 483.062 cm +1 0 0 1 294.367 144.435 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 322.961 482.863 Td [(scatter)]TJ -138.995 -11.955 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ +/F11 9.9626 Tf 297.356 144.236 Td [(av)-36(g)]TJ ET q -1 0 0 1 319.972 471.107 cm +1 0 0 1 313.516 144.435 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 322.961 470.908 Td [(scatter)]TJ +/F8 9.9626 Tf 175.611 132.281 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(in)28(teger)-333(v)55(ariable.)]TJ +0 g 0 G + 141.968 -29.888 Td [(56)]TJ +0 g 0 G ET -q -1 0 0 1 177.988 467.122 cm -[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S -Q + +endstream +endobj +1230 0 obj +<< +/Length 5866 +>> +stream 0 g 0 G -BT -/F8 9.9626 Tf 225.577 439.083 Td [(T)83(able)-333(17:)-444(Data)-334(t)28(yp)-28(es)]TJ 0 g 0 G 0 g 0 G -/F27 9.9626 Tf -124.305 -33.261 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.991 0 Td [(p)-148(s)-149(b)]TJ -ET -q -1 0 0 1 151.298 406.021 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F8 9.9626 Tf 155.766 405.822 Td [(s)-148(c)-149(a)-148(t)-149(t)-148(e)-149(r)-254(\050)-215(g)-110(l)-110(o)-110(b)]TJ -ET -q -1 0 0 1 225.851 406.021 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F8 9.9626 Tf 229.934 405.822 Td [(x)-381(,)-888(l)-127(o)-127(c)]TJ -ET -q -1 0 0 1 267.178 406.021 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F8 9.9626 Tf 271.433 405.822 Td [(x)-415(,)-874(d)-113(e)-112(s)-113(c)]TJ -ET -q -1 0 0 1 315.709 406.021 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q BT -/F8 9.9626 Tf 319.82 405.822 Td [(a)-386(,)-888(i)-127(n)-127(f)-127(o)-415(,)-864(r)-103(o)-103(o)-104(t)-367(,)-808(m)-47(o)-46(l)-47(d)-152(\051)]TJ +/F27 9.9626 Tf 99.895 706.129 Td [(w)32(ork)]TJ 0 g 0 G +/F8 9.9626 Tf 29.432 0 Td [(the)-333(w)27(ork)-333(arra)28(y)83(.)]TJ -4.525 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(one)-333(dimensional)-334(ar)1(ra)27(y)-333(of)-333(the)-334(same)-333(t)28(yp)-28(e)-333(of)]TJ/F11 9.9626 Tf 252.609 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ 0 g 0 G +/F27 9.9626 Tf -283.21 -19.925 Td [(On)-383(Return)]TJ 0 g 0 G -/F27 9.9626 Tf -219.925 -30.766 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ + 0 -19.925 Td [(x)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -21.84 Td [(On)-383(En)32(try)]TJ +/F8 9.9626 Tf 11.028 0 Td [(global)-333(dense)-334(result)-333(matrix)]TJ/F11 9.9626 Tf 116.674 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -108.489 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-474(as:)-727(an)-475(arra)28(y)-474(of)-475(rank)-475(on)1(e)-475(or)-475(t)28(w)28(o)-475(con)28(taining)-474(n)27(u)1(m)27(b)-27(e)-1(r)1(s)-475(of)-475(t)28(yp)-28(e)]TJ 0 -11.955 Td [(sp)-28(eci\014ed)-333(in)-333(T)83(able)]TJ +0 0 1 rg 0 0 1 RG + [-333(15)]TJ 0 g 0 G + [(.)]TJ 0 g 0 G - 0 -21.839 Td [(glob)]TJ -ET -q -1 0 0 1 121.587 331.576 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 125.024 331.377 Td [(x)]TJ +/F27 9.9626 Tf -24.907 -19.926 Td [(info)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(The)-333(arra)27(y)-333(that)-333(m)28(ust)-334(b)-27(e)-334(scattered)-333(in)28(to)-334(lo)-28(cal)-333(pieces.)]TJ -11.25 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-333(or)-334(t)28(w)28(o)-334(arra)28(y)84(.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -21.839 Td [(desc)]TJ -ET -q -1 0 0 1 121.81 261.916 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 125.247 261.717 Td [(a)]TJ +/F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(con)28(tains)-334(d)1(ata)-334(structures)-333(for)-333(com)-1(m)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ -ET -q -1 0 0 1 312.036 214.095 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 315.174 213.896 Td [(desc)]TJ -ET -q -1 0 0 1 336.723 214.095 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 339.861 213.896 Td [(type)]TJ + [-500(If)-316(there)-316(is)-317(no)-316(o)28(v)28(erlap)-316(in)-316(the)-317(data)-316(distribution)-316(asso)-28(ciated)-316(with)-316(the)-316(descrip-)]TJ 12.73 -11.955 Td [(tor,)-333(no)-334(op)-27(erations)-334(are)-333(p)-28(erformed;)]TJ 0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ + -12.73 -19.926 Td [(2.)]TJ 0 g 0 G -/F27 9.9626 Tf -260.887 -21.839 Td [(ro)-32(ot)]TJ + [-500(The)-351(op)-27(erator)]TJ/F11 9.9626 Tf 73.737 0 Td [(P)]TJ/F10 6.9738 Tf 7.78 3.616 Td [(T)]TJ/F8 9.9626 Tf 9.77 -3.616 Td [(p)-28(erforms)-350(the)-351(reduction)-351(sum)-350(of)-351(o)28(v)27(erlap)-350(elemen)28(ts)-1(;)-359(it)-351(i)1(s)-351(a)]TJ -78.557 -11.955 Td [(\134prolongation")-365(op)-28(erator)]TJ/F11 9.9626 Tf 108.923 0 Td [(P)]TJ/F10 6.9738 Tf 7.78 3.615 Td [(T)]TJ/F8 9.9626 Tf 9.914 -3.615 Td [(that)-365(replicates)-365(o)27(v)28(erlap)-365(elemen)28(ts,)-373(accoun)27(tin)1(g)]TJ -126.617 -11.955 Td [(for)-333(the)-334(ph)28(ysical)-333(replication)-333(of)-334(data;)]TJ +0 g 0 G + -12.73 -19.925 Td [(3.)]TJ +0 g 0 G + [-500(The)-255(op)-28(erator)]TJ/F11 9.9626 Tf 71.84 0 Td [(P)]TJ/F10 6.9738 Tf 6.397 -1.495 Td [(a)]TJ/F8 9.9626 Tf 7.364 1.495 Td [(p)-28(erforms)-255(a)-256(scaling)-255(on)-256(the)-255(o)28(v)27(erlap)-255(elemen)28(ts)-256(b)28(y)-256(the)-255(amoun)28(t)]TJ -72.871 -11.956 Td [(of)-290(r)1(e)-1(pl)1(ic)-1(ati)1(on;)-305(th)28(us,)-298(when)-290(com)28(bined)-289(with)-290(the)-289(reduction)-290(op)-28(erator,)-298(it)-289(im)-1(p)1(le-)]TJ 0 -11.955 Td [(men)28(ts)-334(the)-333(a)28(v)28(erage)-334(of)-333(replicated)-333(elem)-1(en)28(ts)-333(o)28(v)27(er)-333(all)-333(of)-333(their)-334(instances.)]TJ/F16 11.9552 Tf -24.907 -19.925 Td [(Example)-388(of)-388(use)]TJ/F8 9.9626 Tf 93.469 0 Td [(Consider)-345(the)-344(discretization)-345(mesh)-345(d)1(e)-1(p)1(icte)-1(d)-344(in)-345(\014g.)]TJ +0 0 1 rg 0 0 1 RG + [-344(8)]TJ 0 g 0 G -/F8 9.9626 Tf 25.931 0 Td [(The)-420(pro)-27(ces)-1(s)-419(that)-420(holds)-419(the)-420(global)-420(cop)28(y)83(.)-703(If)]TJ/F11 9.9626 Tf 194.21 0 Td [(r)-28(oot)]TJ/F8 9.9626 Tf 22.228 0 Td [(=)]TJ/F14 9.9626 Tf 11.949 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)-420(all)-419(the)-420(pro)-28(cesses)]TJ -237.16 -11.956 Td [(ha)28(v)28(e)-334(a)-333(cop)28(y)-334(of)-333(the)-333(global)-334(v)28(ector.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-344(as:)-468(an)-344(in)28(teger)-345(v)55(ariab)1(le)]TJ/F14 9.9626 Tf 142.757 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)]TJ/F14 9.9626 Tf 7.937 0 Td [(\024)]TJ/F11 9.9626 Tf 10.704 0 Td [(r)-28(oot)]TJ/F14 9.9626 Tf 20.983 0 Td [(\024)]TJ/F11 9.9626 Tf 10.705 0 Td [(np)]TJ/F14 9.9626 Tf 13.281 0 Td [(\000)]TJ/F8 9.9626 Tf 10.038 0 Td [(1,)-348(defau)1(lt)]TJ/F30 9.9626 Tf 44.81 0 Td [(psb_root_)]TJ/F8 9.9626 Tf 47.073 0 Td [(,)]TJ -316.037 -11.955 Td [(i.e.)-444(pro)-28(cess)-334(0.)]TJ + [(,)-348(parti-)]TJ -93.469 -11.955 Td [(tioned)-330(among)-330(t)28(w)27(o)-330(pro)-27(c)-1(esses)-330(as)-330(sho)28(wn)-330(b)27(y)-330(the)-330(dashed)-330(lines,)-331(with)-330(an)-330(o)28(v)28(erlap)-330(of)-330(1)]TJ 0 -11.955 Td [(extra)-360(la)28(y)28(er)-360(with)-359(resp)-28(ect)-360(to)-359(the)-360(partition)-359(of)-360(\014g.)]TJ +0 0 1 rg 0 0 1 RG + [-359(7)]TJ 0 g 0 G - 141.968 -29.888 Td [(59)]TJ + [(;)-373(the)-359(data)-360(distribution)-359(is)-360(suc)28(h)]TJ 0 -11.956 Td [(that)-351(eac)27(h)-351(pro)-28(cess)-351(will)-352(o)28(wn)-351(40)-352(en)28(tries)-351(in)-351(the)-352(index)-351(space,)-356(with)-351(an)-352(o)28(v)28(erlap)-351(of)-352(16)]TJ 0 -11.955 Td [(en)28(tries)-326(placed)-325(a)-1(t)-325(lo)-28(cal)-325(indices)-326(25)-326(through)-325(40;)-328(the)-326(halo)-325(w)-1(il)1(l)-326(run)-326(fr)1(om)-326(lo)-28(cal)-326(in)1(dex)]TJ 0 -11.955 Td [(41)-290(through)-291(lo)-27(cal)-291(index)-290(48..)-430(If)-291(pro)-27(cess)-291(0)-290(assigns)-291(an)-290(initial)-290(v)55(alue)-290(of)-291(1)-290(to)-290(its)-291(en)28(tries)]TJ 0 -11.955 Td [(in)-298(the)]TJ/F11 9.9626 Tf 28.079 0 Td [(x)]TJ/F8 9.9626 Tf 8.663 0 Td [(v)28(ector,)-305(and)-298(pro)-28(cess)-298(1)-298(assigns)-299(a)-298(v)56(alue)-298(of)-298(2,)-305(then)-298(after)-298(a)-298(call)-298(to)]TJ/F30 9.9626 Tf 265.127 0 Td [(psb_ovrl)]TJ/F8 9.9626 Tf -301.869 -11.955 Td [(with)]TJ/F30 9.9626 Tf 22.401 0 Td [(psb_avg_)]TJ/F8 9.9626 Tf 44.871 0 Td [(and)-304(a)-304(call)-304(to)]TJ/F30 9.9626 Tf 56.945 0 Td [(psb_halo_)]TJ/F8 9.9626 Tf 50.101 0 Td [(the)-304(con)28(ten)28(ts)-304(of)-304(the)-304(lo)-28(cal)-304(v)28(ectors)-304(will)-304(b)-28(e)]TJ -174.318 -11.955 Td [(the)-333(follo)27(win)1(g)-334(\050sho)28(wing)-333(a)-334(transition)-333(among)-333(the)-334(t)28(w)28(o)-333(sub)-28(domains\051)]TJ +0 g 0 G + 166.875 -143.462 Td [(57)]TJ 0 g 0 G ET endstream endobj -1116 0 obj +1118 0 obj << /Type /ObjStm /N 100 -/First 998 -/Length 12490 +/First 995 +/Length 12718 >> stream -1114 0 260 59 1115 117 1111 176 1124 347 1110 540 1117 688 1118 832 1119 979 1120 1126 -1121 1270 1122 1417 1126 1563 1123 1621 1130 1753 1127 1901 1128 2048 1132 2195 1129 2254 1135 2360 -1133 2499 1137 2646 264 2704 1134 2761 1144 2841 1139 2998 1140 3142 1141 3289 1146 3435 268 3494 -1147 3552 1148 3611 1149 3670 1150 3729 1143 3788 1154 3920 1158 4068 1159 4195 1160 4238 1161 4445 -1162 4683 1163 4959 1142 5195 1152 5342 1156 5489 1157 5547 1153 5606 1167 5754 1169 5872 1166 5931 -1175 6012 1171 6169 1172 6313 1173 6460 1177 6607 272 6665 1178 6722 1179 6781 1180 6839 1181 6897 -1174 6955 1187 7100 1182 7257 1184 7404 1185 7549 1189 7696 1190 7755 1191 7814 1192 7873 1186 7931 -1195 8063 1197 8181 1194 8239 1200 8319 1203 8437 1204 8564 1205 8607 1206 8814 1207 9052 1208 9328 -1202 9564 1193 9623 1199 9682 1215 9778 1211 9935 1212 10079 1213 10226 1217 10373 276 10431 1218 10488 -1219 10547 1220 10605 1221 10663 1214 10721 1223 10878 1225 10996 1222 11055 1229 11148 1226 11287 1231 11434 -% 1114 0 obj -<< -/D [1112 0 R /XYZ 149.705 753.953 null] +1116 0 248 58 1117 115 1113 174 1122 318 1119 466 1120 611 1124 758 252 817 1126 875 +1121 934 1133 1080 1127 1246 1128 1393 1129 1538 1130 1682 1135 1829 256 1887 1136 1944 1137 2003 +1138 2062 1139 2121 1132 2180 1148 2337 1131 2539 1140 2686 1141 2830 1142 2977 1143 3124 1144 3275 +1145 3426 1146 3577 1150 3724 1147 3783 1154 3889 1151 4028 1156 4174 260 4232 1157 4289 1153 4348 +1166 4519 1152 4712 1159 4860 1160 5004 1161 5151 1162 5298 1163 5442 1164 5589 1168 5735 1165 5794 +1172 5926 1169 6074 1170 6221 1174 6368 1171 6426 1177 6532 1175 6671 1179 6819 264 6878 1176 6936 +1185 7016 1180 7173 1181 7317 1182 7464 1187 7611 268 7669 1188 7726 1189 7785 1190 7843 1191 7901 +1184 7959 1195 8091 1199 8239 1200 8366 1201 8409 1202 8616 1203 8854 1204 9130 1183 9366 1193 9513 +1197 9659 1198 9718 1194 9777 1208 9925 1210 10043 1207 10101 1217 10182 1213 10339 1214 10483 1215 10630 +1219 10776 272 10835 1220 10893 1221 10952 1222 11011 1223 11070 1216 11129 1229 11274 1224 11431 1226 11578 +% 1116 0 obj +<< +/D [1114 0 R /XYZ 98.895 753.953 null] >> -% 260 0 obj +% 248 0 obj << -/D [1112 0 R /XYZ 150.705 720.077 null] +/D [1114 0 R /XYZ 99.895 720.077 null] >> -% 1115 0 obj +% 1117 0 obj << -/D [1112 0 R /XYZ 320.941 258.477 null] +/D [1114 0 R /XYZ 270.132 513.305 null] >> -% 1111 0 obj +% 1113 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F11 750 0 R /F14 767 0 R /F13 1082 0 R /F7 765 0 R /F10 766 0 R /F30 764 0 R /F27 556 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F11 755 0 R /F14 772 0 R /F7 770 0 R /F27 560 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 1124 0 obj +% 1122 0 obj << /Type /Page -/Contents 1125 0 R -/Resources 1123 0 R +/Contents 1123 0 R +/Resources 1121 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1084 0 R -/Annots [ 1110 0 R 1117 0 R 1118 0 R 1119 0 R 1120 0 R 1121 0 R 1122 0 R ] +/Parent 1102 0 R +/Annots [ 1119 0 R 1120 0 R ] >> -% 1110 0 obj +% 1119 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [307.672 655.375 314.646 666.223] -/A << /S /GoTo /D (section.3) >> +/Rect [310.273 342.722 387.792 353.847] +/A << /S /GoTo /D (spdata) >> >> -% 1117 0 obj +% 1120 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [368.549 586.627 444.603 597.752] -/A << /S /GoTo /D (vdata) >> ->> -% 1118 0 obj +/Rect [310.273 274.976 377.331 286.101] +/A << /S /GoTo /D (descdata) >> +>> +% 1124 0 obj +<< +/D [1122 0 R /XYZ 149.705 753.953 null] +>> +% 252 0 obj +<< +/D [1122 0 R /XYZ 150.705 720.077 null] +>> +% 1126 0 obj +<< +/D [1122 0 R /XYZ 320.941 513.305 null] +>> +% 1121 0 obj +<< +/Font << /F16 558 0 R /F8 561 0 R /F11 755 0 R /F14 772 0 R /F13 1125 0 R /F27 560 0 R /F30 769 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1133 0 obj +<< +/Type /Page +/Contents 1134 0 R +/Resources 1132 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1102 0 R +/Annots [ 1127 0 R 1128 0 R 1129 0 R 1130 0 R ] +>> +% 1127 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [382.088 276.095 394.043 286.943] +/A << /S /GoTo /D (table.12) >> +>> +% 1128 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [259.464 208.422 336.983 219.547] +/A << /S /GoTo /D (spdata) >> +>> +% 1129 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [368.549 141.026 444.603 152.151] +/A << /S /GoTo /D (vdata) >> +>> +% 1130 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [326.008 129.347 337.963 140.196] +/A << /S /GoTo /D (table.12) >> +>> +% 1135 0 obj +<< +/D [1133 0 R /XYZ 98.895 753.953 null] +>> +% 256 0 obj +<< +/D [1133 0 R /XYZ 99.895 720.077 null] +>> +% 1136 0 obj +<< +/D [1133 0 R /XYZ 239.804 675.784 null] +>> +% 1137 0 obj +<< +/D [1133 0 R /XYZ 236.666 658.376 null] +>> +% 1138 0 obj +<< +/D [1133 0 R /XYZ 236.025 640.968 null] +>> +% 1139 0 obj +<< +/D [1133 0 R /XYZ 270.132 455.558 null] +>> +% 1132 0 obj +<< +/Font << /F16 558 0 R /F8 561 0 R /F11 755 0 R /F14 772 0 R /F10 771 0 R /F7 770 0 R /F27 560 0 R /F30 769 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1148 0 obj +<< +/Type /Page +/Contents 1149 0 R +/Resources 1147 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1102 0 R +/Annots [ 1131 0 R 1140 0 R 1141 0 R 1142 0 R 1143 0 R 1144 0 R 1145 0 R 1146 0 R ] +>> +% 1131 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [432.897 655.375 444.852 666.223] +/A << /S /GoTo /D (table.12) >> +>> +% 1140 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [419.358 588.824 495.412 599.949] +/A << /S /GoTo /D (vdata) >> +>> +% 1141 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [377.029 577.145 388.984 587.994] +/A << /S /GoTo /D (table.12) >> +>> +% 1142 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [310.273 498.639 377.331 509.764] +/A << /S /GoTo /D (descdata) >> +>> +% 1143 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [397.199 462.009 404.172 472.858] +/A << /S /GoTo /D (equation.4.1) >> +>> +% 1144 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [396.202 447.541 403.176 458.389] +/A << /S /GoTo /D (equation.4.2) >> +>> +% 1145 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [396.507 433.073 403.481 443.921] +/A << /S /GoTo /D (equation.4.3) >> +>> +% 1146 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [253.818 191.887 265.774 202.735] +/A << /S /GoTo /D (table.12) >> +>> +% 1150 0 obj +<< +/D [1148 0 R /XYZ 149.705 753.953 null] +>> +% 1147 0 obj +<< +/Font << /F27 560 0 R /F8 561 0 R /F11 755 0 R /F30 769 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1154 0 obj +<< +/Type /Page +/Contents 1155 0 R +/Resources 1153 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1158 0 R +/Annots [ 1151 0 R ] +>> +% 1151 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [326.008 574.949 337.963 585.797] +/Rect [382.088 117.392 394.043 128.24] /A << /S /GoTo /D (table.13) >> >> -% 1119 0 obj +% 1156 0 obj +<< +/D [1154 0 R /XYZ 98.895 753.953 null] +>> +% 260 0 obj +<< +/D [1154 0 R /XYZ 99.895 720.077 null] +>> +% 1157 0 obj +<< +/D [1154 0 R /XYZ 270.132 258.477 null] +>> +% 1153 0 obj +<< +/Font << /F16 558 0 R /F8 561 0 R /F11 755 0 R /F14 772 0 R /F13 1125 0 R /F7 770 0 R /F10 771 0 R /F30 769 0 R /F27 560 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1166 0 obj +<< +/Type /Page +/Contents 1167 0 R +/Resources 1165 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1158 0 R +/Annots [ 1152 0 R 1159 0 R 1160 0 R 1161 0 R 1162 0 R 1163 0 R 1164 0 R ] +>> +% 1152 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [358.482 655.375 365.455 666.223] +/A << /S /GoTo /D (section.3) >> +>> +% 1159 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [419.358 586.627 495.412 597.752] +/A << /S /GoTo /D (vdata) >> +>> +% 1160 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [382.088 494.523 394.043 505.372] +/Rect [376.818 574.949 388.773 585.797] /A << /S /GoTo /D (table.13) >> >> -% 1120 0 obj +% 1161 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [432.897 494.523 444.852 505.372] +/A << /S /GoTo /D (table.13) >> +>> +% 1162 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [368.549 425.776 444.603 436.901] +/Rect [419.358 425.776 495.412 436.901] /A << /S /GoTo /D (vdata) >> >> -% 1121 0 obj +% 1163 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [326.219 414.098 338.174 424.946] +/Rect [377.029 414.098 388.984 424.946] /A << /S /GoTo /D (table.13) >> >> -% 1122 0 obj +% 1164 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [259.464 333.395 326.522 344.52] +/Rect [310.273 333.395 377.331 344.52] /A << /S /GoTo /D (descdata) >> >> -% 1126 0 obj +% 1168 0 obj << -/D [1124 0 R /XYZ 98.895 753.953 null] +/D [1166 0 R /XYZ 149.705 753.953 null] >> -% 1123 0 obj +% 1165 0 obj << -/Font << /F27 556 0 R /F8 557 0 R /F11 750 0 R /F14 767 0 R /F30 764 0 R /F17 730 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F11 755 0 R /F14 772 0 R /F30 769 0 R /F17 735 0 R >> /ProcSet [ /PDF /Text ] >> -% 1130 0 obj +% 1172 0 obj << /Type /Page -/Contents 1131 0 R -/Resources 1129 0 R +/Contents 1173 0 R +/Resources 1171 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1084 0 R -/Annots [ 1127 0 R 1128 0 R ] +/Parent 1158 0 R +/Annots [ 1169 0 R 1170 0 R ] >> -% 1127 0 obj +% 1169 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [213.636 410.238 225.591 419.149] +/Rect [162.826 410.238 174.781 419.149] /A << /S /GoTo /D (table.13) >> >> -% 1128 0 obj +% 1170 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [253.818 228.974 265.774 239.822] +/Rect [203.009 228.974 214.964 239.822] /A << /S /GoTo /D (table.13) >> >> -% 1132 0 obj +% 1174 0 obj << -/D [1130 0 R /XYZ 149.705 753.953 null] +/D [1172 0 R /XYZ 98.895 753.953 null] >> -% 1129 0 obj +% 1171 0 obj << -/Font << /F8 557 0 R /F27 556 0 R /F11 750 0 R /F30 764 0 R >> +/Font << /F8 561 0 R /F27 560 0 R /F11 755 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 1135 0 obj +% 1177 0 obj << /Type /Page -/Contents 1136 0 R -/Resources 1134 0 R +/Contents 1178 0 R +/Resources 1176 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1138 0 R -/Annots [ 1133 0 R ] +/Parent 1158 0 R +/Annots [ 1175 0 R ] >> -% 1133 0 obj +% 1175 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [299.536 657.464 306.51 668.312] +/Rect [350.345 657.464 357.319 668.312] /A << /S /GoTo /D (section.6) >> >> -% 1137 0 obj +% 1179 0 obj << -/D [1135 0 R /XYZ 98.895 753.953 null] +/D [1177 0 R /XYZ 149.705 753.953 null] >> % 264 0 obj << -/D [1135 0 R /XYZ 99.895 716.092 null] +/D [1177 0 R /XYZ 150.705 716.092 null] >> -% 1134 0 obj +% 1176 0 obj << -/Font << /F16 554 0 R /F8 557 0 R >> +/Font << /F16 558 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 1144 0 obj +% 1185 0 obj << /Type /Page -/Contents 1145 0 R -/Resources 1143 0 R +/Contents 1186 0 R +/Resources 1184 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1138 0 R -/Annots [ 1139 0 R 1140 0 R 1141 0 R ] +/Parent 1158 0 R +/Annots [ 1180 0 R 1181 0 R 1182 0 R ] >> -% 1139 0 obj +% 1180 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [419.358 343.463 495.412 354.588] +/Rect [368.549 343.463 444.603 354.588] /A << /S /GoTo /D (vdata) >> >> -% 1140 0 obj +% 1181 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [376.221 331.785 388.176 342.633] +/Rect [325.411 331.785 337.366 342.633] /A << /S /GoTo /D (table.14) >> >> -% 1141 0 obj +% 1182 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.53 264.029 412.588 275.154] +/Rect [294.721 264.029 361.779 275.154] /A << /S /GoTo /D (descdata) >> >> -% 1146 0 obj +% 1187 0 obj << -/D [1144 0 R /XYZ 149.705 753.953 null] +/D [1185 0 R /XYZ 98.895 753.953 null] >> % 268 0 obj << -/D [1144 0 R /XYZ 150.705 720.077 null] +/D [1185 0 R /XYZ 99.895 720.077 null] >> -% 1147 0 obj +% 1188 0 obj << -/D [1144 0 R /XYZ 320.941 514.036 null] +/D [1185 0 R /XYZ 270.132 514.036 null] >> -% 1148 0 obj +% 1189 0 obj << -/D [1144 0 R /XYZ 150.705 482.745 null] +/D [1185 0 R /XYZ 99.895 482.745 null] >> -% 1149 0 obj +% 1190 0 obj << -/D [1144 0 R /XYZ 150.705 484.682 null] +/D [1185 0 R /XYZ 99.895 484.682 null] >> -% 1150 0 obj +% 1191 0 obj << -/D [1144 0 R /XYZ 150.705 472.727 null] +/D [1185 0 R /XYZ 99.895 472.727 null] >> -% 1143 0 obj +% 1184 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F11 750 0 R /F14 767 0 R /F27 556 0 R /F30 764 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F11 755 0 R /F14 772 0 R /F27 560 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 1154 0 obj +% 1195 0 obj << /Type /Page -/Contents 1155 0 R -/Resources 1153 0 R +/Contents 1196 0 R +/Resources 1194 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1138 0 R -/Annots [ 1142 0 R 1152 0 R ] +/Parent 1158 0 R +/Annots [ 1183 0 R 1193 0 R ] >> -% 1158 0 obj +% 1199 0 obj << /Producer (GPL Ghostscript 9.22) /CreationDate (D:20180323100645Z00'00') /ModDate (D:20180323100645Z00'00') >> -% 1159 0 obj +% 1200 0 obj << /Type /ExtGState /OPM 1 >> -% 1160 0 obj +% 1201 0 obj << /BaseFont /XYUGDR+Times-Roman -/FontDescriptor 1162 0 R +/FontDescriptor 1203 0 R /Type /Font /FirstChar 48 /LastChar 57 @@ -13407,10 +13132,10 @@ stream /Encoding /WinAnsiEncoding /Subtype /Type1 >> -% 1161 0 obj +% 1202 0 obj << /BaseFont /XISTAL+Times-Bold -/FontDescriptor 1163 0 R +/FontDescriptor 1204 0 R /Type /Font /FirstChar 48 /LastChar 80 @@ -13418,7 +13143,7 @@ stream /Encoding /WinAnsiEncoding /Subtype /Type1 >> -% 1162 0 obj +% 1203 0 obj << /Type /FontDescriptor /FontName /XYUGDR+Times-Roman @@ -13431,9 +13156,9 @@ stream /StemV 71 /MissingWidth 250 /CharSet (/eight/five/four/nine/one/seven/six/three/two/zero) -/FontFile3 1164 0 R +/FontFile3 1205 0 R >> -% 1163 0 obj +% 1204 0 obj << /Type /FontDescriptor /FontName /XISTAL+Times-Bold @@ -13446,350 +13171,115 @@ stream /StemV 90 /MissingWidth 250 /CharSet (/P/one/zero) -/FontFile3 1165 0 R +/FontFile3 1206 0 R >> -% 1142 0 obj +% 1183 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [162.826 625.431 174.781 634.343] +/Rect [213.636 625.431 225.591 634.343] /A << /S /GoTo /D (table.14) >> >> -% 1152 0 obj +% 1193 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [407.097 278.167 414.071 290.786] +/Rect [457.906 278.167 464.88 290.786] /A << /S /GoTo /D (figure.7) >> >> -% 1156 0 obj +% 1197 0 obj << -/D [1154 0 R /XYZ 98.895 753.953 null] +/D [1195 0 R /XYZ 149.705 753.953 null] >> -% 1157 0 obj +% 1198 0 obj << -/D [1154 0 R /XYZ 232.883 317.353 null] +/D [1195 0 R /XYZ 283.692 317.353 null] >> -% 1153 0 obj +% 1194 0 obj << -/Font << /F27 556 0 R /F8 557 0 R /F11 750 0 R /F16 554 0 R /F30 764 0 R >> -/XObject << /Im3 1151 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F11 755 0 R /F16 558 0 R /F30 769 0 R >> +/XObject << /Im3 1192 0 R >> /ProcSet [ /PDF /Text ] >> -% 1167 0 obj +% 1208 0 obj << /Type /Page -/Contents 1168 0 R -/Resources 1166 0 R +/Contents 1209 0 R +/Resources 1207 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1138 0 R +/Parent 1212 0 R >> -% 1169 0 obj +% 1210 0 obj << -/D [1167 0 R /XYZ 149.705 753.953 null] +/D [1208 0 R /XYZ 98.895 753.953 null] >> -% 1166 0 obj +% 1207 0 obj << -/Font << /F46 1170 0 R /F8 557 0 R >> +/Font << /F46 1211 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 1175 0 obj +% 1217 0 obj << /Type /Page -/Contents 1176 0 R -/Resources 1174 0 R +/Contents 1218 0 R +/Resources 1216 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1138 0 R -/Annots [ 1171 0 R 1172 0 R 1173 0 R ] +/Parent 1212 0 R +/Annots [ 1213 0 R 1214 0 R 1215 0 R ] >> -% 1171 0 obj +% 1213 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [368.549 343.981 444.603 355.106] +/Rect [419.358 343.981 495.412 355.106] /A << /S /GoTo /D (vdata) >> >> -% 1172 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [325.411 332.303 337.366 343.151] -/A << /S /GoTo /D (table.15) >> ->> -% 1173 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 264.991 361.779 276.116] -/A << /S /GoTo /D (descdata) >> ->> -% 1177 0 obj -<< -/D [1175 0 R /XYZ 98.895 753.953 null] ->> -% 272 0 obj -<< -/D [1175 0 R /XYZ 99.895 720.077 null] ->> -% 1178 0 obj -<< -/D [1175 0 R /XYZ 270.132 511.222 null] ->> -% 1179 0 obj -<< -/D [1175 0 R /XYZ 99.895 480.819 null] ->> -% 1180 0 obj -<< -/D [1175 0 R /XYZ 99.895 482.756 null] ->> -% 1181 0 obj -<< -/D [1175 0 R /XYZ 99.895 470.801 null] ->> -% 1174 0 obj -<< -/Font << /F16 554 0 R /F8 557 0 R /F11 750 0 R /F14 767 0 R /F10 766 0 R /F27 556 0 R /F30 764 0 R >> -/ProcSet [ /PDF /Text ] ->> -% 1187 0 obj -<< -/Type /Page -/Contents 1188 0 R -/Resources 1186 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1138 0 R -/Annots [ 1182 0 R 1184 0 R 1185 0 R ] ->> -% 1182 0 obj +% 1214 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [253.818 555.748 265.774 566.597] +/Rect [376.221 332.303 388.176 343.151] /A << /S /GoTo /D (table.15) >> >> -% 1184 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [457.829 326.22 464.803 338.84] -/A << /S /GoTo /D (figure.8) >> ->> -% 1185 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [357.569 302.697 364.543 313.546] -/A << /S /GoTo /D (figure.7) >> ->> -% 1189 0 obj -<< -/D [1187 0 R /XYZ 149.705 753.953 null] ->> -% 1190 0 obj -<< -/D [1187 0 R /XYZ 150.705 465.033 null] ->> -% 1191 0 obj -<< -/D [1187 0 R /XYZ 150.705 431.215 null] ->> -% 1192 0 obj -<< -/D [1187 0 R /XYZ 150.705 387.38 null] ->> -% 1186 0 obj -<< -/Font << /F27 556 0 R /F8 557 0 R /F11 750 0 R /F16 554 0 R /F10 766 0 R /F30 764 0 R >> -/ProcSet [ /PDF /Text ] ->> -% 1195 0 obj -<< -/Type /Page -/Contents 1196 0 R -/Resources 1194 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1198 0 R ->> -% 1197 0 obj -<< -/D [1195 0 R /XYZ 98.895 753.953 null] ->> -% 1194 0 obj -<< -/Font << /F31 770 0 R /F8 557 0 R >> -/ProcSet [ /PDF /Text ] ->> -% 1200 0 obj -<< -/Type /Page -/Contents 1201 0 R -/Resources 1199 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1198 0 R ->> -% 1203 0 obj -<< -/Producer (GPL Ghostscript 9.22) -/CreationDate (D:20180323100658Z00'00') -/ModDate (D:20180323100658Z00'00') ->> -% 1204 0 obj -<< -/Type /ExtGState -/OPM 1 ->> -% 1205 0 obj -<< -/BaseFont /XYUGDR+Times-Roman -/FontDescriptor 1207 0 R -/Type /Font -/FirstChar 48 -/LastChar 57 -/Widths [ 500 500 500 500 500 500 500 500 500 500] -/Encoding /WinAnsiEncoding -/Subtype /Type1 ->> -% 1206 0 obj -<< -/BaseFont /XISTAL+Times-Bold -/FontDescriptor 1208 0 R -/Type /Font -/FirstChar 48 -/LastChar 80 -/Widths [ 500 500 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 611] -/Encoding /WinAnsiEncoding -/Subtype /Type1 ->> -% 1207 0 obj -<< -/Type /FontDescriptor -/FontName /XYUGDR+Times-Roman -/FontBBox [ 0 -14 476 688] -/Flags 65568 -/Ascent 688 -/CapHeight 688 -/Descent -14 -/ItalicAngle 0 -/StemV 71 -/MissingWidth 250 -/CharSet (/eight/five/four/nine/one/seven/six/three/two/zero) -/FontFile3 1209 0 R ->> -% 1208 0 obj -<< -/Type /FontDescriptor -/FontName /XISTAL+Times-Bold -/FontBBox [ 0 -13 600 688] -/Flags 65568 -/Ascent 688 -/CapHeight 676 -/Descent -13 -/ItalicAngle 0 -/StemV 90 -/MissingWidth 250 -/CharSet (/P/one/zero) -/FontFile3 1210 0 R ->> -% 1202 0 obj -<< -/D [1200 0 R /XYZ 149.705 753.953 null] ->> -% 1193 0 obj -<< -/D [1200 0 R /XYZ 283.692 272.519 null] ->> -% 1199 0 obj -<< -/Font << /F8 557 0 R >> -/XObject << /Im4 1183 0 R >> -/ProcSet [ /PDF /Text ] ->> % 1215 0 obj << -/Type /Page -/Contents 1216 0 R -/Resources 1214 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1198 0 R -/Annots [ 1211 0 R 1212 0 R 1213 0 R ] ->> -% 1211 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [368.549 295.182 444.603 306.307] -/A << /S /GoTo /D (vdata) >> ->> -% 1212 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [205.998 285.441 217.953 294.352] -/A << /S /GoTo /D (table.16) >> ->> -% 1213 0 obj -<< /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 215.901 361.779 227.026] +/Rect [345.53 264.991 412.588 276.116] /A << /S /GoTo /D (descdata) >> >> -% 1217 0 obj -<< -/D [1215 0 R /XYZ 98.895 753.953 null] ->> -% 276 0 obj -<< -/D [1215 0 R /XYZ 99.895 720.077 null] ->> -% 1218 0 obj +% 1219 0 obj << -/D [1215 0 R /XYZ 270.132 466.542 null] +/D [1217 0 R /XYZ 149.705 753.953 null] >> -% 1219 0 obj +% 272 0 obj << -/D [1215 0 R /XYZ 99.895 435.558 null] +/D [1217 0 R /XYZ 150.705 720.077 null] >> % 1220 0 obj << -/D [1215 0 R /XYZ 99.895 435.558 null] +/D [1217 0 R /XYZ 320.941 511.222 null] >> % 1221 0 obj << -/D [1215 0 R /XYZ 99.895 423.603 null] +/D [1217 0 R /XYZ 150.705 480.819 null] >> -% 1214 0 obj +% 1222 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F11 750 0 R /F14 767 0 R /F10 766 0 R /F7 765 0 R /F27 556 0 R /F30 764 0 R >> -/ProcSet [ /PDF /Text ] +/D [1217 0 R /XYZ 150.705 482.756 null] >> % 1223 0 obj << -/Type /Page -/Contents 1224 0 R -/Resources 1222 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1198 0 R ->> -% 1225 0 obj -<< -/D [1223 0 R /XYZ 149.705 753.953 null] +/D [1217 0 R /XYZ 150.705 470.801 null] >> -% 1222 0 obj +% 1216 0 obj << -/Font << /F27 556 0 R /F8 557 0 R /F30 764 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F11 755 0 R /F14 772 0 R /F10 771 0 R /F27 560 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> % 1229 0 obj @@ -13798,963 +13288,1268 @@ stream /Contents 1230 0 R /Resources 1228 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1198 0 R -/Annots [ 1226 0 R ] +/Parent 1212 0 R +/Annots [ 1224 0 R 1226 0 R 1227 0 R ] >> -% 1226 0 obj +% 1224 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 210.686 361.779 221.811] -/A << /S /GoTo /D (descdata) >> +/Rect [203.009 555.748 214.964 566.597] +/A << /S /GoTo /D (table.15) >> >> -% 1231 0 obj +% 1226 0 obj << -/D [1229 0 R /XYZ 98.895 753.953 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [407.019 326.22 413.993 338.84] +/A << /S /GoTo /D (figure.8) >> >> endstream endobj -1240 0 obj +1239 0 obj << -/Length 4181 +/Length 3619 >> stream 0 g 0 G 0 g 0 G 0 g 0 G -BT -/F27 9.9626 Tf 150.705 706.129 Td [(mold)]TJ 0 g 0 G -/F8 9.9626 Tf 29.805 0 Td [(The)-333(desired)-334(dynamic)-333(t)28(yp)-28(e)-333(for)-334(th)1(e)-334(in)28(ternal)-333(v)27(ector)-333(storage.)]TJ -4.899 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf 40.576 0 Td [(.)]TJ -70.188 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-273(as:)-414(an)-274(ob)-55(ject)-273(of)-274(a)-273(class)-273(deriv)28(ed)-274(from)]TJ/F30 9.9626 Tf 198.261 0 Td [(psb)]TJ -ET -q -1 0 0 1 390.19 658.507 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 393.329 658.308 Td [(T)]TJ -ET -q -1 0 0 1 399.186 658.507 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 402.325 658.308 Td [(base)]TJ -ET -q -1 0 0 1 423.874 658.507 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q +0 g 0 G BT -/F30 9.9626 Tf 427.012 658.308 Td [(vect)]TJ +/F31 7.9701 Tf 260.921 653.177 Td [(Pro)-29(ce)-1(ss)-354(0)-8986(Pro)-30(cess)-354(1)]TJ -33.381 -9.464 Td [(I)-1500(GLOB\050I\051)-1500(X\050I\051)-5180(I)-1500(GLOB\050I\051)-1500(X\050I\051)]TJ -1.185 -9.465 Td [(1)-5253(1)-2148(1)1(.)-1(0)-5031(1)-4722(33)-2147(1.5)]TJ 0 -9.464 Td [(2)-5253(2)-2148(1)1(.)-1(0)-5031(2)-4722(34)-2147(1.5)]TJ 0 -9.465 Td [(3)-5253(3)-2148(1)1(.)-1(0)-5031(3)-4722(35)-2147(1.5)]TJ 0 -9.464 Td [(4)-5253(4)-2148(1)1(.)-1(0)-5031(4)-4722(36)-2147(1.5)]TJ 0 -9.465 Td [(5)-5253(5)-2148(1)1(.)-1(0)-5031(5)-4722(37)-2147(1.5)]TJ 0 -9.464 Td [(6)-5253(6)-2148(1)1(.)-1(0)-5031(6)-4722(38)-2147(1.5)]TJ 0 -9.465 Td [(7)-5253(7)-2148(1)1(.)-1(0)-5031(7)-4722(39)-2147(1.5)]TJ 0 -9.464 Td [(8)-5253(8)-2148(1)1(.)-1(0)-5031(8)-4722(40)-2147(1.5)]TJ 0 -9.465 Td [(9)-5253(9)-2148(1)1(.)-1(0)-5031(9)-4722(41)-2147(2.0)]TJ -4.234 -9.464 Td [(10)-4722(10)-2147(1.0)-4500(10)-4722(42)-2147(2.0)]TJ 0 -9.465 Td [(11)-4722(11)-2147(1.0)-4500(11)-4722(43)-2147(2.0)]TJ 0 -9.464 Td [(12)-4722(12)-2147(1.0)-4500(12)-4722(44)-2147(2.0)]TJ 0 -9.465 Td [(13)-4722(13)-2147(1.0)-4500(13)-4722(45)-2147(2.0)]TJ 0 -9.464 Td [(14)-4722(14)-2147(1.0)-4500(14)-4722(46)-2147(2.0)]TJ 0 -9.465 Td [(15)-4722(15)-2147(1.0)-4500(15)-4722(47)-2147(2.0)]TJ 0 -9.464 Td [(16)-4722(16)-2147(1.0)-4500(16)-4722(48)-2147(2.0)]TJ 0 -9.465 Td [(17)-4722(17)-2147(1.0)-4500(17)-4722(49)-2147(2.0)]TJ 0 -9.464 Td [(18)-4722(18)-2147(1.0)-4500(18)-4722(50)-2147(2.0)]TJ 0 -9.465 Td [(19)-4722(19)-2147(1.0)-4500(19)-4722(51)-2147(2.0)]TJ 0 -9.464 Td [(20)-4722(20)-2147(1.0)-4500(20)-4722(52)-2147(2.0)]TJ 0 -9.465 Td [(21)-4722(21)-2147(1.0)-4500(21)-4722(53)-2147(2.0)]TJ 0 -9.464 Td [(22)-4722(22)-2147(1.0)-4500(22)-4722(54)-2147(2.0)]TJ 0 -9.465 Td [(23)-4722(23)-2147(1.0)-4500(23)-4722(55)-2147(2.0)]TJ 0 -9.464 Td [(24)-4722(24)-2147(1.0)-4500(24)-4722(56)-2147(2.0)]TJ 0 -9.465 Td [(25)-4722(25)-2147(1.5)-4500(25)-4722(57)-2147(2.0)]TJ 0 -9.464 Td [(26)-4722(26)-2147(1.5)-4500(26)-4722(58)-2147(2.0)]TJ 0 -9.465 Td [(27)-4722(27)-2147(1.5)-4500(27)-4722(59)-2147(2.0)]TJ 0 -9.464 Td [(28)-4722(28)-2147(1.5)-4500(28)-4722(60)-2147(2.0)]TJ 0 -9.465 Td [(29)-4722(29)-2147(1.5)-4500(29)-4722(61)-2147(2.0)]TJ 0 -9.464 Td [(30)-4722(30)-2147(1.5)-4500(30)-4722(62)-2147(2.0)]TJ 0 -9.465 Td [(31)-4722(31)-2147(1.5)-4500(31)-4722(63)-2147(2.0)]TJ 0 -9.464 Td [(32)-4722(32)-2147(1.5)-4500(32)-4722(64)-2147(2.0)]TJ 0 -9.465 Td [(33)-4722(33)-2147(1.5)-4500(33)-4722(25)-2147(1.5)]TJ 0 -9.464 Td [(34)-4722(34)-2147(1.5)-4500(34)-4722(26)-2147(1.5)]TJ 0 -9.465 Td [(35)-4722(35)-2147(1.5)-4500(35)-4722(27)-2147(1.5)]TJ 0 -9.464 Td [(36)-4722(36)-2147(1.5)-4500(36)-4722(28)-2147(1.5)]TJ 0 -9.465 Td [(37)-4722(37)-2147(1.5)-4500(37)-4722(29)-2147(1.5)]TJ 0 -9.464 Td [(38)-4722(38)-2147(1.5)-4500(38)-4722(30)-2147(1.5)]TJ 0 -9.465 Td [(39)-4722(39)-2147(1.5)-4500(39)-4722(31)-2147(1.5)]TJ 0 -9.464 Td [(40)-4722(40)-2147(1.5)-4500(40)-4722(32)-2147(1.5)]TJ 0 -9.465 Td [(41)-4722(41)-2147(2.0)-4500(41)-4722(17)-2147(1.0)]TJ 0 -9.464 Td [(42)-4722(42)-2147(2.0)-4500(42)-4722(18)-2147(1.0)]TJ 0 -9.465 Td [(43)-4722(43)-2147(2.0)-4500(43)-4722(19)-2147(1.0)]TJ 0 -9.464 Td [(44)-4722(44)-2147(2.0)-4500(44)-4722(20)-2147(1.0)]TJ 0 -9.465 Td [(45)-4722(45)-2147(2.0)-4500(45)-4722(21)-2147(1.0)]TJ 0 -9.464 Td [(46)-4722(46)-2147(2.0)-4500(46)-4722(22)-2147(1.0)]TJ 0 -9.465 Td [(47)-4722(47)-2147(2.0)-4500(47)-4722(23)-2147(1.0)]TJ 0 -9.464 Td [(48)-4722(48)-2147(2.0)-4500(48)-4722(24)-2147(1.0)]TJ +0 g 0 G +0 g 0 G +/F8 9.9626 Tf 95.458 -98.979 Td [(58)]TJ +0 g 0 G ET + +endstream +endobj +1243 0 obj +<< +/Length 325 +>> +stream +0 g 0 G +0 g 0 G +0 g 0 G +0 g 0 G +0 g 0 G +1 0 0 1 104.053 292.444 cm q -1 0 0 1 448.561 658.507 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 451.699 658.308 Td [(type)]TJ/F8 9.9626 Tf 20.921 0 Td [(;)-293(this)]TJ -297.009 -11.955 Td [(is)-333(only)-334(allo)28(w)28(ed)-333(when)-334(lo)-28(c)]TJ -ET +.65 0 0 .65 0 0 cm q -1 0 0 1 281.979 646.552 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 0 0 cm +/Im4 Do Q -BT -/F8 9.9626 Tf 284.968 646.353 Td [(x)-333(is)-334(of)-333(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 52.36 0 Td [(psb)]TJ -ET -q -1 0 0 1 353.646 646.552 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q +0 g 0 G +1 0 0 1 -104.053 -292.444 cm BT -/F30 9.9626 Tf 356.784 646.353 Td [(T)]TJ +/F8 9.9626 Tf 189.268 260.564 Td [(Figure)-333(8:)-445(Sample)-333(discretization)-333(mes)-1(h)1(.)]TJ +0 g 0 G +0 g 0 G +0 g 0 G + 77.502 -170.126 Td [(59)]TJ +0 g 0 G ET -q -1 0 0 1 362.642 646.552 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q + +endstream +endobj +1225 0 obj +<< +/Type /XObject +/Subtype /Form +/FormType 1 +/PTEX.FileName (./figures/try8x8_ov.pdf) +/PTEX.PageNumber 1 +/PTEX.InfoDict 1245 0 R +/BBox [0 0 516 439] +/Resources << +/ProcSet [ /PDF /Text ] +/ExtGState << +/R7 1246 0 R +>>/Font << /R8 1247 0 R/R10 1248 0 R>> +>> +/Length 3413 +/Filter /FlateDecode +>> +stream +xA +8s^˒- Svҷj&{|I(m|%Zߟ[ynx?ף?lOgaV+_.=ݥM:߷ZKض[J'Ĵ8͞MTmi&v @%o3o{ lv #"6ف|lvD"@663_dl# Md9D.>}m= m|{DdF@6;.6CZ$ lm"nG6mdK33/ g#"\~>g#"\~N [363_dl# Md9D.>Мqht3L9.LC f4f :f 37fjL9.. ]f h33͙Z3ŌAnjAsyfALA ͠ +lA7b8tS!jq 33BĖ zG.á*jp pF.jo,*o)TwK٥[.Rr▂K-U[rC܎V8V]cz?Z+̣gD_6^=tjnf9 Y2& +\h6O`Ih]g4@h6!PN7#Cw*uAH MGۏ?>Eh!3h$Kh6!P̹mCD]jcf]Q)&2@AZ[YM +͆e|_Ŭ롾oƋ;2ї"F:#}]/~.%0Q&G@_v&a}wQU=}jj.3u˖: 2=ep?TwǕ%v>ʮm).=o|X"ȕ +כAC\Wh ]|ۚ_ܮ2/7k5Ln`1` ps%ks^Qo/ճ*׻ s[AW ]|ۚ_5U慪>ZU @oI|T=b~[ >Z k}o<@g~gU/n\nZ|S+3ع>\vTYqI;sutGD@33t'0smLFD%F푑0.zB.B"+Фz{^t[ާ@`[v ,]$>ȫjHqvEkCTi _']UWMݴ|/Z}\W_'\UkJʼ@g^*yj~œ&?n7 +> 7z3mW=򙿪Ok*#_e}0h;ׇĂUmxPyPp}gZz43cL̵1Y][Vέ5x]Oh5E_ZSYdUZR6Tl4^l]M׵6Nɋ&%ě)?'Q:V\ֆU n|œzC+wum_kC*\b[=?' G_ߙ8"*1L̵1Y=Ƣzځm,uZMuTYaU&[:ZGv_P=-F5louY*oX<M+7uys6cn:|oœԱzS7>Zj?|b+T|oœ}Ա2/P=P[1`z:b$>6uMWֆ}qwf-G>7u|M#_e^z䫬Zaꦓ9X?񶎏x0z~DDE]ׅaX!>do֫\̕w-/Iv!o'ȟ`[G. +endstream +endobj +1251 0 obj +<< +/Filter /FlateDecode +/Subtype /Type1C +/Length 13073 +>> +stream +xwxW?laό rG5hB'ZBL1`pø˶$KeK%Yr-˽w L% $$$m{Ȗ<<~4ss>s +o%!)&c攤}7#-VyR/<1cNc~G8fA>~<ެ5onݼ &.II'KO:mh4&#!.yIV̡Ԥď/<~sL\}Dsݧ<*wjM}~___;bd,`|< +) 'G;?̷с'7ɏ=, c|?1;nkc]4vƍ-p+ +|ApQg ͿؿĿɿӿI0`I@x2 0$TՀ d_ |#p]`Z`f5.b? ~򠸠 ڠ栎A烾 67P('|S8[ppp0Gh +&aGxE ! O^*8|=q?wʇRSsJjOTUBPT'uI=L&%"E0KDSEDEDEE[D"HdEuI% m}WE#!CD!lĐi!C, Y1$2$>Db ) q4t9r!Ð!C~- +S+F~*hb8PoJ)R2dV8ܪ&\YR)z%-V p;qFߦldz3n'-ڵVZX箷mF;k(5:'[2 4i<o ?3[pP ?ϦP8^AQ:̮4 AF%ɖGkgN'vuLB@Q8t{`;'Pp',\8.0O5 +C +bc}{C}¡F΁3bt񪝻O[w +v2RcpmIjk4Ϸ@wؗ/:/>ڱ##*z#Z<{)2mbи߀A0gvN)' £V.<x8M9sc_À%dM$ p`iɩnp}E}*]E|%<$v*'PN¢݇kV0y,!o2LAXpTE&¸1/wg@7jKvYr7%Ptw⣹}im`̬4j +M|B_k6u.$.a>H Z8 /흴3k_ٝ`B(HG4f[Jm{/ e{ ֓]qH'1e_LZ٭ +rĀifeŦruɈah~F/%-&O-yn-7>m|f]5 tySs9Pa:bϝn>y9rc1$bLNg3-%%"AۛK(U3ya1!9b<ᵈ|yzaK#_ޛBJ|b{ʇV>p$x Ka]hc*IfTYt|JQJ у|pz (E g1ǣݨ.$v8O$:@IU*+X0W"ђ8%ף{MNe'!F0K?y ӾwO>Y췋2N{F?Qp [`8&-h3& oysø߈Adl3JR@y{HwE҅ĽjU!wߚ[a8GS#U\cx@?7Rgkf2.'"B>*=K=Ŝ# D6Z55A‡iȪbJU.%Z5 ' 7K 9#kziΒ?JVP@Q*ldžΟ:5%P=Iqq1m}m,`6ˍ}ap-ǣ VEo) +sh,:8?_fdJX;&mm-0T09^1`,/r"g6Qh>N߬ K*rSe.͍`G㶢y|?S-vVpv3ՠ5RU_c9~ K{]5([OSS _ erG-S?fV( +Cs]e tFqM3ߝ+U^WqzE";ՙh5[>#!-&%."W;'3P7`°$W@"A YhDM}].NTv.FC?ӠЋê}lNcnšz~mky1giE{:I^R_HÉkwNy&PPrX_ +;ӸFd4L퓋=w%1l(/Ϸbgz '}`g(ď w +GCv nJH{/p#'n2#FBgE*iuJVeYtb<5Sz6\B>nP8YjقL$B 9R\*g*]8(|Wyjܳ .=IMG+Ih ifqZPχ=72Ǒn$ 3D>bDFϚ$ؤAWveY BoI[a+.J5,JtƤ!Y ̀'5qCPZZd+4rwsÑX"XJEѵaDgH̃\q{O?߾Y#W+wk`Um-OƱ* c8n8G$蠟-\T#oiutXX]憚tcmslbڙqd,$#$ح@AK25,*YYk|,e[e9D?c%TbZZbbsZgGssggZ!?Rö6Z[/Pؒ8Q,_40|b>?G} Spk\ojXZM|8;X 2 `a+^3xSD.Bj= ?5xXVLZpjU!A4>:DWEC ;vQI8Q$p8A$Тz<8`k'hGhvnsK)D㐆+!μ|.*4 +Wb]r$H,kV:SSyLJgˣ9YKhGMCDduRW3Mrl]Kɒb2IYA{$؟_Yg՚909R+y:b>MZ +m~ޙ>y&nڙel}4+*}&|$z#( +fr1.wrl8 ;h+(EvDb7]FqCf(nH#"Kn)(ͨ5Xi{T{'Z/:dWY1칛Yt}džO\E~)h@)ʣ4Elyy!{ ȯŀj R%ߐ I5h2Ujdb@͗T;U̎CҦeiJZf(3<+TJJe^ljmsV72]qlRt^n<%H<B.֞憓Ȃg?"!pQ kp=e , O)1ŵYׁej{h4#܁FZ$rso;#V$dr&e;yf( $AJHP/`䵛UE,q. J$Z5gŞ8voua ~rk22reఄ pR|}R)%rv7BM7'&Q#qbw@?{0@=7HQgHۮwQk:!ym' + F)[+ncіG>?)NCi +!:+V`OLۣ߰L@'LG?wze;HhGFxpv(Hu"(r3(OI.Iw8&(|f|N_CZO%R +;ʪaN{0<8\|Q_ei۶̓ X/2R PQMyTPk?9nWHBՂƸ߮/L1/)%9limo#SYTLZ@b[N,E@wQu`_v+j_1p};DN่Ūq||-ogRiJ2pVCqbB1|A9v8__n{CByCw8}ǃ|+͹yn@H(,^?'AQ4ō}[5 +xⒹg7z±⏮gDŽt0̡yd=Q"G3:֪^ɜWaVAA`)h{aqm_鋂O^8۠tf'1ǒW~Z=~a|/c\@y5|$I5@p }| <3 k<8]M? p .<<o;*£߮`-2v]w>?H;Y5߇LشU3 @1}$$s*7,u/|IxeLb2QN=9Zn x=`g}8 [Edkcֲ-p>pZ3E꫓KP u`wvlu]Gi-=w<[9O15V^0$_J5e`G[ \-㥗_BSW&?"8ooqQQ䃺ÌKq//~bZ9k{9~ko~*b8g*DLHpg.9z,f!hb^ϩ|FD|+uͬL˽`f^㏰G_h>ڲ/'.4ZFu!pfOK5=NJᾩ%Q_CA1{ϜoL8G=az<ê'6'>_Q>ld9:P`F+b*9h/JN°VZ` TUme0 +'+d,kj3fY:f,O5>Gx8,M;77ڷc~~R?E~Ncq|4._⅄& +¿0z?运D6|J `&X*1pCY}#EDBCƅzȄ^sGJ@6G +]"H]sh!tWTVީ.wOJ>&zeģ?M-ly` UYyg||[-eєCf8:0^^WDdpW-]VaUh : XE=M%NWl322 Fr9 + zԊ8Z7y yodVޯ4\ëxN~oHyB t1wfBO\>GNw]6̨dV_AO(50RYl+KKѓ-9ÃlZFV:0,+SgflO;+`Ϗr_\deUm5gV]=-`;[:خVg)qA 툘v?ԝʍ۴¦onj(ufm{rkfER5S__{]?2% u8q87(x|'rQ`^GRYop oN2'^oE_8%gۓӚe:ynɱ3*Esa+ 6oG_,CW\'ų ȕxgu~NQWeFm%Lrڏ'Vͅ5yđ1"di;cz!&]%SѺ|o.[s ,`G[γpgbegyY% dJ&sv*fr\.GM+-6%[k#3Жuu1S(1 8GI [xelzm/o.:pLtԮI_eӖzK()[0%0a +SXEJ°(_'%UU{PH?xl蔌R_1K yTjYD\fzO!۟VjbؒL,Ru kGv\4sOʊybD= }eZj[/aױi$hw@Ray!F( C dѪ:Rb/ZbUYgGjJsN2fGN5Y5]Y})Kvqqlxf*\CXJMt aXvnm\+g%|?RMH=1zgw!MɭI*0D?E\*5328y Sz` 9񵖼2м#'6o",0Wtg*I#[Uu>X=. +4r5Д)d\۫+H쳦; 2g1M ˵kPN |*G~PV-E5b_#>6f;,\;/[|o0W8|I59);HJOOLnJohnlHkNbvV^yFނ_8a,g؇ @|Phb̥&B3$p\Uo`D9_Cn$zQ)gBN;n[F]bTF_gj,֕6uu zWmz^-R0ƢCIiZ]6xr6ls7ĽڴT,.ˤ +g$$_N—zDUVŽqiɺ⫳LDlIc׎ޢ6.}  +Q{Pݫ+çh4 +]{b/C%PZ ?\b@q=U3B>6{cM|&}ZnStBl1^e:!!G"eFYɧ|>DYq.z̵bސ+`tΨlJcQ;ZZ*a5(\QAԕiBZâhgDZ S "ÔF x)2 C)Tk ',&LuMpQ!Δ&meh&OJ?+ᔬOF<З͋ɼyќRnLJ溿=vyXK62bKvlOH-p3xj-[X-r# N"`>ސvm!;OU&2g˙ځ@ 82ē㤶Ə0x}n}v3"ī 䄥([%QG^v$0,ld+(7p?ǏO6-c.°4?oOxxCۯ¯"Q/,QWa4;HFbmC6ddY- KRS^7`^5&=+5*DkͣSI}=-lc!-we2Sh$W/W0sQ,O⺊#A;ح/.>$a@Fj{d.&;.?@wpj~~-aHڔYQt9BOsk͑~񅸳;ƽmoӻQRSÕnPl?[cE zc;mk'TfE9,`Vk&[:"RMGRzW+*ԟz~Vn¼e:XU\E +GP2}Z\*c\o06dY^<6NMZj" "\ث7$[9*ZPpc4SU@hW6A"PI?ْzY6IJ7J|oOPCzkyAK) l)Np,z+a+cV;|# r &%JVĬdQaj Nxsg ޜqDJ)jJ ,~V n&ڕmFA&>:(_trd?JSMZGSFfJS &]>W@փOJ x֏j< ʚGvn޼ ( &i:=+A|3+m(zФ.3iPvAs[_˞ S"$_"A7>h9L:5xd1 fm&}Ʃ2WKKe.iL.UTMs̀m6W ™=x3_xޢ0AH\(6Ψ6FIxELU6T^ΩSc*PZzVoY2ߜOgd5(:|pљZѐÂTR%]G1X*0ph"(*lۿXG~Aygҳh @ gPPu=,Iy,P=G޴<ǧ{H!A += +B]9n6Ym1,PK8K;o76OCӿJ~ݑ&nkό=8'?U\gAK|cK\CA" +\mIU Vi[)Huܪb'aE5q9ӽ%ݕ}[! W~`dw U-mOY#d'@5t;,<-זQO8ykP,nTd+_1yoI*!Q070 8JMv(R*s/Ϧv&Rp!HHFɃ]W$g]Q y%Nԭ UOC\un_~C *%4vܢ%‰كl0^2F~ 996=/ `/v pć0e4:G*,-%| 4Ttuu$5ۇ+J\fo[qC +E'l>h,@[hZBAMr eJ}xsi@B`_)y`mqGz۽bM| tZ) ŽuNcpMSWo3r#]a5Ϳ+Wy{?q*>;^Z9 yƇŒp'\h"ղkpxتTR)oǤp!UK͝Q,K +endstream +endobj +1252 0 obj +<< +/Filter /FlateDecode +/Subtype /Type1C +/Length 11578 +>> +stream +xzwxT/C؅IfF&X* -dLI&d&I2BHB Б*"ǂ~krV< Ͻ̓{wWwI&MqxØtttt4I*͑vJ9Nv9.s\x11ɱƱG:N38-rZ:NNNeN>!N8}r,u~Yty^gogssssMϝs ¹個K%%%եĥe.w\|Df/s͒-mԲYTfʮnޗ}"RDW?TTW7˽Apy<^"7ȫ->o?fv1clj465El9[625c"{'>wKNYER}Џ C7#i׹ "̦b3|E&!/M20,+=? s6Th8<p*NRpXAb8AԒG]5#W@V1 6ZX*|@D&<4?|!%HtP +b˛ Buc*+`ha49ȌVU&=A(+-B0h)((=_?Gg%U!\zFI!h E[)P<rAhh2u= N=UV֞Gn<Mvg(ZeBr@F6 u >3D'_0#m4՛co1336Ӣo|KďdW+jˊ[ TTsvAV8f&33A4%~ pN,ҍ<$ {yˎ[=~B~aQ=N'DW-dcyQQ)WX)SFR۸7r`)qS[SjiiNk ^40B3'i_L_+B+J}n98.]c+Y"ɮW!QC;=L-uӓr**%@XЗ*So +PkKuhx6}mآ"}=k[_HVOZ"?X:-^N9MawU +(l.*)Js3ijݙϡ}[OhĪXS=>R 7m0u2x(5.7x`f += +M f| 4:G%čњ"0=/GqPÝj6^|f 1Y  ś;2{ss8sK2~yx^U*XPz?APg:HSm3x8߭nȠu%\Fa @ez:o8rl3|DKK(xk cٵ9tAn~V"--!5U@r$'Ѯhꄾ:7Љ0SGs4$&wHAԩR2)Yz!jTjv~E`mQ< +SyEPjB1j#8mIT=- ?)9!.,)Ca^A>U=7i + xk\_O +Ou/1I`<O`O('[[O ߨ6ѰWwyDy]tJ~a|Ӯ%a(| +C"tFI""od'iWd>&SEq෺7+^P/ gB.Mŀ1~weHAH,"+}% +\ېZ:_RhV"*;^WXk#DE6$n0% o`z+(c݀Swѫ9yE)ƚҼrо}T`leib=BgznzšIٯO.ZAmSIog\~ʜp&/VSYq!N|K|G᧊RjRLqBXsFAx>+{a/դV +rxtc2Ful]$B[{y +Gdo z_Ag!%6bz.zΓ87QV >dƜL. 6s]zD 125V˵m"°~6HS {GHx:%<8+۲k4\ ?O + ~n\ef +YL4"G^~U^i#UuH%<W'1Y4US8]ZuFsK}~y.*n8r&7=\f29mVQqd>ǢDR1h/K`v`Α}_`A߲Qmb}<;;;:Ei!` KQ}Ikmv%zW +{X!*X^1Ǝ?1L&8+@#(xt6U'M(V;(F漮/4i)Z9#62 sRh45U4r]08ᡞ!pGx'r;P?/Ql5 0Q)&CGj{ߛ4(nzMQ) +4vE`K.,bmspFjMFU]o[#h֗dF)Eʠ&ڀ:x(OVo9*ԟ(鹪^b\`Ʊe +|p ?25,)ͭO񅍌hiiijjiiABz qtwi`?3% 뛹J@' + i:~B,)8'@y>'"*p1QVkS-BҖ+4 S"H0 ՝ܩ(/-S3NiDtQ]4I42&ǁV*/ϱI@Ep)8汣 a@ 6-El%;!ARyyZ _d/ +݈}:kx ݢγ\_Shǃ$R>upB| +(i|էzU I1m+(,,,((/.~Rb(+-(wx7<;lI2,+gO79rM[n.NmєWlR5n}b1L\ ?!WkTUHQЛP::y Sӧ~,f01Ig s H L:5p^jO/n}}}_8Lr f99R>vw;K'II*Z^F*͕JWwHpwtr|U}3O;sxs_^rdp:4tOӿ9s^fg/`XTR&=?tхp2ez.]]]]]Z]κuw-fȞ=/[#-E2dYZ 땝ݐ#'J?#V%+u=C Z&ϒeZyM%ߒ$$^>Nb3Lv}]ƾbAl沥l-{gϰ٫m=dWu닮]_wuWo`XWkkkEkc{,I?n{sj9[uʼn '2:rҰ,i8 9j!\4Ӆ铳Onײ>,7\bkyHu<4<|h>ހ>o"䇎 +F,` Hé"d҈\}6YR+*H1G;+5BzYnQdVy!:-TMI="R;s+|hvtKEL] !쭓Z]qt@au*,0 qZ+ wZ(G?V56tOIc[B򲻳ٷO0]&#@Dl .pR+iaikƲrCWR] ȁ +ˏ.U ApٽwbDSR|Y4Zӑ"J2(b[: u:783G*{BF#^_OnKx*\ 'רCChcp;m:kD~n*vnݓS7d*} +l3Y]\>e'yŌ<M8JPbN> єhʏ>b )ES%4;#+k,3{2dp֗豳fKx]\w<{^yVp~}o~Ux‡o,~Cߏp?\o>-B^zZM;Vxm!ՇMbilAJ?{ё Iуe/ЍpxN jk+yz*2m؇h%附IW2NZ:q~qk"aryEݙZA=h@GIi\No溛[{:RFm:*~DSS&:6iޙ8p0`L +(:8F5 T:FgxU: ݆q?i +H/ ,"tETBRËt2ژYBe֟Egtְ`?t5Tbzsi~eILg?CZLle#,J; t5^E+, +QU_;8Vp3F,^E~SfGϢnS?,x]ۆ,BlUNș\9uFwz<ҹ'UKBo" ݢ<4op*CH~S"\lGh_, _Oh#*7fxh^Cm +Z;Uő5{`A~.L6 55-B RW9qm;4 _¶h +s|h S &+Qͺ+B)(}@Ý '>R@zmz]NvUq]ߑCt"[?bj+:uxISQ1::8sƖKD*MQ`@3<pMֶ5@kh&ԙG=[" N/ -}JU'3Ss҄T7kTe[ӑu rB$q}"`_)d\xAeVUs{֮b|us8 ###G$:]yr(J]CӽVp@>jYhtQ"$ + ű + q𙞓gl{SK$S'N#h!| ݧ#kh-V`xXNr tEƶQ`|́1!q]Yb_A_#<s=ZV (Ĵ(CyVh:b7GtI?\c@@`i{jeqBR=H@G +m_&K + yn߇Ē1"@[EbK9Z{Y?j&:hZf% S5ݡ҉Pݡt]&c}eMg/pHBד'ugD>&FW0Q2z=KWL=Ksn߾mجKTW-WtG+D`s21;{x@^(q?HC_j;|BO:6# r{ByGq.6 Ck +ʄlGUWZmL:`"2?5.,_2:dzj̸<,Vz;m\ҋ +5@;L p63I+LK| y`3XC[*?zmĹYy,Aq}GESl(cx[3a_b)q!vSSPP?GD)D٥o)pCJ# 8x!A?ޜ4oJs[BxLt]U p6|ɧmy&`a6 tpz'פ|Q 1oYb ZWDjcQea)r|?nMĆh9ZQ \VC{?[d y[K0yEGV+߄C|3H42ju#?K=cў p>db HnMl%:HQûz!F\DB,hjŔ5) h Pvܥ>' [ +e@<щP.8+r9|Lh02+cb=]s:ַߜ={\{x}sV='фna;/?d9qt]QfыC +,xC; N 2kܶjPңdֱC~ M\THr`AM} esXnS?=tG[G>w=0aK6nogm7ڣxo[|=:w≯gCXUtrf47jH2 )=-KO.({(BA")Jah y4/p6@S ;`#ёjn:0={aәx P]Q9:7gw:@I> +stream +0 g 0 G +0 g 0 G BT -/F30 9.9626 Tf 365.781 646.353 Td [(vect)]TJ +/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ ET q -1 0 0 1 387.33 646.552 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 171.761 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F30 9.9626 Tf 390.468 646.353 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -260.684 -19.925 Td [(On)-383(Return)]TJ -0 g 0 G -0 g 0 G - 0 -19.926 Td [(lo)-32(c)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(gather)-375(|)-375(Gather)-375(Global)-375(Dense)-375(Matrix)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(These)-384(subroutines)-384(collect)-385(the)-384(p)-27(ortions)-385(of)-384(global)-384(dense)-384(matrix)-384(distributed)-384(o)28(v)27(er)]TJ 0 -11.956 Td [(all)-333(pro)-28(cess)-334(i)1(n)27(to)-333(one)-333(single)-334(arra)28(y)-333(stored)-334(on)-333(one)-333(pro)-28(cess.)]TJ/F11 9.9626 Tf 120.435 -22.804 Td [(g)-36(l)-19(ob)]TJ ET q -1 0 0 1 165.713 606.702 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +1 0 0 1 289.12 653.179 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F27 9.9626 Tf 169.151 606.502 Td [(x)]TJ -0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.117 0 Td [(g)-36(l)-20(ob)]TJ +/F11 9.9626 Tf 292.109 652.98 Td [(x)]TJ/F14 9.9626 Tf 8.461 0 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(col)-20(l)-19(ect)]TJ/F8 9.9626 Tf 28.026 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(l)-20(oc)]TJ ET q -1 0 0 1 374.277 606.702 cm +1 0 0 1 358.107 653.179 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F11 9.9626 Tf 377.266 606.502 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -207.349 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-244(as:)-400(a)-244(rank)-244(on)1(e)-245(or)-243(t)27(w)28(o)-244(ALLOCA)83(T)84(ABLE)-244(arra)28(y)-244(or)-244(an)-244(ob)-56(ject)-244(of)-244(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 0 -11.955 Td [(psb)]TJ +/F11 9.9626 Tf 361.096 652.98 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.494 Td [(i)]TJ/F8 9.9626 Tf 3.317 1.494 Td [(\051)]TJ -219.402 -20.867 Td [(where:)]TJ +0 g 0 G +/F11 9.9626 Tf 0 -19.085 Td [(g)-36(l)-19(o)-1(b)]TJ ET q -1 0 0 1 191.93 546.926 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 168.775 613.227 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F30 9.9626 Tf 195.068 546.727 Td [(T)]TJ +/F11 9.9626 Tf 172.212 613.028 Td [(x)]TJ +0 g 0 G +/F8 9.9626 Tf 10.675 0 Td [(is)-333(the)-334(global)-333(submatrix)]TJ/F11 9.9626 Tf 103.916 0 Td [(g)-36(l)-20(ob)]TJ ET q -1 0 0 1 200.926 546.926 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 304.784 613.227 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F30 9.9626 Tf 204.065 546.727 Td [(vect)]TJ +/F11 9.9626 Tf 307.773 613.028 Td [(x)]TJ/F7 6.9738 Tf 5.694 -1.494 Td [(1:)]TJ/F10 6.9738 Tf 6.226 0 Td [(m;)]TJ/F7 6.9738 Tf 9.436 0 Td [(1:)]TJ/F10 6.9738 Tf 6.227 0 Td [(n)]TJ +0 g 0 G +/F11 9.9626 Tf -184.651 -18.011 Td [(l)-20(oc)]TJ ET q -1 0 0 1 225.613 546.926 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 163.701 593.722 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F30 9.9626 Tf 228.752 546.727 Td [(type)]TJ +/F11 9.9626 Tf 167.139 593.523 Td [(x)]TJ/F10 6.9738 Tf 5.693 -1.494 Td [(i)]TJ 0 g 0 G -/F8 9.9626 Tf 24.242 0 Td [(con)28(taining)-333(n)27(um)28(b)-28(ers)-333(of)-333(the)-334(t)28(yp)-28(e)-333(indicated)-333(in)-333(T)83(able)]TJ -0 0 1 rg 0 0 1 RG - [-333(17)]TJ +/F8 9.9626 Tf 8.299 1.494 Td [(is)-333(the)-334(lo)-27(cal)-334(p)-28(or)1(tion)-334(of)-333(global)-333(dense)-334(matrix)-333(on)-333(pro)-28(cess)]TJ/F11 9.9626 Tf 234.703 0 Td [(i)]TJ/F8 9.9626 Tf 3.433 0 Td [(.)]TJ 0 g 0 G - [(.)]TJ +/F11 9.9626 Tf -268.562 -19.505 Td [(col)-20(l)-19(ect)]TJ 0 g 0 G -/F27 9.9626 Tf -102.289 -19.926 Td [(info)]TJ +/F8 9.9626 Tf 33.007 0 Td [(is)-333(the)-334(collect)-333(function.)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ 0 g 0 G - 141.968 -388.543 Td [(60)]TJ 0 g 0 G ET - -endstream -endobj -1244 0 obj -<< -/Length 6537 ->> -stream -0 g 0 G -0 g 0 G +q +1 0 0 1 228.797 555.154 cm +[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S +Q BT -/F16 14.3462 Tf 99.895 706.129 Td [(6)-1125(Data)-375(managemen)31(t)-375(routines)]TJ/F16 11.9552 Tf 0 -23.814 Td [(psb)]TJ +/F11 9.9626 Tf 234.775 546.587 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.495 Td [(i)]TJ/F11 9.9626 Tf 3.317 1.495 Td [(;)-167(y)]TJ/F27 9.9626 Tf 111.399 0 Td [(Subroutine)]TJ ET q -1 0 0 1 120.951 682.515 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +1 0 0 1 228.797 542.801 cm +[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S Q BT -/F16 11.9552 Tf 124.986 682.315 Td [(cdall)-375(|)-375(Allo)-31(cates)-375(a)-375(comm)31(unication)-375(descriptor)]TJ -0 g 0 G -0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,mg=mg,parts=parts\051)]TJ 0 -11.955 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,vg=vg,[mg=mg,flag=flag]\051)]TJ 0 -11.955 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,vl=vl,[nl=nl,globalcheck=.true.,lidx=lidx]\051)]TJ 0 -11.955 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,nl=nl\051)]TJ 0 -11.956 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,mg=mg,repl=.true.\051)]TJ/F8 9.9626 Tf 14.944 -20.107 Td [(This)-314(subroutine)-314(initializes)-315(the)-314(comm)28(unication)-314(descriptor)-314(as)-1(so)-27(ciated)-315(with)-314(an)]TJ -14.944 -11.955 Td [(index)-326(space.)-442(One)-326(of)-326(the)-327(option)1(al)-327(argumen)28(ts)]TJ/F30 9.9626 Tf 193.68 0 Td [(parts)]TJ/F8 9.9626 Tf 26.151 0 Td [(,)]TJ/F30 9.9626 Tf 6.031 0 Td [(vg)]TJ/F8 9.9626 Tf 10.461 0 Td [(,)]TJ/F30 9.9626 Tf 6.031 0 Td [(vl)]TJ/F8 9.9626 Tf 10.461 0 Td [(,)]TJ/F30 9.9626 Tf 6.031 0 Td [(nl)]TJ/F8 9.9626 Tf 13.709 0 Td [(or)]TJ/F30 9.9626 Tf 12.133 0 Td [(repl)]TJ/F8 9.9626 Tf 24.171 0 Td [(m)28(ust)-326(b)-28(e)]TJ -308.859 -11.955 Td [(sp)-28(eci\014ed,)-333(thereb)28(y)-334(c)28(ho)-28(osing)-333(the)-333(sp)-28(eci\014c)-334(in)1(itialization)-334(strategy)84(.)]TJ -0 g 0 G -/F27 9.9626 Tf 0 -18.477 Td [(On)-383(En)32(try)]TJ -0 g 0 G -0 g 0 G - 0 -19.201 Td [(T)32(yp)-32(e:)]TJ -0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ -0 g 0 G -/F27 9.9626 Tf -33.797 -19.201 Td [(icon)32(txt)]TJ -0 g 0 G -/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -57.707 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -19.201 Td [(vg)]TJ -0 g 0 G -/F8 9.9626 Tf 16.757 0 Td [(Data)-333(allo)-28(cation:)-444(e)-1(ac)28(h)-333(index)]TJ/F11 9.9626 Tf 123.565 0 Td [(i)]TJ/F14 9.9626 Tf 6.199 0 Td [(2)-278(f)]TJ/F8 9.9626 Tf 14.391 0 Td [(1)]TJ/F11 9.9626 Tf 6.641 0 Td [(:)-167(:)-166(:)-167(mg)]TJ/F14 9.9626 Tf 27.14 0 Td [(g)]TJ/F8 9.9626 Tf 8.303 0 Td [(is)-333(allo)-28(cated)-333(to)-334(pro)-27(c)-1(ess)]TJ/F11 9.9626 Tf 99.266 0 Td [(v)-36(g)]TJ/F8 9.9626 Tf 10.296 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051.)]TJ -294.958 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -57.707 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)84(.)]TJ +/F8 9.9626 Tf 234.775 534.233 Td [(In)28(teger)-9028(psb)]TJ +ET +q +1 0 0 1 370.782 534.432 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 373.771 534.233 Td [(gather)]TJ -138.996 -11.955 Td [(Short)-333(Precision)-334(Real)-3102(psb)]TJ +ET +q +1 0 0 1 370.782 522.477 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 373.771 522.278 Td [(gather)]TJ -138.996 -11.955 Td [(Long)-333(Precision)-334(Real)-3314(psb)]TJ +ET +q +1 0 0 1 370.782 510.522 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 373.771 510.323 Td [(gather)]TJ -138.996 -11.956 Td [(Short)-333(Precision)-334(Complex)-1200(psb)]TJ +ET +q +1 0 0 1 370.782 498.567 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 373.771 498.367 Td [(gather)]TJ -138.996 -11.955 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ +ET +q +1 0 0 1 370.782 486.612 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 373.771 486.412 Td [(gather)]TJ +ET +q +1 0 0 1 228.797 482.626 cm +[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S +Q 0 g 0 G -/F27 9.9626 Tf -24.907 -19.201 Td [(\015ag)]TJ +BT +/F8 9.9626 Tf 276.386 454.587 Td [(T)83(able)-333(16:)-444(Data)-334(t)28(yp)-28(es)]TJ 0 g 0 G -/F8 9.9626 Tf 22.644 0 Td [(Sp)-28(eci\014es)-333(whether)-334(en)28(tries)-333(in)]TJ/F11 9.9626 Tf 121.932 0 Td [(v)-36(g)]TJ/F8 9.9626 Tf 13.617 0 Td [(are)-333(zero-)-334(or)-333(one-based.)]TJ -133.286 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -57.707 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue)-333(0)]TJ/F11 9.9626 Tf 135.409 0 Td [(;)]TJ/F8 9.9626 Tf 4.428 0 Td [(1,)-333(default)-334(0.)]TJ -0 g 0 G -/F27 9.9626 Tf -164.744 -19.2 Td [(mg)]TJ -0 g 0 G -/F8 9.9626 Tf 20.258 0 Td [(the)-333(\050global\051)-334(n)28(um)28(b)-28(er)-333(of)-333(ro)27(ws)-333(of)-333(the)-334(pr)1(oblem)-1(.)]TJ 4.649 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -57.707 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-332(as:)-444(an)-333(in)28(teger)-333(v)56(alue.)-445(It)-332(is)-333(required)-332(if)]TJ/F30 9.9626 Tf 203.266 0 Td [(parts)]TJ/F8 9.9626 Tf 29.466 0 Td [(or)]TJ/F30 9.9626 Tf 12.197 0 Td [(repl)]TJ/F8 9.9626 Tf 24.235 0 Td [(is)-333(sp)-27(e)-1(ci\014)1(e)-1(d)1(,)]TJ -269.164 -11.955 Td [(it)-333(is)-334(optional)-333(if)]TJ/F30 9.9626 Tf 67.857 0 Td [(vg)]TJ/F8 9.9626 Tf 13.781 0 Td [(is)-333(sp)-28(eci\014ed.)]TJ -0 g 0 G -/F27 9.9626 Tf -106.545 -19.201 Td [(parts)]TJ -0 g 0 G -/F8 9.9626 Tf 30.609 0 Td [(the)-333(subroutine)-334(th)1(at)-334(de\014nes)-333(the)-334(p)1(artitioning)-334(sc)28(heme.)]TJ -5.702 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -57.707 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(subroutine.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -19.201 Td [(vl)]TJ -0 g 0 G -/F8 9.9626 Tf 14.211 0 Td [(Data)-363(allo)-28(cation:)-504(the)-363(set)-364(of)-363(global)-363(indices)]TJ/F11 9.9626 Tf 182.789 0 Td [(v)-36(l)]TJ/F8 9.9626 Tf 8.355 0 Td [(\0501)-328(:)]TJ/F11 9.9626 Tf 18.151 0 Td [(nl)]TJ/F8 9.9626 Tf 9.148 0 Td [(\051)-363(b)-28(elonging)-363(to)-363(the)-364(calling)]TJ -207.747 -11.955 Td [(pro)-28(cess.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)84(.)]TJ -0 g 0 G - 141.968 -29.888 Td [(61)]TJ 0 g 0 G +/F27 9.9626 Tf -124.304 -30.984 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.737 0 Td [(p)-123(s)-123(b)]TJ ET - -endstream -endobj -1250 0 obj -<< -/Length 6630 ->> -stream -0 g 0 G -0 g 0 G -0 g 0 G +q +1 0 0 1 201.095 423.802 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q BT -/F27 9.9626 Tf 150.705 706.129 Td [(nl)]TJ -0 g 0 G -/F8 9.9626 Tf 14.529 0 Td [(Data)-223(allo)-28(cation)1(:)-390(in)-222(a)-223(generalized)-223(blo)-28(c)28(k-ro)28(w)-223(distribution)-223(the)-222(n)27(um)28(b)-28(er)-222(of)-223(indices)]TJ 10.377 -11.955 Td [(b)-28(elonging)-333(to)-333(the)-334(curren)28(t)-333(pro)-28(cess.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.761 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)-444(Ma)28(y)-334(b)-28(e)-333(sp)-28(eci\014ed)-333(together)-333(with)]TJ/F30 9.9626 Tf 272.479 0 Td [(vl)]TJ/F8 9.9626 Tf 10.461 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -307.846 -20.135 Td [(repl)]TJ -0 g 0 G -/F8 9.9626 Tf 24.498 0 Td [(Data)-351(allo)-28(cation:)-480(build)-351(a)-351(replicated)-351(index)-351(space)-351(\050i.e.)-498(all)-351(pro)-28(cesses)-351(o)27(wn)-351(all)]TJ 0.408 -11.955 Td [(indices\051.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -57.708 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.761 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(the)-333(logical)-333(v)55(alue)]TJ/F30 9.9626 Tf 131.784 0 Td [(.true.)]TJ -0 g 0 G -/F27 9.9626 Tf -156.69 -20.135 Td [(globalc)32(hec)32(k)]TJ -0 g 0 G -/F8 9.9626 Tf 61.948 0 Td [(Data)-333(allo)-28(cation:)-444(do)-334(global)-333(c)28(hec)27(ks)-333(on)-333(the)-334(lo)-27(cal)-334(index)-333(lists)]TJ/F30 9.9626 Tf 250.201 0 Td [(vl)]TJ/F8 9.9626 Tf -287.243 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -57.708 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.761 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(logical)-333(v)55(alue,)-333(default:)]TJ/F30 9.9626 Tf 163.056 0 Td [(.true.)]TJ -0 g 0 G -/F27 9.9626 Tf -187.962 -20.135 Td [(lidx)]TJ -0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Data)-353(allo)-28(cation:)-484(the)-353(set)-353(of)-353(lo)-28(cal)-353(indices)]TJ/F11 9.9626 Tf 176.171 0 Td [(l)-20(idx)]TJ/F8 9.9626 Tf 17.481 0 Td [(\0501)-311(:)]TJ/F11 9.9626 Tf 17.814 0 Td [(nl)]TJ/F8 9.9626 Tf 9.149 0 Td [(\051)-353(to)-353(b)-28(e)-353(assigned)-353(to)-353(the)]TJ -219.467 -11.955 Td [(global)-333(indices)]TJ/F11 9.9626 Tf 62.046 0 Td [(v)-36(l)]TJ/F8 9.9626 Tf 8.355 0 Td [(.)]TJ -70.401 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.761 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)84(.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.906 -22.127 Td [(On)-383(Return)]TJ -0 g 0 G -0 g 0 G - 0 -20.135 Td [(desc)]TJ +/F8 9.9626 Tf 205.31 423.603 Td [(g)-123(a)-123(t)-123(h)-123(e)-123(r)-229(\050)-215(g)-110(l)-110(o)-110(b)]TJ ET q -1 0 0 1 172.619 376.512 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +1 0 0 1 270.682 423.802 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F27 9.9626 Tf 176.057 376.313 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.55 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ +/F8 9.9626 Tf 274.766 423.603 Td [(x)-381(,)-888(l)-127(o)-127(c)]TJ ET q -1 0 0 1 362.845 328.692 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 312.009 423.802 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F30 9.9626 Tf 365.983 328.492 Td [(desc)]TJ +/F8 9.9626 Tf 316.265 423.603 Td [(x)-415(,)-874(d)-113(e)-112(s)-113(c)]TJ ET q -1 0 0 1 387.532 328.692 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 360.541 423.802 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F30 9.9626 Tf 390.67 328.492 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -260.887 -20.135 Td [(info)]TJ -0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ/F16 11.9552 Tf -24.906 -22.128 Td [(Notes)]TJ -0 g 0 G -/F8 9.9626 Tf 12.176 -20.082 Td [(1.)]TJ -0 g 0 G - [-500(One)-241(of)-241(the)-240(optional)-241(argumen)28(ts)]TJ/F30 9.9626 Tf 144.915 0 Td [(parts)]TJ/F8 9.9626 Tf 26.151 0 Td [(,)]TJ/F30 9.9626 Tf 5.351 0 Td [(vg)]TJ/F8 9.9626 Tf 10.461 0 Td [(,)]TJ/F30 9.9626 Tf 5.351 0 Td [(vl)]TJ/F8 9.9626 Tf 10.461 0 Td [(,)]TJ/F30 9.9626 Tf 5.351 0 Td [(nl)]TJ/F8 9.9626 Tf 12.859 0 Td [(or)]TJ/F30 9.9626 Tf 11.283 0 Td [(repl)]TJ/F8 9.9626 Tf 23.321 0 Td [(m)28(ust)-241(b)-28(e)-241(sp)-27(eci\014ed,)]TJ -242.774 -11.956 Td [(thereb)28(y)-334(c)28(ho)-28(osing)-333(the)-333(initialization)-333(strategy)-334(as)-333(follo)28(ws:)]TJ -0 g 0 G -/F27 9.9626 Tf 0 -20.135 Td [(parts)]TJ -0 g 0 G -/F8 9.9626 Tf 30.609 0 Td [(In)-337(this)-338(case)-338(w)28(e)-337(ha)27(v)28(e)-337(a)-338(subroutine)-337(sp)-28(ecifying)-337(the)-338(mapping)-337(b)-28(et)28(w)28(ee)-1(n)]TJ -8.691 -11.955 Td [(global)-225(indices)-225(and)-225(pro)-28(cess/lo)-28(cal)-225(in)1(dex)-225(pairs.)-409(If)-225(this)-225(optional)-225(argu)1(m)-1(en)28(t)]TJ 0 -11.955 Td [(is)-316(sp)-28(eci\014ed,)-320(then)-316(it)-317(is)-316(mandatory)-316(to)-317(sp)-28(ecify)-316(the)-316(argumen)27(t)]TJ/F30 9.9626 Tf 251.563 0 Td [(mg)]TJ/F8 9.9626 Tf 13.612 0 Td [(as)-316(w)27(ell.)]TJ -265.175 -11.955 Td [(The)-333(subroutine)-334(m)28(ust)-333(conform)-333(to)-334(the)-333(follo)28(wing)-334(in)28(terface:)]TJ -0 g 0 G -0 g 0 G -/F30 9.9626 Tf 10.461 -18.09 Td [(interface)]TJ 15.691 -11.955 Td [(subroutine)-525(psb_parts\050glob_index,mg,np,pv,nv\051)]TJ -0 g 0 G -/F8 9.9626 Tf 93.898 -29.888 Td [(62)]TJ -0 g 0 G +/F8 9.9626 Tf 364.652 423.603 Td [(a)-386(,)-888(i)-127(n)-127(f)-127(o)-415(,)-885(r)-124(o)-123(o)-124(t)-230(\051)]TJ/F27 9.9626 Tf -212.57 -11.956 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.737 0 Td [(p)-123(s)-123(b)]TJ ET - -endstream -endobj -1256 0 obj -<< -/Length 10081 ->> -stream -0 g 0 G -0 g 0 G +q +1 0 0 1 201.095 411.847 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q BT -/F30 9.9626 Tf 183.332 706.129 Td [(integer,)-525(intent)-525(\050in\051)-1050(::)-525(glob_index,np,mg)]TJ 0 -11.955 Td [(integer,)-525(intent)-525(\050out\051)-525(::)-525(nv,)-525(pv\050*\051)]TJ -10.46 -11.955 Td [(end)-525(subroutine)-525(psb_parts)]TJ -15.691 -11.956 Td [(end)-525(interface)]TJ/F8 9.9626 Tf -10.461 -17.586 Td [(The)-333(input)-334(argu)1(m)-1(en)28(ts)-333(are:)]TJ -0 g 0 G -/F27 9.9626 Tf 0 -15.594 Td [(glob)]TJ +/F8 9.9626 Tf 205.31 411.647 Td [(g)-123(a)-123(t)-123(h)-123(e)-123(r)-229(\050)-215(g)-110(l)-110(o)-110(b)]TJ ET q -1 0 0 1 168.412 637.283 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +1 0 0 1 270.682 411.847 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F27 9.9626 Tf 171.849 637.083 Td [(index)]TJ -0 g 0 G -/F8 9.9626 Tf 32.191 0 Td [(The)-333(global)-334(index)-333(to)-333(b)-28(e)-333(mapp)-28(ed;)]TJ -0 g 0 G -/F27 9.9626 Tf -57.32 -13.774 Td [(np)]TJ -0 g 0 G -/F8 9.9626 Tf 17.711 0 Td [(The)-333(n)27(um)28(b)-28(er)-333(of)-333(pro)-28(cesses)-333(in)-334(the)-333(mapping;)]TJ -0 g 0 G -/F27 9.9626 Tf -17.711 -13.774 Td [(mg)]TJ -0 g 0 G -/F8 9.9626 Tf 20.257 0 Td [(The)-333(total)-334(n)28(um)28(b)-28(er)-333(of)-333(global)-334(ro)28(ws)-333(in)-334(the)-333(mapping;)]TJ -20.257 -15.594 Td [(The)-333(output)-334(argu)1(m)-1(en)28(ts)-333(are:)]TJ -0 g 0 G -/F27 9.9626 Tf 0 -15.594 Td [(n)32(v)]TJ -0 g 0 G -/F8 9.9626 Tf 17.075 0 Td [(The)-333(n)27(u)1(m)27(b)-27(e)-1(r)-333(of)-333(en)28(tries)-334(in)]TJ/F30 9.9626 Tf 111.637 0 Td [(pv)]TJ/F8 9.9626 Tf 10.46 0 Td [(;)]TJ +/F8 9.9626 Tf 274.766 411.647 Td [(x)-381(,)-888(l)-127(o)-127(c)]TJ +ET +q +1 0 0 1 312.009 411.847 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 316.265 411.647 Td [(x)-415(,)-874(d)-113(e)-112(s)-113(c)]TJ +ET +q +1 0 0 1 360.541 411.847 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 364.652 411.647 Td [(a)-386(,)-888(i)-127(n)-127(f)-127(o)-415(,)-885(r)-124(o)-123(o)-124(t)-230(\051)]TJ 0 g 0 G -/F27 9.9626 Tf -139.172 -13.774 Td [(p)32(v)]TJ 0 g 0 G -/F8 9.9626 Tf 17.075 0 Td [(A)-481(v)28(ector)-481(con)28(taining)-481(the)-481(ind)1(ice)-1(s)-480(of)-481(the)-481(pro)-28(cesses)-481(to)-481(whic)28(h)-481(the)]TJ 1.555 -11.955 Td [(global)-468(index)-468(should)-468(b)-28(e)-468(assigend;)-535(e)-1(ac)28(h)-468(en)28(try)-468(m)28(ust)-469(satisfy)-468(0)]TJ/F14 9.9626 Tf 270.508 0 Td [(\024)]TJ/F11 9.9626 Tf -270.508 -11.956 Td [(pv)]TJ/F8 9.9626 Tf 10.199 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.433 0 Td [(\051)]TJ/F11 9.9626 Tf 8.603 0 Td [(<)-475(np)]TJ/F8 9.9626 Tf 23.47 0 Td [(;)-510(if)]TJ/F11 9.9626 Tf 18.163 0 Td [(nv)-511(>)]TJ/F8 9.9626 Tf 28.373 0 Td [(1)-451(w)27(e)-451(ha)28(v)27(e)-451(an)-452(i)1(ndex)-452(assigned)-451(to)-452(m)28(ultiple)]TJ -96.115 -11.955 Td [(pro)-28(cesses,)-333(i.e.)-445(w)28(e)-333(ha)27(v)28(e)-333(an)-333(o)27(v)28(erlap)-333(among)-333(the)-334(sub)-28(domain)1(s)-1(.)]TJ 0 g 0 G -/F27 9.9626 Tf -40.548 -15.594 Td [(vg)]TJ +/F27 9.9626 Tf -213.947 -26.424 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 16.757 0 Td [(In)-398(t)1(his)-398(case)-398(the)-397(asso)-28(ciation)-398(b)-27(e)-1(t)28(w)28(een)-398(an)-397(index)-398(and)-397(a)-398(pro)-27(ces)-1(s)-397(is)-398(sp)-27(e)-1(c-)]TJ 5.161 -11.955 Td [(i\014ed)-456(via)-456(an)-456(in)28(teger)-457(v)28(ector)]TJ/F30 9.9626 Tf 120.742 0 Td [(vg\0501:mg\051)]TJ/F8 9.9626 Tf 41.843 0 Td [(;)-517(e)-1(ac)28(h)-456(index)]TJ/F11 9.9626 Tf 59.63 0 Td [(i)]TJ/F14 9.9626 Tf 8.238 0 Td [(2)-482(f)]TJ/F8 9.9626 Tf 16.429 0 Td [(1)]TJ/F11 9.9626 Tf 6.642 0 Td [(:)-167(:)-166(:)-167(mg)]TJ/F14 9.9626 Tf 27.14 0 Td [(g)]TJ/F8 9.9626 Tf 9.525 0 Td [(is)]TJ -290.189 -11.955 Td [(assigned)-449(to)-449(pro)-28(cess)]TJ/F11 9.9626 Tf 89.776 0 Td [(v)-36(g)]TJ/F8 9.9626 Tf 10.296 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.433 0 Td [(\051.)-792(The)-449(v)28(ector)]TJ/F30 9.9626 Tf 67.232 0 Td [(vg)]TJ/F8 9.9626 Tf 14.935 0 Td [(m)28(ust)-449(b)-28(e)-449(iden)28(tical)-450(on)-449(all)]TJ -189.546 -11.955 Td [(calling)-452(pro)-28(cesses;)-513(i)1(ts)-453(en)28(tries)-453(ma)28(y)-453(ha)28(v)28(e)-453(t)1(he)-453(ranges)-453(\0500)]TJ/F11 9.9626 Tf 236.604 0 Td [(:)-167(:)-166(:)-167(np)]TJ/F14 9.9626 Tf 27.281 0 Td [(\000)]TJ/F8 9.9626 Tf 10.754 0 Td [(1\051)-453(or)]TJ -274.639 -11.955 Td [(\0501)]TJ/F11 9.9626 Tf 10.516 0 Td [(:)-167(:)-166(:)-167(np)]TJ/F8 9.9626 Tf 24.276 0 Td [(\051)-347(according)-347(to)-347(the)-347(v)55(alu)1(e)-348(of)]TJ/F30 9.9626 Tf 119.292 0 Td [(flag)]TJ/F8 9.9626 Tf 20.921 0 Td [(.)-486(The)-347(size)]TJ/F11 9.9626 Tf 47.231 0 Td [(mg)]TJ/F8 9.9626 Tf 17.314 0 Td [(ma)28(y)-347(b)-28(e)-347(sp)-28(ec-)]TJ -239.55 -11.955 Td [(i\014ed)-414(via)-414(the)-415(opti)1(onal)-415(argumen)28(t)]TJ/F30 9.9626 Tf 142.427 0 Td [(mg)]TJ/F8 9.9626 Tf 10.461 0 Td [(;)-455(the)-414(default)-414(is)-414(to)-414(use)-415(the)-414(en)28(tire)]TJ -152.888 -11.956 Td [(v)28(ector)]TJ/F30 9.9626 Tf 29.916 0 Td [(vg)]TJ/F8 9.9626 Tf 10.46 0 Td [(,)-333(th)27(u)1(s)-334(ha)28(ving)]TJ/F30 9.9626 Tf 60.108 0 Td [(mg=size\050vg\051)]TJ/F8 9.9626 Tf 57.534 0 Td [(.)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -179.936 -15.593 Td [(vl)]TJ +/F27 9.9626 Tf -33.797 -19.505 Td [(On)-383(En)32(try)]TJ 0 g 0 G -/F8 9.9626 Tf 14.211 0 Td [(In)-356(this)-357(case)-356(w)28(e)-357(are)-356(sp)-28(ecifying)-356(the)-357(list)-356(of)-356(indices)]TJ/F30 9.9626 Tf 210.707 0 Td [(vl\0501:nl\051)]TJ/F8 9.9626 Tf 45.394 0 Td [(assigned)-356(to)]TJ -248.394 -11.955 Td [(the)-462(curren)28(t)-462(pro)-27(ces)-1(s;)-526(th)28(us,)-494(the)-461(global)-462(problem)-462(size)]TJ/F11 9.9626 Tf 229.323 0 Td [(mg)]TJ/F8 9.9626 Tf 18.457 0 Td [(is)-462(giv)28(en)-462(b)28(y)]TJ -247.78 -11.956 Td [(the)-405(range)-405(of)-404(the)-405(aggregate)-405(of)-405(the)-405(in)1(dividual)-405(v)28(ectors)]TJ/F30 9.9626 Tf 233.196 0 Td [(vl)]TJ/F8 9.9626 Tf 14.494 0 Td [(sp)-28(eci\014ed)-405(in)]TJ -247.69 -11.955 Td [(the)-481(calling)-481(p)1(ro)-28(cesses.)-887(The)-481(size)-481(ma)28(y)-481(b)-28(e)-481(sp)-27(eci\014ed)-481(via)-481(the)-481(optional)]TJ 0 -11.955 Td [(argumen)28(t)]TJ/F30 9.9626 Tf 44.85 0 Td [(nl)]TJ/F8 9.9626 Tf 10.461 0 Td [(;)-373(the)-361(defaul)1(t)-361(is)-360(to)-360(use)-360(the)-360(en)28(tire)-361(v)28(ector)]TJ/F30 9.9626 Tf 173.727 0 Td [(vl)]TJ/F8 9.9626 Tf 10.461 0 Td [(,)-367(th)28(us)-360(ha)28(ving)]TJ/F30 9.9626 Tf -239.499 -11.955 Td [(nl=size\050vl\051)]TJ/F8 9.9626 Tf 57.534 0 Td [(.)-419(If)]TJ/F30 9.9626 Tf 16.132 0 Td [(globalcheck=.true.)]TJ/F8 9.9626 Tf 96.699 0 Td [(the)-256(subroutine)-256(will)-256(c)27(h)1(e)-1(c)28(k)-256(ho)28(w)]TJ -170.365 -11.955 Td [(man)28(y)-255(times)-255(eac)28(h)-254(en)27(try)-254(in)-255(the)-254(global)-255(index)-254(s)-1(p)1(ac)-1(e)-254(\0501)]TJ/F11 9.9626 Tf 217.24 0 Td [(:)-167(:)-166(:)-167(mg)]TJ/F8 9.9626 Tf 27.14 0 Td [(\051)-255(is)-254(sp)-28(eci\014ed)]TJ -244.38 -11.955 Td [(in)-331(the)-331(input)-331(lists)]TJ/F30 9.9626 Tf 75.842 0 Td [(vl)]TJ/F8 9.9626 Tf 10.461 0 Td [(,)-331(th)27(us)-331(all)1(o)27(wing)-331(for)-330(the)-331(prese)-1(n)1(c)-1(e)-330(of)-331(o)27(v)28(erlap)-331(in)-331(the)]TJ -86.303 -11.956 Td [(input,)-338(and)-337(c)28(hec)27(king)-337(for)-337(\134orphan")-337(indices.)-456(If)]TJ/F30 9.9626 Tf 194.743 0 Td [(globalcheck=.false.)]TJ/F8 9.9626 Tf 99.376 0 Td [(,)]TJ -294.119 -11.955 Td [(the)-409(s)-1(u)1(broutine)-410(will)-409(not)-410(c)28(hec)28(k)-410(for)-409(o)28(v)27(erlap,)-428(and)-409(ma)27(y)-409(b)-28(e)-409(signi\014can)27(tly)]TJ 0 -11.955 Td [(faster,)-362(but)-357(the)-357(user)-356(is)-357(implicitly)-356(g)-1(u)1(aran)27(teeing)-356(that)-357(there)-357(ar)1(e)-357(neither)]TJ 0 -11.955 Td [(orphan)-333(nor)-333(o)27(v)28(erlap)-333(indices.)]TJ 0 g 0 G -/F27 9.9626 Tf -21.918 -15.594 Td [(lidx)]TJ + 0 -19.505 Td [(lo)-32(c)]TJ +ET +q +1 0 0 1 165.713 346.412 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 169.151 346.213 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(The)-463(optional)-462(argumen)28(t)]TJ/F30 9.9626 Tf 107.67 0 Td [(lidx)]TJ/F8 9.9626 Tf 25.531 0 Td [(is)-463(a)28(v)56(ailable)-463(for)-462(those)-463(cases)-463(in)-463(whi)1(c)27(h)]TJ -135.041 -11.955 Td [(the)-446(user)-446(has)-446(already)-446(established)-446(a)-446(global-to-lo)-28(cal)-446(mapping;)-502(if)-446(it)-446(is)]TJ 0 -11.955 Td [(sp)-28(eci\014ed,)-373(eac)28(h)-365(index)-365(in)]TJ/F30 9.9626 Tf 105.175 0 Td [(vl\050i\051)]TJ/F8 9.9626 Tf 29.789 0 Td [(will)-365(b)-28(e)-365(mapp)-28(ed)-365(to)-365(the)-365(corresp)-27(onding)]TJ -134.964 -11.955 Td [(lo)-28(cal)-392(index)]TJ/F30 9.9626 Tf 51.539 0 Td [(lidx\050i\051)]TJ/F8 9.9626 Tf 36.613 0 Td [(.)-621(When)-392(sp)-28(ecifying)-392(the)-392(argumen)28(t)]TJ/F30 9.9626 Tf 148.368 0 Td [(lidx)]TJ/F8 9.9626 Tf 24.828 0 Td [(the)-392(user)]TJ -261.348 -11.956 Td [(w)28(ould)-420(also)-420(lik)28(ely)-419(e)-1(mpl)1(o)27(y)]TJ/F30 9.9626 Tf 113.086 0 Td [(lidx)]TJ/F8 9.9626 Tf 25.103 0 Td [(in)-420(calls)-419(to)]TJ/F30 9.9626 Tf 48.576 0 Td [(psb_cdins)]TJ/F8 9.9626 Tf 51.254 0 Td [(and)]TJ/F30 9.9626 Tf 20.232 0 Td [(local)]TJ/F8 9.9626 Tf 30.333 0 Td [(in)]TJ -288.584 -11.955 Td [(calls)-333(to)]TJ/F30 9.9626 Tf 34.371 0 Td [(psb_spins)]TJ/F8 9.9626 Tf 50.394 0 Td [(and)]TJ/F30 9.9626 Tf 19.372 0 Td [(psb_geins)]TJ/F8 9.9626 Tf 47.073 0 Td [(;)-333(see)-334(also)-333(sec.)]TJ +/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.117 0 Td [(g)-36(l)-20(ob)]TJ +ET +q +1 0 0 1 374.277 346.412 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F11 9.9626 Tf 377.266 346.213 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -207.349 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-255(rank)-254(one)-255(or)-255(t)28(w)27(o)-254(arra)27(y)-254(or)-255(an)-255(ob)-56(j)1(e)-1(ct)-254(of)-255(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG - [-334(2.3.1)]TJ -0 g 0 G - [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -173.128 -15.593 Td [(nl)]TJ -0 g 0 G -/F8 9.9626 Tf 14.529 0 Td [(If)-307(this)-308(argumen)28(t)-307(is)-308(sp)-28(eci\014ed)-307(alone)-308(\050i.)1(e)-1(.)-435(without)]TJ/F30 9.9626 Tf 206.41 0 Td [(vl)]TJ/F8 9.9626 Tf 10.461 0 Td [(\051)-307(the)-308(result)-307(is)-308(a)-307(gen-)]TJ -209.482 -11.956 Td [(eralized)-313(ro)27(w-blo)-27(c)27(k)-313(distribution)-313(in)-314(whic)28(h)-313(eac)27(h)-313(pro)-28(cess)]TJ/F11 9.9626 Tf 232.18 0 Td [(I)]TJ/F8 9.9626 Tf 8.284 0 Td [(gets)-313(as)-1(signed)]TJ -240.464 -11.955 Td [(a)-333(consecutiv)27(e)-333(c)28(h)28(unk)-334(of)]TJ/F11 9.9626 Tf 101.342 0 Td [(N)]TJ/F10 6.9738 Tf 8.005 -1.494 Td [(I)]TJ/F8 9.9626 Tf 7.338 1.494 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(nl)]TJ/F8 9.9626 Tf 12.47 0 Td [(global)-333(indices.)]TJ -0 g 0 G -/F27 9.9626 Tf -161.589 -15.593 Td [(repl)]TJ -0 g 0 G -/F8 9.9626 Tf 24.498 0 Td [(This)-239(argumen)28(ts)-240(sp)-27(e)-1(ci\014es)-239(to)-239(replicate)-239(all)-239(indices)-240(on)-239(all)-239(pro)-28(cesses.)-413(This)]TJ -2.58 -11.956 Td [(is)-312(a)-311(sp)-28(ecial)-312(purp)-27(ose)-312(data)-312(allo)-27(cation)-312(that)-311(is)-312(useful)-312(in)-311(the)-312(construction)]TJ 0 -11.955 Td [(of)-333(some)-334(m)28(ultilev)28(el)-334(p)1(rec)-1(on)1(ditioners.)]TJ -0 g 0 G - -34.648 -19.579 Td [(2.)]TJ -0 g 0 G - [-500(On)-333(exit)-334(from)-333(this)-333(routine)-333(the)-334(descriptor)-333(is)-333(in)-334(the)-333(build)-333(state.)]TJ -0 g 0 G - 154.698 -29.888 Td [(63)]TJ -0 g 0 G +/F30 9.9626 Tf 244.743 0 Td [(psb)]TJ ET - -endstream -endobj -1261 0 obj -<< -/Length 2667 ->> -stream -0 g 0 G -0 g 0 G -0 g 0 G +q +1 0 0 1 436.673 298.592 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q BT -/F8 9.9626 Tf 162.881 706.129 Td [(3.)]TJ -0 g 0 G - [-500(Calling)-339(the)-339(routine)-339(with)]TJ/F30 9.9626 Tf 121.471 0 Td [(vg)]TJ/F8 9.9626 Tf 13.839 0 Td [(or)]TJ/F30 9.9626 Tf 12.262 0 Td [(parts)]TJ/F8 9.9626 Tf 29.53 0 Td [(implies)-339(that)-339(ev)28(e)-1(ry)-339(pro)-27(cess)-340(will)-339(scan)]TJ -164.372 -11.955 Td [(the)-333(en)27(tire)-333(index)-333(space)-334(to)-333(\014gure)-333(out)-334(t)1(he)-334(lo)-28(cal)-333(indices.)]TJ -0 g 0 G - -12.73 -19.926 Td [(4.)]TJ -0 g 0 G - [-500(Ov)28(erlapp)-28(ed)-333(indices)-334(are)-333(p)-28(ossible)-333(with)-333(b)-28(oth)]TJ/F30 9.9626 Tf 199.198 0 Td [(parts)]TJ/F8 9.9626 Tf 29.473 0 Td [(and)]TJ/F30 9.9626 Tf 19.372 0 Td [(vl)]TJ/F8 9.9626 Tf 13.781 0 Td [(in)28(v)28(o)-28(cations.)]TJ -0 g 0 G - -261.824 -19.925 Td [(5.)]TJ -0 g 0 G - [-500(When)-222(the)-222(subroutine)-223(i)1(s)-223(in)28(v)28(ok)28(ed)-223(with)]TJ/F30 9.9626 Tf 170.611 0 Td [(vl)]TJ/F8 9.9626 Tf 12.674 0 Td [(in)-222(conjunction)-222(with)]TJ/F30 9.9626 Tf 84.96 0 Td [(globalcheck=.true.)]TJ/F8 9.9626 Tf 94.146 0 Td [(,)]TJ -349.661 -11.955 Td [(it)-368(will)-369(p)-28(erform)-368(a)-369(scan)-368(of)-368(the)-369(index)-368(space)-369(to)-368(searc)27(h)-368(for)-368(o)27(v)28(erlap)-368(or)-369(orph)1(an)]TJ 0 -11.955 Td [(indices.)]TJ -0 g 0 G - -12.73 -19.925 Td [(6.)]TJ -0 g 0 G - [-500(When)-222(the)-222(subroutine)-223(i)1(s)-223(in)28(v)28(ok)28(ed)-223(with)]TJ/F30 9.9626 Tf 170.611 0 Td [(vl)]TJ/F8 9.9626 Tf 12.674 0 Td [(in)-222(conjunction)-222(with)]TJ/F30 9.9626 Tf 84.96 0 Td [(globalcheck=.false.)]TJ/F8 9.9626 Tf 99.376 0 Td [(,)]TJ -354.891 -11.956 Td [(no)-405(index)-405(space)-405(scan)-405(will)-405(tak)28(e)-405(place.)-660(Th)28(us)-405(it)-405(is)-405(the)-405(resp)-28(onsibilit)28(y)-405(of)-405(the)]TJ 0 -11.955 Td [(user)-419(to)-418(mak)28(e)-419(sure)-418(that)-419(the)-418(indices)-419(sp)-28(eci\014ed)-418(in)]TJ/F30 9.9626 Tf 211.319 0 Td [(vl)]TJ/F8 9.9626 Tf 14.63 0 Td [(ha)28(v)28(e)-419(neither)-418(orphans)]TJ -225.949 -11.955 Td [(nor)-333(o)27(v)28(erlaps;)-333(if)-333(this)-334(assumption)-333(fails,)-333(results)-334(will)-333(b)-28(e)-333(unpredictable.)]TJ -0 g 0 G - -12.73 -19.925 Td [(7.)]TJ -0 g 0 G - [-500(Orphan)-313(and)-312(o)27(v)28(erlap)-312(indices)-313(are)-313(imp)-28(ossible)-313(b)28(y)-313(construction)-312(when)-313(the)-313(sub-)]TJ 12.73 -11.955 Td [(routine)-333(is)-334(in)28(v)28(ok)28(ed)-334(with)]TJ/F30 9.9626 Tf 103.308 0 Td [(nl)]TJ/F8 9.9626 Tf 13.781 0 Td [(\050alone\051,)-333(or)]TJ/F30 9.9626 Tf 48.734 0 Td [(vg)]TJ/F8 9.9626 Tf 10.461 0 Td [(.)]TJ -0 g 0 G - -34.316 -452.304 Td [(64)]TJ -0 g 0 G +/F30 9.9626 Tf 439.811 298.392 Td [(T)]TJ ET - -endstream -endobj -1271 0 obj -<< -/Length 7172 ->> -stream -0 g 0 G -0 g 0 G +q +1 0 0 1 445.669 298.592 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q BT -/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ +/F30 9.9626 Tf 448.807 298.392 Td [(vect)]TJ ET q -1 0 0 1 120.951 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +1 0 0 1 470.356 298.592 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(cdins)-375(|)-375(Comm)31(unication)-375(descriptor)-375(insert)-375(routine)]TJ -0 g 0 G -0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_cdins\050nz,)-525(ia,)-525(ja,)-525(desc_a,)-525(info)-525([,ila,jla]\051)]TJ 0 -11.956 Td [(call)-525(psb_cdins\050nz,ja,desc,info[,jla,mask,lidx]\051)]TJ/F8 9.9626 Tf 14.944 -20.465 Td [(This)-428(subroutine)-427(e)-1(x)1(am)-1(in)1(e)-1(s)-427(the)-428(edges)-428(of)-428(the)-427(graph)-428(asso)-28(ciated)-428(with)-428(the)-427(dis-)]TJ -14.944 -11.955 Td [(cretization)-481(mesh)-480(\050and)-481(isomorphic)-480(to)-481(the)-480(sparsit)27(y)-480(pattern)-481(of)-480(a)-481(linear)-480(system)]TJ 0 -11.955 Td [(co)-28(e\016cien)28(t)-359(matrix\051,)-366(storing)-359(them)-359(as)-359(neces)-1(sary)-359(in)28(to)-359(the)-359(comm)28(unication)-360(d)1(e)-1(scrip-)]TJ 0 -11.955 Td [(tor.)-506(In)-354(th)1(e)-354(\014rst)-354(form)-354(the)-354(edges)-353(are)-354(sp)-28(eci\014ed)-354(as)-354(pairs)-353(of)-354(indices)]TJ/F11 9.9626 Tf 278.053 0 Td [(ia)]TJ/F8 9.9626 Tf 8.699 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)]TJ/F11 9.9626 Tf 3.875 0 Td [(;)-167(j)-57(a)]TJ/F8 9.9626 Tf 14.367 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051;)-364(the)]TJ -319.606 -11.955 Td [(starting)-394(index)]TJ/F11 9.9626 Tf 65.223 0 Td [(ia)]TJ/F8 9.9626 Tf 8.698 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.433 0 Td [(\051)-394(should)-394(b)-28(elong)-394(to)-394(the)-394(c)-1(u)1(rren)27(t)-394(pro)-28(cess.)-627(In)-394(the)-394(second)-394(form)]TJ -81.228 -11.955 Td [(only)-333(the)-334(remote)-333(indices)]TJ/F11 9.9626 Tf 104.968 0 Td [(j)-57(a)]TJ/F8 9.9626 Tf 9.939 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.433 0 Td [(\051)-333(are)-334(sp)-27(ec)-1(i\014)1(e)-1(d)1(.)]TJ -0 g 0 G -/F27 9.9626 Tf -122.214 -20.465 Td [(T)32(yp)-32(e:)]TJ -0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ -0 g 0 G -/F27 9.9626 Tf -33.797 -19.345 Td [(On)-383(En)32(try)]TJ -0 g 0 G +/F30 9.9626 Tf 473.495 298.392 Td [(type)]TJ 0 g 0 G - 0 -19.344 Td [(nz)]TJ -0 g 0 G -/F8 9.9626 Tf 16.439 0 Td [(the)-333(n)28(um)27(b)-27(er)-334(of)-333(p)-28(oin)28(ts)-333(b)-28(eing)-333(inserted.)]TJ 8.468 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -19.344 Td [(ia)]TJ -0 g 0 G -/F8 9.9626 Tf 13.734 0 Td [(the)-333(indices)-334(of)-333(the)-333(starting)-334(v)28(ertex)-333(of)-333(the)-334(edges)-333(b)-28(eing)-333(inserted.)]TJ 11.173 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)-333(of)-333(length)]TJ/F11 9.9626 Tf 172.548 0 Td [(nz)]TJ/F8 9.9626 Tf 11.051 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -208.506 -19.344 Td [(ja)]TJ -0 g 0 G -/F8 9.9626 Tf 14.052 0 Td [(the)-333(indices)-334(of)-333(the)-333(end)-334(v)28(ertex)-333(of)-333(the)-334(edges)-333(b)-28(eing)-333(inserted.)]TJ 10.855 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)-333(of)-333(length)]TJ/F11 9.9626 Tf 172.548 0 Td [(nz)]TJ/F8 9.9626 Tf 11.051 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -208.506 -19.344 Td [(mask)]TJ -0 g 0 G -/F8 9.9626 Tf 30.664 0 Td [(Mask)-330(en)28(tries)-329(in)]TJ/F30 9.9626 Tf 70.038 0 Td [(ja)]TJ/F8 9.9626 Tf 10.461 0 Td [(,)-330(they)-330(are)-329(inserted)-330(only)-329(when)-329(the)-330(corresp)-28(onding)]TJ/F30 9.9626 Tf 211.627 0 Td [(mask)]TJ/F8 9.9626 Tf -297.883 -11.955 Td [(en)28(tries)-334(are)]TJ/F30 9.9626 Tf 48.54 0 Td [(.true.)]TJ/F8 9.9626 Tf -48.54 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(logical)-333(arra)28(y)-334(of)-333(length)]TJ/F11 9.9626 Tf 165.048 0 Td [(nz)]TJ/F8 9.9626 Tf 11.051 0 Td [(,)-333(default)]TJ/F30 9.9626 Tf 39.574 0 Td [(.true.)]TJ/F8 9.9626 Tf 31.382 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -271.962 -19.344 Td [(lidx)]TJ -0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(User)-333(de\014ned)-334(lo)-27(ca)-1(l)-333(indices)-333(for)]TJ/F30 9.9626 Tf 128.851 0 Td [(ja)]TJ/F8 9.9626 Tf 10.46 0 Td [(.)]TJ -138.162 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)-333(of)-333(length)]TJ/F11 9.9626 Tf 172.548 0 Td [(nz)]TJ/F8 9.9626 Tf 11.051 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -208.506 -20.465 Td [(On)-383(Return)]TJ +/F8 9.9626 Tf -297.884 -11.955 Td [(indicated)-333(in)-334(T)84(able)]TJ +0 0 1 rg 0 0 1 RG + [-334(16)]TJ 0 g 0 G + [(.)]TJ 0 g 0 G - 0 -19.344 Td [(desc)]TJ +/F27 9.9626 Tf -24.906 -19.505 Td [(desc)]TJ ET q -1 0 0 1 121.81 168.346 cm +1 0 0 1 172.619 267.131 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 125.247 168.146 Td [(a)]TJ +/F27 9.9626 Tf 176.057 266.932 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(up)-28(dated)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.55 0 Td [(con)28(tains)-334(data)-333(structures)-333(for)-333(c)-1(omm)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 312.036 120.525 cm +1 0 0 1 362.845 219.311 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 315.174 120.326 Td [(desc)]TJ +/F30 9.9626 Tf 365.983 219.111 Td [(desc)]TJ ET q -1 0 0 1 336.723 120.525 cm +1 0 0 1 387.532 219.311 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 339.861 120.326 Td [(type)]TJ +/F30 9.9626 Tf 390.67 219.111 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +/F8 9.9626 Tf 20.922 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -260.887 -19.505 Td [(ro)-32(ot)]TJ +0 g 0 G +/F8 9.9626 Tf 25.93 0 Td [(The)-291(pro)-28(cess)-291(that)-291(holds)-291(the)-291(global)-291(cop)28(y)83(.)-430(If)]TJ/F11 9.9626 Tf 182.523 0 Td [(r)-28(oot)]TJ/F8 9.9626 Tf 20.794 0 Td [(=)]TJ/F14 9.9626 Tf 10.516 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)-291(all)-291(the)-291(pro)-28(cesses)-291(will)]TJ -222.606 -11.955 Td [(ha)28(v)28(e)-334(a)-333(cop)28(y)-334(of)-333(the)-333(global)-334(v)28(ector.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable)]TJ/F14 9.9626 Tf 142.079 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)]TJ/F14 9.9626 Tf 7.748 0 Td [(\024)]TJ/F11 9.9626 Tf 10.516 0 Td [(r)-28(oot)]TJ/F14 9.9626 Tf 20.795 0 Td [(\024)]TJ/F11 9.9626 Tf 10.516 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.963 0 Td [(1,)-333(default)]TJ/F14 9.9626 Tf 44.555 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1.)]TJ +0 g 0 G +/F27 9.9626 Tf -299.782 -19.505 Td [(On)-383(Return)]TJ 0 g 0 G - -94.012 -29.888 Td [(65)]TJ +0 g 0 G +/F8 9.9626 Tf 166.874 -29.888 Td [(60)]TJ 0 g 0 G ET endstream endobj -1276 0 obj +1266 0 obj << -/Length 3163 +/Length 1455 >> stream 0 g 0 G 0 g 0 G 0 g 0 G BT -/F27 9.9626 Tf 150.705 706.129 Td [(info)]TJ -0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.906 -19.925 Td [(ila)]TJ -0 g 0 G -/F8 9.9626 Tf 16.915 0 Td [(the)-333(lo)-28(cal)-333(indices)-334(of)-333(the)-333(s)-1(tar)1(ting)-334(v)28(ertex)-333(of)-334(the)-333(edges)-333(b)-28(eing)-333(inserted.)]TJ 7.991 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf 40.576 0 Td [(.)]TJ -70.188 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)-333(of)-333(length)]TJ/F11 9.9626 Tf 172.548 0 Td [(nz)]TJ/F8 9.9626 Tf 11.051 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -208.505 -19.925 Td [(jla)]TJ -0 g 0 G -/F8 9.9626 Tf 17.234 0 Td [(the)-333(lo)-28(cal)-333(indices)-334(of)-333(the)-333(end)-334(v)28(ertex)-333(of)-334(the)-333(edges)-333(b)-28(eing)-333(inserted.)]TJ 7.672 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf 40.576 0 Td [(.)]TJ -70.188 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)-333(of)-333(length)]TJ/F11 9.9626 Tf 172.548 0 Td [(nz)]TJ/F8 9.9626 Tf 11.051 0 Td [(.)]TJ/F16 11.9552 Tf -208.505 -21.918 Td [(Notes)]TJ -0 g 0 G -/F8 9.9626 Tf 12.176 -19.925 Td [(1.)]TJ -0 g 0 G - [-500(This)-333(routine)-334(ma)28(y)-333(only)-333(b)-28(e)-334(called)-333(if)-333(the)-334(d)1(e)-1(scriptor)-333(is)-333(in)-333(the)-334(build)-333(state;)]TJ -0 g 0 G - 0 -19.925 Td [(2.)]TJ -0 g 0 G - [-500(This)-305(rou)1(tine)-305(automatically)-305(i)1(gnores)-305(edges)-305(that)-304(do)-305(not)-304(insist)-305(on)-304(the)-305(curren)28(t)]TJ 12.73 -11.955 Td [(pro)-28(cess,)-285(i.)1(e)-1(.)-424(edges)-272(for)-273(whic)28(h)-272(neither)-273(the)-272(starting)-272(nor)-273(the)-272(end)-273(v)28(ertex)-272(b)-28(elong)]TJ 0 -11.955 Td [(to)-333(the)-334(curren)28(t)-333(pro)-28(cess.)]TJ +/F27 9.9626 Tf 99.895 706.129 Td [(glob)]TJ +ET +q +1 0 0 1 121.587 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 125.024 706.129 Td [(x)]TJ 0 g 0 G - -12.73 -19.926 Td [(3.)]TJ +/F8 9.9626 Tf 11.028 0 Td [(The)-333(arra)27(y)-333(where)-333(the)-334(lo)-27(cal)-334(parts)-333(m)28(ust)-334(b)-27(e)-334(gathered.)]TJ -11.25 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-333(or)-334(t)28(w)28(o)-334(arra)28(y)-333(with)-333(the)]TJ/F30 9.9626 Tf 204.4 0 Td [(ALLOCATABLE)]TJ/F8 9.9626 Tf 60.855 0 Td [(attribute.)]TJ 0 g 0 G - [-500(The)-437(second)-438(form)-437(of)-437(this)-437(routine)-438(wil)1(l)-438(b)-27(e)-438(useful)-437(when)-437(dealing)-437(with)-438(user-)]TJ 12.73 -11.955 Td [(sp)-28(eci\014ed)-333(index)-333(mappings;)-334(see)-333(also)]TJ -0 0 1 rg 0 0 1 RG - [-334(2.3.1)]TJ +/F27 9.9626 Tf -290.162 -19.925 Td [(info)]TJ 0 g 0 G - [(.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ 0 g 0 G - 141.968 -314.819 Td [(66)]TJ + 141.968 -500.124 Td [(61)]TJ 0 g 0 G ET endstream endobj -1285 0 obj +1273 0 obj << -/Length 4740 +/Length 7803 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ +/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ ET q -1 0 0 1 120.951 706.328 cm +1 0 0 1 171.761 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(cdasb)-375(|)-375(Comm)31(unication)-375(descriptor)-375(assem)31(bly)-375(routine)]TJ -0 g 0 G -0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_cdasb\050desc_a,)-525(info)-525([,)-525(mold]\051)]TJ -0 g 0 G -/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ -0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ -0 g 0 G -/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ -0 g 0 G -0 g 0 G - 0 -19.925 Td [(desc)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(scatter)-375(|)-375(Scatter)-375(Global)-375(Dense)-375(Matrix)]TJ/F8 9.9626 Tf -25.091 -19.28 Td [(These)-315(subroutines)-315(scatters)-315(the)-315(p)-28(ortions)-315(of)-315(global)-315(dense)-315(matrix)-315(o)28(wned)-315(b)27(y)-315(a)-315(pro-)]TJ 0 -11.955 Td [(cess)-333(to)-334(all)-333(the)-333(pro)-28(cesses)-334(in)-333(the)-333(pro)-28(cesses)-334(grid.)]TJ/F11 9.9626 Tf 119.021 -25.291 Td [(l)-20(oc)]TJ ET q -1 0 0 1 121.81 626.17 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +1 0 0 1 282.633 649.802 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F27 9.9626 Tf 125.247 625.971 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ +/F11 9.9626 Tf 285.622 649.603 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.494 Td [(i)]TJ/F14 9.9626 Tf 6.084 1.494 Td [(\040)]TJ/F11 9.9626 Tf 12.73 0 Td [(scatter)]TJ/F8 9.9626 Tf 30.853 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(g)-36(l)-20(ob)]TJ ET q -1 0 0 1 312.036 578.35 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 362.838 649.802 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F30 9.9626 Tf 315.174 578.15 Td [(desc)]TJ +/F11 9.9626 Tf 365.827 649.603 Td [(x)]TJ/F8 9.9626 Tf 5.693 0 Td [(\051)]TJ -220.815 -22.875 Td [(where:)]TJ +0 g 0 G +/F11 9.9626 Tf 0 -21.361 Td [(g)-36(l)-19(o)-1(b)]TJ ET q -1 0 0 1 336.723 578.35 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 168.775 605.567 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F30 9.9626 Tf 339.861 578.15 Td [(type)]TJ +/F11 9.9626 Tf 172.212 605.367 Td [(x)]TJ +0 g 0 G +/F8 9.9626 Tf 10.675 0 Td [(is)-333(the)-334(global)-333(matrix)]TJ/F11 9.9626 Tf 88.917 0 Td [(g)-36(l)-20(ob)]TJ +ET +q +1 0 0 1 289.785 605.567 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F11 9.9626 Tf 292.773 605.367 Td [(x)]TJ/F7 6.9738 Tf 5.694 -1.494 Td [(1:)]TJ/F10 6.9738 Tf 6.227 0 Td [(m;)]TJ/F7 6.9738 Tf 9.436 0 Td [(1:)]TJ/F10 6.9738 Tf 6.226 0 Td [(n)]TJ +0 g 0 G +/F11 9.9626 Tf -169.651 -20.345 Td [(l)-20(oc)]TJ +ET +q +1 0 0 1 163.701 583.727 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F11 9.9626 Tf 167.139 583.528 Td [(x)]TJ/F10 6.9738 Tf 5.693 -1.494 Td [(i)]TJ +0 g 0 G +/F8 9.9626 Tf 8.299 1.494 Td [(is)-333(the)-334(lo)-27(cal)-334(p)-28(or)1(tion)-334(of)-333(global)-333(dense)-334(matrix)-333(on)-333(pro)-28(cess)]TJ/F11 9.9626 Tf 234.703 0 Td [(i)]TJ/F8 9.9626 Tf 3.433 0 Td [(.)]TJ +0 g 0 G +/F11 9.9626 Tf -268.562 -21.839 Td [(scatter)]TJ +0 g 0 G +/F8 9.9626 Tf 35.834 0 Td [(is)-333(the)-334(scatter)-333(function.)]TJ 0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -260.887 -19.925 Td [(mold)]TJ 0 g 0 G -/F8 9.9626 Tf 29.805 0 Td [(The)-333(desired)-334(dynamic)-333(t)28(yp)-28(e)-333(for)-334(the)-333(in)28(ternal)-333(index)-334(storage.)]TJ -4.898 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-222(as:)-389(a)-222(ob)-56(ject)-222(of)-222(t)28(yp)-28(e)-222(deriv)28(ed)-223(from)-222(\050in)28(teger\051)]TJ/F30 9.9626 Tf 219.87 0 Td [(psb)]TJ ET q -1 0 0 1 360.991 510.604 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 228.797 539.65 cm +[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S Q BT -/F30 9.9626 Tf 364.129 510.405 Td [(T)]TJ +/F11 9.9626 Tf 234.775 531.082 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.494 Td [(i)]TJ/F11 9.9626 Tf 3.317 1.494 Td [(;)-167(y)]TJ/F27 9.9626 Tf 111.399 0 Td [(Subroutine)]TJ ET q -1 0 0 1 369.987 510.604 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 228.797 527.296 cm +[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S Q BT -/F30 9.9626 Tf 373.125 510.405 Td [(base)]TJ +/F8 9.9626 Tf 234.775 518.729 Td [(In)28(teger)-9028(psb)]TJ ET q -1 0 0 1 394.674 510.604 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 370.782 518.928 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F30 9.9626 Tf 397.813 510.405 Td [(vect)]TJ +/F8 9.9626 Tf 373.771 518.729 Td [(scatter)]TJ -138.996 -11.956 Td [(Short)-333(Precision)-334(Real)-3102(psb)]TJ ET q -1 0 0 1 419.361 510.604 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 370.782 506.973 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 373.771 506.773 Td [(scatter)]TJ -138.996 -11.955 Td [(Long)-333(Precision)-334(Real)-3314(psb)]TJ +ET +q +1 0 0 1 370.782 495.017 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F30 9.9626 Tf 422.5 510.405 Td [(type)]TJ/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +/F8 9.9626 Tf 373.771 494.818 Td [(scatter)]TJ -138.996 -11.955 Td [(Short)-333(Precision)-334(Complex)-1200(psb)]TJ +ET +q +1 0 0 1 370.782 483.062 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 373.771 482.863 Td [(scatter)]TJ -138.996 -11.955 Td [(Long)-333(Precision)-334(Complex)-1411(psb)]TJ +ET +q +1 0 0 1 370.782 471.107 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 373.771 470.908 Td [(scatter)]TJ +ET +q +1 0 0 1 228.797 467.122 cm +[]0 d 0 J 0.398 w 0 0 m 187.526 0 l S +Q 0 g 0 G -/F27 9.9626 Tf -343.526 -21.918 Td [(On)-383(Return)]TJ +BT +/F8 9.9626 Tf 276.386 439.083 Td [(T)83(able)-333(17:)-444(Data)-334(t)28(yp)-28(es)]TJ 0 g 0 G 0 g 0 G - 0 -19.926 Td [(desc)]TJ +/F27 9.9626 Tf -124.304 -33.261 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.99 0 Td [(p)-148(s)-149(b)]TJ +ET +q +1 0 0 1 202.107 406.021 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 206.575 405.822 Td [(s)-149(c)-148(a)-149(t)-148(t)-148(e)-149(r)-254(\050)-215(g)-110(l)-110(o)-110(b)]TJ +ET +q +1 0 0 1 276.66 406.021 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 280.744 405.822 Td [(x)-381(,)-888(l)-127(o)-127(c)]TJ +ET +q +1 0 0 1 317.987 406.021 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 322.243 405.822 Td [(x)-415(,)-874(d)-113(e)-112(s)-113(c)]TJ ET q -1 0 0 1 121.81 468.761 cm +1 0 0 1 366.519 406.021 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 370.63 405.822 Td [(a)-386(,)-888(i)-127(n)-127(f)-127(o)-415(,)-864(r)-103(o)-103(o)-104(t)-367(,)-808(m)-47(o)-46(l)-47(d)-152(\051)]TJ +0 g 0 G +0 g 0 G +0 g 0 G +/F27 9.9626 Tf -219.925 -30.766 Td [(T)32(yp)-32(e:)]TJ +0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ +0 g 0 G +/F27 9.9626 Tf -33.797 -21.84 Td [(On)-383(En)32(try)]TJ +0 g 0 G +0 g 0 G + 0 -21.839 Td [(glob)]TJ +ET +q +1 0 0 1 172.397 331.576 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 125.247 468.561 Td [(a)]TJ +/F27 9.9626 Tf 175.834 331.377 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 11.028 0 Td [(The)-333(arra)27(y)-333(that)-333(m)28(ust)-334(b)-27(e)-334(scattered)-333(in)28(to)-334(lo)-28(cal)-333(pieces.)]TJ -11.251 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-334(or)-333(t)28(w)28(o)-334(arra)28(y)84(.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.906 -21.839 Td [(desc)]TJ +ET +q +1 0 0 1 172.619 261.916 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 176.057 261.717 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.55 0 Td [(con)28(tains)-334(data)-333(structures)-333(for)-333(c)-1(omm)28(unications.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 312.036 420.94 cm +1 0 0 1 362.845 214.095 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 315.174 420.741 Td [(desc)]TJ +/F30 9.9626 Tf 365.983 213.896 Td [(desc)]TJ ET q -1 0 0 1 336.723 420.94 cm +1 0 0 1 387.532 214.095 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 339.861 420.741 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -260.887 -19.926 Td [(info)]TJ +/F30 9.9626 Tf 390.67 213.896 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ +/F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G -/F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ +/F27 9.9626 Tf -260.887 -21.839 Td [(ro)-32(ot)]TJ 0 g 0 G - [-500(On)-333(exit)-334(from)-333(this)-333(routine)-333(the)-334(descriptor)-333(is)-333(in)-334(the)-333(assem)28(bled)-334(state.)]TJ +/F8 9.9626 Tf 25.93 0 Td [(The)-420(pro)-27(ce)-1(ss)-419(that)-420(holds)-419(the)-420(global)-420(cop)28(y)83(.)-703(If)]TJ/F11 9.9626 Tf 194.21 0 Td [(r)-28(oot)]TJ/F8 9.9626 Tf 22.228 0 Td [(=)]TJ/F14 9.9626 Tf 11.949 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)-420(all)-419(the)-420(pro)-28(cesses)]TJ -237.16 -11.956 Td [(ha)28(v)28(e)-334(a)-333(cop)28(y)-334(of)-333(the)-333(global)-334(v)28(ector.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-344(as)-1(:)-467(an)-344(in)28(tege)-1(r)-344(v)55(ariabl)1(e)]TJ/F14 9.9626 Tf 142.757 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)]TJ/F14 9.9626 Tf 7.937 0 Td [(\024)]TJ/F11 9.9626 Tf 10.705 0 Td [(r)-28(oot)]TJ/F14 9.9626 Tf 20.983 0 Td [(\024)]TJ/F11 9.9626 Tf 10.704 0 Td [(np)]TJ/F14 9.9626 Tf 13.282 0 Td [(\000)]TJ/F8 9.9626 Tf 10.038 0 Td [(1,)-347(default)]TJ/F30 9.9626 Tf 44.809 0 Td [(psb_root_)]TJ/F8 9.9626 Tf 47.073 0 Td [(,)]TJ -316.037 -11.955 Td [(i.e.)-444(pro)-28(cess)-334(0.)]TJ 0 g 0 G - 154.698 -220.714 Td [(67)]TJ + 141.968 -29.888 Td [(62)]TJ 0 g 0 G ET endstream endobj -1293 0 obj +1282 0 obj << -/Length 3278 +/Length 4181 >> stream 0 g 0 G 0 g 0 G +0 g 0 G BT -/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ +/F27 9.9626 Tf 99.895 706.129 Td [(mold)]TJ +0 g 0 G +/F8 9.9626 Tf 29.805 0 Td [(The)-333(desired)-334(dynamic)-333(t)28(yp)-28(e)-333(for)-334(the)-333(in)28(ternal)-333(v)27(ector)-333(storage.)]TJ -4.898 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-273(as:)-414(an)-274(ob)-55(ject)-273(of)-274(a)-273(class)-273(deriv)28(ed)-274(from)]TJ/F30 9.9626 Tf 198.26 0 Td [(psb)]TJ ET q -1 0 0 1 171.761 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +1 0 0 1 339.381 658.507 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(cdcp)31(y)-375(|)-375(Copies)-375(a)-375(comm)31(unication)-375(descriptor)]TJ -0 g 0 G -0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_cdcpy\050desc_in,)-525(desc_out,)-525(info\051)]TJ -0 g 0 G -/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ -0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ -0 g 0 G -/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ -0 g 0 G -0 g 0 G - 0 -19.925 Td [(desc)]TJ +/F30 9.9626 Tf 342.519 658.308 Td [(T)]TJ ET q -1 0 0 1 172.619 626.17 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +1 0 0 1 348.377 658.507 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F27 9.9626 Tf 176.057 625.971 Td [(in)]TJ -0 g 0 G -/F8 9.9626 Tf 14.528 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -14.974 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F30 9.9626 Tf 351.515 658.308 Td [(base)]TJ +ET +q +1 0 0 1 373.064 658.507 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 376.202 658.308 Td [(vect)]TJ +ET +q +1 0 0 1 397.751 658.507 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 400.89 658.308 Td [(type)]TJ/F8 9.9626 Tf 20.921 0 Td [(;)-293(this)]TJ -297.009 -11.955 Td [(is)-333(only)-334(allo)28(w)28(ed)-333(when)-334(lo)-27(c)]TJ +ET +q +1 0 0 1 231.17 646.552 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 234.159 646.353 Td [(x)-333(is)-334(of)-333(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ +/F30 9.9626 Tf 52.359 0 Td [(psb)]TJ ET q -1 0 0 1 362.845 578.35 cm +1 0 0 1 302.837 646.552 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 365.983 578.15 Td [(desc)]TJ +/F30 9.9626 Tf 305.975 646.353 Td [(T)]TJ ET q -1 0 0 1 387.532 578.35 cm +1 0 0 1 311.833 646.552 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 390.67 578.15 Td [(type)]TJ +/F30 9.9626 Tf 314.971 646.353 Td [(vect)]TJ +ET +q +1 0 0 1 336.52 646.552 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 339.658 646.353 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -260.887 -21.917 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf -260.685 -19.925 Td [(On)-383(Return)]TJ 0 g 0 G 0 g 0 G - 0 -19.926 Td [(desc)]TJ + 0 -19.926 Td [(lo)-32(c)]TJ ET q -1 0 0 1 172.619 536.507 cm +1 0 0 1 114.904 606.702 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 176.057 536.307 Td [(out)]TJ +/F27 9.9626 Tf 118.341 606.502 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 21.53 0 Td [(the)-333(comm)27(unication)-333(descriptor)-333(cop)28(y)83(.)]TJ -21.976 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 11.028 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(dense)-333(matrix)]TJ/F11 9.9626 Tf 176.118 0 Td [(g)-36(l)-19(o)-1(b)]TJ +ET +q +1 0 0 1 323.467 606.702 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F11 9.9626 Tf 326.456 606.502 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -207.348 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-244(as:)-400(a)-244(ran)1(k)-244(one)-244(or)-244(t)27(w)28(o)-244(ALLOCA)83(T)84(ABLE)-244(arra)28(y)-244(or)-244(an)-244(ob)-56(ject)-244(of)-244(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ +/F30 9.9626 Tf 0 -11.955 Td [(psb)]TJ +ET +q +1 0 0 1 141.121 546.926 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 144.259 546.727 Td [(T)]TJ ET q -1 0 0 1 362.845 488.686 cm +1 0 0 1 150.117 546.926 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 365.983 488.487 Td [(desc)]TJ +/F30 9.9626 Tf 153.255 546.727 Td [(vect)]TJ ET q -1 0 0 1 387.532 488.686 cm +1 0 0 1 174.804 546.926 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 390.67 488.487 Td [(type)]TJ +/F30 9.9626 Tf 177.942 546.727 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(.)]TJ +/F8 9.9626 Tf 24.242 0 Td [(con)28(taining)-333(n)27(um)28(b)-28(ers)-333(of)-333(the)-334(t)28(yp)-28(e)-333(indicated)-333(in)-333(T)83(able)]TJ +0 0 1 rg 0 0 1 RG + [-334(17)]TJ 0 g 0 G -/F27 9.9626 Tf -260.887 -19.926 Td [(info)]TJ + [(.)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ +/F27 9.9626 Tf -102.289 -19.926 Td [(info)]TJ +0 g 0 G +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ 0 g 0 G - 141.968 -330.303 Td [(68)]TJ + 141.968 -388.543 Td [(63)]TJ 0 g 0 G ET endstream endobj -1298 0 obj +1286 0 obj << -/Length 2243 +/Length 6539 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ +/F16 14.3462 Tf 150.705 706.129 Td [(6)-1125(Data)-375(managemen)31(t)-375(routines)]TJ/F16 11.9552 Tf 0 -23.814 Td [(psb)]TJ ET q -1 0 0 1 120.951 706.328 cm +1 0 0 1 171.761 682.515 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(cdfree)-375(|)-375(F)94(rees)-375(a)-375(comm)31(unication)-375(descriptor)]TJ +/F16 11.9552 Tf 175.796 682.315 Td [(cdall)-375(|)-375(Allo)-31(cates)-375(a)-375(comm)31(unication)-375(descriptor)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_cdfree\050desc_a,)-525(info\051)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,mg=mg,parts=parts\051)]TJ 0 -11.955 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,vg=vg,[mg=mg,flag=flag]\051)]TJ 0 -11.955 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,vl=vl,[nl=nl,globalcheck=.true.,lidx=lidx]\051)]TJ 0 -11.955 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,nl=nl\051)]TJ 0 -11.956 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,mg=mg,repl=.true.\051)]TJ/F8 9.9626 Tf 14.944 -20.107 Td [(This)-314(subroutine)-314(initializes)-315(th)1(e)-315(comm)28(unication)-314(descriptor)-314(ass)-1(o)-27(ciated)-315(with)-314(an)]TJ -14.944 -11.955 Td [(index)-326(space.)-442(One)-326(of)-326(the)-327(op)1(tional)-327(argu)1(m)-1(en)28(ts)]TJ/F30 9.9626 Tf 193.679 0 Td [(parts)]TJ/F8 9.9626 Tf 26.152 0 Td [(,)]TJ/F30 9.9626 Tf 6.031 0 Td [(vg)]TJ/F8 9.9626 Tf 10.461 0 Td [(,)]TJ/F30 9.9626 Tf 6.031 0 Td [(vl)]TJ/F8 9.9626 Tf 10.46 0 Td [(,)]TJ/F30 9.9626 Tf 6.031 0 Td [(nl)]TJ/F8 9.9626 Tf 13.71 0 Td [(or)]TJ/F30 9.9626 Tf 12.133 0 Td [(repl)]TJ/F8 9.9626 Tf 24.17 0 Td [(m)28(ust)-326(b)-28(e)]TJ -308.858 -11.955 Td [(sp)-28(eci\014ed,)-333(thereb)28(y)-334(c)28(ho)-28(osing)-333(the)-333(sp)-28(eci\014c)-333(initialization)-334(strategy)84(.)]TJ +0 g 0 G +/F27 9.9626 Tf 0 -18.477 Td [(On)-383(En)32(try)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ +0 g 0 G + 0 -19.201 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -33.797 -19.201 Td [(icon)32(txt)]TJ 0 g 0 G +/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.95 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -57.707 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.081 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-1(n)-333(in)28(teger)-333(v)55(alue.)]TJ 0 g 0 G - 0 -19.925 Td [(desc)]TJ -ET -q -1 0 0 1 121.81 626.17 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 125.247 625.971 Td [(a)]TJ +/F27 9.9626 Tf -24.907 -19.201 Td [(vg)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(comm)27(unication)-333(descriptor)-333(to)-333(b)-28(e)-334(freed.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ -ET -q -1 0 0 1 312.036 578.35 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 315.174 578.15 Td [(desc)]TJ -ET -q -1 0 0 1 336.723 578.35 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 339.861 578.15 Td [(type)]TJ +/F8 9.9626 Tf 16.757 0 Td [(Data)-333(allo)-28(cation:)-444(eac)27(h)-333(index)]TJ/F11 9.9626 Tf 123.564 0 Td [(i)]TJ/F14 9.9626 Tf 6.2 0 Td [(2)-278(f)]TJ/F8 9.9626 Tf 14.39 0 Td [(1)]TJ/F11 9.9626 Tf 6.642 0 Td [(:)-167(:)-166(:)-167(mg)]TJ/F14 9.9626 Tf 27.14 0 Td [(g)]TJ/F8 9.9626 Tf 8.302 0 Td [(is)-333(allo)-28(cated)-334(t)1(o)-334(pro)-28(cess)]TJ/F11 9.9626 Tf 99.267 0 Td [(v)-36(g)]TJ/F8 9.9626 Tf 10.296 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.433 0 Td [(\051.)]TJ -294.958 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.95 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -57.707 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)84(.)]TJ 0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +/F27 9.9626 Tf -24.907 -19.201 Td [(\015ag)]TJ 0 g 0 G -/F27 9.9626 Tf -260.887 -21.917 Td [(On)-383(Return)]TJ +/F8 9.9626 Tf 22.644 0 Td [(Sp)-28(eci\014es)-333(whether)-333(e)-1(n)28(tries)-333(in)]TJ/F11 9.9626 Tf 121.932 0 Td [(v)-36(g)]TJ/F8 9.9626 Tf 13.617 0 Td [(are)-333(zero-)-334(or)-333(one-based.)]TJ -133.286 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.95 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -57.707 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue)-333(0)]TJ/F11 9.9626 Tf 135.409 0 Td [(;)]TJ/F8 9.9626 Tf 4.428 0 Td [(1,)-333(default)-334(0.)]TJ 0 g 0 G +/F27 9.9626 Tf -164.744 -19.2 Td [(mg)]TJ 0 g 0 G - 0 -19.926 Td [(info)]TJ +/F8 9.9626 Tf 20.257 0 Td [(the)-333(\050global\051)-334(n)28(um)28(b)-28(er)-333(of)-333(ro)27(ws)-333(of)-333(the)-334(probl)1(e)-1(m.)]TJ 4.65 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.95 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -57.707 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-332(as:)-444(an)-333(in)28(teger)-333(v)56(alue.)-444(I)-1(t)-332(is)-333(required)-332(if)]TJ/F30 9.9626 Tf 203.266 0 Td [(parts)]TJ/F8 9.9626 Tf 29.465 0 Td [(or)]TJ/F30 9.9626 Tf 12.198 0 Td [(repl)]TJ/F8 9.9626 Tf 24.235 0 Td [(is)-333(sp)-27(ec)-1(i)1(\014e)-1(d)1(,)]TJ -269.164 -11.955 Td [(it)-333(is)-334(optional)-333(if)]TJ/F30 9.9626 Tf 67.856 0 Td [(vg)]TJ/F8 9.9626 Tf 13.782 0 Td [(is)-333(sp)-28(eci\014ed.)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ +/F27 9.9626 Tf -106.545 -19.201 Td [(parts)]TJ +0 g 0 G +/F8 9.9626 Tf 30.609 0 Td [(the)-333(subroutine)-334(th)1(at)-334(de\014nes)-333(the)-333(partitioning)-334(sc)28(heme.)]TJ -5.702 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.95 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -57.707 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.081 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(subroutine.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.201 Td [(vl)]TJ +0 g 0 G +/F8 9.9626 Tf 14.211 0 Td [(Data)-363(allo)-28(cation:)-504(the)-363(set)-364(of)-363(global)-363(indices)]TJ/F11 9.9626 Tf 182.789 0 Td [(v)-36(l)]TJ/F8 9.9626 Tf 8.355 0 Td [(\0501)-328(:)]TJ/F11 9.9626 Tf 18.15 0 Td [(nl)]TJ/F8 9.9626 Tf 9.149 0 Td [(\051)-363(b)-28(elonging)-363(to)-363(the)-364(callin)1(g)]TJ -207.747 -11.955 Td [(pro)-28(cess.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.95 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.074 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)84(.)]TJ 0 g 0 G - 141.968 -398.049 Td [(69)]TJ + 141.967 -29.888 Td [(64)]TJ 0 g 0 G ET endstream endobj -1304 0 obj +1291 0 obj << -/Length 5916 +/Length 6637 >> stream 0 g 0 G 0 g 0 G +0 g 0 G BT -/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ -ET -q -1 0 0 1 171.761 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 175.796 706.129 Td [(cdbldext)-282(|)-283(Build)-282(an)-282(extended)-283(comm)31(unication)-282(descrip-)]TJ -25.091 -13.948 Td [(tor)]TJ +/F27 9.9626 Tf 99.895 706.129 Td [(nl)]TJ 0 g 0 G +/F8 9.9626 Tf 14.529 0 Td [(Data)-223(allo)-28(cation:)-389(in)-222(a)-223(generalized)-223(blo)-28(c)28(k-ro)28(w)-223(distribution)-223(the)-222(n)27(um)28(b)-28(er)-222(of)-223(indices)]TJ 10.378 -11.955 Td [(b)-28(elonging)-333(to)-333(the)-334(curren)28(t)-333(pro)-28(cess.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)-444(Ma)28(y)-334(b)-27(e)-334(sp)-28(eci\014ed)-333(together)-333(with)]TJ/F30 9.9626 Tf 272.479 0 Td [(vl)]TJ/F8 9.9626 Tf 10.46 0 Td [(.)]TJ 0 g 0 G -/F30 9.9626 Tf 0 -19.114 Td [(call)-525(psb_cdbldext\050a,desc_a,nl,desc_out,)-525(info,)-525(extype\051)]TJ/F8 9.9626 Tf 14.944 -23.476 Td [(This)-298(subroutin)1(e)-298(builds)-298(an)-297(extended)-298(comm)28(unication)-298(descriptor,)-305(based)-297(on)-298(the)]TJ -14.944 -11.955 Td [(input)-389(descriptor)]TJ/F30 9.9626 Tf 74.287 0 Td [(desc_a)]TJ/F8 9.9626 Tf 35.261 0 Td [(and)-389(on)-390(the)-389(stencil)-390(sp)-27(eci\014ed)-390(through)-389(the)-389(input)-390(sparse)]TJ -109.548 -11.956 Td [(matrix)]TJ/F30 9.9626 Tf 32.406 0 Td [(a)]TJ/F8 9.9626 Tf 5.231 0 Td [(.)]TJ +/F27 9.9626 Tf -307.846 -20.135 Td [(repl)]TJ 0 g 0 G -/F27 9.9626 Tf -37.637 -21.094 Td [(T)32(yp)-32(e:)]TJ +/F8 9.9626 Tf 24.499 0 Td [(Data)-351(allo)-28(cation:)-480(build)-351(a)-351(replicated)-351(index)-351(space)-351(\050i.e.)-498(all)-351(pro)-28(cesses)-351(o)27(wn)-351(all)]TJ 0.408 -11.955 Td [(indices\051.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -57.707 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(th)1(e)-334(logical)-333(v)55(alue)]TJ/F30 9.9626 Tf 131.784 0 Td [(.true.)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ +/F27 9.9626 Tf -156.691 -20.135 Td [(globalc)32(hec)32(k)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -21.483 Td [(On)-383(En)32(try)]TJ +/F8 9.9626 Tf 61.948 0 Td [(Data)-333(allo)-28(cation:)-445(d)1(o)-334(global)-333(c)28(hec)27(ks)-333(on)-333(the)-334(lo)-27(cal)-334(index)-333(lists)]TJ/F30 9.9626 Tf 250.201 0 Td [(vl)]TJ/F8 9.9626 Tf -287.242 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -57.707 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(logical)-333(v)55(alue,)-333(default:)]TJ/F30 9.9626 Tf 163.056 0 Td [(.true.)]TJ 0 g 0 G +/F27 9.9626 Tf -187.963 -20.135 Td [(lidx)]TJ 0 g 0 G - 0 -21.484 Td [(a)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Data)-353(allo)-28(cation:)-484(the)-353(set)-353(of)-353(lo)-28(cal)-353(indices)]TJ/F11 9.9626 Tf 176.172 0 Td [(l)-20(idx)]TJ/F8 9.9626 Tf 17.48 0 Td [(\0501)-311(:)]TJ/F11 9.9626 Tf 17.814 0 Td [(nl)]TJ/F8 9.9626 Tf 9.149 0 Td [(\051)-353(to)-353(b)-28(e)-353(assigned)-353(to)-353(the)]TJ -219.466 -11.955 Td [(global)-333(indices)]TJ/F11 9.9626 Tf 62.045 0 Td [(v)-36(l)]TJ/F8 9.9626 Tf 8.355 0 Td [(.)]TJ -70.4 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)84(.)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(A)-333(sparse)-334(matrix)-333(Scop)-28(e:)]TJ/F27 9.9626 Tf 101.176 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -109.893 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.081 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-334(structured)-333(data)-333(t)27(yp)-27(e.)]TJ +/F27 9.9626 Tf -24.907 -22.127 Td [(On)-383(Return)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -21.484 Td [(desc)]TJ +0 g 0 G + 0 -20.135 Td [(desc)]TJ ET q -1 0 0 1 172.619 504.47 cm +1 0 0 1 121.81 376.512 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 176.057 504.27 Td [(a)]TJ +/F27 9.9626 Tf 125.247 376.313 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.55 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.551 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 362.845 456.649 cm +1 0 0 1 312.036 328.692 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 365.983 456.45 Td [(Tspmat)]TJ +/F30 9.9626 Tf 315.174 328.492 Td [(desc)]TJ ET q -1 0 0 1 397.993 456.649 cm +1 0 0 1 336.723 328.692 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 401.131 456.45 Td [(type)]TJ +/F30 9.9626 Tf 339.861 328.492 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -271.347 -21.484 Td [(nl)]TJ +/F27 9.9626 Tf -260.887 -20.135 Td [(info)]TJ 0 g 0 G -/F8 9.9626 Tf 14.529 0 Td [(the)-333(n)28(um)27(b)-27(er)-334(of)-333(additional)-333(la)28(y)27(ers)-333(desired.)]TJ 10.377 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -57.708 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue)]TJ/F11 9.9626 Tf 130.428 0 Td [(nl)]TJ/F14 9.9626 Tf 11.916 0 Td [(\025)]TJ/F8 9.9626 Tf 10.516 0 Td [(0.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ/F16 11.9552 Tf -24.907 -22.128 Td [(Notes)]TJ 0 g 0 G -/F27 9.9626 Tf -177.766 -21.483 Td [(ext)32(yp)-32(e)]TJ +/F8 9.9626 Tf 12.177 -20.082 Td [(1.)]TJ 0 g 0 G -/F8 9.9626 Tf 38.397 0 Td [(the)-333(kind)-334(of)-333(estension)-333(required.)]TJ -13.491 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -57.708 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(optional)]TJ/F8 9.9626 Tf 44.396 0 Td [(.)]TJ -69.58 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-419(as:)-616(an)-420(in)28(teger)-419(v)55(alue)]TJ/F30 9.9626 Tf 135.566 0 Td [(psb_ovt_xhal_)]TJ/F8 9.9626 Tf 67.995 0 Td [(,)]TJ/F30 9.9626 Tf 7.159 0 Td [(psb_ovt_asov_)]TJ/F8 9.9626 Tf 67.994 0 Td [(,)-441(default:)]TJ/F30 9.9626 Tf -278.714 -11.955 Td [(psb_ovt_xhal_)]TJ + [-500(One)-241(of)-241(the)-240(optional)-241(argumen)28(ts)]TJ/F30 9.9626 Tf 144.914 0 Td [(parts)]TJ/F8 9.9626 Tf 26.152 0 Td [(,)]TJ/F30 9.9626 Tf 5.351 0 Td [(vg)]TJ/F8 9.9626 Tf 10.461 0 Td [(,)]TJ/F30 9.9626 Tf 5.351 0 Td [(vl)]TJ/F8 9.9626 Tf 10.46 0 Td [(,)]TJ/F30 9.9626 Tf 5.351 0 Td [(nl)]TJ/F8 9.9626 Tf 12.86 0 Td [(or)]TJ/F30 9.9626 Tf 11.283 0 Td [(repl)]TJ/F8 9.9626 Tf 23.32 0 Td [(m)28(ust)-241(b)-28(e)-241(sp)-27(e)-1(ci\014)1(e)-1(d)1(,)]TJ -242.773 -11.956 Td [(thereb)28(y)-334(c)28(ho)-28(osing)-333(the)-333(initialization)-333(strategy)-334(as)-333(follo)28(ws:)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -23.476 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf 0 -20.135 Td [(parts)]TJ 0 g 0 G +/F8 9.9626 Tf 30.609 0 Td [(In)-337(this)-338(case)-338(w)28(e)-337(ha)28(v)27(e)-337(a)-338(subroutine)-337(sp)-28(ecifying)-337(the)-338(mapping)-337(b)-28(et)28(w)28(een)]TJ -8.691 -11.955 Td [(global)-225(indices)-225(and)-225(pro)-28(cess/lo)-27(c)-1(al)-225(i)1(ndex)-225(pairs.)-409(If)-225(this)-225(optional)-225(ar)1(gume)-1(n)28(t)]TJ 0 -11.955 Td [(is)-316(sp)-28(eci\014ed,)-320(then)-316(it)-317(is)-316(mandatory)-316(to)-317(sp)-28(ecify)-316(the)-316(argumen)28(t)]TJ/F30 9.9626 Tf 251.562 0 Td [(mg)]TJ/F8 9.9626 Tf 13.613 0 Td [(as)-316(w)27(ell.)]TJ -265.175 -11.955 Td [(The)-333(subroutine)-334(m)28(ust)-333(conform)-333(to)-334(the)-333(follo)28(wing)-334(in)28(terface:)]TJ +0 g 0 G +0 g 0 G +/F30 9.9626 Tf 10.461 -18.09 Td [(interface)]TJ 15.691 -11.955 Td [(subroutine)-525(psb_parts\050glob_index,mg,np,pv,nv\051)]TJ +0 g 0 G +/F8 9.9626 Tf 93.898 -29.888 Td [(65)]TJ 0 g 0 G - 0 -21.484 Td [(desc)]TJ ET -q -1 0 0 1 172.619 261.126 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q + +endstream +endobj +1297 0 obj +<< +/Length 10049 +>> +stream +0 g 0 G +0 g 0 G BT -/F27 9.9626 Tf 176.057 260.927 Td [(out)]TJ +/F30 9.9626 Tf 234.142 706.129 Td [(integer,)-525(intent)-525(\050in\051)-1050(::)-525(glob_index,np,mg)]TJ 0 -11.955 Td [(integer,)-525(intent)-525(\050out\051)-525(::)-525(nv,)-525(pv\050*\051)]TJ -10.461 -11.955 Td [(end)-525(subroutine)-525(psb_parts)]TJ -15.691 -11.956 Td [(end)-525(interface)]TJ/F8 9.9626 Tf -10.461 -17.586 Td [(The)-333(input)-334(argumen)28(ts)-333(are:)]TJ 0 g 0 G -/F8 9.9626 Tf 21.53 0 Td [(the)-333(extended)-334(comm)28(unication)-333(descriptor.)]TJ -21.976 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ +/F27 9.9626 Tf 0 -15.594 Td [(glob)]TJ ET q -1 0 0 1 362.845 213.305 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 219.221 637.283 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F30 9.9626 Tf 365.983 213.106 Td [(desc)]TJ +/F27 9.9626 Tf 222.658 637.083 Td [(index)]TJ +0 g 0 G +/F8 9.9626 Tf 32.192 0 Td [(The)-333(global)-334(index)-333(to)-333(b)-28(e)-333(mapp)-28(ed;)]TJ +0 g 0 G +/F27 9.9626 Tf -57.321 -13.774 Td [(np)]TJ +0 g 0 G +/F8 9.9626 Tf 17.712 0 Td [(The)-333(n)27(u)1(m)27(b)-27(e)-1(r)-333(of)-333(pro)-28(cesses)-333(in)-334(the)-333(mapping;)]TJ +0 g 0 G +/F27 9.9626 Tf -17.712 -13.774 Td [(mg)]TJ +0 g 0 G +/F8 9.9626 Tf 20.258 0 Td [(The)-333(total)-334(n)28(um)28(b)-28(er)-333(of)-333(global)-334(ro)28(ws)-333(in)-334(th)1(e)-334(mapping;)]TJ -20.258 -15.594 Td [(The)-333(output)-334(argumen)28(ts)-333(are:)]TJ +0 g 0 G +/F27 9.9626 Tf 0 -15.594 Td [(n)32(v)]TJ +0 g 0 G +/F8 9.9626 Tf 17.075 0 Td [(The)-333(n)27(um)28(b)-28(er)-333(of)-333(en)28(tries)-334(in)]TJ/F30 9.9626 Tf 111.637 0 Td [(pv)]TJ/F8 9.9626 Tf 10.461 0 Td [(;)]TJ +0 g 0 G +/F27 9.9626 Tf -139.173 -13.774 Td [(p)32(v)]TJ +0 g 0 G +/F8 9.9626 Tf 17.075 0 Td [(A)-481(v)28(ector)-481(con)28(taining)-481(the)-481(indi)1(c)-1(es)-480(of)-481(the)-481(pro)-28(cesses)-481(to)-481(whic)28(h)-481(the)]TJ 1.555 -11.955 Td [(global)-468(index)-468(should)-468(b)-28(e)-468(assigend;)-536(eac)28(h)-468(en)28(try)-468(m)28(ust)-469(satisfy)-468(0)]TJ/F14 9.9626 Tf 270.508 0 Td [(\024)]TJ/F11 9.9626 Tf -270.508 -11.956 Td [(pv)]TJ/F8 9.9626 Tf 10.199 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)]TJ/F11 9.9626 Tf 8.603 0 Td [(<)-475(np)]TJ/F8 9.9626 Tf 23.47 0 Td [(;)-511(i)1(f)]TJ/F11 9.9626 Tf 18.163 0 Td [(nv)-511(>)]TJ/F8 9.9626 Tf 28.373 0 Td [(1)-451(w)27(e)-451(ha)28(v)27(e)-451(an)-452(in)1(dex)-452(assigned)-451(to)-452(m)28(ultiple)]TJ -96.115 -11.955 Td [(pro)-28(cesses,)-333(i.e.)-445(w)28(e)-333(ha)27(v)28(e)-333(an)-333(o)27(v)28(erlap)-333(among)-334(t)1(he)-334(sub)-28(domains.)]TJ +0 g 0 G +/F27 9.9626 Tf -40.548 -15.594 Td [(vg)]TJ +0 g 0 G +/F8 9.9626 Tf 16.757 0 Td [(In)-398(th)1(is)-398(case)-398(the)-397(asso)-28(ciation)-398(b)-27(e)-1(t)28(w)28(een)-398(an)-397(index)-398(and)-397(a)-398(pro)-27(ces)-1(s)-397(is)-398(sp)-28(ec-)]TJ 5.161 -11.955 Td [(i\014ed)-456(via)-456(an)-456(in)28(tege)-1(r)-456(v)28(ector)]TJ/F30 9.9626 Tf 120.743 0 Td [(vg\0501:mg\051)]TJ/F8 9.9626 Tf 41.842 0 Td [(;)-518(eac)28(h)-456(index)]TJ/F11 9.9626 Tf 59.63 0 Td [(i)]TJ/F14 9.9626 Tf 8.238 0 Td [(2)-482(f)]TJ/F8 9.9626 Tf 16.429 0 Td [(1)]TJ/F11 9.9626 Tf 6.642 0 Td [(:)-167(:)-166(:)-167(mg)]TJ/F14 9.9626 Tf 27.14 0 Td [(g)]TJ/F8 9.9626 Tf 9.526 0 Td [(is)]TJ -290.19 -11.955 Td [(assigned)-449(to)-449(pro)-28(cess)]TJ/F11 9.9626 Tf 89.776 0 Td [(v)-36(g)]TJ/F8 9.9626 Tf 10.296 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051.)-792(The)-449(v)28(ector)]TJ/F30 9.9626 Tf 67.232 0 Td [(vg)]TJ/F8 9.9626 Tf 14.935 0 Td [(m)28(ust)-449(b)-28(e)-449(iden)28(tica)-1(l)-449(on)-449(all)]TJ -189.546 -11.955 Td [(calling)-452(pro)-28(cesses;)-513(it)1(s)-453(en)28(tries)-453(ma)28(y)-453(ha)28(v)28(e)-453(th)1(e)-453(ranges)-453(\0500)]TJ/F11 9.9626 Tf 236.604 0 Td [(:)-167(:)-166(:)-167(np)]TJ/F14 9.9626 Tf 27.281 0 Td [(\000)]TJ/F8 9.9626 Tf 10.754 0 Td [(1\051)-453(or)]TJ -274.639 -11.955 Td [(\0501)]TJ/F11 9.9626 Tf 10.516 0 Td [(:)-167(:)-166(:)-167(np)]TJ/F8 9.9626 Tf 24.276 0 Td [(\051)-347(according)-347(to)-347(the)-347(v)55(alu)1(e)-348(of)]TJ/F30 9.9626 Tf 119.292 0 Td [(flag)]TJ/F8 9.9626 Tf 20.921 0 Td [(.)-486(The)-347(size)]TJ/F11 9.9626 Tf 47.231 0 Td [(mg)]TJ/F8 9.9626 Tf 17.314 0 Td [(ma)28(y)-347(b)-28(e)-347(sp)-28(ec-)]TJ -239.55 -11.955 Td [(i\014ed)-414(via)-414(the)-415(option)1(al)-415(argumen)28(t)]TJ/F30 9.9626 Tf 142.427 0 Td [(mg)]TJ/F8 9.9626 Tf 10.461 0 Td [(;)-455(the)-414(default)-414(is)-414(to)-414(use)-415(the)-414(en)28(tire)]TJ -152.888 -11.956 Td [(v)28(ector)]TJ/F30 9.9626 Tf 29.916 0 Td [(vg)]TJ/F8 9.9626 Tf 10.46 0 Td [(,)-333(th)27(u)1(s)-334(ha)28(ving)]TJ/F30 9.9626 Tf 60.108 0 Td [(mg=size\050vg\051)]TJ/F8 9.9626 Tf 57.534 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -179.936 -15.593 Td [(vl)]TJ +0 g 0 G +/F8 9.9626 Tf 14.211 0 Td [(In)-356(this)-357(case)-356(w)28(e)-357(are)-356(sp)-28(ecifying)-356(the)-357(list)-356(of)-356(indices)]TJ/F30 9.9626 Tf 210.708 0 Td [(vl\0501:nl\051)]TJ/F8 9.9626 Tf 45.393 0 Td [(assigned)-356(to)]TJ -248.394 -11.955 Td [(the)-462(curren)28(t)-462(pro)-27(ce)-1(ss;)-526(th)28(us,)-494(the)-461(global)-462(problem)-462(size)]TJ/F11 9.9626 Tf 229.323 0 Td [(mg)]TJ/F8 9.9626 Tf 18.457 0 Td [(is)-462(giv)28(en)-462(b)28(y)]TJ -247.78 -11.956 Td [(the)-405(range)-405(of)-404(the)-405(aggregate)-405(of)-405(the)-405(in)1(dividual)-405(v)28(ectors)]TJ/F30 9.9626 Tf 233.196 0 Td [(vl)]TJ/F8 9.9626 Tf 14.494 0 Td [(sp)-28(eci\014ed)-405(in)]TJ -247.69 -11.955 Td [(the)-481(calling)-481(p)1(ro)-28(cesses.)-887(The)-481(size)-481(ma)28(y)-481(b)-28(e)-481(sp)-27(eci\014ed)-481(via)-481(the)-481(optional)]TJ 0 -11.955 Td [(argumen)28(t)]TJ/F30 9.9626 Tf 44.85 0 Td [(nl)]TJ/F8 9.9626 Tf 10.461 0 Td [(;)-373(the)-361(default)-360(is)-360(to)-360(use)-360(the)-360(en)28(tire)-361(v)28(ector)]TJ/F30 9.9626 Tf 173.727 0 Td [(vl)]TJ/F8 9.9626 Tf 10.461 0 Td [(,)-367(th)28(us)-360(ha)28(ving)]TJ/F30 9.9626 Tf -239.499 -11.955 Td [(nl=size\050vl\051)]TJ/F8 9.9626 Tf 57.534 0 Td [(.)-419(If)]TJ/F30 9.9626 Tf 16.133 0 Td [(globalcheck=.true.)]TJ/F8 9.9626 Tf 96.698 0 Td [(the)-256(subroutine)-256(will)-256(c)27(hec)28(k)-256(ho)28(w)]TJ -170.365 -11.955 Td [(man)28(y)-255(times)-255(eac)28(h)-254(en)27(try)-254(in)-255(the)-254(global)-255(index)-254(s)-1(p)1(ac)-1(e)-254(\0501)]TJ/F11 9.9626 Tf 217.24 0 Td [(:)-167(:)-166(:)-167(mg)]TJ/F8 9.9626 Tf 27.14 0 Td [(\051)-255(is)-254(sp)-28(eci\014ed)]TJ -244.38 -11.955 Td [(in)-331(the)-331(input)-331(lists)]TJ/F30 9.9626 Tf 75.842 0 Td [(vl)]TJ/F8 9.9626 Tf 10.461 0 Td [(,)-331(th)27(us)-331(all)1(o)27(wing)-331(for)-331(t)1(he)-331(prese)-1(n)1(c)-1(e)-331(of)-330(o)27(v)28(erlap)-331(in)-331(the)]TJ -86.303 -11.956 Td [(input,)-338(and)-337(c)28(hec)27(king)-337(for)-337(\134orphan")-337(indices.)-456(If)]TJ/F30 9.9626 Tf 194.743 0 Td [(globalcheck=.false.)]TJ/F8 9.9626 Tf 99.376 0 Td [(,)]TJ -294.119 -11.955 Td [(the)-409(s)-1(u)1(broutine)-410(will)-409(not)-410(c)28(hec)28(k)-410(for)-409(o)28(v)27(erlap,)-428(and)-409(ma)27(y)-409(b)-28(e)-409(signi\014can)27(tly)]TJ 0 -11.955 Td [(faster,)-362(but)-357(the)-357(user)-356(is)-357(implicitly)-357(gu)1(aran)27(teeing)-356(that)-357(there)-357(ar)1(e)-357(neither)]TJ 0 -11.955 Td [(orphan)-333(nor)-333(o)27(v)28(erlap)-333(indices.)]TJ +0 g 0 G +/F27 9.9626 Tf -21.918 -15.594 Td [(lidx)]TJ +0 g 0 G +/F8 9.9626 Tf 23.758 0 Td [(The)-463(optional)-462(argumen)28(t)]TJ/F30 9.9626 Tf 107.67 0 Td [(lidx)]TJ/F8 9.9626 Tf 25.531 0 Td [(is)-463(a)28(v)56(ailable)-463(for)-462(those)-463(cases)-463(in)-463(whi)1(c)27(h)]TJ -135.041 -11.955 Td [(the)-446(user)-446(has)-446(already)-446(established)-446(a)-446(global-to-lo)-28(cal)-446(mapping;)-502(if)-446(it)-446(is)]TJ 0 -11.955 Td [(sp)-28(eci\014ed,)-373(eac)28(h)-365(index)-365(in)]TJ/F30 9.9626 Tf 105.175 0 Td [(vl\050i\051)]TJ/F8 9.9626 Tf 29.789 0 Td [(will)-365(b)-28(e)-365(mapp)-28(ed)-365(to)-365(the)-365(corresp)-27(onding)]TJ -134.964 -11.955 Td [(lo)-28(cal)-392(index)]TJ/F30 9.9626 Tf 51.539 0 Td [(lidx\050i\051)]TJ/F8 9.9626 Tf 36.613 0 Td [(.)-621(When)-392(sp)-28(ecifying)-392(the)-392(argumen)28(t)]TJ/F30 9.9626 Tf 148.368 0 Td [(lidx)]TJ/F8 9.9626 Tf 24.828 0 Td [(the)-392(user)]TJ -261.348 -11.956 Td [(w)28(ould)-420(also)-420(lik)28(ely)-419(e)-1(mpl)1(o)27(y)]TJ/F30 9.9626 Tf 113.086 0 Td [(lidx)]TJ/F8 9.9626 Tf 25.103 0 Td [(in)-420(calls)-419(to)]TJ/F30 9.9626 Tf 48.576 0 Td [(psb_cdins)]TJ/F8 9.9626 Tf 51.254 0 Td [(and)]TJ/F30 9.9626 Tf 20.232 0 Td [(local)]TJ/F8 9.9626 Tf 30.333 0 Td [(in)]TJ -288.584 -11.955 Td [(calls)-333(to)]TJ/F30 9.9626 Tf 34.371 0 Td [(psb_spins)]TJ/F8 9.9626 Tf 50.394 0 Td [(and)]TJ/F30 9.9626 Tf 19.372 0 Td [(psb_geins)]TJ/F8 9.9626 Tf 47.073 0 Td [(;)-333(see)-334(also)-333(sec.)]TJ +0 0 1 rg 0 0 1 RG + [-334(2.3.1)]TJ +0 g 0 G + [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -173.128 -15.593 Td [(nl)]TJ +0 g 0 G +/F8 9.9626 Tf 14.529 0 Td [(If)-307(this)-308(argumen)28(t)-307(is)-308(sp)-28(eci\014ed)-307(alone)-308(\050i.e.)-435(without)]TJ/F30 9.9626 Tf 206.41 0 Td [(vl)]TJ/F8 9.9626 Tf 10.461 0 Td [(\051)-307(the)-308(result)-307(is)-308(a)-307(gen-)]TJ -209.482 -11.956 Td [(eralized)-313(ro)27(w-blo)-27(c)27(k)-313(distribution)-313(in)-314(whic)28(h)-313(eac)27(h)-313(pro)-28(cess)]TJ/F11 9.9626 Tf 232.18 0 Td [(I)]TJ/F8 9.9626 Tf 8.284 0 Td [(gets)-313(as)-1(signed)]TJ -240.464 -11.955 Td [(a)-333(consecutiv)27(e)-333(c)28(h)28(unk)-334(of)]TJ/F11 9.9626 Tf 101.342 0 Td [(N)]TJ/F10 6.9738 Tf 8.005 -1.494 Td [(I)]TJ/F8 9.9626 Tf 7.338 1.494 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(nl)]TJ/F8 9.9626 Tf 12.47 0 Td [(global)-333(indices.)]TJ +0 g 0 G +/F27 9.9626 Tf -161.589 -15.593 Td [(repl)]TJ +0 g 0 G +/F8 9.9626 Tf 24.498 0 Td [(This)-239(argumen)28(ts)-240(sp)-27(e)-1(ci\014es)-239(to)-239(replicate)-239(all)-239(indices)-240(on)-239(all)-239(pro)-28(cesses.)-413(This)]TJ -2.58 -11.956 Td [(is)-312(a)-311(sp)-28(ecial)-312(purp)-27(ose)-312(data)-312(allo)-27(cation)-312(that)-311(is)-312(useful)-312(in)-311(the)-312(construction)]TJ 0 -11.955 Td [(of)-333(some)-334(m)28(ultilev)28(el)-334(p)1(rec)-1(on)1(ditioners.)]TJ +0 g 0 G + -34.648 -19.579 Td [(2.)]TJ +0 g 0 G + [-500(On)-333(exit)-334(from)-333(this)-333(routine)-333(the)-334(descriptor)-333(is)-333(in)-334(the)-333(build)-333(state.)]TJ +0 g 0 G + 154.698 -29.888 Td [(66)]TJ +0 g 0 G +ET + +endstream +endobj +1302 0 obj +<< +/Length 2660 +>> +stream +0 g 0 G +0 g 0 G +0 g 0 G +BT +/F8 9.9626 Tf 112.072 706.129 Td [(3.)]TJ +0 g 0 G + [-500(Calling)-339(the)-339(routine)-339(with)]TJ/F30 9.9626 Tf 121.471 0 Td [(vg)]TJ/F8 9.9626 Tf 13.839 0 Td [(or)]TJ/F30 9.9626 Tf 12.262 0 Td [(parts)]TJ/F8 9.9626 Tf 29.53 0 Td [(implies)-339(that)-339(ev)28(ery)-340(pr)1(o)-28(cess)-340(will)-339(scan)]TJ -164.372 -11.955 Td [(the)-333(en)27(tire)-333(index)-333(space)-334(to)-333(\014gure)-333(out)-333(the)-334(lo)-28(cal)-333(indices.)]TJ +0 g 0 G + -12.73 -19.926 Td [(4.)]TJ +0 g 0 G + [-500(Ov)28(erlapp)-28(ed)-333(indices)-334(are)-333(p)-28(ossible)-333(with)-333(b)-28(oth)]TJ/F30 9.9626 Tf 199.198 0 Td [(parts)]TJ/F8 9.9626 Tf 29.472 0 Td [(and)]TJ/F30 9.9626 Tf 19.372 0 Td [(vl)]TJ/F8 9.9626 Tf 13.782 0 Td [(in)28(v)28(o)-28(cations.)]TJ +0 g 0 G + -261.824 -19.925 Td [(5.)]TJ +0 g 0 G + [-500(When)-222(the)-222(subroutine)-222(is)-223(in)28(v)28(ok)28(ed)-223(with)]TJ/F30 9.9626 Tf 170.61 0 Td [(vl)]TJ/F8 9.9626 Tf 12.675 0 Td [(in)-222(conjunction)-222(with)]TJ/F30 9.9626 Tf 84.959 0 Td [(globalcheck=.true.)]TJ/F8 9.9626 Tf 94.147 0 Td [(,)]TJ -349.661 -11.955 Td [(it)-368(will)-369(p)-28(erform)-368(a)-368(s)-1(can)-368(of)-368(the)-369(index)-368(space)-369(to)-368(searc)27(h)-368(for)-368(o)27(v)28(erlap)-368(or)-369(orp)1(han)]TJ 0 -11.955 Td [(indices.)]TJ +0 g 0 G + -12.73 -19.925 Td [(6.)]TJ +0 g 0 G + [-500(When)-222(the)-222(subroutine)-222(is)-223(in)28(v)28(ok)28(ed)-223(with)]TJ/F30 9.9626 Tf 170.61 0 Td [(vl)]TJ/F8 9.9626 Tf 12.675 0 Td [(in)-222(conjunction)-222(with)]TJ/F30 9.9626 Tf 84.959 0 Td [(globalcheck=.false.)]TJ/F8 9.9626 Tf 99.377 0 Td [(,)]TJ -354.891 -11.956 Td [(no)-405(index)-405(space)-405(scan)-405(will)-405(tak)28(e)-405(place.)-660(Th)28(us)-405(it)-405(is)-405(the)-405(resp)-28(onsibilit)28(y)-405(of)-405(the)]TJ 0 -11.955 Td [(user)-419(to)-418(mak)28(e)-419(sure)-418(that)-419(the)-418(indices)-419(sp)-28(eci\014ed)-418(in)]TJ/F30 9.9626 Tf 211.319 0 Td [(vl)]TJ/F8 9.9626 Tf 14.63 0 Td [(ha)28(v)28(e)-419(neither)-418(orphans)]TJ -225.949 -11.955 Td [(nor)-333(o)28(v)27(erlaps;)-333(if)-333(this)-334(assumption)-333(fails,)-333(results)-334(will)-333(b)-28(e)-333(unpredictable.)]TJ +0 g 0 G + -12.73 -19.925 Td [(7.)]TJ +0 g 0 G + [-500(Orphan)-313(and)-312(o)27(v)28(erlap)-312(indices)-313(are)-313(imp)-28(ossible)-313(b)28(y)-313(construction)-312(when)-313(the)-313(sub-)]TJ 12.73 -11.955 Td [(routine)-333(is)-334(in)28(v)28(ok)28(ed)-334(with)]TJ/F30 9.9626 Tf 103.307 0 Td [(nl)]TJ/F8 9.9626 Tf 13.782 0 Td [(\050alone\051,)-333(or)]TJ/F30 9.9626 Tf 48.734 0 Td [(vg)]TJ/F8 9.9626 Tf 10.46 0 Td [(.)]TJ +0 g 0 G + -34.315 -452.304 Td [(67)]TJ +0 g 0 G +ET + +endstream +endobj +1313 0 obj +<< +/Length 7171 +>> +stream +0 g 0 G +0 g 0 G +BT +/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ ET q -1 0 0 1 387.532 213.305 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 171.761 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F30 9.9626 Tf 390.67 213.106 Td [(type)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(cdins)-375(|)-375(Comm)31(unication)-375(descriptor)-375(insert)-375(routine)]TJ 0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -260.887 -21.484 Td [(info)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_cdins\050nz,)-525(ia,)-525(ja,)-525(desc_a,)-525(info)-525([,ila,jla]\051)]TJ 0 -11.956 Td [(call)-525(psb_cdins\050nz,ja,desc,info[,jla,mask,lidx]\051)]TJ/F8 9.9626 Tf 14.944 -20.465 Td [(This)-428(subroutine)-427(examines)-428(the)-428(edges)-428(of)-428(the)-427(graph)-428(asso)-28(ciated)-428(with)-428(t)1(he)-428(dis-)]TJ -14.944 -11.955 Td [(cretization)-481(mesh)-480(\050and)-481(isomorphic)-480(to)-481(the)-480(sparsit)27(y)-480(pattern)-481(of)-480(a)-481(lin)1(e)-1(ar)-480(system)]TJ 0 -11.955 Td [(co)-28(e\016cien)28(t)-359(matrix\051,)-366(storing)-359(them)-359(as)-359(necess)-1(ar)1(y)-360(in)28(to)-359(the)-359(comm)28(unication)-359(des)-1(crip)1(-)]TJ 0 -11.955 Td [(tor.)-506(In)-353(the)-354(\014rst)-354(form)-354(the)-354(edges)-353(are)-354(sp)-28(eci\014ed)-354(as)-354(pairs)-353(of)-354(indices)]TJ/F11 9.9626 Tf 278.053 0 Td [(ia)]TJ/F8 9.9626 Tf 8.698 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)]TJ/F11 9.9626 Tf 3.874 0 Td [(;)-167(j)-57(a)]TJ/F8 9.9626 Tf 14.367 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.433 0 Td [(\051;)-364(the)]TJ -319.606 -11.955 Td [(starting)-394(index)]TJ/F11 9.9626 Tf 65.222 0 Td [(ia)]TJ/F8 9.9626 Tf 8.699 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)-394(should)-394(b)-28(elong)-394(to)-394(the)-395(cur)1(re)-1(n)28(t)-394(pro)-28(cess.)-627(In)-394(the)-394(second)-394(form)]TJ -81.227 -11.955 Td [(only)-333(the)-334(remote)-333(indices)]TJ/F11 9.9626 Tf 104.968 0 Td [(j)-57(a)]TJ/F8 9.9626 Tf 9.939 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)-333(are)-334(sp)-27(e)-1(ci\014ed.)]TJ +0 g 0 G +/F27 9.9626 Tf -122.213 -20.465 Td [(T)32(yp)-32(e:)]TJ +0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +0 g 0 G +/F27 9.9626 Tf -33.797 -19.345 Td [(On)-383(En)32(try)]TJ +0 g 0 G +0 g 0 G + 0 -19.344 Td [(nz)]TJ +0 g 0 G +/F8 9.9626 Tf 16.438 0 Td [(the)-333(n)27(u)1(m)27(b)-27(e)-1(r)-333(of)-333(p)-28(oin)28(ts)-333(b)-28(eing)-333(inserte)-1(d)1(.)]TJ 8.469 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.451 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(alue.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.344 Td [(ia)]TJ +0 g 0 G +/F8 9.9626 Tf 13.733 0 Td [(the)-333(indices)-334(of)-333(the)-333(starting)-334(v)28(ertex)-333(of)-333(the)-334(edges)-333(b)-28(eing)-333(inserted.)]TJ 11.174 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.451 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(arra)27(y)-333(of)-333(length)]TJ/F11 9.9626 Tf 172.547 0 Td [(nz)]TJ/F8 9.9626 Tf 11.051 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -208.505 -19.344 Td [(ja)]TJ +0 g 0 G +/F8 9.9626 Tf 14.051 0 Td [(the)-333(indices)-334(of)-333(the)-333(end)-334(v)28(ertex)-333(of)-334(t)1(he)-334(edges)-333(b)-28(eing)-333(inserted.)]TJ 10.856 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.451 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(arra)27(y)-333(of)-333(length)]TJ/F11 9.9626 Tf 172.547 0 Td [(nz)]TJ/F8 9.9626 Tf 11.051 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -208.505 -19.344 Td [(mask)]TJ +0 g 0 G +/F8 9.9626 Tf 30.664 0 Td [(Mask)-329(e)-1(n)28(tries)-329(in)]TJ/F30 9.9626 Tf 70.038 0 Td [(ja)]TJ/F8 9.9626 Tf 10.461 0 Td [(,)-330(they)-330(are)-329(inserted)-330(only)-329(when)-329(the)-330(corresp)-28(onding)]TJ/F30 9.9626 Tf 211.627 0 Td [(mask)]TJ/F8 9.9626 Tf -297.883 -11.955 Td [(en)28(tries)-334(are)]TJ/F30 9.9626 Tf 48.54 0 Td [(.true.)]TJ/F8 9.9626 Tf -48.54 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.451 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(logical)-333(arra)28(y)-334(of)-333(length)]TJ/F11 9.9626 Tf 165.048 0 Td [(nz)]TJ/F8 9.9626 Tf 11.051 0 Td [(,)-333(default)]TJ/F30 9.9626 Tf 39.574 0 Td [(.true.)]TJ/F8 9.9626 Tf 31.382 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -271.962 -19.344 Td [(lidx)]TJ +0 g 0 G +/F8 9.9626 Tf 23.758 0 Td [(User)-333(de\014ned)-334(lo)-27(cal)-334(indices)-333(for)]TJ/F30 9.9626 Tf 128.85 0 Td [(ja)]TJ/F8 9.9626 Tf 10.461 0 Td [(.)]TJ -138.162 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.451 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)-333(of)-333(length)]TJ/F11 9.9626 Tf 172.547 0 Td [(nz)]TJ/F8 9.9626 Tf 11.052 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -208.506 -20.465 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G + 0 -19.344 Td [(desc)]TJ +ET +q +1 0 0 1 172.619 168.346 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 176.057 168.146 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.55 0 Td [(the)-333(up)-28(dated)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ +ET +q +1 0 0 1 362.845 120.525 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 365.983 120.326 Td [(desc)]TJ +ET +q +1 0 0 1 387.532 120.525 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 390.67 120.326 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ/F16 11.9552 Tf -24.906 -23.476 Td [(Notes)]TJ +/F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G -/F8 9.9626 Tf 166.874 -29.888 Td [(70)]TJ + -94.013 -29.888 Td [(68)]TJ 0 g 0 G ET endstream endobj -1308 0 obj +1318 0 obj << -/Length 1591 +/Length 3156 >> stream 0 g 0 G 0 g 0 G 0 g 0 G BT -/F8 9.9626 Tf 112.072 706.129 Td [(1.)]TJ +/F27 9.9626 Tf 99.895 706.129 Td [(info)]TJ 0 g 0 G - [-500(Sp)-28(ecifying)]TJ/F30 9.9626 Tf 60.091 0 Td [(psb_ovt_xhal_)]TJ/F8 9.9626 Tf 70.801 0 Td [(for)-282(the)]TJ/F30 9.9626 Tf 31.377 0 Td [(extype)]TJ/F8 9.9626 Tf 34.188 0 Td [(argumen)28(t)-282(the)-282(user)-281(will)-282(obtain)-281(a)]TJ -183.727 -11.955 Td [(descriptor)-258(f)1(o)-1(r)-257(a)-258(domain)-257(partition)-258(in)-257(whic)28(h)-258(the)-257(additional)-258(la)28(y)28(ers)-258(are)-257(fetc)27(hed)]TJ 0 -11.955 Td [(as)-415(part)-415(of)-415(an)-415(\050extended\051)-415(halo;)-456(ho)28(w)27(ev)28(er)-415(the)-415(index-to-pro)-28(cess)-415(mapping)-415(is)]TJ 0 -11.956 Td [(iden)28(tical)-334(t)1(o)-334(that)-333(of)-333(the)-334(base)-333(descriptor;)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ 0 g 0 G - -12.73 -19.925 Td [(2.)]TJ +/F27 9.9626 Tf -24.907 -19.925 Td [(ila)]TJ +0 g 0 G +/F8 9.9626 Tf 16.916 0 Td [(the)-333(lo)-28(cal)-333(indices)-334(of)-333(the)-333(starting)-334(v)28(ertex)-333(of)-334(the)-333(edges)-333(b)-28(eing)-333(inserted.)]TJ 7.991 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)-333(of)-333(length)]TJ/F11 9.9626 Tf 172.548 0 Td [(nz)]TJ/F8 9.9626 Tf 11.051 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -208.506 -19.925 Td [(jla)]TJ 0 g 0 G - [-500(Sp)-28(ecifying)]TJ/F30 9.9626 Tf 60.957 0 Td [(psb_ovt_asov_)]TJ/F8 9.9626 Tf 71.666 0 Td [(for)-368(the)]TJ/F30 9.9626 Tf 33.107 0 Td [(extype)]TJ/F8 9.9626 Tf 35.054 0 Td [(argumen)28(t)-369(the)-368(user)-369(will)-368(obtain)]TJ -188.054 -11.955 Td [(a)-458(descriptor)-459(with)-458(an)-458(o)28(v)27(erlapp)-27(ed)-459(decomp)-27(os)-1(iti)1(on:)-695(the)-458(additional)-458(la)27(y)28(er)-458(is)]TJ 0 -11.955 Td [(aggregated)-413(to)-413(the)-413(lo)-28(cal)-413(sub)-28(domain)-413(\050and)-413(th)28(us)-414(is)-413(an)-413(o)28(v)28(erlap\051,)-433(and)-413(a)-414(new)]TJ 0 -11.955 Td [(halo)-333(extending)-334(b)-27(ey)27(on)1(d)-334(the)-333(last)-333(additional)-334(la)28(y)28(er)-333(is)-334(formed.)]TJ +/F8 9.9626 Tf 17.234 0 Td [(the)-333(lo)-28(cal)-333(indices)-334(of)-333(the)-333(end)-334(v)28(ertex)-333(of)-334(the)-333(edges)-333(b)-28(eing)-333(inserted.)]TJ 7.673 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)-333(of)-333(length)]TJ/F11 9.9626 Tf 172.548 0 Td [(nz)]TJ/F8 9.9626 Tf 11.051 0 Td [(.)]TJ/F16 11.9552 Tf -208.506 -21.918 Td [(Notes)]TJ 0 g 0 G - 141.968 -524.035 Td [(71)]TJ +/F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ +0 g 0 G + [-500(This)-333(routine)-334(ma)28(y)-333(only)-333(b)-28(e)-334(called)-333(if)-333(the)-333(des)-1(crip)1(tor)-334(is)-333(in)-333(the)-334(build)-333(state;)]TJ +0 g 0 G + 0 -19.925 Td [(2.)]TJ +0 g 0 G + [-500(This)-305(r)1(o)-1(u)1(tine)-305(automatically)-304(ignores)-305(edges)-305(that)-304(do)-305(not)-304(insist)-305(on)-304(the)-305(curren)28(t)]TJ 12.73 -11.955 Td [(pro)-28(cess,)-284(i.e)-1(.)-424(edges)-272(for)-273(whic)28(h)-272(neither)-273(the)-272(starting)-272(nor)-273(the)-272(end)-273(v)28(ertex)-272(b)-28(elong)]TJ 0 -11.955 Td [(to)-333(the)-334(curren)28(t)-333(pro)-28(cess.)]TJ +0 g 0 G + -12.73 -19.926 Td [(3.)]TJ +0 g 0 G + [-500(The)-437(second)-438(form)-437(of)-437(this)-437(routine)-437(will)-438(b)-27(e)-438(useful)-437(when)-437(dealing)-437(with)-438(user-)]TJ 12.73 -11.955 Td [(sp)-28(eci\014ed)-333(index)-333(mappings;)-334(see)-333(also)]TJ +0 0 1 rg 0 0 1 RG + [-334(2.)1(3.1)]TJ +0 g 0 G + [(.)]TJ +0 g 0 G + 141.968 -314.819 Td [(69)]TJ 0 g 0 G ET endstream endobj -1316 0 obj +1327 0 obj << -/Length 4890 +/Length 4747 >> stream 0 g 0 G @@ -14767,10 +14562,10 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(spall)-375(|)-375(Allo)-31(cates)-375(a)-375(sparse)-375(matrix)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(cdasb)-375(|)-375(Comm)31(unication)-375(descriptor)-375(assem)31(bly)-375(routine)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_spall\050a,)-525(desc_a,)-525(info,)-525(nnz\051)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_cdasb\050desc_a,)-525(info)-525([,)-525(mold]\051)]TJ 0 g 0 G /F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G @@ -14788,7 +14583,7 @@ Q BT /F27 9.9626 Tf 176.057 625.971 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.55 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.55 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET @@ -14808,60 +14603,87 @@ BT 0 g 0 G /F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -260.887 -19.925 Td [(nnz)]TJ +/F27 9.9626 Tf -260.887 -19.925 Td [(mold)]TJ 0 g 0 G -/F8 9.9626 Tf 22.803 0 Td [(An)-309(estimate)-309(of)-308(the)-309(n)28(um)27(b)-27(er)-309(of)-309(nonzero)-28(es)-308(in)-309(the)-309(lo)-28(cal)-308(part)-309(of)-309(the)-309(assem)28(bled)]TJ 2.103 -11.955 Td [(matrix.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf 40.576 0 Td [(.)]TJ -70.188 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)]TJ +/F8 9.9626 Tf 29.805 0 Td [(The)-333(desired)-334(dynamic)-333(t)28(yp)-28(e)-333(for)-334(th)1(e)-334(in)28(ternal)-333(index)-334(storage.)]TJ -4.899 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf 40.576 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-222(as:)-389(a)-222(ob)-56(ject)-222(of)-222(t)28(yp)-28(e)-222(deriv)28(e)-1(d)-222(from)-222(\050in)28(teger\051)]TJ/F30 9.9626 Tf 219.871 0 Td [(psb)]TJ +ET +q +1 0 0 1 411.8 510.604 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 414.939 510.405 Td [(T)]TJ +ET +q +1 0 0 1 420.797 510.604 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 423.935 510.405 Td [(base)]TJ +ET +q +1 0 0 1 445.484 510.604 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 448.622 510.405 Td [(vect)]TJ +ET +q +1 0 0 1 470.171 510.604 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 473.309 510.405 Td [(type)]TJ/F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -21.918 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf -343.526 -21.918 Td [(On)-383(Return)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(a)]TJ + 0 -19.926 Td [(desc)]TJ +ET +q +1 0 0 1 172.619 468.761 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 176.057 468.561 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.55 0 Td [(the)-333(matrix)-334(to)-333(b)-28(e)-333(allo)-28(cated.)]TJ 14.356 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.951 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf -25.184 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.55 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 362.845 408.985 cm +1 0 0 1 362.845 420.94 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 365.983 408.786 Td [(Tspmat)]TJ +/F30 9.9626 Tf 365.983 420.741 Td [(desc)]TJ ET q -1 0 0 1 397.993 408.985 cm +1 0 0 1 387.532 420.94 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 401.131 408.786 Td [(type)]TJ +/F30 9.9626 Tf 390.67 420.741 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +/F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -271.347 -19.926 Td [(info)]TJ +/F27 9.9626 Tf -260.887 -19.926 Td [(info)]TJ 0 g 0 G /F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ/F16 11.9552 Tf -24.906 -21.918 Td [(Notes)]TJ 0 g 0 G /F8 9.9626 Tf 12.176 -19.925 Td [(1.)]TJ 0 g 0 G - [-500(On)-333(exit)-334(from)-333(this)-333(routine)-333(the)-334(sparse)-333(matrix)-334(i)1(s)-334(in)-333(the)-333(build)-334(state.)]TJ -0 g 0 G - 0 -19.926 Td [(2.)]TJ -0 g 0 G - [-500(The)-333(descriptor)-334(ma)28(y)-333(b)-28(e)-333(in)-334(either)-333(the)-333(build)-333(or)-334(assem)28(bled)-333(s)-1(tat)1(e)-1(.)]TJ -0 g 0 G - 0 -19.925 Td [(3.)]TJ -0 g 0 G - [-500(Pro)28(viding)-307(a)-308(go)-27(o)-28(d)-307(e)-1(stimate)-307(for)-307(the)-307(n)27(um)28(b)-28(er)-307(of)-307(nonzero)-28(es)]TJ/F11 9.9626 Tf 254.288 0 Td [(nnz)]TJ/F8 9.9626 Tf 20.093 0 Td [(in)-307(the)-308(assem-)]TJ -261.651 -11.955 Td [(bled)-402(matrix)-401(ma)28(y)-402(substan)28(tially)-401(impro)27(v)28(e)-401(p)-28(erformance)-402(in)-401(the)-402(matrix)-401(build)]TJ 0 -11.955 Td [(phase,)-458(as)-433(it)-432(will)-433(reduce)-433(or)-433(eliminate)-433(the)-433(need)-432(for)-433(\050p)-28(oten)28(tially)-433(m)28(ultiple\051)]TJ 0 -11.956 Td [(data)-333(reallo)-28(cations.)]TJ + [-500(On)-333(exit)-334(from)-333(this)-333(routine)-333(the)-334(descriptor)-333(is)-333(in)-334(the)-333(assem)28(bled)-334(state.)]TJ 0 g 0 G - 141.968 -133.042 Td [(72)]TJ + 154.698 -220.714 Td [(70)]TJ 0 g 0 G ET endstream endobj -1326 0 obj +1334 0 obj << -/Length 6436 +/Length 3277 >> stream 0 g 0 G @@ -14874,769 +14696,776 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(spins)-306(|)-307(Insert)-306(a)-306(cloud)-306(of)-307(elemen)32(ts)-307(in)32(to)-307(a)-306(sparse)-306(matrix)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(cdcp)31(y)-375(|)-375(Copies)-375(a)-375(comm)31(unication)-375(descriptor)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -18.647 Td [(call)-525(psb_spins\050nz,)-525(ia,)-525(ja,)-525(val,)-525(a,)-525(desc_a,)-525(info)-525([,local]\051)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_cdcpy\050desc_in,)-525(desc_out,)-525(info\051)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -22.334 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -20.479 Td [(On)-383(En)32(try)]TJ -0 g 0 G -0 g 0 G - 0 -20.479 Td [(nz)]TJ -0 g 0 G -/F8 9.9626 Tf 16.439 0 Td [(the)-333(n)28(um)27(b)-27(er)-334(of)-333(elemen)28(ts)-334(to)-333(b)-28(e)-333(inserted.)]TJ 8.468 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(scalar.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -20.479 Td [(ia)]TJ -0 g 0 G -/F8 9.9626 Tf 13.734 0 Td [(the)-333(ro)28(w)-334(indices)-333(of)-333(the)-334(elemen)28(ts)-334(to)-333(b)-28(e)-333(inserted.)]TJ 11.173 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)-333(of)-333(size)]TJ/F11 9.9626 Tf 160.98 0 Td [(nz)]TJ/F8 9.9626 Tf 11.051 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -196.938 -20.479 Td [(ja)]TJ -0 g 0 G -/F8 9.9626 Tf 14.052 0 Td [(the)-333(column)-334(indices)-333(of)-333(the)-334(elemen)28(ts)-333(to)-334(b)-27(e)-334(inserted.)]TJ 10.855 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)-333(of)-333(size)]TJ/F11 9.9626 Tf 160.98 0 Td [(nz)]TJ/F8 9.9626 Tf 11.051 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -196.938 -20.479 Td [(v)64(al)]TJ +/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ 0 g 0 G -/F8 9.9626 Tf 19.144 0 Td [(the)-333(elemen)27(ts)-333(to)-333(b)-28(e)-333(inserted.)]TJ 5.763 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-375(as:)-528(an)-375(arra)28(y)-375(of)-375(size)]TJ/F11 9.9626 Tf 130.933 0 Td [(nz)]TJ/F8 9.9626 Tf 11.051 0 Td [(.)-570(Must)-375(b)-28(e)-375(of)-375(the)-375(same)-375(t)28(yp)-28(e)-375(and)-375(kind)-375(of)]TJ -141.984 -11.955 Td [(the)-333(co)-28(e\016cien)28(ts)-334(of)-333(the)-333(s)-1(p)1(ars)-1(e)-333(matrix)]TJ/F11 9.9626 Tf 158.517 0 Td [(a)]TJ/F8 9.9626 Tf 5.266 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -188.69 -20.479 Td [(desc)]TJ + 0 -19.925 Td [(desc)]TJ ET q -1 0 0 1 121.81 339.234 cm +1 0 0 1 121.81 626.17 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 125.247 339.035 Td [(a)]TJ +/F27 9.9626 Tf 125.247 625.971 Td [(in)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(The)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(v)56(ariable)-334(of)-333(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 14.529 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -14.974 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 137.346 0 Td [(psb)]TJ +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 278.467 291.413 cm +1 0 0 1 312.036 578.35 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 281.605 291.214 Td [(desc)]TJ +/F30 9.9626 Tf 315.174 578.15 Td [(desc)]TJ ET q -1 0 0 1 303.154 291.413 cm +1 0 0 1 336.723 578.35 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 306.292 291.214 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -227.319 -32.434 Td [(lo)-32(cal)]TJ +/F30 9.9626 Tf 339.861 578.15 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 28.055 0 Td [(Whether)-465(the)-464(en)27(tr)1(ie)-1(s)-464(in)-465(the)-465(in)1(dice)-1(s)-464(v)28(ec)-1(tor)1(s)]TJ/F30 9.9626 Tf 194.825 0 Td [(ia)]TJ/F8 9.9626 Tf 10.461 0 Td [(,)]TJ/F30 9.9626 Tf 7.724 0 Td [(ja)]TJ/F8 9.9626 Tf 15.09 0 Td [(are)-465(already)-464(in)-465(lo)-28(cal)]TJ -231.248 -11.956 Td [(n)28(um)28(b)-28(ering.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(logical)-333(v)55(alue;)-333(default:)]TJ/F30 9.9626 Tf 163.056 0 Td [(.false.)]TJ/F8 9.9626 Tf 36.612 0 Td [(.)]TJ +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -224.575 -22.333 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf -260.887 -21.917 Td [(On)-383(Return)]TJ 0 g 0 G 0 g 0 G - 0 -20.48 Td [(a)]TJ + 0 -19.926 Td [(desc)]TJ +ET +q +1 0 0 1 121.81 536.507 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 125.247 536.307 Td [(out)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(matrix)-334(in)28(to)-333(whic)28(h)-334(elemen)28(ts)-333(will)-334(b)-27(e)-334(inserted.)]TJ 14.356 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.951 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf -25.183 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 21.53 0 Td [(the)-333(comm)27(unication)-333(descriptor)-333(cop)28(y)83(.)]TJ -21.975 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 312.036 120.525 cm +1 0 0 1 312.036 488.686 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 315.174 120.326 Td [(Tspmat)]TJ +/F30 9.9626 Tf 315.174 488.487 Td [(desc)]TJ ET q -1 0 0 1 347.183 120.525 cm +1 0 0 1 336.723 488.686 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 350.322 120.326 Td [(type)]TJ +/F30 9.9626 Tf 339.861 488.487 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G - -104.473 -29.888 Td [(73)]TJ +/F27 9.9626 Tf -260.887 -19.926 Td [(info)]TJ +0 g 0 G +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ +0 g 0 G + 141.968 -330.303 Td [(71)]TJ 0 g 0 G ET endstream endobj -1331 0 obj +1339 0 obj << -/Length 6086 +/Length 2243 >> stream 0 g 0 G 0 g 0 G -0 g 0 G BT -/F27 9.9626 Tf 150.705 706.129 Td [(desc)]TJ +/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ +ET +q +1 0 0 1 171.761 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 175.796 706.129 Td [(cdfree)-375(|)-375(F)94(rees)-375(a)-375(comm)31(unication)-375(descriptor)]TJ +0 g 0 G +0 g 0 G +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_cdfree\050desc_a,)-525(info\051)]TJ +0 g 0 G +/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ +0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ +0 g 0 G +/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(desc)]TJ ET q -1 0 0 1 172.619 706.328 cm +1 0 0 1 172.619 626.17 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 176.057 706.129 Td [(a)]TJ +/F27 9.9626 Tf 176.057 625.971 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.55 0 Td [(The)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.51 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(v)56(ariable)-334(of)-333(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.55 0 Td [(the)-333(comm)27(unication)-333(descriptor)-333(to)-334(b)-27(e)-334(freed.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 137.347 0 Td [(psb)]TJ +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 329.276 658.507 cm +1 0 0 1 362.845 578.35 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 332.415 658.308 Td [(desc)]TJ +/F30 9.9626 Tf 365.983 578.15 Td [(desc)]TJ ET q -1 0 0 1 353.964 658.507 cm +1 0 0 1 387.532 578.35 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 357.102 658.308 Td [(type)]TJ +/F30 9.9626 Tf 390.67 578.15 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -227.318 -31.88 Td [(info)]TJ -0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ/F16 11.9552 Tf -24.906 -21.918 Td [(Notes)]TJ -0 g 0 G -/F8 9.9626 Tf 12.176 -19.925 Td [(1.)]TJ -0 g 0 G - [-500(On)-487(en)28(try)-487(to)-488(this)-487(routine)-487(the)-487(descriptor)-487(ma)28(y)-488(b)-27(e)-488(in)-487(either)-487(the)-487(build)-487(or)]TJ 12.73 -11.955 Td [(assem)28(bled)-334(state.)]TJ -0 g 0 G - -12.73 -19.925 Td [(2.)]TJ -0 g 0 G - [-500(On)-363(en)28(try)-363(to)-362(this)-363(routine)-362(the)-363(sparse)-363(matrix)-363(ma)28(y)-363(b)-27(e)-363(in)-363(either)-362(the)-363(build)-363(or)]TJ 12.73 -11.956 Td [(up)-28(date)-333(state.)]TJ -0 g 0 G - -12.73 -19.925 Td [(3.)]TJ -0 g 0 G - [-500(If)-230(the)-231(descriptor)-230(is)-231(in)-230(the)-231(build)-230(state,)-251(then)-231(the)-230(sparse)-231(matrix)-230(m)28(ust)-231(also)-230(b)-28(e)-231(in)]TJ 12.73 -11.955 Td [(the)-327(build)-327(state;)-329(the)-328(action)-327(of)-327(the)-327(routine)-327(is)-327(to)-327(\050implicitly\051)-327(call)]TJ/F30 9.9626 Tf 271.732 0 Td [(psb_cdins)]TJ/F8 9.9626 Tf -271.732 -11.955 Td [(to)-419(add)-419(en)28(tries)-419(to)-419(the)-418(sparsit)27(y)-418(pattern;)-462(eac)28(h)-419(sparse)-419(matrix)-419(en)28(try)-419(implic-)]TJ 0 -11.955 Td [(itly)-360(d)1(e)-1(\014)1(nes)-360(a)-360(graph)-359(edge,)-366(that)-360(is)-359(passed)-360(to)-359(the)-360(descriptor)-359(routine)-360(for)-359(the)]TJ 0 -11.956 Td [(appropriate)-333(pro)-28(cessing;)]TJ -0 g 0 G - -12.73 -19.925 Td [(4.)]TJ -0 g 0 G - [-500(The)-540(co)-28(e\016cien)28(ts)-541(to)-540(b)-28(e)-540(inserted)-540(are)-541(represen)28(ted)-540(b)28(y)-541(the)-540(ordered)-540(triples)]TJ/F11 9.9626 Tf 12.73 -11.955 Td [(ia)]TJ/F8 9.9626 Tf 8.699 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)]TJ/F11 9.9626 Tf 3.875 0 Td [(;)-167(j)-57(a)]TJ/F8 9.9626 Tf 14.367 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)]TJ/F11 9.9626 Tf 3.875 0 Td [(;)-167(v)-36(al)]TJ/F8 9.9626 Tf 18.049 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.433 0 Td [(\051,)-503(for)]TJ/F11 9.9626 Tf 28.256 0 Td [(i)]TJ/F8 9.9626 Tf 8.455 0 Td [(=)-504(1)]TJ/F11 9.9626 Tf 17.752 0 Td [(;)-167(:)-166(:)-167(:)-167(;)-166(nz)]TJ/F8 9.9626 Tf 33.191 0 Td [(;)-537(these)-469(triples)-469(should)-470(b)-27(elong)-469(to)-470(the)]TJ -158.438 -11.955 Td [(curren)28(t)-351(pro)-28(cess,)-356(i.e.)]TJ/F11 9.9626 Tf 90.238 0 Td [(ia)]TJ/F8 9.9626 Tf 8.699 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.433 0 Td [(\051)-351(should)-351(b)-28(e)-351(one)-351(of)-352(the)-351(lo)-28(cal)-351(indices,)-355(but)-351(are)-352(oth-)]TJ -106.244 -11.955 Td [(erwise)-333(arbitrary;)]TJ -0 g 0 G - -12.73 -19.926 Td [(5.)]TJ -0 g 0 G - [-500(There)-386(is)-385(no)-386(requiremen)28(t)-386(that)-386(a)-385(giv)28(e)-1(n)-385(ro)28(w)-386(m)28(ust)-386(b)-28(e)-385(pass)-1(ed)-385(in)-386(its)-386(en)28(tiret)28(y)]TJ 12.73 -11.955 Td [(to)-355(a)-354(single)-355(call)-354(to)-355(this)-354(routine:)-487(the)-355(buildup)-354(of)-355(a)-354(ro)28(w)-355(ma)28(y)-355(b)-28(e)-354(split)-355(in)28(to)-355(as)]TJ 0 -11.955 Td [(man)28(y)-334(calls)-333(as)-333(desired;)]TJ -0 g 0 G - -12.73 -19.925 Td [(6.)]TJ -0 g 0 G - [-500(Co)-28(e\016cien)28(ts)-409(from)-410(di\013eren)28(t)-409(ro)28(ws)-410(ma)28(y)-409(also)-409(b)-28(e)-409(m)-1(i)1(xe)-1(d)-409(up)-409(freely)-409(in)-409(a)-410(single)]TJ 12.73 -11.956 Td [(call,)-333(according)-334(to)-333(the)-333(application)-334(n)1(e)-1(eds;)]TJ -0 g 0 G - -12.73 -19.925 Td [(7.)]TJ -0 g 0 G - [-500(An)28(y)-416(co)-28(e\016cien)28(ts)-416(from)-416(matrix)-416(ro)28(ws)-416(not)-416(o)28(wned)-416(b)28(y)-416(the)-416(calling)-416(pro)-28(cess)-416(are)]TJ 12.73 -11.955 Td [(silen)28(tly)-334(ignor)1(e)-1(d)1(;)]TJ +/F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G - -12.73 -19.925 Td [(8.)]TJ +/F27 9.9626 Tf -260.887 -21.917 Td [(On)-383(Return)]TJ 0 g 0 G - [-500(If)-358(the)-359(descriptor)-358(is)-359(in)-358(the)-359(assem)28(bled)-359(state,)-364(then)-359(an)28(y)-359(en)28(tries)-358(in)-359(the)-358(sparse)]TJ 12.73 -11.955 Td [(matrix)-430(that)-429(w)27(ould)-429(generate)-430(additional)-430(comm)28(unication)-430(requiremen)28(ts)-430(are)]TJ 0 -11.956 Td [(ignored;)]TJ 0 g 0 G - -12.73 -19.925 Td [(9.)]TJ + 0 -19.926 Td [(info)]TJ 0 g 0 G - [-500(If)-309(the)-308(matrix)-309(is)-308(in)-309(the)-308(up)-28(date)-309(state,)-313(an)28(y)-309(en)28(tries)-309(in)-308(p)-28(ositions)-309(that)-308(w)28(ere)-309(not)]TJ 12.73 -11.955 Td [(presen)28(t)-334(in)-333(the)-333(original)-333(matrix)-334(are)-333(ignored.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ 0 g 0 G - 141.968 -95.641 Td [(74)]TJ + 141.968 -398.049 Td [(72)]TJ 0 g 0 G ET endstream endobj -1235 0 obj +1236 0 obj << /Type /ObjStm /N 100 -/First 977 -/Length 10542 +/First 981 +/Length 11151 >> stream -280 0 1232 57 1233 116 1234 174 1228 232 1239 389 1227 546 1236 690 1237 834 1241 980 -1238 1039 1243 1145 1245 1263 284 1321 288 1378 1242 1435 1249 1567 1247 1706 1251 1852 1252 1911 -1248 1970 1255 2089 1253 2228 1257 2386 1258 2444 1254 2502 1260 2634 1262 2752 1263 2811 1264 2870 -1265 2929 1266 2988 1267 3047 1259 3104 1270 3184 1268 3323 1272 3469 292 3527 1269 3584 1275 3703 -1273 3842 1277 4000 1278 4059 1279 4118 1280 4177 1274 4236 1284 4342 1281 4490 1282 4636 1286 4783 -296 4841 1287 4898 1283 4956 1292 5062 1289 5210 1290 5355 1294 5501 300 5560 1291 5618 1297 5724 -1295 5863 1299 6009 304 6067 1296 6124 1303 6230 1300 6378 1301 6521 1305 6667 308 6726 1302 6784 -1307 6916 1309 7034 1310 7092 1311 7150 1306 7208 1315 7288 1312 7436 1313 7581 1317 7723 312 7782 -1318 7840 1319 7899 1320 7958 1314 8017 1325 8136 1321 8284 1322 8430 1327 8574 316 8632 1324 8689 -1330 8808 1323 8947 1332 9094 1333 9153 1334 9212 1335 9271 1336 9330 1337 9388 1338 9447 1339 9506 -% 280 0 obj +1227 0 1231 147 1232 205 1233 263 1234 321 1228 378 1238 510 1240 628 1237 687 1242 767 +1245 885 1246 1012 1247 1055 1248 1262 1249 1500 1250 1776 1244 2012 1235 2070 1241 2129 1257 2225 +1253 2382 1254 2526 1255 2673 1259 2819 276 2878 1260 2936 1261 2995 1262 3054 1263 3113 1256 3172 +1265 3329 1267 3447 1264 3505 1272 3598 1269 3737 1274 3883 280 3942 1275 4000 1276 4059 1277 4118 +1271 4177 1281 4334 1270 4491 1278 4635 1279 4778 1283 4924 1280 4982 1285 5088 1287 5206 284 5265 +288 5323 1284 5381 1290 5513 1288 5652 1292 5799 1293 5857 1289 5915 1296 6034 1294 6173 1298 6331 +1299 6390 1295 6449 1301 6581 1303 6699 1304 6757 1305 6815 1306 6873 1307 6931 1308 6989 1300 7045 +1312 7125 1310 7264 1314 7409 292 7468 1311 7526 1317 7645 1315 7784 1319 7942 1320 8000 1321 8058 +1322 8116 1316 8174 1326 8280 1323 8428 1324 8573 1328 8719 296 8778 1329 8836 1325 8895 1333 9001 +1330 9149 1331 9295 1335 9442 300 9500 1332 9557 1338 9663 1336 9802 1340 9947 304 10006 1337 10064 +% 1227 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [306.759 302.697 313.733 313.546] +/A << /S /GoTo /D (figure.7) >> +>> +% 1231 0 obj << -/D [1229 0 R /XYZ 99.895 720.077 null] +/D [1229 0 R /XYZ 98.895 753.953 null] >> % 1232 0 obj << -/D [1229 0 R /XYZ 270.132 451.038 null] +/D [1229 0 R /XYZ 99.895 465.033 null] >> % 1233 0 obj << -/D [1229 0 R /XYZ 99.895 417.777 null] +/D [1229 0 R /XYZ 99.895 431.215 null] >> % 1234 0 obj << -/D [1229 0 R /XYZ 99.895 417.777 null] +/D [1229 0 R /XYZ 99.895 387.38 null] >> % 1228 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F11 750 0 R /F10 766 0 R /F14 767 0 R /F7 765 0 R /F27 556 0 R /F30 764 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F11 755 0 R /F16 558 0 R /F10 771 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 1239 0 obj +% 1238 0 obj << /Type /Page -/Contents 1240 0 R -/Resources 1238 0 R +/Contents 1239 0 R +/Resources 1237 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1198 0 R -/Annots [ 1227 0 R 1236 0 R 1237 0 R ] ->> -% 1227 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [336.331 643.143 412.385 654.268] -/A << /S /GoTo /D (vdata) >> +/Parent 1212 0 R >> -% 1236 0 obj +% 1240 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [174.615 543.516 250.669 554.641] -/A << /S /GoTo /D (vdata) >> +/D [1238 0 R /XYZ 149.705 753.953 null] >> % 1237 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [473.75 543.516 485.705 554.641] -/A << /S /GoTo /D (table.17) >> ->> -% 1241 0 obj -<< -/D [1239 0 R /XYZ 149.705 753.953 null] ->> -% 1238 0 obj -<< -/Font << /F27 556 0 R /F8 557 0 R /F30 764 0 R /F11 750 0 R >> +/Font << /F31 775 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 1243 0 obj +% 1242 0 obj << /Type /Page -/Contents 1244 0 R -/Resources 1242 0 R +/Contents 1243 0 R +/Resources 1241 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1246 0 R +/Parent 1212 0 R >> % 1245 0 obj << -/D [1243 0 R /XYZ 98.895 753.953 null] +/Producer (GPL Ghostscript 9.22) +/CreationDate (D:20180323100658Z00'00') +/ModDate (D:20180323100658Z00'00') >> -% 284 0 obj +% 1246 0 obj << -/D [1243 0 R /XYZ 99.895 716.092 null] +/Type /ExtGState +/OPM 1 >> -% 288 0 obj +% 1247 0 obj << -/D [1243 0 R /XYZ 99.895 696.263 null] +/BaseFont /XYUGDR+Times-Roman +/FontDescriptor 1249 0 R +/Type /Font +/FirstChar 48 +/LastChar 57 +/Widths [ 500 500 500 500 500 500 500 500 500 500] +/Encoding /WinAnsiEncoding +/Subtype /Type1 >> -% 1242 0 obj +% 1248 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F27 556 0 R /F11 750 0 R /F14 767 0 R >> -/ProcSet [ /PDF /Text ] +/BaseFont /XISTAL+Times-Bold +/FontDescriptor 1250 0 R +/Type /Font +/FirstChar 48 +/LastChar 80 +/Widths [ 500 500 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 611] +/Encoding /WinAnsiEncoding +/Subtype /Type1 >> % 1249 0 obj << -/Type /Page -/Contents 1250 0 R -/Resources 1248 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1246 0 R -/Annots [ 1247 0 R ] +/Type /FontDescriptor +/FontName /XYUGDR+Times-Roman +/FontBBox [ 0 -14 476 688] +/Flags 65568 +/Ascent 688 +/CapHeight 688 +/Descent -14 +/ItalicAngle 0 +/StemV 71 +/MissingWidth 250 +/CharSet (/eight/five/four/nine/one/seven/six/three/two/zero) +/FontFile3 1251 0 R >> -% 1247 0 obj +% 1250 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.53 325.282 412.588 336.407] -/A << /S /GoTo /D (descdata) >> +/Type /FontDescriptor +/FontName /XISTAL+Times-Bold +/FontBBox [ 0 -13 600 688] +/Flags 65568 +/Ascent 688 +/CapHeight 676 +/Descent -13 +/ItalicAngle 0 +/StemV 90 +/MissingWidth 250 +/CharSet (/P/one/zero) +/FontFile3 1252 0 R >> -% 1251 0 obj +% 1244 0 obj << -/D [1249 0 R /XYZ 149.705 753.953 null] +/D [1242 0 R /XYZ 98.895 753.953 null] >> -% 1252 0 obj +% 1235 0 obj << -/D [1249 0 R /XYZ 150.705 234.372 null] +/D [1242 0 R /XYZ 232.883 272.519 null] >> -% 1248 0 obj +% 1241 0 obj << -/Font << /F27 556 0 R /F8 557 0 R /F30 764 0 R /F11 750 0 R /F16 554 0 R >> +/Font << /F8 561 0 R >> +/XObject << /Im4 1225 0 R >> /ProcSet [ /PDF /Text ] >> -% 1255 0 obj +% 1257 0 obj << /Type /Page -/Contents 1256 0 R -/Resources 1254 0 R +/Contents 1258 0 R +/Resources 1256 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1246 0 R -/Annots [ 1253 0 R ] +/Parent 1212 0 R +/Annots [ 1253 0 R 1254 0 R 1255 0 R ] >> % 1253 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [357.982 215.702 380.454 226.827] -/A << /S /GoTo /D (subsubsection.2.3.1) >> +/Rect [419.358 295.182 495.412 306.307] +/A << /S /GoTo /D (vdata) >> >> -% 1257 0 obj +% 1254 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [256.807 285.441 268.762 294.352] +/A << /S /GoTo /D (table.16) >> +>> +% 1255 0 obj << -/D [1255 0 R /XYZ 98.895 753.953 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [345.53 215.901 412.588 227.026] +/A << /S /GoTo /D (descdata) >> >> -% 1258 0 obj +% 1259 0 obj << -/D [1255 0 R /XYZ 99.895 134.155 null] +/D [1257 0 R /XYZ 149.705 753.953 null] >> -% 1254 0 obj +% 276 0 obj << -/Font << /F30 764 0 R /F8 557 0 R /F27 556 0 R /F14 767 0 R /F11 750 0 R /F10 766 0 R >> -/ProcSet [ /PDF /Text ] +/D [1257 0 R /XYZ 150.705 720.077 null] >> % 1260 0 obj << -/Type /Page -/Contents 1261 0 R -/Resources 1259 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1246 0 R +/D [1257 0 R /XYZ 320.941 466.542 null] +>> +% 1261 0 obj +<< +/D [1257 0 R /XYZ 150.705 435.558 null] >> % 1262 0 obj << -/D [1260 0 R /XYZ 149.705 753.953 null] +/D [1257 0 R /XYZ 150.705 435.558 null] >> % 1263 0 obj << -/D [1260 0 R /XYZ 150.705 716.092 null] +/D [1257 0 R /XYZ 150.705 423.603 null] >> -% 1264 0 obj +% 1256 0 obj << -/D [1260 0 R /XYZ 150.705 688.251 null] +/Font << /F16 558 0 R /F8 561 0 R /F11 755 0 R /F14 772 0 R /F10 771 0 R /F7 770 0 R /F27 560 0 R /F30 769 0 R >> +/ProcSet [ /PDF /Text ] >> % 1265 0 obj << -/D [1260 0 R /XYZ 150.705 668.049 null] ->> -% 1266 0 obj -<< -/D [1260 0 R /XYZ 150.705 626.428 null] +/Type /Page +/Contents 1266 0 R +/Resources 1264 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1268 0 R >> % 1267 0 obj << -/D [1260 0 R /XYZ 150.705 568.7 null] +/D [1265 0 R /XYZ 98.895 753.953 null] >> -% 1259 0 obj +% 1264 0 obj << -/Font << /F8 557 0 R /F30 764 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 1270 0 obj +% 1272 0 obj << /Type /Page -/Contents 1271 0 R -/Resources 1269 0 R +/Contents 1273 0 R +/Resources 1271 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1246 0 R -/Annots [ 1268 0 R ] +/Parent 1268 0 R +/Annots [ 1269 0 R ] >> -% 1268 0 obj +% 1269 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 117.115 361.779 128.24] +/Rect [345.53 210.686 412.588 221.811] /A << /S /GoTo /D (descdata) >> >> -% 1272 0 obj -<< -/D [1270 0 R /XYZ 98.895 753.953 null] ->> -% 292 0 obj +% 1274 0 obj << -/D [1270 0 R /XYZ 99.895 720.077 null] +/D [1272 0 R /XYZ 149.705 753.953 null] >> -% 1269 0 obj +% 280 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F11 750 0 R /F27 556 0 R >> -/ProcSet [ /PDF /Text ] +/D [1272 0 R /XYZ 150.705 720.077 null] >> % 1275 0 obj << -/Type /Page -/Contents 1276 0 R -/Resources 1274 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1246 0 R -/Annots [ 1273 0 R ] +/D [1272 0 R /XYZ 320.941 451.038 null] >> -% 1273 0 obj +% 1276 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [325.383 402.324 347.855 413.172] -/A << /S /GoTo /D (subsubsection.2.3.1) >> +/D [1272 0 R /XYZ 150.705 417.777 null] >> % 1277 0 obj << -/D [1275 0 R /XYZ 149.705 753.953 null] ->> -% 1278 0 obj -<< -/D [1275 0 R /XYZ 150.705 496.913 null] ->> -% 1279 0 obj -<< -/D [1275 0 R /XYZ 150.705 475.051 null] ->> -% 1280 0 obj -<< -/D [1275 0 R /XYZ 150.705 431.215 null] +/D [1272 0 R /XYZ 150.705 417.777 null] >> -% 1274 0 obj +% 1271 0 obj << -/Font << /F27 556 0 R /F8 557 0 R /F11 750 0 R /F16 554 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F11 755 0 R /F10 771 0 R /F14 772 0 R /F7 770 0 R /F27 560 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 1284 0 obj +% 1281 0 obj << /Type /Page -/Contents 1285 0 R -/Resources 1283 0 R +/Contents 1282 0 R +/Resources 1280 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1288 0 R -/Annots [ 1281 0 R 1282 0 R ] +/Parent 1268 0 R +/Annots [ 1270 0 R 1278 0 R 1279 0 R ] >> -% 1281 0 obj +% 1270 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 574.94 361.779 586.065] -/A << /S /GoTo /D (descdata) >> +/Rect [285.522 643.143 361.576 654.268] +/A << /S /GoTo /D (vdata) >> >> -% 1282 0 obj +% 1278 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 417.531 361.779 428.656] -/A << /S /GoTo /D (descdata) >> ->> -% 1286 0 obj -<< -/D [1284 0 R /XYZ 98.895 753.953 null] +/Rect [123.806 543.516 199.86 554.641] +/A << /S /GoTo /D (vdata) >> >> -% 296 0 obj +% 1279 0 obj << -/D [1284 0 R /XYZ 99.895 720.077 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [422.94 543.516 434.896 554.641] +/A << /S /GoTo /D (table.17) >> >> -% 1287 0 obj +% 1283 0 obj << -/D [1284 0 R /XYZ 99.895 327.092 null] +/D [1281 0 R /XYZ 98.895 753.953 null] >> -% 1283 0 obj +% 1280 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F30 769 0 R /F11 755 0 R >> /ProcSet [ /PDF /Text ] >> -% 1292 0 obj +% 1285 0 obj << /Type /Page -/Contents 1293 0 R -/Resources 1291 0 R +/Contents 1286 0 R +/Resources 1284 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1288 0 R -/Annots [ 1289 0 R 1290 0 R ] ->> -% 1289 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.53 574.94 412.588 586.065] -/A << /S /GoTo /D (descdata) >> +/Parent 1268 0 R >> -% 1290 0 obj +% 1287 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.53 485.277 412.588 496.401] -/A << /S /GoTo /D (descdata) >> +/D [1285 0 R /XYZ 149.705 753.953 null] >> -% 1294 0 obj +% 284 0 obj << -/D [1292 0 R /XYZ 149.705 753.953 null] +/D [1285 0 R /XYZ 150.705 716.092 null] >> -% 300 0 obj +% 288 0 obj << -/D [1292 0 R /XYZ 150.705 720.077 null] +/D [1285 0 R /XYZ 150.705 696.263 null] >> -% 1291 0 obj +% 1284 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F27 560 0 R /F11 755 0 R /F14 772 0 R >> /ProcSet [ /PDF /Text ] >> -% 1297 0 obj +% 1290 0 obj << /Type /Page -/Contents 1298 0 R -/Resources 1296 0 R +/Contents 1291 0 R +/Resources 1289 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1288 0 R -/Annots [ 1295 0 R ] +/Parent 1268 0 R +/Annots [ 1288 0 R ] >> -% 1295 0 obj +% 1288 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 574.94 361.779 586.065] +/Rect [294.721 325.282 361.779 336.407] /A << /S /GoTo /D (descdata) >> >> -% 1299 0 obj +% 1292 0 obj << -/D [1297 0 R /XYZ 98.895 753.953 null] +/D [1290 0 R /XYZ 98.895 753.953 null] >> -% 304 0 obj +% 1293 0 obj << -/D [1297 0 R /XYZ 99.895 720.077 null] +/D [1290 0 R /XYZ 99.895 234.372 null] >> -% 1296 0 obj +% 1289 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F30 769 0 R /F11 755 0 R /F16 558 0 R >> /ProcSet [ /PDF /Text ] >> -% 1303 0 obj +% 1296 0 obj << /Type /Page -/Contents 1304 0 R -/Resources 1302 0 R +/Contents 1297 0 R +/Resources 1295 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1288 0 R -/Annots [ 1300 0 R 1301 0 R ] ->> -% 1300 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.53 453.24 423.049 464.364] -/A << /S /GoTo /D (spdata) >> +/Parent 1268 0 R +/Annots [ 1294 0 R ] >> -% 1301 0 obj +% 1294 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.53 209.896 412.588 221.021] -/A << /S /GoTo /D (descdata) >> +/Rect [408.792 215.702 431.263 226.827] +/A << /S /GoTo /D (subsubsection.2.3.1) >> >> -% 1305 0 obj +% 1298 0 obj << -/D [1303 0 R /XYZ 149.705 753.953 null] +/D [1296 0 R /XYZ 149.705 753.953 null] >> -% 308 0 obj +% 1299 0 obj << -/D [1303 0 R /XYZ 150.705 720.077 null] +/D [1296 0 R /XYZ 150.705 134.155 null] >> -% 1302 0 obj +% 1295 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F27 556 0 R /F11 750 0 R /F14 767 0 R >> +/Font << /F30 769 0 R /F8 561 0 R /F27 560 0 R /F14 772 0 R /F11 755 0 R /F10 771 0 R >> /ProcSet [ /PDF /Text ] >> -% 1307 0 obj +% 1301 0 obj << /Type /Page -/Contents 1308 0 R -/Resources 1306 0 R +/Contents 1302 0 R +/Resources 1300 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1288 0 R +/Parent 1309 0 R >> -% 1309 0 obj +% 1303 0 obj << -/D [1307 0 R /XYZ 98.895 753.953 null] +/D [1301 0 R /XYZ 98.895 753.953 null] >> -% 1310 0 obj +% 1304 0 obj << -/D [1307 0 R /XYZ 99.895 716.092 null] +/D [1301 0 R /XYZ 99.895 716.092 null] >> -% 1311 0 obj +% 1305 0 obj << -/D [1307 0 R /XYZ 99.895 664.341 null] +/D [1301 0 R /XYZ 99.895 688.251 null] >> % 1306 0 obj << -/Font << /F8 557 0 R /F30 764 0 R >> +/D [1301 0 R /XYZ 99.895 668.049 null] +>> +% 1307 0 obj +<< +/D [1301 0 R /XYZ 99.895 626.428 null] +>> +% 1308 0 obj +<< +/D [1301 0 R /XYZ 99.895 568.7 null] +>> +% 1300 0 obj +<< +/Font << /F8 561 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 1315 0 obj +% 1312 0 obj << /Type /Page -/Contents 1316 0 R -/Resources 1314 0 R +/Contents 1313 0 R +/Resources 1311 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1288 0 R -/Annots [ 1312 0 R 1313 0 R ] +/Parent 1309 0 R +/Annots [ 1310 0 R ] >> -% 1312 0 obj +% 1310 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.53 574.94 412.588 586.065] +/Rect [345.53 117.115 412.588 128.24] /A << /S /GoTo /D (descdata) >> >> -% 1313 0 obj +% 1314 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.53 405.575 423.049 416.7] -/A << /S /GoTo /D (spdata) >> +/D [1312 0 R /XYZ 149.705 753.953 null] >> -% 1317 0 obj +% 292 0 obj << -/D [1315 0 R /XYZ 149.705 753.953 null] +/D [1312 0 R /XYZ 150.705 720.077 null] >> -% 312 0 obj +% 1311 0 obj +<< +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F11 755 0 R /F27 560 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1317 0 obj << -/D [1315 0 R /XYZ 150.705 720.077 null] +/Type /Page +/Contents 1318 0 R +/Resources 1316 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1309 0 R +/Annots [ 1315 0 R ] >> -% 1318 0 obj +% 1315 0 obj << -/D [1315 0 R /XYZ 150.705 315.137 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [274.574 402.324 297.045 413.172] +/A << /S /GoTo /D (subsubsection.2.3.1) >> >> % 1319 0 obj << -/D [1315 0 R /XYZ 150.705 293.274 null] +/D [1317 0 R /XYZ 98.895 753.953 null] >> % 1320 0 obj << -/D [1315 0 R /XYZ 150.705 273.349 null] +/D [1317 0 R /XYZ 99.895 496.913 null] >> -% 1314 0 obj +% 1321 0 obj +<< +/D [1317 0 R /XYZ 99.895 475.051 null] +>> +% 1322 0 obj +<< +/D [1317 0 R /XYZ 99.895 431.215 null] +>> +% 1316 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R /F11 750 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F11 755 0 R /F16 558 0 R >> /ProcSet [ /PDF /Text ] >> -% 1325 0 obj +% 1326 0 obj << /Type /Page -/Contents 1326 0 R -/Resources 1324 0 R +/Contents 1327 0 R +/Resources 1325 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1328 0 R -/Annots [ 1321 0 R 1322 0 R ] +/Parent 1309 0 R +/Annots [ 1323 0 R 1324 0 R ] >> -% 1321 0 obj +% 1323 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [261.152 288.004 328.21 299.129] +/Rect [345.53 574.94 412.588 586.065] /A << /S /GoTo /D (descdata) >> >> -% 1322 0 obj +% 1324 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 117.115 372.239 128.24] -/A << /S /GoTo /D (spdata) >> +/Rect [345.53 417.531 412.588 428.656] +/A << /S /GoTo /D (descdata) >> >> -% 1327 0 obj +% 1328 0 obj << -/D [1325 0 R /XYZ 98.895 753.953 null] +/D [1326 0 R /XYZ 149.705 753.953 null] >> -% 316 0 obj +% 296 0 obj << -/D [1325 0 R /XYZ 99.895 720.077 null] +/D [1326 0 R /XYZ 150.705 720.077 null] >> -% 1324 0 obj +% 1329 0 obj +<< +/D [1326 0 R /XYZ 150.705 327.092 null] +>> +% 1325 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R /F11 750 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 1330 0 obj +% 1333 0 obj << /Type /Page -/Contents 1331 0 R -/Resources 1329 0 R +/Contents 1334 0 R +/Resources 1332 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1328 0 R -/Annots [ 1323 0 R ] +/Parent 1309 0 R +/Annots [ 1330 0 R 1331 0 R ] >> -% 1323 0 obj +% 1330 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [311.962 655.098 379.019 666.223] +/Rect [294.721 574.94 361.779 586.065] /A << /S /GoTo /D (descdata) >> >> -% 1332 0 obj +% 1331 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [294.721 485.277 361.779 496.401] +/A << /S /GoTo /D (descdata) >> +>> +% 1335 0 obj << -/D [1330 0 R /XYZ 149.705 753.953 null] +/D [1333 0 R /XYZ 98.895 753.953 null] >> -% 1333 0 obj +% 300 0 obj << -/D [1330 0 R /XYZ 150.705 552.704 null] +/D [1333 0 R /XYZ 99.895 720.077 null] >> -% 1334 0 obj +% 1332 0 obj << -/D [1330 0 R /XYZ 150.705 520.824 null] +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R >> +/ProcSet [ /PDF /Text ] >> -% 1335 0 obj +% 1338 0 obj << -/D [1330 0 R /XYZ 150.705 487.006 null] +/Type /Page +/Contents 1339 0 R +/Resources 1337 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1309 0 R +/Annots [ 1336 0 R ] >> % 1336 0 obj << -/D [1330 0 R /XYZ 150.705 419.26 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [345.53 574.94 412.588 586.065] +/A << /S /GoTo /D (descdata) >> >> -% 1337 0 obj +% 1340 0 obj << -/D [1330 0 R /XYZ 150.705 363.469 null] +/D [1338 0 R /XYZ 149.705 753.953 null] >> -% 1338 0 obj +% 304 0 obj << -/D [1330 0 R /XYZ 150.705 319.634 null] +/D [1338 0 R /XYZ 150.705 720.077 null] >> -% 1339 0 obj +% 1337 0 obj << -/D [1330 0 R /XYZ 150.705 287.753 null] +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R >> +/ProcSet [ /PDF /Text ] >> endstream endobj -1347 0 obj +1345 0 obj << -/Length 6641 +/Length 5927 >> stream 0 g 0 G @@ -15649,121 +15478,96 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(spasb)-375(|)-375(Sparse)-375(matrix)-375(assem)31(bly)-375(routine)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(cdbldext)-282(|)-283(Build)-282(an)-282(ex)-1(tended)-282(comm)31(unication)-282(descrip-)]TJ -25.091 -13.948 Td [(tor)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_spasb\050a,)-525(desc_a,)-525(info,)-525(afmt,)-525(upd,)-525(dupl,)-525(mold\051)]TJ +/F30 9.9626 Tf 0 -19.114 Td [(call)-525(psb_cdbldext\050a,desc_a,nl,desc_out,)-525(info,)-525(extype\051)]TJ/F8 9.9626 Tf 14.944 -23.476 Td [(This)-298(subroutine)-297(builds)-298(an)-297(extended)-298(comm)28(unication)-298(descriptor,)-305(based)-297(on)-298(the)]TJ -14.944 -11.955 Td [(input)-389(descriptor)]TJ/F30 9.9626 Tf 74.288 0 Td [(desc_a)]TJ/F8 9.9626 Tf 35.261 0 Td [(and)-389(on)-390(the)-389(stencil)-389(s)-1(p)-27(eci\014ed)-390(through)-389(the)-389(input)-390(sparse)]TJ -109.549 -11.956 Td [(matrix)]TJ/F30 9.9626 Tf 32.407 0 Td [(a)]TJ/F8 9.9626 Tf 5.23 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -21.202 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf -37.637 -21.094 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.639 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -33.797 -21.483 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.638 Td [(desc)]TJ + 0 -21.484 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.551 0 Td [(A)-333(sparse)-334(matrix)-333(Scop)-28(e:)]TJ/F27 9.9626 Tf 101.176 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -109.893 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(t)27(yp)-27(e.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -21.484 Td [(desc)]TJ ET q -1 0 0 1 121.81 627.46 cm +1 0 0 1 121.81 504.47 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 125.247 627.261 Td [(a)]TJ +/F27 9.9626 Tf 125.247 504.27 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.551 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 312.036 579.639 cm +1 0 0 1 312.036 456.649 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 315.174 579.44 Td [(desc)]TJ +/F30 9.9626 Tf 315.174 456.45 Td [(Tspmat)]TJ ET q -1 0 0 1 336.723 579.639 cm +1 0 0 1 347.183 456.649 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 339.861 579.44 Td [(type)]TJ +/F30 9.9626 Tf 350.322 456.45 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -260.887 -19.639 Td [(afm)32(t)]TJ -0 g 0 G -/F8 9.9626 Tf 27.737 0 Td [(the)-333(storage)-334(format)-333(for)-333(the)-334(sparse)-333(matrix.)]TJ -2.83 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(arra)28(y)-333(of)-334(c)28(haracters.)-444(Defalt:)-445('CSR'.)]TJ +/F27 9.9626 Tf -271.348 -21.484 Td [(nl)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.639 Td [(up)-32(d)]TJ +/F8 9.9626 Tf 14.529 0 Td [(the)-333(n)27(u)1(m)27(b)-27(e)-1(r)-333(of)-333(additional)-333(la)28(y)27(ers)-333(desired.)]TJ 10.378 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -57.707 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue)]TJ/F11 9.9626 Tf 130.428 0 Td [(nl)]TJ/F14 9.9626 Tf 11.916 0 Td [(\025)]TJ/F8 9.9626 Tf 10.516 0 Td [(0.)]TJ 0 g 0 G -/F8 9.9626 Tf 24.395 0 Td [(Pro)28(vide)-333(for)-334(up)-27(dates)-334(to)-333(the)-333(matrix)-334(co)-28(e\016cien)28(ts.)]TJ 0.512 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(in)28(teger,)-333(p)-28(ossible)-333(v)55(alues:)]TJ/F30 9.9626 Tf 164.633 0 Td [(psb_upd_srch_)]TJ/F8 9.9626 Tf 67.994 0 Td [(,)]TJ/F30 9.9626 Tf 6.089 0 Td [(psb_upd_perm_)]TJ +/F27 9.9626 Tf -177.767 -21.483 Td [(ext)32(yp)-32(e)]TJ 0 g 0 G -/F27 9.9626 Tf -263.623 -19.639 Td [(dupl)]TJ +/F8 9.9626 Tf 38.398 0 Td [(the)-333(kind)-334(of)-333(estension)-333(required.)]TJ -13.491 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -57.707 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 44.396 0 Td [(.)]TJ -69.579 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-419(as:)-616(an)-420(in)28(teger)-419(v)55(alue)]TJ/F30 9.9626 Tf 135.566 0 Td [(psb_ovt_xhal_)]TJ/F8 9.9626 Tf 67.994 0 Td [(,)]TJ/F30 9.9626 Tf 7.159 0 Td [(psb_ovt_asov_)]TJ/F8 9.9626 Tf 67.995 0 Td [(,)-441(default:)]TJ/F30 9.9626 Tf -278.714 -11.955 Td [(psb_ovt_xhal_)]TJ 0 g 0 G -/F8 9.9626 Tf 27.259 0 Td [(Ho)28(w)-334(to)-333(handle)-333(duplicate)-333(co)-28(e\016cien)27(ts.)]TJ -2.352 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-308(as:)-432(in)27(teger,)-313(p)-28(ossible)-309(v)56(alues:)]TJ/F30 9.9626 Tf 163.696 0 Td [(psb_dupl_ovwrt_)]TJ/F8 9.9626 Tf 78.456 0 Td [(,)]TJ/F30 9.9626 Tf 5.891 0 Td [(psb_dupl_add_)]TJ/F8 9.9626 Tf 67.994 0 Td [(,)]TJ/F30 9.9626 Tf -316.037 -11.955 Td [(psb_dupl_err_)]TJ/F8 9.9626 Tf 67.994 0 Td [(.)]TJ +/F27 9.9626 Tf -24.907 -23.476 Td [(On)-383(Return)]TJ 0 g 0 G -/F27 9.9626 Tf -92.901 -19.639 Td [(mold)]TJ 0 g 0 G -/F8 9.9626 Tf 29.805 0 Td [(The)-333(desired)-334(dynamic)-333(t)28(yp)-28(e)-333(for)-334(the)-333(in)28(ternal)-333(matrix)-334(storage.)]TJ -4.898 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(a)-333(class)-334(deriv)28(ed)-333(from)]TJ/F30 9.9626 Tf 203.349 0 Td [(psb)]TJ -ET -q -1 0 0 1 344.47 297.847 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 347.608 297.647 Td [(T)]TJ -ET -q -1 0 0 1 353.466 297.847 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 356.604 297.647 Td [(base)]TJ -ET -q -1 0 0 1 378.153 297.847 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 381.291 297.647 Td [(sparse)]TJ + 0 -21.484 Td [(desc)]TJ ET q -1 0 0 1 413.301 297.847 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 121.81 261.126 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F30 9.9626 Tf 416.439 297.647 Td [(mat)]TJ/F8 9.9626 Tf 15.691 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -332.235 -21.201 Td [(On)-383(Return)]TJ -0 g 0 G -0 g 0 G - 0 -19.639 Td [(a)]TJ +/F27 9.9626 Tf 125.247 260.927 Td [(out)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(matrix)-334(to)-333(b)-28(e)-333(assem)28(bled.)]TJ 14.356 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.951 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf -25.183 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 21.53 0 Td [(the)-333(extended)-334(comm)28(unication)-333(descriptor.)]TJ -21.975 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 312.036 209.186 cm +1 0 0 1 312.036 213.305 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 315.174 208.986 Td [(Tspmat)]TJ +/F30 9.9626 Tf 315.174 213.106 Td [(desc)]TJ ET q -1 0 0 1 347.183 209.186 cm +1 0 0 1 336.723 213.305 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 350.322 208.986 Td [(type)]TJ +/F30 9.9626 Tf 339.861 213.106 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -271.348 -19.638 Td [(info)]TJ +/F27 9.9626 Tf -260.887 -21.484 Td [(info)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ/F16 11.9552 Tf -24.907 -21.201 Td [(Notes)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ/F16 11.9552 Tf -24.907 -23.476 Td [(Notes)]TJ 0 g 0 G -/F8 9.9626 Tf 166.875 -29.888 Td [(75)]TJ +/F8 9.9626 Tf 166.875 -29.888 Td [(73)]TJ 0 g 0 G ET @@ -15771,7 +15575,7 @@ endstream endobj 1351 0 obj << -/Length 2255 +/Length 1587 >> stream 0 g 0 G @@ -15780,37 +15584,21 @@ stream BT /F8 9.9626 Tf 162.881 706.129 Td [(1.)]TJ 0 g 0 G - [-500(On)-406(en)28(try)-406(to)-406(this)-406(routine)-406(the)-406(descriptor)-406(m)28(ust)-406(b)-28(e)-406(in)-406(the)-406(assem)27(b)1(led)-406(s)-1(tate,)]TJ 12.73 -11.955 Td [(i.e.)]TJ/F30 9.9626 Tf 17.158 0 Td [(psb_cdasb)]TJ/F8 9.9626 Tf 50.394 0 Td [(m)28(ust)-334(already)-333(ha)28(v)28(e)-334(b)-27(een)-334(called.)]TJ -0 g 0 G - -80.282 -19.926 Td [(2.)]TJ -0 g 0 G - [-500(The)-333(sparse)-334(matrix)-333(ma)28(y)-334(b)-27(e)-334(in)-333(either)-333(the)-334(build)-333(or)-333(up)-28(date)-333(state;)]TJ -0 g 0 G - 0 -19.925 Td [(3.)]TJ -0 g 0 G - [-500(Duplicate)-250(en)28(tries)-250(are)-249(dete)-1(cted)-249(and)-250(handled)-250(in)-249(b)-28(oth)-250(build)-249(and)-250(up)-28(date)-249(state,)]TJ 12.73 -11.955 Td [(with)-282(the)-283(exception)-282(of)-282(the)-283(error)-282(action)-282(that)-283(is)-282(only)-282(tak)28(en)-283(in)-282(the)-282(build)-283(state,)]TJ 0 -11.955 Td [(i.e.)-444(on)-334(the)-333(\014rst)-333(asse)-1(m)28(bly;)]TJ + [-500(Sp)-28(ecifying)]TJ/F30 9.9626 Tf 60.092 0 Td [(psb_ovt_xhal_)]TJ/F8 9.9626 Tf 70.801 0 Td [(for)-282(the)]TJ/F30 9.9626 Tf 31.376 0 Td [(extype)]TJ/F8 9.9626 Tf 34.189 0 Td [(argumen)28(t)-282(the)-282(u)1(s)-1(er)-281(will)-282(obtain)-281(a)]TJ -183.728 -11.955 Td [(descriptor)-258(for)-257(a)-258(domain)-257(partition)-258(in)-257(whic)28(h)-258(the)-257(additional)-258(la)28(y)28(ers)-258(are)-257(fetc)27(hed)]TJ 0 -11.955 Td [(as)-415(part)-415(of)-415(an)-415(\050extended\051)-415(halo;)-456(ho)28(w)27(ev)28(er)-415(the)-415(index-to-pro)-28(cess)-415(mapping)-415(is)]TJ 0 -11.956 Td [(iden)28(tical)-334(to)-333(that)-333(of)-333(the)-334(base)-333(descriptor;)]TJ 0 g 0 G - -12.73 -19.925 Td [(4.)]TJ -0 g 0 G - [-500(If)-224(the)-224(up)-28(date)-223(c)27(hoice)-224(is)]TJ/F30 9.9626 Tf 107.516 0 Td [(psb_upd_perm_)]TJ/F8 9.9626 Tf 67.994 0 Td [(,)-246(then)-224(subsequen)28(t)-224(calls)-224(to)]TJ/F30 9.9626 Tf 108.952 0 Td [(psb_spins)]TJ/F8 9.9626 Tf -271.732 -11.956 Td [(to)-246(up)-28(date)-246(the)-246(matrix)-246(m)28(ust)-246(b)-28(e)-246(arranged)-246(in)-246(suc)28(h)-246(a)-246(w)28(a)27(y)-246(as)-246(to)-246(pro)-27(duce)-246(exactly)]TJ 0 -11.955 Td [(the)-228(same)-229(sequence)-228(of)-228(co)-28(e\016cien)27(t)-228(v)56(alues)-229(as)-228(encoun)28(tered)-228(at)-229(the)-228(\014rst)-228(assem)27(b)1(ly;)]TJ -0 g 0 G - -12.73 -19.925 Td [(5.)]TJ -0 g 0 G - [-500(The)-333(output)-334(storage)-333(format)-333(need)-334(not)-333(b)-28(e)-333(the)-333(same)-334(on)-333(all)-333(pro)-28(cesses;)]TJ -0 g 0 G - 0 -19.925 Td [(6.)]TJ + -12.73 -19.925 Td [(2.)]TJ 0 g 0 G - [-500(On)-370(exit)-370(from)-370(this)-370(routine)-370(the)-370(matrix)-370(is)-370(in)-370(the)-370(assem)28(bled)-370(state,)-380(an)1(d)-370(th)27(us)]TJ 12.73 -11.956 Td [(is)-333(suitable)-334(for)-333(the)-333(computational)-334(rou)1(tines)-1(.)]TJ + [-500(Sp)-28(ecifying)]TJ/F30 9.9626 Tf 60.957 0 Td [(psb_ovt_asov_)]TJ/F8 9.9626 Tf 71.666 0 Td [(for)-368(the)]TJ/F30 9.9626 Tf 33.108 0 Td [(extype)]TJ/F8 9.9626 Tf 35.053 0 Td [(argumen)28(t)-369(the)-368(user)-369(will)-368(obtain)]TJ -188.054 -11.955 Td [(a)-458(descriptor)-459(with)-458(an)-458(o)28(v)27(erlapp)-27(ed)-459(decomp)-28(osition:)-694(the)-458(additional)-458(la)27(y)28(er)-458(is)]TJ 0 -11.955 Td [(aggregated)-413(to)-413(the)-414(l)1(o)-28(cal)-413(sub)-28(domain)-413(\050and)-413(th)27(u)1(s)-414(is)-413(an)-413(o)28(v)28(erlap\051,)-433(and)-413(a)-414(new)]TJ 0 -11.955 Td [(halo)-333(extending)-334(b)-27(ey)27(ond)-333(the)-333(last)-334(ad)1(ditional)-334(la)28(y)28(er)-333(is)-334(formed.)]TJ 0 g 0 G - 141.968 -444.333 Td [(76)]TJ + 141.968 -524.035 Td [(74)]TJ 0 g 0 G ET endstream endobj -1363 0 obj +1359 0 obj << -/Length 3086 +/Length 4887 >> stream 0 g 0 G @@ -15823,10 +15611,10 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(spfree)-375(|)-375(F)94(rees)-375(a)-375(sparse)-375(matrix)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(spall)-375(|)-375(Allo)-31(cates)-375(a)-375(sparse)-375(matrix)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_spfree\050a,)-525(desc_a,)-525(info\051)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_spall\050a,)-525(desc_a,)-525(info,)-525(nnz\051)]TJ 0 g 0 G /F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G @@ -15835,9 +15623,16 @@ BT /F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(a)]TJ + 0 -19.925 Td [(desc)]TJ +ET +q +1 0 0 1 121.81 626.17 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 125.247 625.971 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(matrix)-334(to)-333(b)-28(e)-333(freed.)]TJ 14.356 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.951 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf -25.183 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.551 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET @@ -15846,54 +15641,63 @@ q []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 315.174 578.15 Td [(Tspmat)]TJ +/F30 9.9626 Tf 315.174 578.15 Td [(desc)]TJ ET q -1 0 0 1 347.183 578.35 cm +1 0 0 1 336.723 578.35 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 350.322 578.15 Td [(type)]TJ +/F30 9.9626 Tf 339.861 578.15 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -271.348 -19.925 Td [(desc)]TJ -ET -q -1 0 0 1 121.81 558.424 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 125.247 558.225 Td [(a)]TJ +/F27 9.9626 Tf -260.887 -19.925 Td [(nnz)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 22.804 0 Td [(An)-309(estimate)-309(of)-308(the)-309(n)28(um)28(b)-28(er)-309(of)-309(nonzero)-27(es)-309(in)-309(the)-309(lo)-28(cal)-308(part)-309(of)-309(the)-308(as)-1(sem)28(bled)]TJ 2.103 -11.955 Td [(matrix.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -21.918 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.551 0 Td [(the)-333(matrix)-334(to)-333(b)-28(e)-333(allo)-28(cated.)]TJ 14.356 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.951 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf -25.183 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 312.036 510.604 cm +1 0 0 1 312.036 408.985 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 315.174 510.405 Td [(desc)]TJ +/F30 9.9626 Tf 315.174 408.786 Td [(Tspmat)]TJ ET q -1 0 0 1 336.723 510.604 cm +1 0 0 1 347.183 408.985 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 339.861 510.405 Td [(type)]TJ +/F30 9.9626 Tf 350.322 408.786 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -260.887 -21.918 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf -271.348 -19.926 Td [(info)]TJ +0 g 0 G +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ 0 g 0 G +/F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ 0 g 0 G - 0 -19.926 Td [(info)]TJ + [-500(On)-333(exit)-334(from)-333(this)-333(routine)-333(the)-334(sparse)-333(matrix)-333(is)-334(in)-333(the)-333(build)-334(state.)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ + 0 -19.926 Td [(2.)]TJ +0 g 0 G + [-500(The)-333(descriptor)-334(ma)28(y)-333(b)-28(e)-333(in)-334(either)-333(the)-333(build)-333(or)-334(assem)28(bled)-333(state.)]TJ +0 g 0 G + 0 -19.925 Td [(3.)]TJ 0 g 0 G - 141.968 -330.303 Td [(77)]TJ + [-500(Pro)28(viding)-307(a)-308(go)-27(o)-28(d)-307(es)-1(timate)-307(for)-307(the)-307(n)27(um)28(b)-28(er)-307(of)-307(nonzero)-28(es)]TJ/F11 9.9626 Tf 254.288 0 Td [(nnz)]TJ/F8 9.9626 Tf 20.092 0 Td [(in)-307(the)-308(assem-)]TJ -261.65 -11.955 Td [(bled)-401(m)-1(atr)1(ix)-402(ma)28(y)-402(substan)28(tially)-401(impro)27(v)28(e)-401(p)-28(erformance)-402(in)-401(the)-402(matrix)-401(build)]TJ 0 -11.955 Td [(phase,)-458(as)-433(it)-432(will)-433(reduce)-433(or)-433(eliminate)-433(the)-433(need)-432(for)-433(\050p)-28(oten)28(tially)-433(m)28(ultiple\051)]TJ 0 -11.956 Td [(data)-333(reallo)-28(cations.)]TJ +0 g 0 G + 141.968 -133.042 Td [(75)]TJ 0 g 0 G ET @@ -15901,7 +15705,7 @@ endstream endobj 1369 0 obj << -/Length 3976 +/Length 6453 >> stream 0 g 0 G @@ -15914,199 +15718,185 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(sprn)-391(|)-391(Reinit)-391(sparse)-391(matrix)-391(structure)-391(for)-391(psblas)-391(rou-)]TJ -25.091 -13.948 Td [(tines.)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(spins)-306(|)-307(Insert)-306(a)-306(cloud)-306(of)-306(elemen)31(ts)-307(in)32(to)-306(a)-307(sparse)-306(matrix)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf 0 -18.389 Td [(call)-525(psb_sprn\050a,)-525(decsc_a,)-525(info,)-525(clear\051)]TJ +/F30 9.9626 Tf -25.091 -18.647 Td [(call)-525(psb_spins\050nz,)-525(ia,)-525(ja,)-525(val,)-525(a,)-525(desc_a,)-525(info)-525([,local]\051)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf 0 -22.334 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -33.797 -20.479 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.926 Td [(a)]TJ + 0 -20.479 Td [(nz)]TJ +0 g 0 G +/F8 9.9626 Tf 16.438 0 Td [(the)-333(n)27(u)1(m)27(b)-27(e)-1(r)-333(of)-333(elemen)28(ts)-334(to)-333(b)-28(e)-333(inserted.)]TJ 8.469 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.95 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(sc)-1(alar)1(.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.906 -20.479 Td [(ia)]TJ +0 g 0 G +/F8 9.9626 Tf 13.733 0 Td [(the)-333(ro)27(w)-333(indices)-333(of)-334(th)1(e)-334(elemen)28(ts)-334(to)-333(b)-28(e)-333(inserted.)]TJ 11.173 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)-333(of)-333(size)]TJ/F11 9.9626 Tf 160.98 0 Td [(nz)]TJ/F8 9.9626 Tf 11.052 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -196.938 -20.479 Td [(ja)]TJ +0 g 0 G +/F8 9.9626 Tf 14.051 0 Td [(the)-333(column)-334(indices)-333(of)-333(the)-334(elemen)28(ts)-333(to)-334(b)-27(e)-334(inserted.)]TJ 10.855 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)-333(of)-333(size)]TJ/F11 9.9626 Tf 160.98 0 Td [(nz)]TJ/F8 9.9626 Tf 11.051 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -196.937 -20.479 Td [(v)64(al)]TJ +0 g 0 G +/F8 9.9626 Tf 19.143 0 Td [(the)-333(elemen)27(ts)-333(to)-333(b)-28(e)-333(inse)-1(r)1(te)-1(d)1(.)]TJ 5.763 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-375(as:)-528(an)-375(arra)28(y)-375(of)-375(size)]TJ/F11 9.9626 Tf 130.933 0 Td [(nz)]TJ/F8 9.9626 Tf 11.051 0 Td [(.)-570(Must)-375(b)-28(e)-375(of)-375(the)-375(same)-375(t)28(yp)-28(e)-375(and)-375(kind)-375(of)]TJ -141.984 -11.955 Td [(the)-333(co)-28(e\016cien)27(ts)-333(of)-333(the)-334(spar)1(s)-1(e)-333(matrix)]TJ/F11 9.9626 Tf 158.517 0 Td [(a)]TJ/F8 9.9626 Tf 5.266 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -188.689 -20.479 Td [(desc)]TJ +ET +q +1 0 0 1 172.619 339.234 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 176.057 339.035 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(matrix)-334(to)-333(b)-28(e)-333(reinitialized.)]TJ 14.356 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.95 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.95 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf -25.183 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-334(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.55 0 Td [(The)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.51 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(v)56(ariable)-334(of)-333(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.914 0 Td [(psb)]TJ +/F30 9.9626 Tf 137.347 0 Td [(psb)]TJ ET q -1 0 0 1 362.845 564.402 cm +1 0 0 1 329.276 291.413 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 365.983 564.203 Td [(Tspmat)]TJ +/F30 9.9626 Tf 332.415 291.214 Td [(desc)]TJ ET q -1 0 0 1 397.993 564.402 cm +1 0 0 1 353.964 291.413 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 401.131 564.203 Td [(type)]TJ +/F30 9.9626 Tf 357.102 291.214 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -271.347 -19.925 Td [(desc)]TJ -ET -q -1 0 0 1 172.619 544.477 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 176.057 544.278 Td [(a)]TJ +/F27 9.9626 Tf -227.318 -32.434 Td [(lo)-32(cal)]TJ 0 g 0 G -/F8 9.9626 Tf 10.55 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 28.054 0 Td [(Whether)-465(the)-464(en)27(tries)-464(in)-465(the)-465(ind)1(ic)-1(es)-464(v)28(e)-1(ctors)]TJ/F30 9.9626 Tf 194.825 0 Td [(ia)]TJ/F8 9.9626 Tf 10.461 0 Td [(,)]TJ/F30 9.9626 Tf 7.724 0 Td [(ja)]TJ/F8 9.9626 Tf 15.09 0 Td [(are)-465(already)-464(in)-465(lo)-28(cal)]TJ -231.248 -11.956 Td [(n)28(um)28(b)-28(ering.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.761 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(logical)-333(v)55(alue;)-333(default:)]TJ/F30 9.9626 Tf 163.056 0 Td [(.false.)]TJ/F8 9.9626 Tf 36.612 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -224.574 -22.333 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G + 0 -20.48 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.55 0 Td [(the)-333(matrix)-334(in)28(to)-333(whic)28(h)-334(elemen)28(ts)-333(will)-334(b)-27(e)-334(inserted.)]TJ 14.356 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.951 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf -25.184 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 362.845 496.656 cm +1 0 0 1 362.845 120.525 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 365.983 496.457 Td [(desc)]TJ +/F30 9.9626 Tf 365.983 120.326 Td [(Tspmat)]TJ ET q -1 0 0 1 387.532 496.656 cm +1 0 0 1 397.993 120.525 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 390.67 496.457 Td [(type)]TJ +/F30 9.9626 Tf 401.131 120.326 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -260.887 -19.925 Td [(clear)]TJ -0 g 0 G -/F8 9.9626 Tf 28.795 0 Td [(Cho)-28(ose)-333(whether)-333(to)-334(zero)-333(out)-333(m)-1(atr)1(ix)-334(co)-28(e\016cien)28(ts)]TJ -3.888 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.95 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Default:)-444(true.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -21.918 Td [(On)-383(Return)]TJ -0 g 0 G -0 g 0 G - 0 -19.925 Td [(info)]TJ -0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.034 -11.955 Td [(An)-333(in)28(teger)-334(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detected.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ -0 g 0 G -/F8 9.9626 Tf 12.176 -19.925 Td [(1.)]TJ -0 g 0 G - [-500(On)-333(exit)-334(from)-333(this)-333(routine)-334(t)1(he)-334(sparse)-333(matrix)-334(is)-333(in)-333(the)-333(up)-28(date)-334(state.)]TJ +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G - 154.698 -206.766 Td [(78)]TJ + -104.473 -29.888 Td [(76)]TJ 0 g 0 G ET endstream endobj -1376 0 obj +1373 0 obj << -/Length 5107 +/Length 6087 >> stream 0 g 0 G 0 g 0 G +0 g 0 G BT -/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ +/F27 9.9626 Tf 99.895 706.129 Td [(desc)]TJ ET q -1 0 0 1 120.951 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +1 0 0 1 121.81 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(geall)-375(|)-375(Allo)-31(cates)-375(a)-375(dense)-375(matrix)]TJ +/F27 9.9626 Tf 125.247 706.129 Td [(a)]TJ 0 g 0 G +/F8 9.9626 Tf 10.551 0 Td [(The)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(v)56(ariable)-334(of)-333(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 137.346 0 Td [(psb)]TJ +ET +q +1 0 0 1 278.467 658.507 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 281.605 658.308 Td [(desc)]TJ +ET +q +1 0 0 1 303.154 658.507 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 306.292 658.308 Td [(type)]TJ 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_geall\050x,)-525(desc_a,)-525(info,)-525(n,)-525(lb\051)]TJ +/F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf -227.319 -31.88 Td [(info)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ +/F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ 0 g 0 G + [-500(On)-487(en)28(try)-487(to)-488(this)-487(routine)-487(the)-487(descriptor)-487(ma)28(y)-488(b)-27(e)-488(in)-487(either)-487(the)-487(build)-487(or)]TJ 12.73 -11.955 Td [(assem)28(bled)-334(state.)]TJ 0 g 0 G - 0 -19.925 Td [(desc)]TJ -ET -q -1 0 0 1 121.81 626.17 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 125.247 625.971 Td [(a)]TJ + -12.73 -19.925 Td [(2.)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(The)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(v)56(ariable)-334(of)-333(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 137.346 0 Td [(psb)]TJ -ET -q -1 0 0 1 278.467 578.35 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 281.605 578.15 Td [(desc)]TJ -ET -q -1 0 0 1 303.154 578.35 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 306.292 578.15 Td [(type)]TJ + [-500(On)-363(en)28(try)-362(to)-363(this)-363(routine)-362(the)-363(sparse)-363(matrix)-363(ma)28(y)-363(b)-27(e)-363(in)-363(either)-362(the)-363(build)-363(or)]TJ 12.73 -11.956 Td [(up)-28(date)-333(state.)]TJ 0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(.)]TJ + -12.73 -19.925 Td [(3.)]TJ 0 g 0 G -/F27 9.9626 Tf -227.319 -31.88 Td [(n)]TJ + [-500(If)-230(the)-231(descriptor)-230(is)-231(in)-230(the)-231(build)-230(state,)-251(then)-231(the)-230(sparse)-231(matrix)-230(m)28(ust)-231(also)-230(b)-28(e)-231(in)]TJ 12.73 -11.955 Td [(the)-327(build)-327(state;)-329(the)-328(action)-327(of)-327(the)-327(routine)-327(is)-327(to)-327(\050implicitly\051)-327(call)]TJ/F30 9.9626 Tf 271.731 0 Td [(psb_cdins)]TJ/F8 9.9626 Tf -271.731 -11.955 Td [(to)-419(add)-419(en)28(tries)-419(to)-419(th)1(e)-419(sparsit)27(y)-418(pattern;)-462(eac)28(h)-419(sparse)-419(matrix)-419(en)28(try)-419(implic-)]TJ 0 -11.955 Td [(itly)-359(de\014nes)-360(a)-360(grap)1(h)-360(edge,)-366(that)-360(is)-359(passed)-360(to)-359(the)-360(descriptor)-359(routine)-360(for)-359(the)]TJ 0 -11.956 Td [(appropriate)-333(pro)-28(cessing;)]TJ 0 g 0 G -/F8 9.9626 Tf 11.347 0 Td [(The)-333(n)27(u)1(m)27(b)-27(e)-1(r)-333(of)-333(columns)-333(of)-334(the)-333(dense)-333(m)-1(atr)1(ix)-334(to)-333(b)-28(e)-333(allo)-28(cated.)]TJ 13.56 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-343(as:)-463(In)27(teger)-343(scalar,)-345(default)-343(1.)-473(It)-343(is)-343(not)-343(a)-343(v)56(alid)-343(argumen)28(t)-343(if)]TJ/F11 9.9626 Tf 294.599 0 Td [(x)]TJ/F8 9.9626 Tf 9.11 0 Td [(is)-343(a)]TJ -303.709 -11.955 Td [(rank-1)-333(arra)28(y)83(.)]TJ + -12.73 -19.925 Td [(4.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.925 Td [(lb)]TJ + [-500(The)-540(co)-28(e\016cien)28(ts)-541(to)-540(b)-28(e)-540(inserted)-540(are)-541(represen)28(ted)-540(b)28(y)-541(the)-540(ordered)-540(triples)]TJ/F11 9.9626 Tf 12.73 -11.955 Td [(ia)]TJ/F8 9.9626 Tf 8.698 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)]TJ/F11 9.9626 Tf 3.874 0 Td [(;)-167(j)-57(a)]TJ/F8 9.9626 Tf 14.367 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)]TJ/F11 9.9626 Tf 3.874 0 Td [(;)-167(v)-36(al)]TJ/F8 9.9626 Tf 18.049 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051,)-503(for)]TJ/F11 9.9626 Tf 28.256 0 Td [(i)]TJ/F8 9.9626 Tf 8.455 0 Td [(=)-504(1)]TJ/F11 9.9626 Tf 17.753 0 Td [(;)-167(:)-166(:)-167(:)-167(;)-166(nz)]TJ/F8 9.9626 Tf 33.19 0 Td [(;)-537(these)-469(triples)-469(s)-1(h)1(ould)-470(b)-27(elong)-469(to)-470(the)]TJ -158.437 -11.955 Td [(curren)28(t)-351(pro)-28(cess,)-356(i.e.)]TJ/F11 9.9626 Tf 90.238 0 Td [(ia)]TJ/F8 9.9626 Tf 8.698 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)-351(should)-351(b)-28(e)-351(one)-351(of)-352(the)-351(lo)-28(cal)-351(indices,)-355(but)-352(ar)1(e)-352(oth-)]TJ -106.243 -11.955 Td [(erwise)-333(arbitrary;)]TJ 0 g 0 G -/F8 9.9626 Tf 14.529 0 Td [(The)-489(lo)28(w)27(er)-489(b)-27(ound)-489(for)-489(the)-490(column)-489(index)-489(range)-489(of)-489(the)-489(dense)-489(matrix)-489(to)-489(b)-28(e)]TJ 10.378 -11.955 Td [(allo)-28(cated.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-343(as:)-463(In)27(teger)-343(scalar,)-345(default)-343(1.)-473(It)-343(is)-343(not)-343(a)-343(v)56(alid)-343(argumen)28(t)-343(if)]TJ/F11 9.9626 Tf 294.599 0 Td [(x)]TJ/F8 9.9626 Tf 9.11 0 Td [(is)-343(a)]TJ -303.709 -11.955 Td [(rank-1)-333(arra)28(y)83(.)]TJ + -12.73 -19.926 Td [(5.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -21.918 Td [(On)-383(Return)]TJ + [-500(There)-386(is)-385(no)-386(requiremen)28(t)-386(that)-386(a)-385(giv)28(en)-386(ro)28(w)-386(m)28(ust)-386(b)-28(e)-385(passe)-1(d)-385(in)-386(its)-385(e)-1(n)28(tiret)28(y)]TJ 12.73 -11.955 Td [(to)-355(a)-354(single)-355(call)-354(to)-355(this)-354(routine:)-487(the)-355(buildup)-354(of)-355(a)-354(ro)28(w)-355(ma)28(y)-355(b)-28(e)-354(split)-355(in)28(to)-354(as)]TJ 0 -11.955 Td [(man)28(y)-334(calls)-333(as)-333(desired;)]TJ 0 g 0 G + -12.73 -19.925 Td [(6.)]TJ 0 g 0 G - 0 -19.925 Td [(x)]TJ + [-500(Co)-28(e\016cien)28(ts)-409(from)-410(di\013eren)28(t)-409(ro)28(ws)-410(ma)28(y)-409(also)-409(b)-28(e)-409(mixed)-410(up)-409(freely)-409(in)-409(a)-410(single)]TJ 12.73 -11.956 Td [(call,)-333(according)-334(to)-333(the)-333(application)-333(nee)-1(d)1(s)-1(;)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(The)-333(dense)-334(matrix)-333(to)-333(b)-28(e)-334(all)1(o)-28(cated.)]TJ 13.879 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-303(as:)-430(a)-304(rank)-303(one)-304(or)-304(t)28(w)28(o)-304(arra)28(y)-304(with)-303(the)-304(ALLOCA)83(T)83(ABLE)-303(attribute)]TJ 0 -11.955 Td [(or)-333(an)-334(ob)-55(ject)-333(of)-334(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 89.968 0 Td [(psb)]TJ -ET -q -1 0 0 1 231.089 293.418 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 234.227 293.219 Td [(T)]TJ -ET -q -1 0 0 1 240.085 293.418 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 243.223 293.219 Td [(vect)]TJ -ET -q -1 0 0 1 264.772 293.418 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 267.911 293.219 Td [(type)]TJ + -12.73 -19.925 Td [(7.)]TJ 0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(,)-333(of)-334(t)28(yp)-28(e)-333(real,)-333(complex)-334(or)-333(in)28(teger.)]TJ + [-500(An)28(y)-416(co)-28(e\016cien)28(ts)-416(from)-416(matrix)-416(ro)28(ws)-416(not)-416(o)28(wned)-416(b)28(y)-416(the)-416(calling)-416(pro)-28(cess)-416(are)]TJ 12.73 -11.955 Td [(silen)28(tly)-334(i)1(g)-1(n)1(ored;)]TJ +0 g 0 G + -12.73 -19.925 Td [(8.)]TJ 0 g 0 G -/F27 9.9626 Tf -188.937 -31.88 Td [(info)]TJ + [-500(If)-358(the)-359(descriptor)-358(is)-359(in)-358(the)-359(assem)28(bled)-359(state,)-364(then)-359(an)28(y)-359(en)28(tries)-358(in)-359(the)-358(sparse)]TJ 12.73 -11.955 Td [(matrix)-430(that)-429(w)27(ould)-429(generate)-430(additional)-430(comm)28(unication)-430(requiremen)28(ts)-430(are)]TJ 0 -11.956 Td [(ignored;)]TJ +0 g 0 G + -12.73 -19.925 Td [(9.)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ + [-500(If)-309(th)1(e)-309(matrix)-309(is)-308(in)-309(the)-308(up)-28(date)-309(state,)-313(an)28(y)-309(en)28(tries)-309(in)-308(p)-28(ositions)-309(that)-308(w)28(ere)-309(not)]TJ 12.73 -11.955 Td [(presen)28(t)-334(in)-333(the)-333(original)-333(matrix)-334(are)-333(ignored.)]TJ 0 g 0 G - 141.968 -123.08 Td [(79)]TJ + 141.968 -95.641 Td [(77)]TJ 0 g 0 G ET endstream endobj -1383 0 obj +1388 0 obj << -/Length 6841 +/Length 6648 >> stream 0 g 0 G @@ -16119,135 +15909,168 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(geins)-375(|)-375(Dense)-375(matrix)-375(insertion)-375(routine)]TJ -0 g 0 G -0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_geins\050m,)-525(irw,)-525(val,)-525(x,)-525(desc_a,)-525(info)-525([,dupl,local]\051)]TJ -0 g 0 G -/F27 9.9626 Tf 0 -20.681 Td [(T)32(yp)-32(e:)]TJ -0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ -0 g 0 G -/F27 9.9626 Tf -33.797 -19.43 Td [(On)-383(En)32(try)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(spasb)-375(|)-375(Sparse)-375(matrix)-375(assem)31(bly)-375(routine)]TJ 0 g 0 G 0 g 0 G - 0 -19.431 Td [(m)]TJ -0 g 0 G -/F8 9.9626 Tf 14.529 0 Td [(Num)28(b)-28(er)-333(of)-334(ro)28(ws)-333(in)]TJ/F11 9.9626 Tf 84.516 0 Td [(v)-36(al)]TJ/F8 9.9626 Tf 16.942 0 Td [(to)-333(b)-28(e)-333(inse)-1(r)1(te)-1(d)1(.)]TJ -91.081 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_spasb\050a,)-525(desc_a,)-525(info,)-525(afmt,)-525(upd,)-525(dupl,)-525(mold\051)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -19.431 Td [(irw)]TJ +/F27 9.9626 Tf 0 -21.202 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 21.157 0 Td [(Indices)-444(of)-445(the)-444(ro)27(ws)-444(to)-445(b)-27(e)-445(inserted.)-778(Sp)-28(eci\014cally)84(,)-472(ro)27(w)]TJ/F11 9.9626 Tf 237.973 0 Td [(i)]TJ/F8 9.9626 Tf 7.861 0 Td [(of)]TJ/F11 9.9626 Tf 12.454 0 Td [(v)-36(al)]TJ/F8 9.9626 Tf 18.049 0 Td [(will)-444(b)-28(e)-445(in-)]TJ -272.588 -11.955 Td [(serted)-435(in)28(to)-436(th)1(e)-436(lo)-27(cal)-436(ro)28(w)-435(corresp)-28(onding)-435(to)-435(the)-435(global)-435(ro)28(w)-435(index)]TJ/F11 9.9626 Tf 289.252 0 Td [(ir)-28(w)]TJ/F8 9.9626 Tf 15.605 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051.)]TJ -312.163 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)84(.)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -19.43 Td [(v)64(al)]TJ +/F27 9.9626 Tf -33.797 -19.639 Td [(On)-383(En)32(try)]TJ 0 g 0 G -/F8 9.9626 Tf 19.143 0 Td [(the)-333(dense)-334(submatrix)-333(to)-333(b)-28(e)-333(inserted.)]TJ 5.763 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(1)-333(o)-1(r)-333(2)-333(arra)28(y)83(.)-444(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-334(v)56(alue.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -19.43 Td [(desc)]TJ + 0 -19.638 Td [(desc)]TJ ET q -1 0 0 1 172.619 414.689 cm +1 0 0 1 172.619 627.46 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 176.057 414.49 Td [(a)]TJ +/F27 9.9626 Tf 176.057 627.261 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.55 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.55 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 362.845 366.869 cm +1 0 0 1 362.845 579.639 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 365.983 366.669 Td [(desc)]TJ +/F30 9.9626 Tf 365.983 579.44 Td [(desc)]TJ ET q -1 0 0 1 387.532 366.869 cm +1 0 0 1 387.532 579.639 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 390.67 366.669 Td [(type)]TJ +/F30 9.9626 Tf 390.67 579.44 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -260.887 -19.43 Td [(dupl)]TJ +/F27 9.9626 Tf -260.887 -19.639 Td [(afm)32(t)]TJ 0 g 0 G -/F8 9.9626 Tf 27.259 0 Td [(Ho)28(w)-334(to)-333(handle)-333(duplicate)-333(co)-28(e\016cien)27(ts.)]TJ -2.352 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf 40.576 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-308(as:)-432(in)27(teger,)-313(p)-28(ossible)-309(v)56(alues:)]TJ/F30 9.9626 Tf 163.697 0 Td [(psb_dupl_ovwrt_)]TJ/F8 9.9626 Tf 78.455 0 Td [(,)]TJ/F30 9.9626 Tf 5.891 0 Td [(psb_dupl_add_)]TJ/F8 9.9626 Tf 67.995 0 Td [(.)]TJ +/F8 9.9626 Tf 27.736 0 Td [(the)-333(storage)-334(format)-333(for)-333(the)-334(sparse)-333(matrix.)]TJ -2.829 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.451 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(arra)28(y)-333(of)-334(c)28(haracters.)-444(Defalt:)-445('CSR'.)]TJ 0 g 0 G -/F27 9.9626 Tf -340.944 -19.43 Td [(lo)-32(cal)]TJ +/F27 9.9626 Tf -24.907 -19.639 Td [(up)-32(d)]TJ 0 g 0 G -/F8 9.9626 Tf 28.054 0 Td [(Whether)-289(the)-289(en)28(tries)-289(in)-289(the)-289(index)-288(v)27(ector)]TJ/F30 9.9626 Tf 172.77 0 Td [(irw)]TJ/F8 9.9626 Tf 15.691 0 Td [(,)-298(are)-289(already)-289(in)-288(lo)-28(cal)-289(n)28(um)28(b)-28(er-)]TJ -191.608 -11.955 Td [(ing.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.95 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-334(logical)-333(v)55(alue;)-333(default:)]TJ/F30 9.9626 Tf 163.055 0 Td [(.false.)]TJ/F8 9.9626 Tf 36.612 0 Td [(.)]TJ +/F8 9.9626 Tf 24.394 0 Td [(Pro)28(vide)-334(f)1(or)-334(up)-27(dates)-334(to)-333(the)-334(matri)1(x)-334(co)-28(e\016cien)28(ts.)]TJ 0.513 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(in)27(teger,)-333(p)-28(ossible)-333(v)55(alues:)]TJ/F30 9.9626 Tf 164.632 0 Td [(psb_upd_srch_)]TJ/F8 9.9626 Tf 67.995 0 Td [(,)]TJ/F30 9.9626 Tf 6.088 0 Td [(psb_upd_perm_)]TJ 0 g 0 G -/F27 9.9626 Tf -224.574 -20.68 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf -263.622 -19.639 Td [(dupl)]TJ 0 g 0 G +/F8 9.9626 Tf 27.259 0 Td [(Ho)28(w)-334(to)-333(handle)-333(duplicate)-333(co)-28(e\016cien)27(ts.)]TJ -2.352 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-308(as:)-432(in)27(teger,)-313(p)-28(ossible)-309(v)56(alues:)]TJ/F30 9.9626 Tf 163.696 0 Td [(psb_dupl_ovwrt_)]TJ/F8 9.9626 Tf 78.455 0 Td [(,)]TJ/F30 9.9626 Tf 5.891 0 Td [(psb_dupl_add_)]TJ/F8 9.9626 Tf 67.995 0 Td [(,)]TJ/F30 9.9626 Tf -316.037 -11.955 Td [(psb_dupl_err_)]TJ/F8 9.9626 Tf 67.994 0 Td [(.)]TJ 0 g 0 G - 0 -19.43 Td [(x)]TJ +/F27 9.9626 Tf -92.901 -19.639 Td [(mold)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(the)-333(output)-334(d)1(e)-1(n)1(s)-1(e)-333(matrix.)]TJ 13.879 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-232(as:)-394(a)-233(rank)-233(one)-232(or)-233(t)28(w)28(o)-233(arra)28(y)-233(or)-232(an)-233(ob)-55(ject)-233(of)-233(t)28(yp)-27(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 241.975 0 Td [(psb)]TJ +/F8 9.9626 Tf 29.805 0 Td [(The)-333(desired)-334(dynamic)-333(t)28(yp)-28(e)-333(for)-334(the)-333(in)28(ternal)-333(matrix)-334(storage.)]TJ -4.898 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.451 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(a)-333(class)-334(deriv)28(ed)-333(from)]TJ/F30 9.9626 Tf 203.349 0 Td [(psb)]TJ +ET +q +1 0 0 1 395.279 297.847 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 398.417 297.647 Td [(T)]TJ +ET +q +1 0 0 1 404.275 297.847 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 407.413 297.647 Td [(base)]TJ +ET +q +1 0 0 1 428.962 297.847 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 432.101 297.647 Td [(sparse)]TJ ET q -1 0 0 1 433.906 144.435 cm +1 0 0 1 464.11 297.847 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 437.044 144.236 Td [(T)]TJ +/F30 9.9626 Tf 467.248 297.647 Td [(mat)]TJ/F8 9.9626 Tf 15.691 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -332.234 -21.201 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G + 0 -19.639 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.551 0 Td [(the)-333(matrix)-334(to)-333(b)-28(e)-333(assem)28(bled.)]TJ 14.355 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.951 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf -25.184 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 442.902 144.435 cm +1 0 0 1 362.845 209.186 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 446.04 144.236 Td [(vect)]TJ +/F30 9.9626 Tf 365.983 208.986 Td [(Tspmat)]TJ ET q -1 0 0 1 467.589 144.435 cm +1 0 0 1 397.993 209.186 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 470.727 144.236 Td [(type)]TJ +/F30 9.9626 Tf 401.131 208.986 Td [(type)]TJ +0 g 0 G +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -271.347 -19.638 Td [(info)]TJ 0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(,)]TJ -316.038 -11.955 Td [(of)-333(t)27(yp)-27(e)-334(real,)-333(complex)-333(or)-334(in)28(teger.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ/F16 11.9552 Tf -24.906 -21.201 Td [(Notes)]TJ 0 g 0 G - 141.968 -41.843 Td [(80)]TJ +/F8 9.9626 Tf 166.874 -29.888 Td [(78)]TJ 0 g 0 G ET endstream endobj -1387 0 obj +1392 0 obj << -/Length 1111 +/Length 2248 >> stream 0 g 0 G 0 g 0 G 0 g 0 G BT -/F27 9.9626 Tf 99.895 706.129 Td [(info)]TJ +/F8 9.9626 Tf 112.072 706.129 Td [(1.)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ + [-500(On)-406(en)28(try)-406(to)-406(this)-406(routine)-406(the)-406(descriptor)-406(m)28(ust)-406(b)-28(e)-406(in)-406(the)-406(assem)28(bled)-406(state)-1(,)]TJ 12.73 -11.955 Td [(i.e.)]TJ/F30 9.9626 Tf 17.158 0 Td [(psb_cdasb)]TJ/F8 9.9626 Tf 50.394 0 Td [(m)28(ust)-334(already)-333(ha)28(v)28(e)-334(b)-27(een)-334(called.)]TJ 0 g 0 G -/F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ + -80.282 -19.926 Td [(2.)]TJ 0 g 0 G - [-500(Dense)-333(v)27(ectors/matrices)-333(do)-333(not)-334(ha)28(v)28(e)-334(an)-333(asso)-28(ciated)-333(state;)]TJ + [-500(The)-333(sparse)-334(matrix)-333(ma)28(y)-334(b)-27(e)-334(in)-333(either)-333(the)-334(build)-333(or)-333(up)-28(date)-333(state;)]TJ 0 g 0 G - 0 -19.925 Td [(2.)]TJ + 0 -19.925 Td [(3.)]TJ +0 g 0 G + [-500(Duplicate)-250(en)28(tries)-250(are)-249(detec)-1(ted)-249(and)-250(handled)-250(in)-249(b)-28(oth)-250(build)-249(and)-250(up)-28(date)-249(state,)]TJ 12.73 -11.955 Td [(with)-282(the)-283(exception)-282(of)-282(the)-283(error)-282(action)-282(that)-283(i)1(s)-283(only)-282(tak)28(en)-283(in)-282(the)-282(build)-282(s)-1(tate,)]TJ 0 -11.955 Td [(i.e.)-444(on)-334(the)-333(\014rst)-333(assem)27(bly;)]TJ +0 g 0 G + -12.73 -19.925 Td [(4.)]TJ +0 g 0 G + [-500(If)-224(the)-224(up)-28(d)1(ate)-224(c)27(hoice)-224(is)]TJ/F30 9.9626 Tf 107.516 0 Td [(psb_upd_perm_)]TJ/F8 9.9626 Tf 67.994 0 Td [(,)-246(then)-224(subsequen)28(t)-224(calls)-224(to)]TJ/F30 9.9626 Tf 108.951 0 Td [(psb_spins)]TJ/F8 9.9626 Tf -271.731 -11.956 Td [(to)-246(up)-28(date)-246(the)-246(matrix)-246(m)28(ust)-246(b)-28(e)-246(arranged)-246(in)-246(suc)28(h)-246(a)-246(w)28(a)27(y)-246(as)-246(to)-246(pro)-27(duce)-246(exactly)]TJ 0 -11.955 Td [(the)-228(same)-229(sequence)-228(of)-228(co)-28(e\016cien)28(t)-229(v)56(alues)-228(as)-229(encoun)28(tered)-228(at)-229(the)-228(\014rst)-228(assem)28(bly;)]TJ +0 g 0 G + -12.73 -19.925 Td [(5.)]TJ +0 g 0 G + [-500(The)-333(output)-334(storage)-333(format)-333(need)-334(not)-333(b)-28(e)-333(the)-333(same)-334(on)-333(all)-333(pro)-28(cesses;)]TJ +0 g 0 G + 0 -19.925 Td [(6.)]TJ 0 g 0 G - [-500(Duplicate)-292(en)28(tries)-293(are)-292(either)-292(o)28(v)28(erwritten)-292(or)-293(added,)-300(there)-292(is)-292(no)-292(pro)27(vision)-292(for)]TJ 12.73 -11.955 Td [(raising)-333(an)-334(error)-333(condition.)]TJ + [-500(On)-370(exit)-370(from)-370(this)-370(routine)-370(the)-370(matrix)-370(is)-370(in)-370(the)-370(assem)28(bled)-370(state,)-379(and)-370(th)27(us)]TJ 12.73 -11.956 Td [(is)-333(suitable)-334(for)-333(the)-333(computational)-334(r)1(outines.)]TJ 0 g 0 G - 141.968 -494.147 Td [(81)]TJ + 141.968 -444.333 Td [(79)]TJ 0 g 0 G ET endstream endobj -1396 0 obj +1405 0 obj << -/Length 5215 +/Length 3084 >> stream 0 g 0 G @@ -16260,10 +16083,10 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(geasb)-375(|)-375(Assem)31(bly)-375(a)-375(dense)-375(matrix)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(spfree)-375(|)-375(F)94(rees)-375(a)-375(sparse)-375(matrix)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_geasb\050x,)-525(desc_a,)-525(info,)-525(mold\051)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_spfree\050a,)-525(desc_a,)-525(info\051)]TJ 0 g 0 G /F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G @@ -16272,137 +16095,73 @@ BT /F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(desc)]TJ -ET -q -1 0 0 1 172.619 626.17 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 176.057 625.971 Td [(a)]TJ + 0 -19.925 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.55 0 Td [(The)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(v)56(ariable)-334(of)-333(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.551 0 Td [(the)-333(matrix)-334(to)-333(b)-28(e)-333(freed.)]TJ 14.356 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.95 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.95 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf -25.183 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-334(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 137.347 0 Td [(psb)]TJ +/F30 9.9626 Tf 170.914 0 Td [(psb)]TJ ET q -1 0 0 1 329.276 578.35 cm +1 0 0 1 362.845 578.35 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 332.415 578.15 Td [(desc)]TJ +/F30 9.9626 Tf 365.983 578.15 Td [(Tspmat)]TJ ET q -1 0 0 1 353.964 578.35 cm +1 0 0 1 397.993 578.35 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 357.102 578.15 Td [(type)]TJ +/F30 9.9626 Tf 401.131 578.15 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -227.318 -31.88 Td [(mold)]TJ -0 g 0 G -/F8 9.9626 Tf 29.805 0 Td [(The)-333(desired)-334(dynamic)-333(t)28(yp)-28(e)-333(for)-334(th)1(e)-334(in)28(ternal)-333(v)27(ector)-333(storage.)]TJ -4.899 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf 40.576 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-273(as:)-414(an)-274(ob)-55(ject)-273(of)-274(a)-273(class)-273(deriv)28(ed)-274(from)]TJ/F30 9.9626 Tf 198.261 0 Td [(psb)]TJ -ET -q -1 0 0 1 390.19 498.649 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 393.329 498.449 Td [(T)]TJ -ET -q -1 0 0 1 399.186 498.649 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 402.325 498.449 Td [(base)]TJ -ET -q -1 0 0 1 423.874 498.649 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 427.012 498.449 Td [(vect)]TJ +/F27 9.9626 Tf -271.347 -19.925 Td [(desc)]TJ ET q -1 0 0 1 448.561 498.649 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 172.619 558.424 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F30 9.9626 Tf 451.699 498.449 Td [(type)]TJ/F8 9.9626 Tf 20.921 0 Td [(;)-293(this)]TJ -297.009 -11.955 Td [(is)-333(only)-334(allo)28(w)28(ed)-333(when)]TJ/F11 9.9626 Tf 93.317 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(is)-333(of)-334(t)28(yp)-28(e)]TJ +/F27 9.9626 Tf 176.057 558.225 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.55 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 43.78 0 Td [(psb)]TJ -ET -q -1 0 0 1 338.042 486.693 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 341.18 486.494 Td [(T)]TJ +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 347.038 486.693 cm +1 0 0 1 362.845 510.604 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 350.177 486.494 Td [(vect)]TJ +/F30 9.9626 Tf 365.983 510.405 Td [(desc)]TJ ET q -1 0 0 1 371.725 486.693 cm +1 0 0 1 387.532 510.604 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 374.864 486.494 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -245.08 -21.918 Td [(On)-383(Return)]TJ +/F30 9.9626 Tf 390.67 510.405 Td [(type)]TJ 0 g 0 G +/F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G - 0 -19.925 Td [(x)]TJ -0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(The)-333(dense)-334(matrix)-333(to)-333(b)-28(e)-333(as)-1(sem)28(bled.)]TJ 13.878 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-433(as:)-645(a)-433(rank)-433(one)-434(or)-433(t)28(w)28(o)-434(arra)28(y)-433(with)-433(the)-434(ALLOCA)84(T)83(ABLE)-433(or)-434(an)]TJ 0 -11.955 Td [(ob)-56(ject)-333(of)-333(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 63.927 0 Td [(psb)]TJ -ET -q -1 0 0 1 255.857 385.075 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 258.995 384.875 Td [(T)]TJ -ET -q -1 0 0 1 264.853 385.075 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 267.992 384.875 Td [(vect)]TJ -ET -q -1 0 0 1 289.541 385.075 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 292.679 384.875 Td [(type)]TJ +/F27 9.9626 Tf -260.887 -21.918 Td [(On)-383(Return)]TJ 0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(,)-333(of)-334(t)28(yp)-28(e)-333(real,)-333(complex)-334(or)-333(in)28(teger.)]TJ 0 g 0 G -/F27 9.9626 Tf -162.895 -31.88 Td [(info)]TJ + 0 -19.926 Td [(info)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ 0 g 0 G - 141.968 -214.736 Td [(82)]TJ + 141.968 -330.303 Td [(80)]TJ 0 g 0 G ET endstream endobj -1402 0 obj +1411 0 obj << -/Length 3378 +/Length 3991 >> stream 0 g 0 G @@ -16415,92 +16174,93 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(gefree)-375(|)-375(F)94(rees)-375(a)-375(dense)-375(matrix)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(sprn)-391(|)-391(Reinit)-391(sparse)-391(matrix)-391(structure)-391(for)-391(psblas)-391(rou-)]TJ -25.091 -13.948 Td [(tines.)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_gefree\050x,)-525(desc_a,)-525(info\051)]TJ +/F30 9.9626 Tf 0 -18.389 Td [(call)-525(psb_sprn\050a,)-525(decsc_a,)-525(info,)-525(clear\051)]TJ 0 g 0 G /F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(x)]TJ + 0 -19.926 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(The)-333(dense)-334(matrix)-333(to)-333(b)-28(e)-334(f)1(re)-1(ed.)]TJ 13.879 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-433(as:)-645(a)-433(rank)-433(one)-433(or)-434(t)28(w)28(o)-434(arra)28(y)-433(with)-433(the)-434(ALLOCA)84(T)83(ABLE)-433(or)-434(an)]TJ 0 -11.955 Td [(ob)-56(j)1(e)-1(ct)-333(of)-333(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.551 0 Td [(the)-333(matrix)-334(to)-333(b)-28(e)-333(reinitialized.)]TJ 14.356 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.951 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf -25.183 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 63.927 0 Td [(psb)]TJ -ET -q -1 0 0 1 205.048 566.395 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 208.186 566.195 Td [(T)]TJ +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 214.044 566.395 cm +1 0 0 1 312.036 564.402 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 217.182 566.195 Td [(vect)]TJ +/F30 9.9626 Tf 315.174 564.203 Td [(Tspmat)]TJ ET q -1 0 0 1 238.731 566.395 cm +1 0 0 1 347.183 564.402 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 241.869 566.195 Td [(type)]TJ +/F30 9.9626 Tf 350.322 564.203 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(,)-333(of)-334(t)28(yp)-28(e)-333(real,)-333(complex)-334(or)-333(in)28(teger.)]TJ +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -162.896 -31.88 Td [(desc)]TJ +/F27 9.9626 Tf -271.348 -19.925 Td [(desc)]TJ ET q -1 0 0 1 121.81 534.514 cm +1 0 0 1 121.81 544.477 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 125.247 534.315 Td [(a)]TJ +/F27 9.9626 Tf 125.247 544.278 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(The)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(v)56(ariable)-334(of)-333(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.551 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 137.346 0 Td [(psb)]TJ +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 278.467 486.693 cm +1 0 0 1 312.036 496.656 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 281.605 486.494 Td [(desc)]TJ +/F30 9.9626 Tf 315.174 496.457 Td [(desc)]TJ ET q -1 0 0 1 303.154 486.693 cm +1 0 0 1 336.723 496.656 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 306.292 486.494 Td [(type)]TJ +/F30 9.9626 Tf 339.861 496.457 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(.)]TJ +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -260.887 -19.925 Td [(clear)]TJ 0 g 0 G -/F27 9.9626 Tf -227.319 -33.873 Td [(On)-383(Return)]TJ +/F8 9.9626 Tf 28.795 0 Td [(Cho)-28(ose)-333(whether)-334(to)-333(zero)-333(out)-334(matrix)-333(co)-28(e\016cien)28(ts)]TJ -3.888 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Default:)-444(true.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -21.918 Td [(On)-383(Return)]TJ 0 g 0 G 0 g 0 G 0 -19.925 Td [(info)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ +0 g 0 G +/F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ +0 g 0 G + [-500(On)-333(exit)-334(from)-333(this)-333(routine)-333(the)-334(sparse)-333(matrix)-333(is)-334(in)-333(the)-333(up)-28(date)-333(s)-1(tat)1(e)-1(.)]TJ 0 g 0 G - 141.968 -294.437 Td [(83)]TJ + 154.698 -206.766 Td [(81)]TJ 0 g 0 G ET endstream endobj -1406 0 obj +1418 0 obj << -/Length 3438 +/Length 5111 >> stream 0 g 0 G @@ -16513,46 +16273,100 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(gelp)-375(|)-375(Applies)-375(a)-375(left)-375(p)-31(erm)31(utation)-375(to)-375(a)-375(dense)-375(matrix)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(geall)-375(|)-375(Allo)-31(cates)-375(a)-375(dense)-375(matrix)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_gelp\050trans,)-525(iperm,)-525(x,)-525(info\051)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_geall\050x,)-525(desc_a,)-525(info,)-525(n,)-525(lb\051)]TJ 0 g 0 G /F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G /F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(trans)]TJ -0 g 0 G -/F8 9.9626 Tf 30.609 0 Td [(A)-333(c)27(har)1(ac)-1(ter)-333(that)-333(sp)-28(eci\014es)-333(whether)-334(to)-333(p)-28(erm)28(ute)]TJ/F11 9.9626 Tf 204.179 0 Td [(A)]TJ/F8 9.9626 Tf 10.793 0 Td [(or)]TJ/F11 9.9626 Tf 12.204 0 Td [(A)]TJ/F10 6.9738 Tf 7.472 3.616 Td [(T)]TJ/F8 9.9626 Tf 6.276 -3.616 Td [(.)]TJ -246.626 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-334(single)-333(c)28(haracter)-334(with)-333(v)56(alue)-334('N')-333(for)]TJ/F11 9.9626 Tf 217.435 0 Td [(A)]TJ/F8 9.9626 Tf 10.792 0 Td [(or)-333('T')-334(for)]TJ/F11 9.9626 Tf 43.504 0 Td [(A)]TJ/F10 6.9738 Tf 7.472 3.616 Td [(T)]TJ/F8 9.9626 Tf 6.276 -3.616 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -310.386 -31.88 Td [(ip)-32(erm)]TJ -0 g 0 G -/F8 9.9626 Tf 34.364 0 Td [(An)-333(in)28(tege)-1(r)-333(arra)28(y)-333(con)27(tain)1(ing)-334(p)-28(erm)28(utation)-333(information.)]TJ -9.457 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-1(n)-333(in)28(teger)-333(one-dimensional)-334(arra)28(y)84(.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -31.88 Td [(x)]TJ + 0 -19.925 Td [(desc)]TJ +ET +q +1 0 0 1 172.619 626.17 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 176.057 625.971 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(The)-333(dense)-334(matrix)-333(to)-333(b)-28(e)-333(p)-28(erm)27(u)1(te)-1(d)1(.)]TJ 13.879 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(one)-333(or)-333(t)27(w)28(o)-333(dimensional)-334(arra)28(y)84(.)]TJ +/F8 9.9626 Tf 10.55 0 Td [(The)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(v)56(ariable)-334(of)-333(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 137.347 0 Td [(psb)]TJ +ET +q +1 0 0 1 329.276 578.35 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 332.415 578.15 Td [(desc)]TJ +ET +q +1 0 0 1 353.964 578.35 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 357.102 578.15 Td [(type)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -33.873 Td [(On)-383(Return)]TJ +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G +/F27 9.9626 Tf -227.318 -31.88 Td [(n)]TJ 0 g 0 G - 0 -19.925 Td [(info)]TJ +/F8 9.9626 Tf 11.346 0 Td [(The)-333(n)27(um)28(b)-28(er)-333(of)-333(columns)-334(of)-333(the)-333(dense)-334(matrix)-333(to)-333(b)-28(e)-333(allo)-28(cated.)]TJ 13.56 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-343(as:)-463(In)27(teger)-343(scalar,)-345(default)-343(1.)-473(It)-343(is)-343(not)-343(a)-343(v)56(alid)-343(argumen)27(t)-342(if)]TJ/F11 9.9626 Tf 294.599 0 Td [(x)]TJ/F8 9.9626 Tf 9.111 0 Td [(is)-343(a)]TJ -303.71 -11.955 Td [(rank-1)-333(arra)28(y)83(.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.906 -19.925 Td [(lb)]TJ +0 g 0 G +/F8 9.9626 Tf 14.529 0 Td [(The)-489(lo)28(w)27(er)-489(b)-27(ound)-489(for)-489(the)-490(colu)1(m)-1(n)-489(ind)1(e)-1(x)-489(range)-489(of)-489(the)-489(dense)-489(matrix)-489(to)-489(b)-28(e)]TJ 10.377 -11.955 Td [(allo)-28(cated.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-343(as:)-463(In)27(teger)-343(scalar,)-345(default)-343(1.)-473(It)-343(is)-343(not)-343(a)-343(v)56(alid)-343(argumen)27(t)-342(if)]TJ/F11 9.9626 Tf 294.599 0 Td [(x)]TJ/F8 9.9626 Tf 9.111 0 Td [(is)-343(a)]TJ -303.71 -11.955 Td [(rank-1)-333(arra)28(y)83(.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.906 -21.918 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(x)]TJ +0 g 0 G +/F8 9.9626 Tf 11.028 0 Td [(The)-333(dense)-334(matrix)-333(to)-333(b)-28(e)-333(allo)-28(cated.)]TJ 13.878 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-303(as)-1(:)-429(a)-304(rank)-303(one)-304(or)-304(t)28(w)28(o)-304(arra)28(y)-304(with)-304(th)1(e)-304(ALLOCA)83(T)83(ABLE)-303(attribute)]TJ 0 -11.955 Td [(or)-333(an)-334(ob)-55(ject)-334(of)-333(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 89.969 0 Td [(psb)]TJ +ET +q +1 0 0 1 281.898 293.418 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 285.037 293.219 Td [(T)]TJ +ET +q +1 0 0 1 290.895 293.418 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 294.033 293.219 Td [(vect)]TJ +ET +q +1 0 0 1 315.582 293.418 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 318.72 293.219 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.034 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detected.)]TJ +/F8 9.9626 Tf 20.921 0 Td [(,)-333(of)-334(t)28(yp)-28(e)-333(real,)-333(complex)-334(or)-333(in)28(teger.)]TJ +0 g 0 G +/F27 9.9626 Tf -188.936 -31.88 Td [(info)]TJ 0 g 0 G - 141.967 -226.691 Td [(84)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ +0 g 0 G + 141.968 -123.08 Td [(82)]TJ 0 g 0 G ET endstream endobj -1411 0 obj +1424 0 obj << -/Length 6540 +/Length 6817 >> stream 0 g 0 G @@ -16565,120 +16379,135 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(glob)]TJ -ET -q -1 0 0 1 150.451 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 154.486 706.129 Td [(to)]TJ -ET -q -1 0 0 1 167.248 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 171.283 706.129 Td [(lo)-31(c)-375(|)-375(Global)-375(to)-375(lo)-31(cal)-375(indices)-375(con)31(v)31(ertion)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(geins)-375(|)-375(Dense)-375(matrix)-375(insertion)-375(routine)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -71.388 -18.389 Td [(call)-525(psb_glob_to_loc\050x,)-525(y,)-525(desc_a,)-525(info,)-525(iact,owned\051)]TJ 0 -11.956 Td [(call)-525(psb_glob_to_loc\050x,)-525(desc_a,)-525(info,)-525(iact,owned\051)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_geins\050m,)-525(irw,)-525(val,)-525(x,)-525(desc_a,)-525(info)-525([,dupl,local]\051)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -21.201 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf 0 -20.681 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.639 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -33.797 -19.43 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.639 Td [(x)]TJ + 0 -19.431 Td [(m)]TJ +0 g 0 G +/F8 9.9626 Tf 14.529 0 Td [(Num)28(b)-28(er)-333(of)-334(ro)28(ws)-333(in)]TJ/F11 9.9626 Tf 84.517 0 Td [(v)-36(al)]TJ/F8 9.9626 Tf 16.942 0 Td [(to)-333(b)-28(e)-333(inserted.)]TJ -91.081 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.431 Td [(irw)]TJ +0 g 0 G +/F8 9.9626 Tf 21.157 0 Td [(Indices)-445(of)-444(the)-444(ro)27(ws)-444(to)-445(b)-27(e)-445(inserted.)-778(Sp)-28(eci\014cally)84(,)-473(r)1(o)27(w)]TJ/F11 9.9626 Tf 237.974 0 Td [(i)]TJ/F8 9.9626 Tf 7.861 0 Td [(of)]TJ/F11 9.9626 Tf 12.453 0 Td [(v)-36(al)]TJ/F8 9.9626 Tf 18.05 0 Td [(will)-444(b)-28(e)-445(in-)]TJ -272.588 -11.955 Td [(serted)-435(in)28(to)-435(the)-436(lo)-27(cal)-436(r)1(o)27(w)-435(corresp)-28(onding)-435(to)-435(the)-435(global)-435(ro)28(w)-435(index)]TJ/F11 9.9626 Tf 289.252 0 Td [(ir)-28(w)]TJ/F8 9.9626 Tf 15.604 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.433 0 Td [(\051.)]TJ -312.163 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)84(.)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(An)-333(in)28(te)-1(ger)-333(v)28(ector)-333(of)-334(indices)-333(to)-333(b)-28(e)-334(con)28(v)28(erted.)]TJ 13.879 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in,)-383(inout)]TJ/F8 9.9626 Tf 42.645 0 Td [(.)]TJ -76.131 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-333(in)27(teger)-333(arra)28(y)83(.)]TJ +/F27 9.9626 Tf -24.907 -19.43 Td [(v)64(al)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -31.594 Td [(desc)]TJ +/F8 9.9626 Tf 19.144 0 Td [(the)-333(dense)-334(submatrix)-333(to)-333(b)-28(e)-333(inserted.)]TJ 5.763 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(1)-333(or)-334(2)-333(arra)28(y)83(.)-444(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-334(v)56(alue.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.43 Td [(desc)]TJ ET q -1 0 0 1 121.81 536.09 cm +1 0 0 1 121.81 414.689 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 125.247 535.891 Td [(a)]TJ +/F27 9.9626 Tf 125.247 414.49 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.551 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 312.036 488.27 cm +1 0 0 1 312.036 366.869 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 315.174 488.07 Td [(desc)]TJ +/F30 9.9626 Tf 315.174 366.669 Td [(desc)]TJ ET q -1 0 0 1 336.723 488.27 cm +1 0 0 1 336.723 366.869 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 339.861 488.07 Td [(type)]TJ +/F30 9.9626 Tf 339.861 366.669 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -260.887 -19.638 Td [(iact)]TJ -0 g 0 G -/F8 9.9626 Tf 23.281 0 Td [(sp)-28(eci\014es)-333(action)-334(to)-333(b)-28(e)-333(tak)28(en)-334(in)-333(case)-333(of)-334(range)-333(errors.)-444(Scop)-28(e:)]TJ/F27 9.9626 Tf 257.147 0 Td [(global)]TJ/F8 9.9626 Tf -255.521 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-256(c)28(haracter)-255(v)56(ariable)]TJ/F30 9.9626 Tf 143.584 0 Td [(I)]TJ/F8 9.9626 Tf 5.23 0 Td [(gnore,)]TJ/F30 9.9626 Tf 29.293 0 Td [(W)]TJ/F8 9.9626 Tf 5.23 0 Td [(arning)-255(or)]TJ/F30 9.9626 Tf 41.67 0 Td [(A)]TJ/F8 9.9626 Tf 5.231 0 Td [(b)-28(ort,)-270(default)]TJ/F30 9.9626 Tf 56.741 0 Td [(I)]TJ/F8 9.9626 Tf 5.231 0 Td [(gnore.)]TJ -0 g 0 G -/F27 9.9626 Tf -317.117 -19.639 Td [(o)32(wned)]TJ -0 g 0 G -/F8 9.9626 Tf 36.647 0 Td [(Sp)-28(ec\014es)-333(v)55(alid)-333(range)-333(of)-334(i)1(nput)-334(Scop)-27(e:)]TJ/F27 9.9626 Tf 158.933 0 Td [(global)]TJ/F8 9.9626 Tf -170.673 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(If)-294(true,)-302(then)-294(only)-295(indices)-294(strictly)-294(o)28(wned)-295(b)28(y)-294(the)-294(curren)28(t)-295(pro)-27(ces)-1(s)-294(are)-294(consid-)]TJ 0 -11.955 Td [(ered)-333(v)55(alid,)-333(if)-333(false)-334(then)-333(halo)-333(indices)-334(are)-333(also)-333(accepted.)-445(Default:)-444(false.)]TJ +/F27 9.9626 Tf -260.887 -19.43 Td [(dupl)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -21.202 Td [(On)-383(Return)]TJ +/F8 9.9626 Tf 27.259 0 Td [(Ho)28(w)-334(to)-333(handle)-333(duplicate)-333(co)-28(e\016cien)27(ts.)]TJ -2.352 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-308(as:)-432(in)27(teger,)-313(p)-28(ossible)-309(v)56(alues:)]TJ/F30 9.9626 Tf 163.696 0 Td [(psb_dupl_ovwrt_)]TJ/F8 9.9626 Tf 78.456 0 Td [(,)]TJ/F30 9.9626 Tf 5.891 0 Td [(psb_dupl_add_)]TJ/F8 9.9626 Tf 67.994 0 Td [(.)]TJ 0 g 0 G +/F27 9.9626 Tf -340.944 -19.43 Td [(lo)-32(cal)]TJ 0 g 0 G - 0 -19.639 Td [(x)]TJ +/F8 9.9626 Tf 28.055 0 Td [(Whether)-289(the)-289(en)28(tries)-289(in)-289(the)-289(index)-288(v)27(ector)]TJ/F30 9.9626 Tf 172.769 0 Td [(irw)]TJ/F8 9.9626 Tf 15.692 0 Td [(,)-298(are)-289(already)-288(in)-289(lo)-28(cal)-289(n)28(um)28(b)-28(er-)]TJ -191.609 -11.955 Td [(ing.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(logical)-333(v)55(alue;)-333(default:)]TJ/F30 9.9626 Tf 163.056 0 Td [(.false.)]TJ/F8 9.9626 Tf 36.612 0 Td [(.)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(If)]TJ/F11 9.9626 Tf 10.133 0 Td [(y)]TJ/F8 9.9626 Tf 8.733 0 Td [(is)-350(not)-351(presen)28(t,)-355(then)]TJ/F11 9.9626 Tf 88.586 0 Td [(x)]TJ/F8 9.9626 Tf 9.185 0 Td [(is)-350(o)27(v)28(erwritten)-350(with)-351(th)1(e)-351(translated)-350(in)28(teger)-351(indices.)]TJ -102.758 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-333(in)27(teger)-333(arra)28(y)83(.)]TJ +/F27 9.9626 Tf -224.575 -20.68 Td [(On)-383(Return)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.639 Td [(y)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(If)]TJ/F11 9.9626 Tf 10.04 0 Td [(y)]TJ/F8 9.9626 Tf 8.64 0 Td [(is)-341(presen)28(t,)-343(then)]TJ/F11 9.9626 Tf 70.405 0 Td [(y)]TJ/F8 9.9626 Tf 8.64 0 Td [(is)-341(o)28(v)27(erwri)1(tte)-1(n)-341(with)-341(the)-341(translated)-341(in)28(teger)-341(indices,)-343(and)]TJ/F11 9.9626 Tf -83.846 -11.955 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(is)-333(left)-334(unc)28(hanged.)-444(Scop)-28(e:)]TJ/F27 9.9626 Tf 113.242 0 Td [(global)]TJ/F8 9.9626 Tf -122.257 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-333(in)27(teger)-333(arra)28(y)83(.)]TJ + 0 -19.43 Td [(x)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.638 Td [(info)]TJ +/F8 9.9626 Tf 11.028 0 Td [(the)-333(output)-334(dense)-333(matrix.)]TJ 13.879 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-232(as:)-394(a)-233(rank)-233(one)-232(or)-233(t)28(w)28(o)-233(arra)28(y)-233(or)-232(an)-233(ob)-55(ject)-233(of)-233(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 241.975 0 Td [(psb)]TJ +ET +q +1 0 0 1 383.096 144.435 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 386.234 144.236 Td [(T)]TJ +ET +q +1 0 0 1 392.092 144.435 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 395.231 144.236 Td [(vect)]TJ +ET +q +1 0 0 1 416.779 144.435 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 419.918 144.236 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ/F16 11.9552 Tf -24.907 -21.202 Td [(Notes)]TJ +/F8 9.9626 Tf 20.921 0 Td [(,)]TJ -316.037 -11.955 Td [(of)-333(t)27(y)1(p)-28(e)-334(real,)-333(complex)-333(or)-334(in)28(teger.)]TJ 0 g 0 G -/F8 9.9626 Tf 166.875 -29.887 Td [(85)]TJ + 141.968 -41.843 Td [(83)]TJ 0 g 0 G ET endstream endobj -1416 0 obj +1428 0 obj << -/Length 705 +/Length 1115 >> stream 0 g 0 G 0 g 0 G 0 g 0 G BT -/F8 9.9626 Tf 162.881 706.129 Td [(1.)]TJ +/F27 9.9626 Tf 150.705 706.129 Td [(info)]TJ 0 g 0 G - [-500(If)-352(an)-353(input)-352(index)-352(is)-353(out)-352(of)-353(r)1(ange)-1(,)-357(then)-352(the)-352(corres)-1(p)-27(onding)-353(ou)1(tput)-353(index)-352(is)]TJ 12.73 -11.955 Td [(set)-333(to)-334(a)-333(negativ)28(e)-334(n)28(um)28(b)-28(er;)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ/F16 11.9552 Tf -24.906 -21.918 Td [(Notes)]TJ 0 g 0 G - -12.73 -19.926 Td [(2.)]TJ +/F8 9.9626 Tf 12.176 -19.925 Td [(1.)]TJ +0 g 0 G + [-500(Dense)-333(v)27(ectors/matrices)-333(do)-333(not)-334(ha)28(v)28(e)-334(an)-333(asso)-28(ciated)-333(state;)]TJ +0 g 0 G + 0 -19.925 Td [(2.)]TJ 0 g 0 G - [-500(The)-476(default)]TJ/F30 9.9626 Tf 69.543 0 Td [(I)]TJ/F8 9.9626 Tf 5.23 0 Td [(gnore)-476(means)-477(that)-476(the)-476(negativ)28(e)-477(out)1(put)-477(is)-476(the)-476(only)-476(action)]TJ -62.043 -11.955 Td [(tak)28(en)-334(on)-333(an)-333(out-of-range)-333(input.)]TJ + [-500(Duplicate)-292(en)28(tries)-293(are)-292(either)-292(o)28(v)28(erwritten)-293(or)-292(added,)-300(there)-292(is)-292(no)-293(p)1(ro)27(vision)-292(for)]TJ 12.73 -11.955 Td [(raising)-333(an)-334(error)-333(condition.)]TJ 0 g 0 G - 141.968 -571.855 Td [(86)]TJ + 141.968 -494.147 Td [(84)]TJ 0 g 0 G ET endstream endobj -1423 0 obj +1437 0 obj << -/Length 5721 +/Length 5215 >> stream 0 g 0 G @@ -16691,93 +16520,149 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(lo)-31(c)]TJ -ET -q -1 0 0 1 142.605 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 146.64 706.129 Td [(to)]TJ -ET -q -1 0 0 1 159.402 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 163.437 706.129 Td [(glob)-375(|)-375(Lo)-31(cal)-375(to)-375(global)-375(indices)-375(con)31(v)31(ersion)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(geasb)-375(|)-375(Assem)31(bly)-375(a)-375(dense)-375(matrix)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -63.542 -18.389 Td [(call)-525(psb_loc_to_glob\050x,)-525(y,)-525(desc_a,)-525(info,)-525(iact\051)]TJ 0 -11.956 Td [(call)-525(psb_loc_to_glob\050x,)-525(desc_a,)-525(info,)-525(iact\051)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_geasb\050x,)-525(desc_a,)-525(info,)-525(mold\051)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -21.917 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G /F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(x)]TJ -0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(An)-333(in)28(te)-1(ger)-333(v)28(ector)-333(of)-334(indices)-333(to)-333(b)-28(e)-334(con)28(v)28(erted.)]TJ 13.879 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in,)-383(inout)]TJ/F8 9.9626 Tf 42.645 0 Td [(.)]TJ -76.131 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-333(in)27(teger)-333(arra)28(y)83(.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -31.88 Td [(desc)]TJ + 0 -19.925 Td [(desc)]TJ ET q -1 0 0 1 121.81 534.514 cm +1 0 0 1 121.81 626.17 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 125.247 534.315 Td [(a)]TJ +/F27 9.9626 Tf 125.247 625.971 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.551 0 Td [(The)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(v)56(ariable)-334(of)-333(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ +/F30 9.9626 Tf 137.346 0 Td [(psb)]TJ ET q -1 0 0 1 312.036 486.693 cm +1 0 0 1 278.467 578.35 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 315.174 486.494 Td [(desc)]TJ +/F30 9.9626 Tf 281.605 578.15 Td [(desc)]TJ ET q -1 0 0 1 336.723 486.693 cm +1 0 0 1 303.154 578.35 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 339.861 486.494 Td [(type)]TJ +/F30 9.9626 Tf 306.292 578.15 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +/F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -260.887 -19.925 Td [(iact)]TJ +/F27 9.9626 Tf -227.319 -31.88 Td [(mold)]TJ 0 g 0 G -/F8 9.9626 Tf 23.281 0 Td [(sp)-28(eci\014es)-333(action)-334(to)-333(b)-28(e)-333(tak)28(en)-334(in)-333(case)-333(of)-334(range)-333(errors.)-444(Scop)-28(e:)]TJ/F27 9.9626 Tf 257.147 0 Td [(global)]TJ/F8 9.9626 Tf -255.521 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-256(c)28(haracter)-255(v)56(ariable)]TJ/F30 9.9626 Tf 143.584 0 Td [(I)]TJ/F8 9.9626 Tf 5.23 0 Td [(gnore,)]TJ/F30 9.9626 Tf 29.293 0 Td [(W)]TJ/F8 9.9626 Tf 5.23 0 Td [(arning)-255(or)]TJ/F30 9.9626 Tf 41.67 0 Td [(A)]TJ/F8 9.9626 Tf 5.231 0 Td [(b)-28(ort,)-270(default)]TJ/F30 9.9626 Tf 56.741 0 Td [(I)]TJ/F8 9.9626 Tf 5.231 0 Td [(gnore.)]TJ +/F8 9.9626 Tf 29.805 0 Td [(The)-333(desired)-334(dynamic)-333(t)28(yp)-28(e)-333(for)-334(the)-333(in)28(ternal)-333(v)27(ector)-333(storage.)]TJ -4.898 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-273(as:)-414(an)-274(ob)-55(ject)-273(of)-274(a)-273(class)-273(deriv)28(ed)-274(from)]TJ/F30 9.9626 Tf 198.26 0 Td [(psb)]TJ +ET +q +1 0 0 1 339.381 498.649 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 342.519 498.449 Td [(T)]TJ +ET +q +1 0 0 1 348.377 498.649 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 351.515 498.449 Td [(base)]TJ +ET +q +1 0 0 1 373.064 498.649 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 376.202 498.449 Td [(vect)]TJ +ET +q +1 0 0 1 397.751 498.649 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 400.89 498.449 Td [(type)]TJ/F8 9.9626 Tf 20.921 0 Td [(;)-293(this)]TJ -297.009 -11.955 Td [(is)-333(only)-334(allo)28(w)28(ed)-333(when)]TJ/F11 9.9626 Tf 93.317 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(is)-333(of)-334(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 43.78 0 Td [(psb)]TJ +ET +q +1 0 0 1 287.233 486.693 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 290.371 486.494 Td [(T)]TJ +ET +q +1 0 0 1 296.229 486.693 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 299.367 486.494 Td [(vect)]TJ +ET +q +1 0 0 1 320.916 486.693 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 324.054 486.494 Td [(type)]TJ 0 g 0 G -/F27 9.9626 Tf -317.117 -21.917 Td [(On)-383(Return)]TJ +/F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G +/F27 9.9626 Tf -245.081 -21.918 Td [(On)-383(Return)]TJ 0 g 0 G - 0 -19.926 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(If)]TJ/F11 9.9626 Tf 10.133 0 Td [(y)]TJ/F8 9.9626 Tf 8.733 0 Td [(is)-350(not)-351(presen)28(t,)-355(then)]TJ/F11 9.9626 Tf 88.586 0 Td [(x)]TJ/F8 9.9626 Tf 9.185 0 Td [(is)-350(o)27(v)28(erwritten)-350(with)-351(th)1(e)-351(translated)-350(in)28(teger)-351(indices.)]TJ -102.758 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-333(in)27(teger)-333(arra)28(y)83(.)]TJ + 0 -19.925 Td [(x)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.926 Td [(y)]TJ +/F8 9.9626 Tf 11.028 0 Td [(The)-333(dense)-334(matrix)-333(to)-333(b)-28(e)-334(assem)28(bled.)]TJ 13.879 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-433(as:)-645(a)-433(rank)-433(one)-433(or)-434(t)28(w)28(o)-434(arra)28(y)-433(with)-433(the)-434(ALLOCA)84(T)83(ABLE)-433(or)-434(an)]TJ 0 -11.955 Td [(ob)-56(j)1(e)-1(ct)-333(of)-333(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 63.927 0 Td [(psb)]TJ +ET +q +1 0 0 1 205.048 385.075 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 208.186 384.875 Td [(T)]TJ +ET +q +1 0 0 1 214.044 385.075 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 217.182 384.875 Td [(vect)]TJ +ET +q +1 0 0 1 238.731 385.075 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 241.869 384.875 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(If)]TJ/F11 9.9626 Tf 10.167 0 Td [(y)]TJ/F8 9.9626 Tf 8.767 0 Td [(is)-354(not)-354(presen)28(t,)-359(then)]TJ/F11 9.9626 Tf 88.732 0 Td [(y)]TJ/F8 9.9626 Tf 8.766 0 Td [(is)-354(o)28(v)28(erwritten)-354(with)-354(the)-354(translated)-353(in)27(teger)-353(indices,)]TJ -102.553 -11.955 Td [(and)]TJ/F11 9.9626 Tf 19.372 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(is)-333(left)-334(unc)28(hanged.)-444(Scop)-28(e:)]TJ/F27 9.9626 Tf 113.242 0 Td [(global)]TJ/F8 9.9626 Tf -141.629 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-333(in)27(teger)-333(arra)28(y)83(.)]TJ +/F8 9.9626 Tf 20.922 0 Td [(,)-333(of)-334(t)28(yp)-28(e)-333(real,)-333(complex)-334(or)-333(in)28(teger.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.926 Td [(info)]TJ +/F27 9.9626 Tf -162.896 -31.88 Td [(info)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ 0 g 0 G - 141.968 -115.11 Td [(87)]TJ + 141.968 -214.736 Td [(85)]TJ 0 g 0 G ET endstream endobj -1428 0 obj +1444 0 obj << -/Length 3279 +/Length 3379 >> stream 0 g 0 G @@ -16790,78 +16675,92 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(is)]TJ -ET -q -1 0 0 1 185.644 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 189.679 706.129 Td [(o)31(wned)-375(|)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(gefree)-375(|)-375(F)94(rees)-375(a)-375(dense)-375(matrix)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -38.974 -18.389 Td [(call)-525(psb_is_owned\050x,)-525(desc_a\051)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_gefree\050x,)-525(desc_a,)-525(info\051)]TJ 0 g 0 G /F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G /F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G 0 -19.925 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(In)28(teger)-334(ind)1(e)-1(x.)]TJ 13.879 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-334(scalar)-333(in)28(teger.)]TJ +/F8 9.9626 Tf 11.028 0 Td [(The)-333(dense)-334(matrix)-333(to)-333(b)-28(e)-333(free)-1(d)1(.)]TJ 13.879 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-433(as:)-645(a)-433(rank)-433(one)-433(or)-434(t)28(w)28(o)-434(arr)1(a)27(y)-433(with)-433(the)-434(ALLOCA)84(T)83(ABLE)-433(or)-434(an)]TJ 0 -11.955 Td [(ob)-55(jec)-1(t)-333(of)-333(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 63.927 0 Td [(psb)]TJ +ET +q +1 0 0 1 255.857 566.395 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 258.995 566.195 Td [(T)]TJ +ET +q +1 0 0 1 264.853 566.395 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 267.992 566.195 Td [(vect)]TJ +ET +q +1 0 0 1 289.541 566.395 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 292.679 566.195 Td [(type)]TJ +0 g 0 G +/F8 9.9626 Tf 20.921 0 Td [(,)-333(of)-334(t)28(yp)-28(e)-333(real,)-333(complex)-334(or)-333(in)28(teger.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -31.88 Td [(desc)]TJ +/F27 9.9626 Tf -162.895 -31.88 Td [(desc)]TJ ET q -1 0 0 1 172.619 546.469 cm +1 0 0 1 172.619 534.514 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 176.057 546.27 Td [(a)]TJ +/F27 9.9626 Tf 176.057 534.315 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.55 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.55 0 Td [(The)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(v)56(ariable)-334(of)-333(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ +/F30 9.9626 Tf 137.347 0 Td [(psb)]TJ ET q -1 0 0 1 362.845 498.649 cm +1 0 0 1 329.276 486.693 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 365.983 498.449 Td [(desc)]TJ +/F30 9.9626 Tf 332.415 486.494 Td [(desc)]TJ ET q -1 0 0 1 387.532 498.649 cm +1 0 0 1 353.964 486.693 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 390.67 498.449 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -260.887 -21.917 Td [(On)-383(Return)]TJ +/F30 9.9626 Tf 357.102 486.494 Td [(type)]TJ 0 g 0 G +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G - 0 -19.926 Td [(F)96(unction)-384(v)64(alue)]TJ +/F27 9.9626 Tf -227.318 -33.873 Td [(On)-383(Return)]TJ 0 g 0 G -/F8 9.9626 Tf 78.386 0 Td [(A)-302(logical)-301(mask)-302(whic)28(h)-302(is)-302(tru)1(e)-302(if)]TJ/F11 9.9626 Tf 134.085 0 Td [(x)]TJ/F8 9.9626 Tf 8.7 0 Td [(is)-302(o)28(wned)-302(b)28(y)-301(the)-302(curren)28(t)-302(pro-)]TJ -196.265 -11.955 Td [(cess)-334(Scop)-27(e:)]TJ/F27 9.9626 Tf 52.415 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -52.415 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ/F16 11.9552 Tf -74.941 -33.873 Td [(Notes)]TJ 0 g 0 G -/F8 9.9626 Tf 12.176 -19.926 Td [(1.)]TJ + 0 -19.925 Td [(info)]TJ 0 g 0 G - [-500(This)-300(routine)-300(r)1(e)-1(tu)1(rns)-300(a)]TJ/F30 9.9626 Tf 111.214 0 Td [(.true.)]TJ/F8 9.9626 Tf 34.368 0 Td [(v)56(alue)-300(for)-300(an)-300(index)-299(that)-300(is)-300(strictly)-300(o)28(wned)-300(b)28(y)]TJ -132.852 -11.955 Td [(the)-333(curren)27(t)-333(pro)-28(cess,)-333(excluding)-333(the)-334(halo)-333(indices)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ 0 g 0 G - 141.968 -264.549 Td [(88)]TJ + 141.968 -294.437 Td [(86)]TJ 0 g 0 G ET endstream endobj -1434 0 obj +1448 0 obj << -/Length 4979 +/Length 3437 >> stream 0 g 0 G @@ -16874,17 +16773,10 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(o)31(wned)]TJ -ET -q -1 0 0 1 162.939 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 166.974 706.129 Td [(index)-375(|)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(gelp)-375(|)-375(Applies)-375(a)-375(left)-375(p)-31(erm)31(utation)-375(to)-375(a)-375(dense)-375(matrix)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -67.079 -18.389 Td [(call)-525(psb_owned_index\050y,)-525(x,)-525(desc_a,)-525(info\051)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_gelp\050trans,)-525(iperm,)-525(x,)-525(info\051)]TJ 0 g 0 G /F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G @@ -16893,307 +16785,85 @@ BT /F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(x)]TJ + 0 -19.925 Td [(trans)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(In)28(teger)-334(indices.)]TJ 13.879 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in,)-383(inout)]TJ/F8 9.9626 Tf 42.645 0 Td [(.)]TJ -76.131 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(scalar)-333(or)-334(a)-333(rank)-333(one)-333(in)27(teger)-333(arra)28(y)83(.)]TJ +/F8 9.9626 Tf 30.609 0 Td [(A)-333(c)27(haracter)-333(that)-333(sp)-28(eci\014es)-333(whether)-334(to)-333(p)-28(erm)28(ute)]TJ/F11 9.9626 Tf 204.179 0 Td [(A)]TJ/F8 9.9626 Tf 10.793 0 Td [(or)]TJ/F11 9.9626 Tf 12.204 0 Td [(A)]TJ/F10 6.9738 Tf 7.472 3.616 Td [(T)]TJ/F8 9.9626 Tf 6.276 -3.616 Td [(.)]TJ -246.626 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(single)-333(c)28(haracte)-1(r)-333(with)-333(v)55(alu)1(e)-334('N')-333(for)]TJ/F11 9.9626 Tf 217.435 0 Td [(A)]TJ/F8 9.9626 Tf 10.793 0 Td [(or)-333('T')-334(for)]TJ/F11 9.9626 Tf 43.503 0 Td [(A)]TJ/F10 6.9738 Tf 7.472 3.616 Td [(T)]TJ/F8 9.9626 Tf 6.277 -3.616 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -31.88 Td [(desc)]TJ -ET -q -1 0 0 1 121.81 546.469 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 125.247 546.27 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ -ET -q -1 0 0 1 312.036 498.649 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 315.174 498.449 Td [(desc)]TJ -ET -q -1 0 0 1 336.723 498.649 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 339.861 498.449 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -260.887 -19.925 Td [(iact)]TJ -0 g 0 G -/F8 9.9626 Tf 23.281 0 Td [(sp)-28(eci\014es)-333(action)-334(to)-333(b)-28(e)-333(tak)28(en)-334(in)-333(case)-333(of)-334(range)-333(errors.)-444(Scop)-28(e:)]TJ/F27 9.9626 Tf 257.147 0 Td [(global)]TJ/F8 9.9626 Tf -255.521 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-256(c)28(haracter)-255(v)56(ariable)]TJ/F30 9.9626 Tf 143.584 0 Td [(I)]TJ/F8 9.9626 Tf 5.23 0 Td [(gnore,)]TJ/F30 9.9626 Tf 29.293 0 Td [(W)]TJ/F8 9.9626 Tf 5.23 0 Td [(arning)-255(or)]TJ/F30 9.9626 Tf 41.67 0 Td [(A)]TJ/F8 9.9626 Tf 5.231 0 Td [(b)-28(ort,)-270(default)]TJ/F30 9.9626 Tf 56.741 0 Td [(I)]TJ/F8 9.9626 Tf 5.231 0 Td [(gnore.)]TJ -0 g 0 G -/F27 9.9626 Tf -317.117 -21.918 Td [(On)-383(Return)]TJ -0 g 0 G -0 g 0 G - 0 -19.926 Td [(y)]TJ -0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(A)-294(logical)-294(mask)-294(whic)28(h)-294(is)-294(true)-294(for)-294(all)-294(corresp)-28(onding)-294(en)28(tries)-294(of)]TJ/F11 9.9626 Tf 259.229 0 Td [(x)]TJ/F8 9.9626 Tf 8.623 0 Td [(that)-294(are)-294(o)28(wned)]TJ -253.973 -11.955 Td [(b)28(y)-333(the)-334(curren)28(t)-333(pro)-28(cess)-334(Scop)-27(e:)]TJ/F27 9.9626 Tf 132.752 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -132.752 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(scalar)-333(or)-334(ran)1(k)-334(one)-333(logical)-333(arra)27(y)84(.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -19.926 Td [(info)]TJ -0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ -0 g 0 G -/F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ -0 g 0 G - [-500(This)-475(routine)-474(returns)-475(a)]TJ/F30 9.9626 Tf 118.186 0 Td [(.true.)]TJ/F8 9.9626 Tf 36.111 0 Td [(v)56(alue)-475(for)-475(those)-475(indices)-474(that)-475(are)-475(strictly)]TJ -141.567 -11.955 Td [(o)28(wned)-334(b)28(y)-333(the)-333(curren)27(t)-333(pro)-28(cess,)-333(excluding)-333(the)-334(halo)-333(indices)]TJ -0 g 0 G - 141.968 -141.013 Td [(89)]TJ -0 g 0 G -ET - -endstream -endobj -1440 0 obj -<< -/Length 3247 ->> -stream -0 g 0 G -0 g 0 G -BT -/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ -ET -q -1 0 0 1 171.761 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 175.796 706.129 Td [(is)]TJ -ET -q -1 0 0 1 185.644 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 189.679 706.129 Td [(lo)-31(cal)-375(|)]TJ -0 g 0 G -0 g 0 G -/F30 9.9626 Tf -38.974 -18.389 Td [(call)-525(psb_is_local\050x,)-525(desc_a\051)]TJ -0 g 0 G -/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ -0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ -0 g 0 G -/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ -0 g 0 G -0 g 0 G - 0 -19.925 Td [(x)]TJ -0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(In)28(teger)-334(ind)1(e)-1(x.)]TJ 13.879 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-334(scalar)-333(in)28(teger.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -31.88 Td [(desc)]TJ -ET -q -1 0 0 1 172.619 546.469 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 176.057 546.27 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.55 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ -ET -q -1 0 0 1 362.845 498.649 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 365.983 498.449 Td [(desc)]TJ -ET -q -1 0 0 1 387.532 498.649 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 390.67 498.449 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -260.887 -21.917 Td [(On)-383(Return)]TJ -0 g 0 G -0 g 0 G - 0 -19.926 Td [(F)96(unction)-384(v)64(alue)]TJ -0 g 0 G -/F8 9.9626 Tf 78.386 0 Td [(A)-264(logical)-265(mask)-264(whic)27(h)-264(is)-265(true)-264(if)]TJ/F11 9.9626 Tf 131.492 0 Td [(x)]TJ/F8 9.9626 Tf 8.329 0 Td [(is)-265(lo)-27(cal)-265(to)-264(the)-265(curren)28(t)-264(pro)-28(cess)]TJ -193.301 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ/F16 11.9552 Tf -74.941 -33.873 Td [(Notes)]TJ -0 g 0 G -/F8 9.9626 Tf 12.176 -19.926 Td [(1.)]TJ -0 g 0 G - [-500(This)-239(routine)-239(returns)-239(a)]TJ/F30 9.9626 Tf 108.787 0 Td [(.true.)]TJ/F8 9.9626 Tf 33.762 0 Td [(v)56(alue)-239(for)-239(an)-239(index)-239(that)-239(is)-239(lo)-27(cal)-239(to)-239(the)-239(curren)28(t)]TJ -129.819 -11.955 Td [(pro)-28(cess,)-333(including)-333(the)-334(halo)-333(indices)]TJ -0 g 0 G - 141.968 -264.549 Td [(90)]TJ -0 g 0 G -ET - -endstream -endobj -1446 0 obj -<< -/Length 4963 ->> -stream -0 g 0 G -0 g 0 G -BT -/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ -ET -q -1 0 0 1 120.951 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 124.986 706.129 Td [(lo)-31(cal)]TJ -ET -q -1 0 0 1 152.879 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 156.914 706.129 Td [(index)-375(|)]TJ -0 g 0 G -0 g 0 G -/F30 9.9626 Tf -57.019 -18.389 Td [(call)-525(psb_local_index\050y,)-525(x,)-525(desc_a,)-525(info\051)]TJ -0 g 0 G -/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ -0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ -0 g 0 G -/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ -0 g 0 G -0 g 0 G - 0 -19.925 Td [(x)]TJ -0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(In)28(teger)-334(indices.)]TJ 13.879 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in,)-383(inout)]TJ/F8 9.9626 Tf 42.645 0 Td [(.)]TJ -76.131 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(scalar)-333(or)-334(a)-333(rank)-333(one)-333(in)27(teger)-333(arra)28(y)83(.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -31.88 Td [(desc)]TJ -ET -q -1 0 0 1 121.81 546.469 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 125.247 546.27 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ -ET -q -1 0 0 1 312.036 498.649 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 315.174 498.449 Td [(desc)]TJ -ET -q -1 0 0 1 336.723 498.649 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 339.861 498.449 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -260.887 -19.925 Td [(iact)]TJ +/F27 9.9626 Tf -310.387 -31.88 Td [(ip)-32(erm)]TJ 0 g 0 G -/F8 9.9626 Tf 23.281 0 Td [(sp)-28(eci\014es)-333(action)-334(to)-333(b)-28(e)-333(tak)28(en)-334(in)-333(case)-333(of)-334(range)-333(errors.)-444(Scop)-28(e:)]TJ/F27 9.9626 Tf 257.147 0 Td [(global)]TJ/F8 9.9626 Tf -255.521 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-256(c)28(haracter)-255(v)56(ariable)]TJ/F30 9.9626 Tf 143.584 0 Td [(I)]TJ/F8 9.9626 Tf 5.23 0 Td [(gnore,)]TJ/F30 9.9626 Tf 29.293 0 Td [(W)]TJ/F8 9.9626 Tf 5.23 0 Td [(arning)-255(or)]TJ/F30 9.9626 Tf 41.67 0 Td [(A)]TJ/F8 9.9626 Tf 5.231 0 Td [(b)-28(ort,)-270(default)]TJ/F30 9.9626 Tf 56.741 0 Td [(I)]TJ/F8 9.9626 Tf 5.231 0 Td [(gnore.)]TJ +/F8 9.9626 Tf 34.364 0 Td [(An)-333(in)28(te)-1(ger)-333(arra)28(y)-333(con)27(tainin)1(g)-334(p)-28(erm)28(utation)-333(information.)]TJ -9.457 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(one-dimensional)-334(arra)28(y)83(.)]TJ 0 g 0 G -/F27 9.9626 Tf -317.117 -21.918 Td [(On)-383(Return)]TJ -0 g 0 G -0 g 0 G - 0 -19.926 Td [(y)]TJ +/F27 9.9626 Tf -24.907 -31.88 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(A)-346(logical)-345(mask)-346(whic)28(h)-346(is)-345(true)-346(for)-345(all)-346(corresp)-28(onding)-345(en)28(tries)-346(of)]TJ/F11 9.9626 Tf 264.883 0 Td [(x)]TJ/F8 9.9626 Tf 9.136 0 Td [(that)-346(are)-345(lo)-28(cal)]TJ -260.14 -11.955 Td [(to)-333(the)-334(curren)28(t)-333(pro)-28(cess)-333(Scop)-28(e:)]TJ/F27 9.9626 Tf 131.092 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -131.092 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(scalar)-333(or)-334(ran)1(k)-334(one)-333(logical)-333(arra)27(y)84(.)]TJ +/F8 9.9626 Tf 11.028 0 Td [(The)-333(dense)-334(matrix)-333(to)-333(b)-28(e)-334(p)-27(erm)27(ut)1(e)-1(d.)]TJ 13.879 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(one)-333(or)-334(t)28(w)28(o)-333(dimensional)-334(arra)28(y)84(.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.926 Td [(info)]TJ +/F27 9.9626 Tf -24.907 -33.873 Td [(On)-383(Return)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ 0 g 0 G -/F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ + 0 -19.925 Td [(info)]TJ 0 g 0 G - [-500(This)-308(routine)-309(retur)1(ns)-309(a)]TJ/F30 9.9626 Tf 111.554 0 Td [(.true.)]TJ/F8 9.9626 Tf 34.454 0 Td [(v)56(alue)-309(for)-308(those)-308(indices)-309(that)-308(are)-308(lo)-28(cal)-308(to)-309(the)]TJ -133.278 -11.955 Td [(curren)28(t)-333(pro)-28(cess,)-334(including)-333(the)-333(halo)-333(indices.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ 0 g 0 G - 141.968 -141.013 Td [(91)]TJ + 141.968 -226.691 Td [(87)]TJ 0 g 0 G ET endstream endobj -1342 0 obj +1347 0 obj << /Type /ObjStm /N 100 -/First 974 -/Length 10880 +/First 976 +/Length 10633 >> stream -1340 0 1341 59 1329 118 1346 237 1343 385 1344 531 1348 676 320 734 1345 791 1350 897 -1352 1015 1353 1074 1354 1133 1355 1192 1356 1251 1357 1310 1358 1369 1349 1427 1362 1507 1359 1655 -1360 1799 1364 1946 324 2004 1361 2061 1368 2167 1365 2315 1366 2459 1370 2605 328 2664 1371 2722 -1367 2781 1375 2887 1372 3035 1373 3180 1377 3324 332 3382 1374 3439 1382 3558 1379 3706 1380 3852 -1384 3996 336 4055 1381 4113 1386 4232 1388 4350 1389 4408 1390 4466 1385 4524 1395 4617 1391 4774 -1392 4920 1393 5064 1397 5207 340 5266 1394 5324 1401 5443 1398 5591 1399 5734 1403 5880 344 5938 -1400 5995 1405 6101 1407 6219 348 6278 1404 6336 1410 6468 1408 6607 1412 6753 352 6811 1409 6868 -1415 6987 1417 7105 1418 7164 1419 7223 1414 7282 1422 7362 1420 7501 1424 7648 356 7706 1421 7763 -1427 7882 1425 8021 1429 8167 360 8226 1430 8284 1426 8343 1433 8462 1431 8601 1435 8748 364 8806 -1436 8863 1432 8921 1439 9040 1437 9179 1441 9325 368 9384 1442 9442 1438 9501 1445 9620 1443 9759 -% 1340 0 obj -<< -/D [1330 0 R /XYZ 150.705 255.873 null] ->> -% 1341 0 obj -<< -/D [1330 0 R /XYZ 150.705 212.037 null] ->> -% 1329 0 obj -<< -/Font << /F27 556 0 R /F8 557 0 R /F30 764 0 R /F16 554 0 R /F11 750 0 R >> -/ProcSet [ /PDF /Text ] ->> -% 1346 0 obj +1344 0 1341 148 1342 292 1346 439 308 497 1343 554 1350 686 1352 804 1353 863 1354 922 +1349 981 1358 1061 1355 1209 1356 1355 1360 1498 312 1556 1361 1613 1362 1671 1363 1729 1357 1787 +1368 1906 1364 2054 1365 2201 1370 2344 316 2403 1367 2461 1372 2580 1366 2719 1374 2865 1375 2923 +1376 2981 1377 3039 1378 3097 1379 3154 1380 3212 1381 3270 1382 3328 1383 3386 1371 3444 1387 3563 +1384 3711 1385 3856 1389 4000 320 4059 1386 4117 1391 4223 1393 4341 1394 4399 1395 4457 1396 4515 +1397 4573 1398 4631 1399 4689 1390 4746 1404 4826 1401 4974 1402 5117 1406 5263 324 5322 1403 5380 +1410 5486 1407 5634 1408 5779 1412 5926 328 5984 1413 6041 1409 6099 1417 6205 1414 6353 1415 6499 +1419 6643 332 6702 1416 6760 1423 6879 1420 7027 1421 7174 1425 7318 336 7376 1422 7433 1427 7552 +1429 7670 1430 7729 1431 7788 1426 7847 1436 7940 1432 8097 1433 8242 1434 8386 1438 8529 340 8587 +1435 8644 1443 8763 1440 8911 1441 9054 1445 9201 344 9260 1442 9318 1447 9424 1449 9542 348 9600 +% 1344 0 obj << /Type /Page -/Contents 1347 0 R -/Resources 1345 0 R +/Contents 1345 0 R +/Resources 1343 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1328 0 R -/Annots [ 1343 0 R 1344 0 R ] +/Parent 1348 0 R +/Annots [ 1341 0 R 1342 0 R ] >> -% 1343 0 obj +% 1341 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 576.23 361.779 587.355] -/A << /S /GoTo /D (descdata) >> +/Rect [294.721 453.24 372.239 464.364] +/A << /S /GoTo /D (spdata) >> >> -% 1344 0 obj +% 1342 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 205.776 372.239 216.901] -/A << /S /GoTo /D (spdata) >> +/Rect [294.721 209.896 361.779 221.021] +/A << /S /GoTo /D (descdata) >> >> -% 1348 0 obj +% 1346 0 obj << -/D [1346 0 R /XYZ 98.895 753.953 null] +/D [1344 0 R /XYZ 98.895 753.953 null] >> -% 320 0 obj +% 308 0 obj << -/D [1346 0 R /XYZ 99.895 720.077 null] +/D [1344 0 R /XYZ 99.895 720.077 null] >> -% 1345 0 obj +% 1343 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F27 560 0 R /F11 755 0 R /F14 772 0 R >> /ProcSet [ /PDF /Text ] >> % 1350 0 obj @@ -17202,7 +16872,7 @@ stream /Contents 1351 0 R /Resources 1349 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1328 0 R +/Parent 1348 0 R >> % 1352 0 obj << @@ -17214,65 +16884,61 @@ stream >> % 1354 0 obj << -/D [1350 0 R /XYZ 150.705 687.975 null] ->> -% 1355 0 obj -<< -/D [1350 0 R /XYZ 150.705 668.326 null] ->> -% 1356 0 obj -<< -/D [1350 0 R /XYZ 150.705 624.491 null] ->> -% 1357 0 obj -<< -/D [1350 0 R /XYZ 150.705 580.655 null] ->> -% 1358 0 obj -<< -/D [1350 0 R /XYZ 150.705 560.73 null] +/D [1350 0 R /XYZ 150.705 664.341 null] >> % 1349 0 obj << -/Font << /F8 557 0 R /F30 764 0 R >> +/Font << /F8 561 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 1362 0 obj +% 1358 0 obj << /Type /Page -/Contents 1363 0 R -/Resources 1361 0 R +/Contents 1359 0 R +/Resources 1357 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1328 0 R -/Annots [ 1359 0 R 1360 0 R ] +/Parent 1348 0 R +/Annots [ 1355 0 R 1356 0 R ] >> -% 1359 0 obj +% 1355 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 574.94 372.239 586.065] -/A << /S /GoTo /D (spdata) >> +/Rect [294.721 574.94 361.779 586.065] +/A << /S /GoTo /D (descdata) >> >> -% 1360 0 obj +% 1356 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 507.194 361.779 518.319] -/A << /S /GoTo /D (descdata) >> +/Rect [294.721 405.575 372.239 416.7] +/A << /S /GoTo /D (spdata) >> >> -% 1364 0 obj +% 1360 0 obj << -/D [1362 0 R /XYZ 98.895 753.953 null] +/D [1358 0 R /XYZ 98.895 753.953 null] >> -% 324 0 obj +% 312 0 obj << -/D [1362 0 R /XYZ 99.895 720.077 null] +/D [1358 0 R /XYZ 99.895 720.077 null] >> % 1361 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R >> +/D [1358 0 R /XYZ 99.895 315.137 null] +>> +% 1362 0 obj +<< +/D [1358 0 R /XYZ 99.895 293.274 null] +>> +% 1363 0 obj +<< +/D [1358 0 R /XYZ 99.895 273.349 null] +>> +% 1357 0 obj +<< +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R /F11 755 0 R >> /ProcSet [ /PDF /Text ] >> % 1368 0 obj @@ -17281,246 +16947,215 @@ stream /Contents 1369 0 R /Resources 1367 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1328 0 R -/Annots [ 1365 0 R 1366 0 R ] +/Parent 1348 0 R +/Annots [ 1364 0 R 1365 0 R ] >> -% 1365 0 obj +% 1364 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.53 560.993 423.049 572.118] -/A << /S /GoTo /D (spdata) >> +/Rect [311.962 288.004 379.019 299.129] +/A << /S /GoTo /D (descdata) >> >> -% 1366 0 obj +% 1365 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.53 493.247 412.588 504.372] -/A << /S /GoTo /D (descdata) >> +/Rect [345.53 117.115 423.049 128.24] +/A << /S /GoTo /D (spdata) >> >> % 1370 0 obj << /D [1368 0 R /XYZ 149.705 753.953 null] >> -% 328 0 obj +% 316 0 obj << /D [1368 0 R /XYZ 150.705 720.077 null] >> -% 1371 0 obj -<< -/D [1368 0 R /XYZ 150.705 313.144 null] ->> % 1367 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R /F11 755 0 R >> /ProcSet [ /PDF /Text ] >> -% 1375 0 obj +% 1372 0 obj << /Type /Page -/Contents 1376 0 R -/Resources 1374 0 R +/Contents 1373 0 R +/Resources 1371 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1378 0 R -/Annots [ 1372 0 R 1373 0 R ] +/Parent 1348 0 R +/Annots [ 1366 0 R ] >> -% 1372 0 obj +% 1366 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [261.152 574.94 328.21 586.065] +/Rect [261.152 655.098 328.21 666.223] /A << /S /GoTo /D (descdata) >> >> -% 1373 0 obj +% 1374 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [213.774 290.009 289.828 301.134] -/A << /S /GoTo /D (vdata) >> +/D [1372 0 R /XYZ 98.895 753.953 null] >> -% 1377 0 obj +% 1375 0 obj << -/D [1375 0 R /XYZ 98.895 753.953 null] +/D [1372 0 R /XYZ 99.895 552.704 null] >> -% 332 0 obj +% 1376 0 obj << -/D [1375 0 R /XYZ 99.895 720.077 null] +/D [1372 0 R /XYZ 99.895 520.824 null] >> -% 1374 0 obj +% 1377 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R /F11 750 0 R >> -/ProcSet [ /PDF /Text ] +/D [1372 0 R /XYZ 99.895 487.006 null] >> -% 1382 0 obj +% 1378 0 obj << -/Type /Page -/Contents 1383 0 R -/Resources 1381 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1378 0 R -/Annots [ 1379 0 R 1380 0 R ] +/D [1372 0 R /XYZ 99.895 419.26 null] >> % 1379 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.53 363.459 412.588 374.584] -/A << /S /GoTo /D (descdata) >> +/D [1372 0 R /XYZ 99.895 363.469 null] >> % 1380 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [416.591 141.026 492.645 152.151] -/A << /S /GoTo /D (vdata) >> +/D [1372 0 R /XYZ 99.895 319.634 null] >> -% 1384 0 obj +% 1381 0 obj << -/D [1382 0 R /XYZ 149.705 753.953 null] +/D [1372 0 R /XYZ 99.895 287.753 null] >> -% 336 0 obj +% 1382 0 obj << -/D [1382 0 R /XYZ 150.705 720.077 null] +/D [1372 0 R /XYZ 99.895 255.873 null] >> -% 1381 0 obj +% 1383 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R /F11 750 0 R >> +/D [1372 0 R /XYZ 99.895 212.037 null] +>> +% 1371 0 obj +<< +/Font << /F27 560 0 R /F8 561 0 R /F30 769 0 R /F16 558 0 R /F11 755 0 R >> /ProcSet [ /PDF /Text ] >> -% 1386 0 obj +% 1387 0 obj << /Type /Page -/Contents 1387 0 R -/Resources 1385 0 R +/Contents 1388 0 R +/Resources 1386 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1378 0 R +/Parent 1348 0 R +/Annots [ 1384 0 R 1385 0 R ] >> -% 1388 0 obj +% 1384 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [345.53 576.23 412.588 587.355] +/A << /S /GoTo /D (descdata) >> +>> +% 1385 0 obj << -/D [1386 0 R /XYZ 98.895 753.953 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [345.53 205.776 423.049 216.901] +/A << /S /GoTo /D (spdata) >> >> % 1389 0 obj << -/D [1386 0 R /XYZ 99.895 632.405 null] +/D [1387 0 R /XYZ 149.705 753.953 null] >> -% 1390 0 obj +% 320 0 obj << -/D [1386 0 R /XYZ 99.895 609.989 null] +/D [1387 0 R /XYZ 150.705 720.077 null] >> -% 1385 0 obj +% 1386 0 obj << -/Font << /F27 556 0 R /F8 557 0 R /F16 554 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 1395 0 obj +% 1391 0 obj << /Type /Page -/Contents 1396 0 R -/Resources 1394 0 R +/Contents 1392 0 R +/Resources 1390 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1378 0 R -/Annots [ 1391 0 R 1392 0 R 1393 0 R ] +/Parent 1400 0 R >> -% 1391 0 obj +% 1393 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [311.962 574.94 379.019 586.065] -/A << /S /GoTo /D (descdata) >> +/D [1391 0 R /XYZ 98.895 753.953 null] >> -% 1392 0 obj +% 1394 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [320.727 483.284 396.781 494.409] -/A << /S /GoTo /D (vdata) >> +/D [1391 0 R /XYZ 99.895 716.092 null] >> -% 1393 0 obj +% 1395 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [238.542 381.665 314.596 392.79] -/A << /S /GoTo /D (vdata) >> +/D [1391 0 R /XYZ 99.895 687.975 null] +>> +% 1396 0 obj +<< +/D [1391 0 R /XYZ 99.895 668.326 null] >> % 1397 0 obj << -/D [1395 0 R /XYZ 149.705 753.953 null] +/D [1391 0 R /XYZ 99.895 624.491 null] >> -% 340 0 obj +% 1398 0 obj << -/D [1395 0 R /XYZ 150.705 720.077 null] +/D [1391 0 R /XYZ 99.895 580.655 null] >> -% 1394 0 obj +% 1399 0 obj +<< +/D [1391 0 R /XYZ 99.895 560.73 null] +>> +% 1390 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R /F11 750 0 R >> +/Font << /F8 561 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 1401 0 obj +% 1404 0 obj << /Type /Page -/Contents 1402 0 R -/Resources 1400 0 R +/Contents 1405 0 R +/Resources 1403 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1378 0 R -/Annots [ 1398 0 R 1399 0 R ] +/Parent 1400 0 R +/Annots [ 1401 0 R 1402 0 R ] >> -% 1398 0 obj +% 1401 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [187.733 562.985 263.787 574.11] -/A << /S /GoTo /D (vdata) >> +/Rect [345.53 574.94 423.049 586.065] +/A << /S /GoTo /D (spdata) >> >> -% 1399 0 obj +% 1402 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [261.152 483.284 328.21 494.409] +/Rect [345.53 507.194 412.588 518.319] /A << /S /GoTo /D (descdata) >> >> -% 1403 0 obj -<< -/D [1401 0 R /XYZ 98.895 753.953 null] ->> -% 344 0 obj -<< -/D [1401 0 R /XYZ 99.895 720.077 null] ->> -% 1400 0 obj -<< -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R >> -/ProcSet [ /PDF /Text ] ->> -% 1405 0 obj -<< -/Type /Page -/Contents 1406 0 R -/Resources 1404 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1378 0 R ->> -% 1407 0 obj +% 1406 0 obj << -/D [1405 0 R /XYZ 149.705 753.953 null] +/D [1404 0 R /XYZ 149.705 753.953 null] >> -% 348 0 obj +% 324 0 obj << -/D [1405 0 R /XYZ 150.705 720.077 null] +/D [1404 0 R /XYZ 150.705 720.077 null] >> -% 1404 0 obj +% 1403 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R /F11 750 0 R /F10 766 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> % 1410 0 obj @@ -17529,83 +17164,116 @@ stream /Contents 1411 0 R /Resources 1409 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1413 0 R -/Annots [ 1408 0 R ] +/Parent 1400 0 R +/Annots [ 1407 0 R 1408 0 R ] +>> +% 1407 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [294.721 560.993 372.239 572.118] +/A << /S /GoTo /D (spdata) >> >> % 1408 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 484.86 361.779 495.985] +/Rect [294.721 493.247 361.779 504.372] /A << /S /GoTo /D (descdata) >> >> % 1412 0 obj << /D [1410 0 R /XYZ 98.895 753.953 null] >> -% 352 0 obj +% 328 0 obj << /D [1410 0 R /XYZ 99.895 720.077 null] >> +% 1413 0 obj +<< +/D [1410 0 R /XYZ 99.895 313.144 null] +>> % 1409 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R /F11 750 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 1415 0 obj +% 1417 0 obj << /Type /Page -/Contents 1416 0 R -/Resources 1414 0 R +/Contents 1418 0 R +/Resources 1416 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1413 0 R +/Parent 1400 0 R +/Annots [ 1414 0 R 1415 0 R ] >> -% 1417 0 obj +% 1414 0 obj << -/D [1415 0 R /XYZ 149.705 753.953 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [311.962 574.94 379.019 586.065] +/A << /S /GoTo /D (descdata) >> >> -% 1418 0 obj +% 1415 0 obj << -/D [1415 0 R /XYZ 150.705 716.092 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [264.584 290.009 340.638 301.134] +/A << /S /GoTo /D (vdata) >> >> % 1419 0 obj << -/D [1415 0 R /XYZ 150.705 688.251 null] +/D [1417 0 R /XYZ 149.705 753.953 null] >> -% 1414 0 obj +% 332 0 obj +<< +/D [1417 0 R /XYZ 150.705 720.077 null] +>> +% 1416 0 obj << -/Font << /F8 557 0 R /F30 764 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R /F11 755 0 R >> /ProcSet [ /PDF /Text ] >> -% 1422 0 obj +% 1423 0 obj << /Type /Page -/Contents 1423 0 R -/Resources 1421 0 R +/Contents 1424 0 R +/Resources 1422 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1413 0 R -/Annots [ 1420 0 R ] +/Parent 1400 0 R +/Annots [ 1420 0 R 1421 0 R ] >> % 1420 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 483.284 361.779 494.409] +/Rect [294.721 363.459 361.779 374.584] /A << /S /GoTo /D (descdata) >> >> -% 1424 0 obj +% 1421 0 obj << -/D [1422 0 R /XYZ 98.895 753.953 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [365.781 141.026 441.835 152.151] +/A << /S /GoTo /D (vdata) >> >> -% 356 0 obj +% 1425 0 obj << -/D [1422 0 R /XYZ 99.895 720.077 null] +/D [1423 0 R /XYZ 98.895 753.953 null] >> -% 1421 0 obj +% 336 0 obj +<< +/D [1423 0 R /XYZ 99.895 720.077 null] +>> +% 1422 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R /F11 750 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R /F11 755 0 R >> /ProcSet [ /PDF /Text ] >> % 1427 0 obj @@ -17614,125 +17282,131 @@ stream /Contents 1428 0 R /Resources 1426 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1413 0 R -/Annots [ 1425 0 R ] ->> -% 1425 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.53 495.239 412.588 506.364] -/A << /S /GoTo /D (descdata) >> +/Parent 1400 0 R >> % 1429 0 obj << /D [1427 0 R /XYZ 149.705 753.953 null] >> -% 360 0 obj +% 1430 0 obj << -/D [1427 0 R /XYZ 150.705 720.077 null] +/D [1427 0 R /XYZ 150.705 632.405 null] >> -% 1430 0 obj +% 1431 0 obj << -/D [1427 0 R /XYZ 150.705 382.883 null] +/D [1427 0 R /XYZ 150.705 609.989 null] >> % 1426 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R /F11 750 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F16 558 0 R >> /ProcSet [ /PDF /Text ] >> -% 1433 0 obj +% 1436 0 obj << /Type /Page -/Contents 1434 0 R -/Resources 1432 0 R +/Contents 1437 0 R +/Resources 1435 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1413 0 R -/Annots [ 1431 0 R ] +/Parent 1439 0 R +/Annots [ 1432 0 R 1433 0 R 1434 0 R ] >> -% 1431 0 obj +% 1432 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 495.239 361.779 506.364] +/Rect [261.152 574.94 328.21 586.065] /A << /S /GoTo /D (descdata) >> >> -% 1435 0 obj +% 1433 0 obj << -/D [1433 0 R /XYZ 98.895 753.953 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [269.918 483.284 345.972 494.409] +/A << /S /GoTo /D (vdata) >> >> -% 364 0 obj +% 1434 0 obj << -/D [1433 0 R /XYZ 99.895 720.077 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [187.733 381.665 263.787 392.79] +/A << /S /GoTo /D (vdata) >> >> -% 1436 0 obj +% 1438 0 obj << -/D [1433 0 R /XYZ 99.895 259.346 null] +/D [1436 0 R /XYZ 98.895 753.953 null] >> -% 1432 0 obj +% 340 0 obj +<< +/D [1436 0 R /XYZ 99.895 720.077 null] +>> +% 1435 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R /F11 750 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R /F11 755 0 R >> /ProcSet [ /PDF /Text ] >> -% 1439 0 obj +% 1443 0 obj << /Type /Page -/Contents 1440 0 R -/Resources 1438 0 R +/Contents 1444 0 R +/Resources 1442 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1413 0 R -/Annots [ 1437 0 R ] +/Parent 1439 0 R +/Annots [ 1440 0 R 1441 0 R ] >> -% 1437 0 obj +% 1440 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.53 495.239 412.588 506.364] -/A << /S /GoTo /D (descdata) >> +/Rect [238.542 562.985 314.596 574.11] +/A << /S /GoTo /D (vdata) >> >> % 1441 0 obj << -/D [1439 0 R /XYZ 149.705 753.953 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [311.962 483.284 379.019 494.409] +/A << /S /GoTo /D (descdata) >> >> -% 368 0 obj +% 1445 0 obj << -/D [1439 0 R /XYZ 150.705 720.077 null] +/D [1443 0 R /XYZ 149.705 753.953 null] >> -% 1442 0 obj +% 344 0 obj << -/D [1439 0 R /XYZ 150.705 382.883 null] +/D [1443 0 R /XYZ 150.705 720.077 null] >> -% 1438 0 obj +% 1442 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R /F11 750 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 1445 0 obj +% 1447 0 obj << /Type /Page -/Contents 1446 0 R -/Resources 1444 0 R +/Contents 1448 0 R +/Resources 1446 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1449 0 R -/Annots [ 1443 0 R ] +/Parent 1439 0 R >> -% 1443 0 obj +% 1449 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 495.239 361.779 506.364] -/A << /S /GoTo /D (descdata) >> +/D [1447 0 R /XYZ 98.895 753.953 null] +>> +% 348 0 obj +<< +/D [1447 0 R /XYZ 99.895 720.077 null] >> endstream endobj 1454 0 obj << -/Length 3804 +/Length 6547 >> stream 0 g 0 G @@ -17745,284 +17419,303 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(get)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(glob)]TJ ET q -1 0 0 1 194.695 706.328 cm +1 0 0 1 201.26 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 205.295 706.129 Td [(to)]TJ +ET +q +1 0 0 1 218.057 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 198.729 706.129 Td [(b)-31(oundary)-375(|)-375(Extract)-375(list)-375(of)-375(b)-32(oundary)-375(elemen)32(ts)]TJ +/F16 11.9552 Tf 222.092 706.129 Td [(lo)-31(c)-375(|)-375(Global)-375(to)-375(lo)-31(cal)-375(indices)-375(con)31(v)31(ertion)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -48.024 -18.389 Td [(call)-525(psb_get_boundary\050bndel,)-525(desc,)-525(info\051)]TJ +/F30 9.9626 Tf -71.387 -18.389 Td [(call)-525(psb_glob_to_loc\050x,)-525(y,)-525(desc_a,)-525(info,)-525(iact,owned\051)]TJ 0 -11.956 Td [(call)-525(psb_glob_to_loc\050x,)-525(desc_a,)-525(info,)-525(iact,owned\051)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf 0 -21.201 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -33.797 -19.639 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(desc)]TJ + 0 -19.639 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 26.208 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -1.302 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 11.028 0 Td [(An)-333(in)28(tege)-1(r)-333(v)28(ector)-333(of)-334(indices)-333(to)-333(b)-28(e)-334(con)28(v)28(erted.)]TJ 13.878 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in,)-383(inout)]TJ/F8 9.9626 Tf 42.645 0 Td [(.)]TJ -76.131 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-334(i)1(n)27(teger)-333(arra)28(y)83(.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.906 -31.594 Td [(desc)]TJ +ET +q +1 0 0 1 172.619 536.09 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 176.057 535.891 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.55 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 362.845 578.35 cm +1 0 0 1 362.845 488.27 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 365.983 578.15 Td [(desc)]TJ +/F30 9.9626 Tf 365.983 488.07 Td [(desc)]TJ ET q -1 0 0 1 387.532 578.35 cm +1 0 0 1 387.532 488.27 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 390.67 578.15 Td [(type)]TJ +/F30 9.9626 Tf 390.67 488.07 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -260.887 -21.917 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf -260.887 -19.638 Td [(iact)]TJ 0 g 0 G +/F8 9.9626 Tf 23.28 0 Td [(sp)-28(eci\014es)-333(action)-334(to)-333(b)-28(e)-333(tak)28(en)-334(in)-333(case)-333(of)-334(range)-333(errors.)-444(Scop)-28(e:)]TJ/F27 9.9626 Tf 257.148 0 Td [(global)]TJ/F8 9.9626 Tf -255.522 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-256(c)28(haracter)-255(v)56(ariable)]TJ/F30 9.9626 Tf 143.584 0 Td [(I)]TJ/F8 9.9626 Tf 5.231 0 Td [(gnore,)]TJ/F30 9.9626 Tf 29.293 0 Td [(W)]TJ/F8 9.9626 Tf 5.23 0 Td [(arning)-255(or)]TJ/F30 9.9626 Tf 41.67 0 Td [(A)]TJ/F8 9.9626 Tf 5.23 0 Td [(b)-28(ort,)-271(d)1(e)-1(f)1(ault)]TJ/F30 9.9626 Tf 56.742 0 Td [(I)]TJ/F8 9.9626 Tf 5.23 0 Td [(gnore.)]TJ 0 g 0 G - 0 -19.926 Td [(bndel)]TJ +/F27 9.9626 Tf -317.116 -19.639 Td [(o)32(wned)]TJ 0 g 0 G -/F8 9.9626 Tf 32.51 0 Td [(The)-268(list)-267(of)-268(b)-27(oundary)-268(elemen)28(ts)-268(on)-267(the)-268(calling)-267(pro)-28(cess,)-281(in)-267(lo)-28(cal)-268(n)28(um)28(b)-28(ering.)]TJ -7.604 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-456(as:)-691(a)-457(rank)-456(one)-457(arra)28(y)-457(with)-456(the)-457(ALLOCA)84(T)83(ABLE)-456(attribute,)-488(of)]TJ 0 -11.955 Td [(t)28(yp)-28(e)-333(in)27(teger.)]TJ +/F8 9.9626 Tf 36.647 0 Td [(Sp)-28(ec\014es)-333(v)55(alid)-333(range)-333(of)-333(input)-334(Scop)-27(e:)]TJ/F27 9.9626 Tf 158.932 0 Td [(global)]TJ/F8 9.9626 Tf -170.673 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(If)-294(true,)-302(then)-294(only)-295(indices)-294(strictly)-294(o)28(wned)-295(b)28(y)-294(the)-294(curren)28(t)-295(pro)-27(ce)-1(ss)-294(are)-294(consid-)]TJ 0 -11.955 Td [(ered)-333(v)55(alid,)-333(if)-333(false)-334(then)-333(halo)-333(indices)-334(are)-333(also)-333(accepted.)-445(Default:)-444(false.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -31.881 Td [(info)]TJ +/F27 9.9626 Tf -24.906 -21.202 Td [(On)-383(Return)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.956 Td [(An)-333(in)28(te)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ/F16 11.9552 Tf -24.906 -21.917 Td [(Notes)]TJ 0 g 0 G -/F8 9.9626 Tf 12.176 -19.926 Td [(1.)]TJ + 0 -19.639 Td [(x)]TJ 0 g 0 G - [-500(If)-269(there)-269(are)-269(no)-269(b)-28(oundary)-269(elemen)28(ts)-269(\050i.e.,)-282(if)-269(the)-269(lo)-28(cal)-269(part)-269(of)-269(the)-270(connectivit)28(y)]TJ 12.73 -11.955 Td [(graph)-449(is)-450(self-con)28(tained\051)-450(the)-449(output)-450(v)28(ector)-449(is)-450(set)-449(to)-450(the)-449(\134not)-450(allo)-28(cated")]TJ 0 -11.955 Td [(state.)]TJ +/F8 9.9626 Tf 11.028 0 Td [(If)]TJ/F11 9.9626 Tf 10.132 0 Td [(y)]TJ/F8 9.9626 Tf 8.733 0 Td [(is)-350(not)-351(presen)28(t,)-355(then)]TJ/F11 9.9626 Tf 88.587 0 Td [(x)]TJ/F8 9.9626 Tf 9.185 0 Td [(is)-350(o)27(v)28(erwritten)-350(with)-350(the)-351(translated)-350(in)28(teger)-351(indices.)]TJ -102.759 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-334(i)1(n)27(teger)-333(arra)28(y)83(.)]TJ 0 g 0 G - -12.73 -19.925 Td [(2.)]TJ +/F27 9.9626 Tf -24.906 -19.639 Td [(y)]TJ +0 g 0 G +/F8 9.9626 Tf 11.028 0 Td [(If)]TJ/F11 9.9626 Tf 10.04 0 Td [(y)]TJ/F8 9.9626 Tf 8.64 0 Td [(is)-341(presen)28(t,)-343(then)]TJ/F11 9.9626 Tf 70.404 0 Td [(y)]TJ/F8 9.9626 Tf 8.64 0 Td [(is)-341(o)28(v)27(erwritten)-341(with)-341(the)-341(translated)-341(in)28(teger)-341(indices,)-343(and)]TJ/F11 9.9626 Tf -83.846 -11.955 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(is)-333(left)-334(unc)28(hanged.)-444(Scop)-28(e:)]TJ/F27 9.9626 Tf 113.242 0 Td [(global)]TJ/F8 9.9626 Tf -122.257 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-334(i)1(n)27(teger)-333(arra)28(y)83(.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.906 -19.638 Td [(info)]TJ 0 g 0 G - [-500(Otherwise)-288(the)-289(size)-288(of)]TJ/F30 9.9626 Tf 105.44 0 Td [(bndel)]TJ/F8 9.9626 Tf 29.024 0 Td [(will)-288(b)-28(e)-288(exactly)-288(e)-1(qu)1(al)-289(to)-288(the)-288(n)28(um)27(b)-27(er)-289(of)-288(b)-28(oun)1(d-)]TJ -121.734 -11.956 Td [(ary)-333(elemen)27(ts.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(te)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(t)1(e)-1(d.)]TJ/F16 11.9552 Tf -24.906 -21.202 Td [(Notes)]TJ 0 g 0 G - 141.968 -208.758 Td [(92)]TJ +/F8 9.9626 Tf 166.874 -29.887 Td [(88)]TJ 0 g 0 G ET endstream endobj -1461 0 obj +1458 0 obj << -/Length 3654 +/Length 692 >> stream 0 g 0 G 0 g 0 G +0 g 0 G BT -/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ +/F8 9.9626 Tf 112.072 706.129 Td [(1.)]TJ +0 g 0 G + [-500(If)-352(an)-353(input)-352(index)-352(is)-353(out)-352(of)-352(range,)-358(then)-352(the)-352(corresp)-28(onding)-352(output)-353(index)-352(is)]TJ 12.73 -11.955 Td [(set)-333(to)-334(a)-333(negativ)28(e)-334(n)28(um)28(b)-28(er;)]TJ +0 g 0 G + -12.73 -19.926 Td [(2.)]TJ +0 g 0 G + [-500(The)-476(default)]TJ/F30 9.9626 Tf 69.542 0 Td [(I)]TJ/F8 9.9626 Tf 5.231 0 Td [(gnore)-476(means)-477(th)1(at)-477(the)-476(negativ)28(e)-476(output)-477(is)-476(the)-476(only)-476(action)]TJ -62.043 -11.955 Td [(tak)28(en)-334(on)-333(an)-333(out-of-range)-333(input.)]TJ +0 g 0 G + 141.968 -571.855 Td [(89)]TJ +0 g 0 G +ET + +endstream +endobj +1465 0 obj +<< +/Length 5736 +>> +stream +0 g 0 G +0 g 0 G +BT +/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ ET q -1 0 0 1 120.951 706.328 cm +1 0 0 1 171.761 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(get)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(lo)-31(c)]TJ ET q -1 0 0 1 143.885 706.328 cm +1 0 0 1 193.415 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 197.45 706.129 Td [(to)]TJ +ET +q +1 0 0 1 210.212 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 147.92 706.129 Td [(o)31(v)31(erlap)-375(|)-375(Extract)-375(list)-375(of)-375(o)32(v)31(erlap)-375(elemen)31(ts)]TJ +/F16 11.9552 Tf 214.247 706.129 Td [(glob)-375(|)-375(Lo)-31(cal)-375(to)-375(global)-375(indices)-375(con)31(v)31(ersion)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -48.025 -18.389 Td [(call)-525(psb_get_overlap\050ovrel,)-525(desc,)-525(info\051)]TJ +/F30 9.9626 Tf -63.542 -18.389 Td [(call)-525(psb_loc_to_glob\050x,)-525(y,)-525(desc_a,)-525(info,)-525(iact\051)]TJ 0 -11.956 Td [(call)-525(psb_loc_to_glob\050x,)-525(desc_a,)-525(info,)-525(iact\051)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf 0 -21.917 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G /F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(desc)]TJ + 0 -19.925 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 26.209 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -1.302 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 11.028 0 Td [(An)-333(in)28(tege)-1(r)-333(v)28(ector)-333(of)-334(indices)-333(to)-333(b)-28(e)-334(con)28(v)28(erted.)]TJ 13.879 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in,)-383(inout)]TJ/F8 9.9626 Tf 42.646 0 Td [(.)]TJ -76.131 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-334(rank)-333(one)-333(in)27(teger)-333(arra)28(y)83(.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -31.88 Td [(desc)]TJ +ET +q +1 0 0 1 172.619 534.514 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 176.057 534.315 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.55 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 312.036 578.35 cm +1 0 0 1 362.845 486.693 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 315.174 578.15 Td [(desc)]TJ +/F30 9.9626 Tf 365.983 486.494 Td [(desc)]TJ ET q -1 0 0 1 336.723 578.35 cm +1 0 0 1 387.532 486.693 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 339.861 578.15 Td [(type)]TJ +/F30 9.9626 Tf 390.67 486.494 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +/F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -260.887 -21.917 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf -260.887 -19.925 Td [(iact)]TJ 0 g 0 G +/F8 9.9626 Tf 23.28 0 Td [(sp)-28(eci\014es)-333(action)-334(to)-333(b)-28(e)-333(tak)28(en)-334(in)-333(case)-333(of)-334(range)-333(errors.)-444(Scop)-28(e:)]TJ/F27 9.9626 Tf 257.148 0 Td [(global)]TJ/F8 9.9626 Tf -255.522 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-256(c)28(haracter)-255(v)56(ariable)]TJ/F30 9.9626 Tf 143.584 0 Td [(I)]TJ/F8 9.9626 Tf 5.231 0 Td [(gnore,)]TJ/F30 9.9626 Tf 29.293 0 Td [(W)]TJ/F8 9.9626 Tf 5.23 0 Td [(arning)-255(or)]TJ/F30 9.9626 Tf 41.67 0 Td [(A)]TJ/F8 9.9626 Tf 5.23 0 Td [(b)-28(ort,)-271(d)1(e)-1(f)1(ault)]TJ/F30 9.9626 Tf 56.742 0 Td [(I)]TJ/F8 9.9626 Tf 5.23 0 Td [(gnore.)]TJ 0 g 0 G - 0 -19.926 Td [(o)32(vrel)]TJ +/F27 9.9626 Tf -317.116 -21.917 Td [(On)-383(Return)]TJ 0 g 0 G -/F8 9.9626 Tf 29.591 0 Td [(The)-333(list)-334(of)-333(o)28(v)28(erlap)-334(elemen)28(ts)-333(on)-334(the)-333(calling)-333(pro)-28(cess,)-333(in)-334(lo)-28(cal)-333(n)28(um)28(b)-28(ering.)]TJ -4.684 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-456(as:)-691(a)-457(rank)-456(one)-457(arra)28(y)-456(with)-457(the)-457(ALLOCA)84(T)83(ABLE)-456(attribute,)-488(of)]TJ 0 -11.955 Td [(t)28(yp)-28(e)-333(in)28(te)-1(ger.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -31.881 Td [(info)]TJ + 0 -19.926 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.956 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ/F16 11.9552 Tf -24.907 -21.917 Td [(Notes)]TJ +/F8 9.9626 Tf 11.028 0 Td [(If)]TJ/F11 9.9626 Tf 10.132 0 Td [(y)]TJ/F8 9.9626 Tf 8.733 0 Td [(is)-350(not)-351(presen)28(t,)-355(then)]TJ/F11 9.9626 Tf 88.587 0 Td [(x)]TJ/F8 9.9626 Tf 9.185 0 Td [(is)-350(o)27(v)28(erwritten)-350(with)-350(the)-351(translated)-350(in)28(teger)-351(indices.)]TJ -102.759 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-334(i)1(n)27(teger)-333(arra)28(y)83(.)]TJ 0 g 0 G -/F8 9.9626 Tf 12.177 -19.926 Td [(1.)]TJ +/F27 9.9626 Tf -24.906 -19.926 Td [(y)]TJ 0 g 0 G - [-500(If)-343(there)-343(are)-344(no)-343(o)28(v)28(erlap)-344(elemen)28(ts)-343(the)-343(output)-344(v)28(ector)-343(is)-343(set)-344(to)-343(the)-343(\134not)-343(allo-)]TJ 12.73 -11.955 Td [(cated")-333(state.)]TJ +/F8 9.9626 Tf 11.028 0 Td [(If)]TJ/F11 9.9626 Tf 10.166 0 Td [(y)]TJ/F8 9.9626 Tf 8.767 0 Td [(is)-354(not)-354(presen)28(t,)-359(then)]TJ/F11 9.9626 Tf 88.732 0 Td [(y)]TJ/F8 9.9626 Tf 8.767 0 Td [(is)-354(o)28(v)28(erwritten)-354(with)-354(the)-354(translated)-353(in)27(teger)-353(indices,)]TJ -102.554 -11.955 Td [(and)]TJ/F11 9.9626 Tf 19.372 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(is)-333(left)-334(unc)28(hanged.)-444(Scop)-28(e:)]TJ/F27 9.9626 Tf 113.242 0 Td [(global)]TJ/F8 9.9626 Tf -141.629 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-334(i)1(n)27(teger)-333(arra)28(y)83(.)]TJ 0 g 0 G - -12.73 -19.925 Td [(2.)]TJ +/F27 9.9626 Tf -24.906 -19.926 Td [(info)]TJ 0 g 0 G - [-500(Otherwise)-284(the)-284(size)-283(of)]TJ/F30 9.9626 Tf 105.261 0 Td [(ovrel)]TJ/F8 9.9626 Tf 28.979 0 Td [(will)-284(b)-27(e)-284(exactly)-284(equal)-284(to)-284(th)1(e)-284(n)28(um)27(b)-27(er)-284(of)-284(o)28(v)28(erlap)]TJ -121.51 -11.955 Td [(elemen)28(ts.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(te)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(t)1(e)-1(d.)]TJ 0 g 0 G - 141.968 -220.714 Td [(93)]TJ + 141.968 -115.11 Td [(90)]TJ 0 g 0 G ET endstream endobj -1468 0 obj +1470 0 obj << -/Length 5790 +/Length 3271 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ +/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ ET q -1 0 0 1 171.761 706.328 cm +1 0 0 1 120.951 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(sp)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(is)]TJ ET q -1 0 0 1 189.38 706.328 cm +1 0 0 1 134.834 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 193.415 706.129 Td [(getro)31(w)-375(|)-375(Extract)-375(ro)32(w\050s)-1(\051)-375(from)-375(a)-375(sparse)-375(matrix)]TJ +/F16 11.9552 Tf 138.869 706.129 Td [(o)31(wned)-375(|)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -42.71 -18.647 Td [(call)-525(psb_sp_getrow\050row,)-525(a,)-525(nz,)-525(ia,)-525(ja,)-525(val,)-525(info,)-525(&)]TJ 73.225 -11.955 Td [(&)-525(append,)-525(nzin,)-525(lrw\051)]TJ +/F30 9.9626 Tf -38.974 -18.389 Td [(call)-525(psb_is_owned\050x,)-525(desc_a\051)]TJ 0 g 0 G -/F27 9.9626 Tf -73.225 -22.334 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -20.479 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -20.479 Td [(ro)32(w)]TJ + 0 -19.925 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 23.384 0 Td [(The)-333(\050\014rst\051)-334(ro)28(w)-333(to)-334(b)-27(e)-334(extracted.)]TJ 1.523 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.95 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.95 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf -25.183 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)]TJ/F11 9.9626 Tf 104.69 0 Td [(>)]TJ/F8 9.9626 Tf 10.517 0 Td [(0.)]TJ +/F8 9.9626 Tf 11.028 0 Td [(In)28(teger)-334(index.)]TJ 13.879 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(scalar)-333(in)28(teger.)]TJ 0 g 0 G -/F27 9.9626 Tf -140.114 -20.479 Td [(a)]TJ +/F27 9.9626 Tf -24.907 -31.88 Td [(desc)]TJ +ET +q +1 0 0 1 121.81 546.469 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 125.247 546.27 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(matrix)-334(from)-333(whic)28(h)-333(to)-334(get)-333(ro)28(ws.)]TJ 14.356 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.95 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.95 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf -25.183 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-334(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.551 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 362.845 496.313 cm +1 0 0 1 312.036 498.649 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 365.983 496.114 Td [(Tspmat)]TJ +/F30 9.9626 Tf 315.174 498.449 Td [(desc)]TJ ET q -1 0 0 1 397.993 496.313 cm +1 0 0 1 336.723 498.649 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 401.131 496.114 Td [(type)]TJ +/F30 9.9626 Tf 339.861 498.449 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -271.347 -20.479 Td [(app)-32(end)]TJ -0 g 0 G -/F8 9.9626 Tf 41.58 0 Td [(Whether)-333(to)-334(app)-27(end)-334(or)-333(o)28(v)28(erwrite)-334(existing)-333(output.)]TJ -16.674 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.951 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(optional)]TJ/F8 9.9626 Tf -25.184 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(logical)-333(v)55(alue)-333(default:)-444(false)-334(\050o)28(v)28(erwrite\051.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.906 -20.479 Td [(nzin)]TJ -0 g 0 G -/F8 9.9626 Tf 25.986 0 Td [(Input)-333(size)-334(to)-333(b)-28(e)-333(app)-28(ended)-333(to.)]TJ -1.08 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.951 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(optional)]TJ/F8 9.9626 Tf -25.184 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-398(as:)-573(an)-398(in)28(teger)]TJ/F11 9.9626 Tf 107.908 0 Td [(>)]TJ/F8 9.9626 Tf 11.588 0 Td [(0.)-638(When)-398(app)-28(end)-398(is)-397(true,)-414(s)-1(p)-27(eci\014es)-398(ho)28(w)-398(man)27(y)]TJ -119.496 -11.955 Td [(en)28(tries)-334(in)-333(the)-333(output)-333(v)27(ectors)-333(are)-333(already)-334(\014lled.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.906 -20.479 Td [(lrw)]TJ -0 g 0 G -/F8 9.9626 Tf 21.156 0 Td [(The)-333(last)-334(ro)28(w)-333(to)-334(b)-27(e)-334(extracted.)]TJ 3.75 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.951 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(optional)]TJ/F8 9.9626 Tf -25.184 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)]TJ/F11 9.9626 Tf 104.691 0 Td [(>)]TJ/F8 9.9626 Tf 10.516 0 Td [(0,)-333(default:)]TJ/F11 9.9626 Tf 48.43 0 Td [(r)-28(ow)]TJ/F8 9.9626 Tf 17.001 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -205.544 -22.334 Td [(On)-383(Return)]TJ -0 g 0 G -0 g 0 G - 0 -20.479 Td [(nz)]TJ -0 g 0 G -/F8 9.9626 Tf 16.438 0 Td [(the)-333(n)27(u)1(m)27(b)-27(e)-1(r)-333(of)-333(elemen)28(ts)-334(returned)-333(b)28(y)-334(thi)1(s)-334(call.)]TJ 8.468 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.956 Td [(Returned)-333(as:)-445(an)-333(in)28(teger)-334(scalar.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.906 -20.479 Td [(ia)]TJ -0 g 0 G -/F8 9.9626 Tf 13.733 0 Td [(the)-333(ro)27(w)-333(indices.)]TJ 11.173 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)-333(with)-333(the)]TJ/F30 9.9626 Tf 170.611 0 Td [(ALLOCATABLE)]TJ/F8 9.9626 Tf 60.854 0 Td [(attribute.)]TJ -0 g 0 G - -89.497 -29.887 Td [(94)]TJ -0 g 0 G -ET - -endstream -endobj -1472 0 obj -<< -/Length 3701 ->> -stream -0 g 0 G -0 g 0 G -0 g 0 G -BT -/F27 9.9626 Tf 99.895 706.129 Td [(ja)]TJ -0 g 0 G -/F8 9.9626 Tf 14.052 0 Td [(the)-333(column)-334(indices)-333(of)-333(the)-334(elemen)28(ts)-333(to)-334(b)-27(e)-334(inserted.)]TJ 10.855 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)-333(with)-333(the)]TJ/F30 9.9626 Tf 170.61 0 Td [(ALLOCATABLE)]TJ/F8 9.9626 Tf 60.855 0 Td [(attribute.)]TJ -0 g 0 G -/F27 9.9626 Tf -256.372 -19.925 Td [(v)64(al)]TJ -0 g 0 G -/F8 9.9626 Tf 19.144 0 Td [(the)-333(elemen)27(ts)-333(to)-333(b)-28(e)-333(inserted.)]TJ 5.763 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(real)-333(arra)28(y)-334(with)-333(the)]TJ/F30 9.9626 Tf 151.515 0 Td [(ALLOCATABLE)]TJ/F8 9.9626 Tf 60.855 0 Td [(attribute.)]TJ -0 g 0 G -/F27 9.9626 Tf -237.277 -19.925 Td [(info)]TJ -0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ -0 g 0 G -/F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ +/F27 9.9626 Tf -260.887 -21.917 Td [(On)-383(Return)]TJ 0 g 0 G - [-500(The)-368(output)]TJ/F11 9.9626 Tf 66.552 0 Td [(nz)]TJ/F8 9.9626 Tf 14.717 0 Td [(is)-368(alw)28(a)28(ys)-368(the)-368(size)-368(of)-368(the)-368(output)-368(generated)-367(b)27(y)-367(the)-368(curren)28(t)]TJ -68.539 -11.955 Td [(call;)-314(th)28(us,)-309(if)]TJ/F30 9.9626 Tf 54.123 0 Td [(append=.true.)]TJ/F8 9.9626 Tf 67.995 0 Td [(,)-310(the)-303(total)-304(output)-304(size)-304(will)-303(b)-28(e)]TJ/F11 9.9626 Tf 128.95 0 Td [(nz)-44(in)]TJ/F8 9.9626 Tf 22.088 0 Td [(+)]TJ/F11 9.9626 Tf 9.373 0 Td [(nz)]TJ/F8 9.9626 Tf 11.051 0 Td [(,)-310(with)]TJ -293.58 -11.955 Td [(the)-372(newly)-372(extracted)-372(co)-28(e\016cien)28(ts)-372(stored)-372(in)-372(en)28(tries)]TJ/F30 9.9626 Tf 216.307 0 Td [(nzin+1:nzin+nz)]TJ/F8 9.9626 Tf 76.93 0 Td [(of)-372(the)]TJ -293.237 -11.955 Td [(arra)28(y)-333(argume)-1(n)28(ts;)]TJ 0 g 0 G - -12.73 -19.926 Td [(2.)]TJ + 0 -19.926 Td [(F)96(unction)-384(v)64(alue)]TJ 0 g 0 G - [-500(When)]TJ/F30 9.9626 Tf 41.788 0 Td [(append=.true.)]TJ/F8 9.9626 Tf 71.315 0 Td [(the)-333(output)-334(arr)1(a)27(ys)-333(are)-333(reallo)-28(cated)-334(as)-333(necessary;)]TJ +/F8 9.9626 Tf 78.387 0 Td [(A)-302(logical)-301(mask)-302(whic)28(h)-302(is)-302(t)1(rue)-302(if)]TJ/F11 9.9626 Tf 134.085 0 Td [(x)]TJ/F8 9.9626 Tf 8.699 0 Td [(is)-302(o)28(wned)-302(b)28(y)-301(the)-302(curren)28(t)-302(pro-)]TJ -196.264 -11.955 Td [(cess)-334(S)1(c)-1(op)-27(e:)]TJ/F27 9.9626 Tf 52.415 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -52.415 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ/F16 11.9552 Tf -74.942 -33.873 Td [(Notes)]TJ 0 g 0 G - -113.103 -19.925 Td [(3.)]TJ +/F8 9.9626 Tf 12.177 -19.926 Td [(1.)]TJ 0 g 0 G - [-500(The)-253(ro)28(w)-252(and)-253(column)-253(ind)1(ic)-1(es)-252(are)-253(returned)-252(in)-253(the)-253(lo)-27(cal)-253(n)28(um)28(b)-28(ering)-253(sc)28(heme;)-280(if)]TJ 12.73 -11.955 Td [(the)-222(global)-222(n)27(um)28(b)-28(erin)1(g)-223(is)-222(desired,)-244(the)-223(user)-222(ma)28(y)-222(emplo)27(y)-222(the)]TJ/F30 9.9626 Tf 243.172 0 Td [(psb_loc_to_glob)]TJ/F8 9.9626 Tf -243.172 -11.955 Td [(routine)-333(on)-334(th)1(e)-334(output.)]TJ + [-500(This)-300(routine)-299(returns)-300(a)]TJ/F30 9.9626 Tf 111.213 0 Td [(.true.)]TJ/F8 9.9626 Tf 34.369 0 Td [(v)56(alue)-300(for)-300(an)-300(index)-299(that)-300(is)-300(strictly)-300(o)28(wned)-300(b)28(y)]TJ -132.852 -11.955 Td [(the)-333(curren)28(t)-334(pro)-28(cess,)-333(excluding)-333(the)-334(halo)-333(indices)]TJ 0 g 0 G - 141.968 -290.909 Td [(95)]TJ + 141.968 -264.549 Td [(91)]TJ 0 g 0 G ET endstream endobj -1482 0 obj +1477 0 obj << -/Length 4126 +/Length 4983 >> stream 0 g 0 G @@ -18035,602 +17728,552 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(sizeof)-375(|)-375(Memory)-375(o)-31(ccupation)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-333(function)-334(computes)-333(the)-333(memory)-334(o)-27(c)-1(cup)1(ation)-334(of)-333(a)-333(PSBLAS)-334(ob)-55(ject.)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(o)31(wned)]TJ +ET +q +1 0 0 1 213.748 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 217.783 706.129 Td [(index)-375(|)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf 0 -21.918 Td [(isz)-525(=)-525(psb_sizeof\050a\051)]TJ 0 -11.955 Td [(isz)-525(=)-525(psb_sizeof\050desc_a\051)]TJ 0 -11.956 Td [(isz)-525(=)-525(psb_sizeof\050prec\051)]TJ +/F30 9.9626 Tf -67.078 -18.389 Td [(call)-525(psb_owned_index\050y,)-525(x,)-525(desc_a,)-525(info\051)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -21.917 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G /F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(A)-333(sparse)-334(matrix)]TJ/F11 9.9626 Tf 73.225 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(.)]TJ -66.342 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ -ET -q -1 0 0 1 362.845 532.522 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 365.983 532.322 Td [(Tspmat)]TJ -ET -q -1 0 0 1 397.993 532.522 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 401.131 532.322 Td [(type)]TJ + 0 -19.925 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +/F8 9.9626 Tf 11.028 0 Td [(In)28(teger)-334(ind)1(ice)-1(s.)]TJ 13.878 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in,)-383(inout)]TJ/F8 9.9626 Tf 42.645 0 Td [(.)]TJ -76.131 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(scalar)-333(or)-334(a)-333(rank)-333(one)-334(in)28(teger)-333(arra)28(y)83(.)]TJ 0 g 0 G -/F27 9.9626 Tf -271.347 -19.925 Td [(desc)]TJ +/F27 9.9626 Tf -24.906 -31.88 Td [(desc)]TJ ET q -1 0 0 1 172.619 512.596 cm +1 0 0 1 172.619 546.469 cm []0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F27 9.9626 Tf 176.057 512.397 Td [(a)]TJ +/F27 9.9626 Tf 176.057 546.27 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.55 0 Td [(Comm)28(unication)-334(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.55 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 362.845 464.776 cm +1 0 0 1 362.845 498.649 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 365.983 464.576 Td [(desc)]TJ +/F30 9.9626 Tf 365.983 498.449 Td [(desc)]TJ ET q -1 0 0 1 387.532 464.776 cm +1 0 0 1 387.532 498.649 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 390.67 464.576 Td [(type)]TJ +/F30 9.9626 Tf 390.67 498.449 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -260.887 -19.925 Td [(prec)]TJ +/F27 9.9626 Tf -260.887 -19.925 Td [(iact)]TJ 0 g 0 G -/F8 9.9626 Tf 26.408 0 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -33.879 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-334(preconditioner)-333(data)-333(structure)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 197.537 0 Td [(psb)]TJ -ET -q -1 0 0 1 389.467 408.985 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 392.606 408.786 Td [(prec)]TJ -ET -q -1 0 0 1 414.155 408.985 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 417.293 408.786 Td [(type)]TJ +/F8 9.9626 Tf 23.28 0 Td [(sp)-28(eci\014es)-333(action)-334(to)-333(b)-28(e)-333(tak)28(en)-334(in)-333(case)-333(of)-334(range)-333(errors.)-444(Scop)-28(e:)]TJ/F27 9.9626 Tf 257.148 0 Td [(global)]TJ/F8 9.9626 Tf -255.522 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-256(c)28(haracter)-255(v)56(ariable)]TJ/F30 9.9626 Tf 143.584 0 Td [(I)]TJ/F8 9.9626 Tf 5.231 0 Td [(gnore,)]TJ/F30 9.9626 Tf 29.293 0 Td [(W)]TJ/F8 9.9626 Tf 5.23 0 Td [(arning)-255(or)]TJ/F30 9.9626 Tf 41.67 0 Td [(A)]TJ/F8 9.9626 Tf 5.23 0 Td [(b)-28(ort,)-271(d)1(e)-1(f)1(ault)]TJ/F30 9.9626 Tf 56.742 0 Td [(I)]TJ/F8 9.9626 Tf 5.23 0 Td [(gnore.)]TJ 0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +/F27 9.9626 Tf -317.116 -21.918 Td [(On)-383(Return)]TJ 0 g 0 G -/F27 9.9626 Tf -287.509 -19.926 Td [(On)-383(Return)]TJ 0 g 0 G + 0 -19.926 Td [(y)]TJ 0 g 0 G - 0 -19.925 Td [(F)96(unction)-384(v)64(alue)]TJ +/F8 9.9626 Tf 11.028 0 Td [(A)-294(logical)-294(mask)-294(whic)28(h)-294(is)-294(true)-294(for)-294(all)-294(corresp)-28(onding)-294(en)28(tries)-294(of)]TJ/F11 9.9626 Tf 259.229 0 Td [(x)]TJ/F8 9.9626 Tf 8.623 0 Td [(that)-294(are)-294(o)28(wned)]TJ -253.974 -11.955 Td [(b)28(y)-334(the)-333(curren)28(t)-333(pro)-28(cess)-334(Scop)-27(e:)]TJ/F27 9.9626 Tf 132.753 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -132.752 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-334(scalar)-333(or)-334(r)1(ank)-334(one)-333(logical)-333(arra)27(y)84(.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.926 Td [(info)]TJ 0 g 0 G -/F8 9.9626 Tf 78.386 0 Td [(The)-332(memory)-331(o)-28(ccupation)-332(of)-331(the)-332(ob)-55(jec)-1(t)-331(sp)-28(eci\014ed)-332(in)-331(the)-332(calling)]TJ -53.48 -11.955 Td [(sequence,)-333(in)-334(b)28(ytes.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(Returned)-333(as:)-445(an)]TJ/F30 9.9626 Tf 73.835 0 Td [(integer\050psb_long_int_k_\051)]TJ/F8 9.9626 Tf 128.849 0 Td [(n)28(um)28(b)-28(er.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.034 -11.955 Td [(An)-333(in)28(teger)-334(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detected.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ 0 g 0 G - -60.716 -242.632 Td [(96)]TJ +/F8 9.9626 Tf 12.176 -19.925 Td [(1.)]TJ +0 g 0 G + [-500(This)-475(routine)-474(returns)-475(a)]TJ/F30 9.9626 Tf 118.186 0 Td [(.true.)]TJ/F8 9.9626 Tf 36.112 0 Td [(v)56(alue)-475(for)-475(those)-475(indices)-474(that)-475(are)-475(strictly)]TJ -141.567 -11.955 Td [(o)28(wned)-334(b)28(y)-333(the)-333(curren)27(t)-333(pro)-28(cess,)-333(excluding)-333(the)-334(halo)-333(indices)]TJ +0 g 0 G + 141.967 -141.013 Td [(92)]TJ 0 g 0 G ET endstream endobj -1486 0 obj +1483 0 obj << -/Length 5761 +/Length 3240 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 99.895 706.129 Td [(Sorting)-375(utilities)-375(|)]TJ 0 -19.593 Td [(psb)]TJ -ET -q -1 0 0 1 120.951 686.736 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 124.986 686.536 Td [(msort)-375(|)-375(Sorting)-375(b)31(y)-375(the)-375(Merge-sort)-375(algorithm)]TJ -25.091 -12.601 Td [(psb)]TJ +/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ ET q -1 0 0 1 120.951 674.134 cm +1 0 0 1 120.951 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 673.935 Td [(qsort)-375(|)-375(Sorting)-375(b)31(y)-375(the)-375(Quic)31(ksort)-375(algorithm)]TJ -25.091 -12.602 Td [(psb)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(is)]TJ ET q -1 0 0 1 120.951 661.532 cm +1 0 0 1 134.834 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 661.333 Td [(hsort)-375(|)-375(Sorting)-375(b)31(y)-375(the)-375(Heapsort)-375(algorithm)]TJ +/F16 11.9552 Tf 138.869 706.129 Td [(lo)-31(cal)-375(|)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -22.511 Td [(call)-525(psb_msort\050x,ix,dir,flag\051)]TJ 0 -11.955 Td [(call)-525(psb_qsort\050x,ix,dir,flag\051)]TJ 0 -11.955 Td [(call)-525(psb_hsort\050x,ix,dir,flag\051)]TJ/F8 9.9626 Tf 14.944 -21.865 Td [(These)-332(serial)-332(rou)1(tines)-332(sort)-332(a)-332(sequence)]TJ/F11 9.9626 Tf 162.708 0 Td [(X)]TJ/F8 9.9626 Tf 12.34 0 Td [(in)28(to)-332(ascending)-332(or)-331(descending)-332(order.)]TJ -189.992 -11.955 Td [(The)-320(argumen)28(t)-321(meaning)-320(is)-320(iden)28(tical)-320(for)-320(the)-321(thr)1(e)-1(e)-320(calls;)-324(the)-321(on)1(ly)-321(di\013erence)-320(is)-320(the)]TJ 0 -11.955 Td [(algorithm)-333(used)-334(to)-333(accomplish)-333(the)-334(task)-333(\050see)-334(Usage)-333(Notes)-333(b)-28(elo)28(w\051.)]TJ +/F30 9.9626 Tf -38.974 -18.389 Td [(call)-525(psb_is_local\050x,)-525(desc_a\051)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -21.865 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -22.511 Td [(On)-383(En)32(try)]TJ -0 g 0 G -0 g 0 G - 0 -22.511 Td [(x)]TJ -0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(The)-333(sequence)-334(to)-333(b)-28(e)-333(sorted.)]TJ 13.879 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger,)-333(real)-334(or)-333(complex)-333(arra)27(y)-333(of)-333(rank)-333(1.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -22.511 Td [(ix)]TJ -0 g 0 G -/F8 9.9626 Tf 14.211 0 Td [(A)-333(v)27(ector)-333(of)-333(indices.)]TJ 10.696 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)-333(of)-333(\050at)-333(le)-1(ast\051)-333(the)-333(same)-334(size)-333(as)]TJ/F11 9.9626 Tf 258.559 0 Td [(X)]TJ/F8 9.9626 Tf 9.035 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -292.501 -22.511 Td [(dir)]TJ -0 g 0 G -/F8 9.9626 Tf 19.248 0 Td [(The)-333(desired)-334(ordering.)]TJ 5.659 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue:)]TJ +/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -22.511 Td [(In)32(teger)-383(and)-384(real)-383(data:)]TJ 0 g 0 G -/F30 9.9626 Tf 114.397 0 Td [(psb_sort_up_)]TJ/F8 9.9626 Tf 62.764 0 Td [(,)]TJ/F30 9.9626 Tf 5.203 0 Td [(psb_sort_down_)]TJ/F8 9.9626 Tf 73.224 0 Td [(,)]TJ/F30 9.9626 Tf 5.203 0 Td [(psb_asort_up_)]TJ/F8 9.9626 Tf 67.994 0 Td [(,)]TJ/F30 9.9626 Tf -306.867 -11.955 Td [(psb_asort_down_)]TJ/F8 9.9626 Tf 78.455 0 Td [(;)-333(default)]TJ/F30 9.9626 Tf 39.574 0 Td [(psb_sort_up_)]TJ/F8 9.9626 Tf 62.764 0 Td [(.)]TJ + 0 -19.925 Td [(x)]TJ 0 g 0 G -/F27 9.9626 Tf -202.711 -17.233 Td [(Complex)-383(data:)]TJ +/F8 9.9626 Tf 11.028 0 Td [(In)28(teger)-334(index.)]TJ 13.879 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(scalar)-333(in)28(teger.)]TJ 0 g 0 G -/F30 9.9626 Tf 78.338 0 Td [(psb_lsort_up_)]TJ/F8 9.9626 Tf 67.994 0 Td [(,)]TJ/F30 9.9626 Tf 5.203 0 Td [(psb_lsort_down_)]TJ/F8 9.9626 Tf 78.455 0 Td [(,)]TJ/F30 9.9626 Tf 5.203 0 Td [(psb_asort_up_)]TJ/F8 9.9626 Tf 67.994 0 Td [(,)]TJ/F30 9.9626 Tf 5.203 0 Td [(psb_asort_down_)]TJ/F8 9.9626 Tf 78.455 0 Td [(;)]TJ -364.927 -11.955 Td [(default)]TJ/F30 9.9626 Tf 33.485 0 Td [(psb_lsort_up_)]TJ/F8 9.9626 Tf 67.995 0 Td [(.)]TJ +/F27 9.9626 Tf -24.907 -31.88 Td [(desc)]TJ +ET +q +1 0 0 1 121.81 546.469 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 125.247 546.27 Td [(a)]TJ 0 g 0 G -/F27 9.9626 Tf -148.305 -22.511 Td [(\015ag)]TJ +/F8 9.9626 Tf 10.551 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ +ET +q +1 0 0 1 312.036 498.649 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 315.174 498.449 Td [(desc)]TJ +ET +q +1 0 0 1 336.723 498.649 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 339.861 498.449 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 22.645 0 Td [(Whether)-333(to)-334(k)28(eep)-333(the)-333(original)-334(v)56(alues)-333(in)]TJ/F11 9.9626 Tf 170.582 0 Td [(I)-78(X)]TJ/F8 9.9626 Tf 14.197 0 Td [(.)]TJ -182.517 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.956 Td [(Sp)-28(eci\014ed)-222(as:)-389(an)-222(in)28(teger)-222(v)55(alue)]TJ/F30 9.9626 Tf 125.446 0 Td [(psb_sort_ovw_idx_)]TJ/F8 9.9626 Tf 91.13 0 Td [(or)]TJ/F30 9.9626 Tf 11.097 0 Td [(psb_sort_keep_idx_)]TJ/F8 9.9626 Tf 94.147 0 Td [(;)]TJ -321.82 -11.955 Td [(default)]TJ/F30 9.9626 Tf 33.486 0 Td [(psb_sort_ovw_idx_)]TJ/F8 9.9626 Tf 88.915 0 Td [(.)]TJ +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -147.308 -24.503 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf -260.887 -21.917 Td [(On)-383(Return)]TJ 0 g 0 G 0 g 0 G - 0 -22.511 Td [(x)]TJ + 0 -19.926 Td [(F)96(unction)-384(v)64(alue)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(The)-333(sequence)-334(of)-333(v)55(alues,)-333(in)-333(the)-334(c)28(hosen)-333(ordering.)]TJ 13.879 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger,)-333(real)-334(or)-333(complex)-333(arra)27(y)-333(of)-333(rank)-333(1.)]TJ +/F8 9.9626 Tf 78.387 0 Td [(A)-264(logical)-265(mask)-264(whic)27(h)-264(is)-265(true)-264(if)]TJ/F11 9.9626 Tf 131.492 0 Td [(x)]TJ/F8 9.9626 Tf 8.329 0 Td [(is)-264(lo)-28(cal)-265(to)-264(the)-265(curren)28(t)-264(pro)-28(cess)]TJ -193.301 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ/F16 11.9552 Tf -74.942 -33.873 Td [(Notes)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -22.511 Td [(ix)]TJ +/F8 9.9626 Tf 12.177 -19.926 Td [(1.)]TJ 0 g 0 G -/F8 9.9626 Tf 14.211 0 Td [(A)-333(v)27(ector)-333(of)-333(indices.)]TJ 10.696 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(Optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(An)-332(in)27(teger)-332(arra)28(y)-333(of)-332(rank)-333(1,)-332(whose)-333(en)28(tries)-332(are)-333(mo)28(v)28(ed)-333(to)-332(the)-333(same)-332(p)-28(osition)]TJ 0 -11.955 Td [(as)-333(the)-334(corresp)-28(on)1(ding)-334(en)28(tries)-333(in)]TJ/F11 9.9626 Tf 136.959 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ + [-500(This)-239(routine)-239(returns)-239(a)]TJ/F30 9.9626 Tf 108.787 0 Td [(.true.)]TJ/F8 9.9626 Tf 33.762 0 Td [(v)56(alue)-239(for)-239(an)-239(index)-239(that)-239(is)-238(lo)-28(cal)-239(to)-239(the)-239(curren)28(t)]TJ -129.819 -11.955 Td [(pro)-28(cess,)-333(including)-333(the)-334(halo)-333(indices)]TJ 0 g 0 G - -0.685 -43.727 Td [(97)]TJ + 141.968 -264.549 Td [(93)]TJ 0 g 0 G ET endstream endobj -1491 0 obj +1489 0 obj << -/Length 6990 +/Length 4992 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 150.705 706.129 Td [(Notes)]TJ +/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ +ET +q +1 0 0 1 171.761 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 175.796 706.129 Td [(lo)-31(cal)]TJ +ET +q +1 0 0 1 203.689 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 207.724 706.129 Td [(index)-375(|)]TJ 0 g 0 G -/F8 9.9626 Tf 12.176 -19.925 Td [(1.)]TJ 0 g 0 G - [-500(F)83(or)-466(in)28(te)-1(ger)-466(or)-467(real)-466(data)-467(the)-467(sorting)-466(can)-467(b)-28(e)-466(p)-28(erformed)-467(in)-466(the)-467(up/do)28(wn)]TJ 12.73 -11.956 Td [(direction,)-333(on)-334(the)-333(natural)-333(or)-333(absolute)-334(v)56(alues;)]TJ +/F30 9.9626 Tf -57.019 -18.389 Td [(call)-525(psb_local_index\050y,)-525(x,)-525(desc_a,)-525(info\051)]TJ 0 g 0 G - -12.73 -19.925 Td [(2.)]TJ -0 g 0 G - [-500(F)83(or)-397(complex)-398(data)-398(the)-397(sorting)-398(can)-398(b)-27(e)-398(done)-398(in)-397(a)-398(lexicographic)-398(order)-397(\050i.e.:)]TJ 12.73 -11.955 Td [(sort)-316(on)-316(the)-315(real)-316(part)-316(with)-316(ties)-316(brok)28(en)-316(according)-315(to)-316(the)-316(imaginary)-316(part\051)-315(or)]TJ 0 -11.955 Td [(on)-333(the)-334(absolute)-333(v)56(alues;)]TJ +/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G - -12.73 -19.925 Td [(3.)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G - [-500(The)-257(routines)-258(return)-257(the)-257(items)-257(in)-258(the)-257(c)28(hosen)-258(or)1(dering;)-283(the)-257(output)-257(di\013erence)]TJ 12.73 -11.956 Td [(is)-259(the)-259(handling)-259(of)-259(ties)-259(\050i.e.)-419(items)-259(with)-259(an)-259(equal)-259(v)55(alu)1(e)-1(\051)-258(in)-259(the)-259(original)-259(input.)]TJ 0 -11.955 Td [(With)-493(the)-493(merge-sort)-493(algorithm)-493(ties)-493(are)-493(preserv)27(ed)-493(in)-493(the)-493(same)-493(relativ)28(e)]TJ 0 -11.955 Td [(order)-405(as)-406(they)-405(had)-406(in)-405(the)-406(or)1(iginal)-406(sequence,)-423(while)-406(this)-405(is)-406(not)-405(guaran)28(teed)]TJ 0 -11.955 Td [(for)-333(quic)28(ks)-1(or)1(t)-334(or)-333(heapsort;)]TJ +/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ 0 g 0 G - -12.73 -19.925 Td [(4.)]TJ 0 g 0 G - [-500(If)]TJ/F11 9.9626 Tf 21.89 0 Td [(f)-108(l)-19(ag)]TJ/F8 9.9626 Tf 22.261 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(psb)]TJ -ET -q -1 0 0 1 232.104 542.941 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F11 9.9626 Tf 235.093 542.742 Td [(sor)-28(t)]TJ -ET -q -1 0 0 1 253.559 542.941 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F11 9.9626 Tf 256.548 542.742 Td [(ov)-36(w)]TJ -ET -q -1 0 0 1 274.562 542.941 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F11 9.9626 Tf 277.55 542.742 Td [(idx)]TJ -ET -q -1 0 0 1 292.46 542.941 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F8 9.9626 Tf 297.966 542.742 Td [(then)-253(the)-252(en)27(tries)-252(in)]TJ/F11 9.9626 Tf 80.169 0 Td [(ix)]TJ/F8 9.9626 Tf 9.126 0 Td [(\0501)-278(:)]TJ/F11 9.9626 Tf 17.158 0 Td [(n)]TJ/F8 9.9626 Tf 5.98 0 Td [(\051)-253(where)]TJ/F11 9.9626 Tf 34.397 0 Td [(n)]TJ/F8 9.9626 Tf 8.498 0 Td [(is)-253(the)-252(size)]TJ -277.683 -11.956 Td [(of)]TJ/F11 9.9626 Tf 11.911 0 Td [(x)]TJ/F8 9.9626 Tf 9.579 0 Td [(are)-390(initialized)-390(to)]TJ/F11 9.9626 Tf 76.439 0 Td [(ix)]TJ/F8 9.9626 Tf 9.127 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)]TJ/F14 9.9626 Tf 7.582 0 Td [(\040)]TJ/F11 9.9626 Tf 13.67 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(;)-418(th)28(us,)-405(u)1(p)-28(on)-390(return)-390(from)-390(the)-390(subroutine,)]TJ -139.046 -11.955 Td [(for)-333(eac)27(h)-333(index)]TJ/F11 9.9626 Tf 64.505 0 Td [(i)]TJ/F8 9.9626 Tf 6.752 0 Td [(w)28(e)-333(ha)27(v)28(e)-333(in)]TJ/F11 9.9626 Tf 49.256 0 Td [(ix)]TJ/F8 9.9626 Tf 9.126 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)-333(the)-333(p)-28(osition)-333(that)-333(the)-334(item)]TJ/F11 9.9626 Tf 123.751 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)-333(o)-28(ccupied)]TJ -273.697 -11.955 Td [(in)-333(the)-334(original)-333(data)-333(sequence;)]TJ + 0 -19.925 Td [(x)]TJ 0 g 0 G - -12.73 -19.925 Td [(5.)]TJ +/F8 9.9626 Tf 11.028 0 Td [(In)28(teger)-334(ind)1(ic)-1(es.)]TJ 13.879 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.378 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in,)-383(inout)]TJ/F8 9.9626 Tf 42.646 0 Td [(.)]TJ -76.131 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-334(scalar)-333(or)-334(a)-333(rank)-333(one)-333(in)27(teger)-333(arra)28(y)83(.)]TJ 0 g 0 G - [-500(If)]TJ/F11 9.9626 Tf 23.404 0 Td [(f)-108(l)-19(ag)]TJ/F8 9.9626 Tf 23.446 0 Td [(=)]TJ/F11 9.9626 Tf 11.701 0 Td [(psb)]TJ -ET -q -1 0 0 1 235.988 487.15 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F11 9.9626 Tf 238.977 486.951 Td [(sor)-28(t)]TJ +/F27 9.9626 Tf -24.907 -31.88 Td [(desc)]TJ ET q -1 0 0 1 257.443 487.15 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 172.619 546.469 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F11 9.9626 Tf 260.432 486.951 Td [(k)-31(ee)-1(p)]TJ +/F27 9.9626 Tf 176.057 546.27 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.55 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 280.82 487.15 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 362.845 498.649 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F11 9.9626 Tf 283.809 486.951 Td [(idx)]TJ +/F30 9.9626 Tf 365.983 498.449 Td [(desc)]TJ ET q -1 0 0 1 298.718 487.15 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 387.532 498.649 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F8 9.9626 Tf 305.739 486.951 Td [(the)-405(routine)-404(will)-405(assume)-405(that)-404(the)-405(en)28(tries)-405(in)]TJ/F11 9.9626 Tf -130.128 -11.955 Td [(ix)]TJ/F8 9.9626 Tf 9.127 0 Td [(\050:\051)-333(ha)28(v)27(e)-333(already)-333(b)-28(een)-333(initialized)-334(b)28(y)-333(the)-333(use)-1(r;)]TJ -0 g 0 G - -21.857 -19.926 Td [(6.)]TJ +/F30 9.9626 Tf 390.67 498.449 Td [(type)]TJ 0 g 0 G - [-500(The)-376(three)-375(sorting)-376(algorithms)-376(ha)28(v)28(e)-376(a)-376(similar)]TJ/F11 9.9626 Tf 208.295 0 Td [(O)]TJ/F8 9.9626 Tf 7.876 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(n)]TJ/F8 9.9626 Tf 7.64 0 Td [(log)]TJ/F11 9.9626 Tf 14.529 0 Td [(n)]TJ/F8 9.9626 Tf 5.98 0 Td [(\051)-376(exp)-27(ec)-1(t)1(e)-1(d)-375(running)]TJ -235.465 -11.955 Td [(time;)-349(in)-343(the)-344(a)28(v)28(erage)-344(case)-344(qu)1(ic)27(ksort)-343(will)-344(b)-28(e)-343(the)-344(fastest)-343(and)-344(merge-sort)-343(the)]TJ 0 -11.955 Td [(slo)28(w)27(est.)-444(Ho)28(w)27(ev)28(er)-333(note)-333(that:)]TJ +/F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G - 4.207 -19.925 Td [(\050a\051)]TJ +/F27 9.9626 Tf -260.887 -19.925 Td [(iact)]TJ 0 g 0 G - [-500(The)-419(w)28(orst)-419(case)-419(run)1(ning)-419(time)-419(for)-419(qui)1(c)27(ksort)-418(is)]TJ/F11 9.9626 Tf 221.058 0 Td [(O)]TJ/F8 9.9626 Tf 7.876 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(n)]TJ/F7 6.9738 Tf 5.98 3.615 Td [(2)]TJ/F8 9.9626 Tf 4.469 -3.615 Td [(\051;)-461(the)-419(algorithm)]TJ -225.547 -11.955 Td [(implemen)28(ted)-319(here)-319(follo)28(ws)-319(the)-319(w)27(ell-kno)28(wn)-319(median-of-three)-319(heuristics,)]TJ 0 -11.956 Td [(but)-333(the)-334(w)28(orst)-333(case)-334(ma)28(y)-333(still)-334(app)1(ly;)]TJ +/F8 9.9626 Tf 23.28 0 Td [(sp)-28(eci\014es)-333(action)-334(to)-333(b)-28(e)-333(tak)28(en)-334(in)-333(case)-333(of)-334(range)-333(errors.)-444(Scop)-28(e:)]TJ/F27 9.9626 Tf 257.148 0 Td [(global)]TJ/F8 9.9626 Tf -255.522 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-255(as:)-405(a)-256(c)28(haracter)-255(v)56(ariable)]TJ/F30 9.9626 Tf 143.584 0 Td [(I)]TJ/F8 9.9626 Tf 5.231 0 Td [(gnore,)]TJ/F30 9.9626 Tf 29.293 0 Td [(W)]TJ/F8 9.9626 Tf 5.23 0 Td [(arning)-255(or)]TJ/F30 9.9626 Tf 41.67 0 Td [(A)]TJ/F8 9.9626 Tf 5.23 0 Td [(b)-28(ort,)-271(d)1(e)-1(f)1(ault)]TJ/F30 9.9626 Tf 56.742 0 Td [(I)]TJ/F8 9.9626 Tf 5.23 0 Td [(gnore.)]TJ 0 g 0 G - -18.265 -15.94 Td [(\050b\051)]TJ +/F27 9.9626 Tf -317.116 -21.918 Td [(On)-383(Return)]TJ 0 g 0 G - [-500(The)-222(w)28(orst)-223(case)-222(running)-222(time)-222(for)-223(merge-sort)-222(and)-222(heap-sort)-222(is)]TJ/F11 9.9626 Tf 273.309 0 Td [(O)]TJ/F8 9.9626 Tf 7.876 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(n)]TJ/F8 9.9626 Tf 7.64 0 Td [(log)]TJ/F11 9.9626 Tf 14.529 0 Td [(n)]TJ/F8 9.9626 Tf 5.98 0 Td [(\051)]TJ -294.944 -11.955 Td [(as)-333(the)-334(a)28(v)28(erage)-334(case;)]TJ 0 g 0 G - -17.158 -15.94 Td [(\050c\051)]TJ + 0 -19.926 Td [(y)]TJ 0 g 0 G - [-500(The)-358(merge-sort)-358(algorithm)-357(is)-358(implemen)28(ted)-358(to)-358(tak)28(e)-358(adv)56(an)28(tage)-358(of)-358(sub-)]TJ 17.158 -11.955 Td [(sequences)-401(that)-400(ma)28(y)-401(b)-28(e)-400(already)-401(in)-400(the)-401(desired)-400(ordering)-400(prior)-401(to)-400(the)]TJ 0 -11.956 Td [(subroutine)-246(call;)-275(this)-246(situation)-246(is)-247(relativ)28(ely)-246(common)-246(when)-246(dealing)-246(with)]TJ 0 -11.955 Td [(groups)-301(of)-301(indices)-301(of)-302(sparse)-301(matrix)-301(en)28(tries,)-308(th)28(us)-301(merge-sort)-302(is)-301(the)-301(pre-)]TJ 0 -11.955 Td [(ferred)-249(c)28(hoice)-249(when)-249(a)-249(sorting)-248(is)-249(needed)-249(b)28(y)-249(other)-249(routines)-249(in)-249(t)1(he)-249(library)83(.)]TJ +/F8 9.9626 Tf 11.028 0 Td [(A)-346(logical)-345(mask)-346(whic)28(h)-346(is)-345(true)-346(for)-345(all)-346(corresp)-28(ondin)1(g)-346(en)28(tries)-346(of)]TJ/F11 9.9626 Tf 264.882 0 Td [(x)]TJ/F8 9.9626 Tf 9.137 0 Td [(that)-346(ar)1(e)-346(lo)-28(cal)]TJ -260.141 -11.955 Td [(to)-333(the)-334(curren)28(t)-333(pro)-28(cess)-333(Scop)-28(e:)]TJ/F27 9.9626 Tf 131.092 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -131.092 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(scalar)-333(or)-334(rank)-333(one)-333(logical)-334(ar)1(ra)27(y)84(.)]TJ 0 g 0 G - 120.05 -205.23 Td [(98)]TJ +/F27 9.9626 Tf -24.906 -19.926 Td [(info)]TJ 0 g 0 G -ET - -endstream -endobj -1504 0 obj -<< -/Length 181 ->> -stream +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(te)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ/F16 11.9552 Tf -24.906 -21.918 Td [(Notes)]TJ 0 g 0 G +/F8 9.9626 Tf 12.176 -19.925 Td [(1.)]TJ 0 g 0 G -BT -/F16 14.3462 Tf 99.895 706.129 Td [(7)-1125(P)31(arallel)-375(en)31(vironmen)32(t)-375(routines)]TJ + [-500(This)-308(routine)-309(return)1(s)-309(a)]TJ/F30 9.9626 Tf 111.554 0 Td [(.true.)]TJ/F8 9.9626 Tf 34.454 0 Td [(v)56(alue)-309(for)-308(those)-308(indices)-309(that)-308(are)-308(lo)-28(cal)-308(to)-309(the)]TJ -133.278 -11.955 Td [(curren)28(t)-334(p)1(ro)-28(cess,)-334(including)-333(the)-333(halo)-334(i)1(ndices)-1(.)]TJ 0 g 0 G -/F8 9.9626 Tf 166.875 -615.691 Td [(99)]TJ + 141.968 -141.013 Td [(94)]TJ 0 g 0 G ET endstream endobj -1508 0 obj +1495 0 obj << -/Length 5574 +/Length 3821 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ +/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ ET q -1 0 0 1 171.761 706.328 cm +1 0 0 1 120.951 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(init)-375(|)-375(Initializes)-375(PSBLAS)-375(parallel)-375(en)31(vironmen)31(t)]TJ -0 g 0 G -0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_init\050icontxt,)-525(np,)-525(basectxt,)-525(ids\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-294(subroutine)-294(initial)1(iz)-1(es)-293(the)-294(PSBLAS)-294(parallel)-294(en)28(vironmen)28(t,)-302(de\014ning)-294(a)-294(vir-)]TJ -14.944 -11.955 Td [(tual)-333(parallel)-334(mac)28(hine.)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(get)]TJ +ET +q +1 0 0 1 143.885 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 147.92 706.129 Td [(b)-31(oundary)-375(|)-375(Extract)-375(list)-375(of)-375(b)-32(oundary)-375(elemen)32(ts)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -19.926 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ +/F30 9.9626 Tf -48.025 -18.389 Td [(call)-525(psb_get_boundary\050bndel,)-525(desc,)-525(info\051)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G - 0 -19.925 Td [(np)]TJ +/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ 0 g 0 G -/F8 9.9626 Tf 17.711 0 Td [(Num)28(b)-28(er)-333(of)-334(pro)-27(cess)-1(es)-333(in)-333(the)-334(P)1(SBLA)-1(S)-333(virtual)-333(parallel)-333(mac)27(hin)1(e)-1(.)]TJ 7.196 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(alue.)-778(Defau)1(lt:)-445(use)-333(all)-334(a)28(v)56(ailable)-333(pro)-28(cesses.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.925 Td [(basectxt)]TJ + 0 -19.925 Td [(desc)]TJ 0 g 0 G -/F8 9.9626 Tf 46.736 0 Td [(the)-356(initial)-357(comm)28(unication)-356(con)28(text.)-514(The)-356(new)-357(con)28(text)-356(will)-357(b)-27(e)-357(de\014ned)]TJ -21.829 -11.955 Td [(from)-333(the)-334(pro)-27(cesse)-1(s)-333(participating)-333(in)-333(the)-334(initial)-333(one.)]TJ 0 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)-778(Defau)1(lt:)-445(use)-333(MPI)]TJ +/F8 9.9626 Tf 26.209 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -1.302 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 389.991 466.768 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 312.036 578.35 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F8 9.9626 Tf 392.98 466.569 Td [(COMM)]TJ +/F30 9.9626 Tf 315.174 578.15 Td [(desc)]TJ ET q -1 0 0 1 426.787 466.768 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 336.723 578.35 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F8 9.9626 Tf 429.775 466.569 Td [(W)28(ORLD.)]TJ +/F30 9.9626 Tf 339.861 578.15 Td [(type)]TJ 0 g 0 G -/F27 9.9626 Tf -279.07 -19.925 Td [(ids)]TJ +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F8 9.9626 Tf 19.048 0 Td [(Iden)28(tities)-497(of)-497(the)-497(pro)-28(cesses)-497(to)-497(use)-497(for)-497(the)-497(new)-498(con)28(text;)-579(the)-497(argumen)28(t)-497(is)]TJ 5.858 -11.956 Td [(ignored)-428(when)]TJ/F30 9.9626 Tf 63.346 0 Td [(np)]TJ/F8 9.9626 Tf 14.723 0 Td [(is)-428(not)-428(sp)-27(eci\014ed.)-728(This)-428(allo)28(ws)-428(the)-428(pro)-27(ces)-1(ses)-427(in)-428(the)-428(new)]TJ -78.069 -11.955 Td [(en)28(vironmen)28(t)-334(to)-333(b)-28(e)-333(in)-333(an)-334(order)-333(di\013eren)28(t)-334(from)-333(the)-333(original)-333(one.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf 40.576 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)84(.)-778(Default:)-444(use)-334(the)-333(indices)-333(\0500)]TJ/F11 9.9626 Tf 254.159 0 Td [(:)-167(:)-166(:)-167(np)]TJ/F14 9.9626 Tf 26.489 0 Td [(\000)]TJ/F8 9.9626 Tf 9.963 0 Td [(1\051.)]TJ +/F27 9.9626 Tf -260.887 -21.917 Td [(On)-383(Return)]TJ 0 g 0 G -/F27 9.9626 Tf -315.517 -21.918 Td [(On)-383(Return)]TJ 0 g 0 G + 0 -19.926 Td [(bndel)]TJ 0 g 0 G - 0 -19.925 Td [(icon)32(txt)]TJ +/F8 9.9626 Tf 32.51 0 Td [(The)-268(list)-267(of)-268(b)-27(oundary)-268(elemen)28(ts)-268(on)-267(the)-268(calling)-267(pro)-28(cess,)-281(in)-267(lo)-28(cal)-268(n)28(um)28(b)-28(ering.)]TJ -7.603 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-456(as:)-691(a)-457(rank)-456(one)-457(arra)28(y)-456(with)-457(the)-457(ALLOCA)84(T)83(ABLE)-456(attribute,)-488(of)]TJ 0 -11.955 Td [(t)28(yp)-28(e)-333(in)28(te)-1(ger.)]TJ 0 g 0 G -/F8 9.9626 Tf 39.989 0 Td [(the)-457(c)-1(omm)28(unication)-457(con)28(te)-1(x)1(t)-458(iden)28(tifying)-458(the)-457(virtual)-458(p)1(arallel)-458(mac)28(hine.)]TJ -15.083 -11.956 Td [(Note)-335(that)-335(this)-335(is)-336(alw)28(a)28(ys)-335(a)-335(duplicate)-335(of)]TJ/F30 9.9626 Tf 169.953 0 Td [(basectxt)]TJ/F8 9.9626 Tf 41.843 0 Td [(,)-336(so)-335(that)-335(library)-335(comm)28(u-)]TJ -211.796 -11.955 Td [(nications)-305(are)-305(completely)-306(separated)-305(from)-305(other)-305(comm)28(unication)-305(op)-28(erations.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.51 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable.)]TJ/F16 11.9552 Tf -24.906 -21.917 Td [(Notes)]TJ +/F27 9.9626 Tf -24.907 -31.881 Td [(info)]TJ 0 g 0 G -/F8 9.9626 Tf 12.176 -19.926 Td [(1.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.956 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ/F16 11.9552 Tf -24.907 -21.917 Td [(Notes)]TJ 0 g 0 G - [-500(A)-333(call)-334(to)-333(this)-333(routine)-334(m)28(ust)-333(precede)-334(an)28(y)-333(other)-333(PSBLAS)-334(call.)]TJ +/F8 9.9626 Tf 12.177 -19.926 Td [(1.)]TJ 0 g 0 G - 0 -19.925 Td [(2.)]TJ + [-500(If)-269(there)-269(are)-269(no)-269(b)-28(oundary)-269(elemen)28(ts)-269(\050i.e.,)-282(if)-269(the)-269(lo)-28(cal)-269(part)-269(of)-269(the)-269(c)-1(onn)1(e)-1(ctivi)1(t)27(y)]TJ 12.73 -11.955 Td [(graph)-449(is)-450(self-con)28(tained\051)-450(the)-449(output)-449(v)27(ector)-449(is)-450(set)-449(to)-450(the)-449(\134not)-450(allo)-27(c)-1(ated")]TJ 0 -11.955 Td [(state.)]TJ +0 g 0 G + -12.73 -19.925 Td [(2.)]TJ 0 g 0 G - [-500(It)-262(is)-262(an)-262(error)-262(to)-262(sp)-28(ecify)-262(a)-262(v)56(alue)-262(for)]TJ/F11 9.9626 Tf 159.87 0 Td [(np)]TJ/F8 9.9626 Tf 13.602 0 Td [(greater)-262(than)-262(the)-262(n)28(um)28(b)-28(er)-262(of)-262(pro)-28(cesses)]TJ -160.742 -11.955 Td [(a)28(v)55(ailable)-333(in)-333(the)-334(und)1(e)-1(r)1(lying)-334(base)-333(parallel)-333(en)27(viron)1(m)-1(en)28(t.)]TJ + [-500(Otherwise)-288(the)-289(size)-288(of)]TJ/F30 9.9626 Tf 105.44 0 Td [(bndel)]TJ/F8 9.9626 Tf 29.023 0 Td [(will)-288(b)-28(e)-288(exactly)-289(equal)-288(to)-288(the)-288(n)28(um)27(b)-27(er)-289(of)-288(b)-28(ound)1(-)]TJ -121.733 -11.956 Td [(ary)-333(elemen)27(ts.)]TJ 0 g 0 G - 139.477 -97.177 Td [(100)]TJ + 141.968 -208.758 Td [(95)]TJ 0 g 0 G ET endstream endobj -1514 0 obj +1502 0 obj << -/Length 4647 +/Length 3654 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ +/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ ET q -1 0 0 1 120.951 706.328 cm +1 0 0 1 171.761 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 175.796 706.129 Td [(get)]TJ +ET +q +1 0 0 1 194.695 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(info)-306(|)-307(Return)-306(information)-306(ab)-31(out)-307(PSBLAS)-306(parallel)-306(en-)]TJ -25.091 -13.948 Td [(vironmen)31(t)]TJ +/F16 11.9552 Tf 198.729 706.129 Td [(o)31(v)31(erlap)-375(|)-375(Extract)-375(list)-375(of)-375(o)32(v)31(erlap)-375(elemen)31(ts)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf 0 -18.389 Td [(call)-525(psb_info\050icontxt,)-525(iam,)-525(np\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-456(subroutine)-456(returns)-456(inf)1(orma)-1(t)1(ion)-456(ab)-28(out)-456(the)-456(PSBLAS)-456(paral)1(le)-1(l)-455(en)27(viron-)]TJ -14.944 -11.955 Td [(men)28(t,)-334(de\014nin)1(g)-334(a)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ +/F30 9.9626 Tf -48.024 -18.389 Td [(call)-525(psb_get_overlap\050ovrel,)-525(desc,)-525(info\051)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -19.925 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G /F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(icon)32(txt)]TJ + 0 -19.925 Td [(desc)]TJ 0 g 0 G -/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyin)1(g)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable.)]TJ +/F8 9.9626 Tf 26.208 0 Td [(the)-333(comm)27(unication)-333(descriptor.)]TJ -1.302 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ +ET +q +1 0 0 1 362.845 578.35 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 365.983 578.15 Td [(desc)]TJ +ET +q +1 0 0 1 387.532 578.35 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 390.67 578.15 Td [(type)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -21.918 Td [(On)-383(Return)]TJ +/F8 9.9626 Tf 20.922 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -260.887 -21.917 Td [(On)-383(Return)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(iam)]TJ + 0 -19.926 Td [(o)32(vrel)]TJ 0 g 0 G -/F8 9.9626 Tf 23.281 0 Td [(Iden)28(ti\014er)-333(of)-334(curren)28(t)-333(pro)-28(cess)-333(in)-334(the)-333(PSBLAS)-333(virtual)-334(par)1(allel)-334(mac)28(hine.)]TJ 1.626 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)]TJ/F14 9.9626 Tf 134.302 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)]TJ/F14 9.9626 Tf 7.749 0 Td [(\024)]TJ/F11 9.9626 Tf 10.516 0 Td [(iam)]TJ/F14 9.9626 Tf 20.213 0 Td [(\024)]TJ/F11 9.9626 Tf 10.516 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.963 0 Td [(1)]TJ +/F8 9.9626 Tf 29.59 0 Td [(The)-333(list)-334(of)-333(o)28(v)28(erlap)-334(elemen)28(ts)-333(on)-334(the)-333(calling)-333(pro)-28(cess,)-334(in)-333(lo)-28(cal)-333(n)28(um)28(b)-28(ering.)]TJ -4.684 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-456(as:)-691(a)-457(rank)-456(one)-457(arra)28(y)-457(with)-456(the)-457(ALLOCA)84(T)83(ABLE)-456(attribute,)-488(of)]TJ 0 -11.955 Td [(t)28(yp)-28(e)-333(in)27(teger.)]TJ 0 g 0 G -/F27 9.9626 Tf -239.121 -19.926 Td [(np)]TJ +/F27 9.9626 Tf -24.906 -31.881 Td [(info)]TJ 0 g 0 G -/F8 9.9626 Tf 17.712 0 Td [(Num)28(b)-28(er)-333(of)-334(pro)-27(cesse)-1(s)-333(in)-333(the)-333(PSBLAS)-334(virtual)-333(parallel)-333(mac)27(h)1(ine.)]TJ 7.195 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -71.51 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.956 Td [(An)-333(in)28(te)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ/F16 11.9552 Tf -24.906 -21.917 Td [(Notes)]TJ 0 g 0 G -/F8 9.9626 Tf 12.177 -19.926 Td [(1.)]TJ +/F8 9.9626 Tf 12.176 -19.926 Td [(1.)]TJ 0 g 0 G - [-500(F)83(or)-500(pro)-27(cesse)-1(s)-500(in)-500(th)1(e)-501(v)1(irtual)-500(parallel)-500(mac)27(hin)1(e)-501(th)1(e)-501(id)1(e)-1(n)28(ti\014er)-500(will)-500(satisfy)]TJ 12.73 -11.955 Td [(0)]TJ/F14 9.9626 Tf 7.749 0 Td [(\024)]TJ/F11 9.9626 Tf 10.516 0 Td [(iam)]TJ/F14 9.9626 Tf 20.213 0 Td [(\024)]TJ/F11 9.9626 Tf 10.516 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.963 0 Td [(1;)]TJ + [-500(If)-343(there)-344(ar)1(e)-344(no)-343(o)28(v)28(erlap)-344(elemen)28(ts)-343(the)-343(output)-344(v)28(ector)-343(is)-343(set)-344(to)-343(the)-343(\134not)-343(allo-)]TJ 12.73 -11.955 Td [(cated")-333(state.)]TJ 0 g 0 G - -84.893 -19.925 Td [(2.)]TJ + -12.73 -19.925 Td [(2.)]TJ 0 g 0 G - [-500(If)-432(the)-433(user)-432(has)-433(requested)-432(on)]TJ/F30 9.9626 Tf 143.13 0 Td [(psb_init)]TJ/F8 9.9626 Tf 46.151 0 Td [(a)-432(n)27(um)28(b)-28(er)-432(of)-432(pro)-28(cesses)-433(less)-432(than)]TJ -176.551 -11.955 Td [(the)-417(total)-416(a)28(v)55(ailable)-416(in)-417(the)-416(parallel)-417(execution)-416(en)28(vironmen)28(t,)-438(the)-416(remaining)]TJ 0 -11.955 Td [(pro)-28(cesses)-359(will)-359(ha)28(v)28(e)-359(on)-359(return)]TJ/F11 9.9626 Tf 130.486 0 Td [(iam)]TJ/F8 9.9626 Tf 20.639 0 Td [(=)]TJ/F14 9.9626 Tf 10.941 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1;)-372(the)-359(only)-359(call)-359(in)28(v)28(olving)]TJ/F30 9.9626 Tf 112.377 0 Td [(icontxt)]TJ/F8 9.9626 Tf -282.192 -11.956 Td [(that)-333(an)28(y)-334(suc)28(h)-333(pro)-28(cess)-334(ma)28(y)-333(execute)-334(is)-333(to)]TJ/F30 9.9626 Tf 177.086 0 Td [(psb_exit)]TJ/F8 9.9626 Tf 41.843 0 Td [(.)]TJ + [-500(Otherwise)-284(the)-284(size)-283(of)]TJ/F30 9.9626 Tf 105.262 0 Td [(ovrel)]TJ/F8 9.9626 Tf 28.978 0 Td [(will)-284(b)-27(e)-284(exactly)-284(equal)-284(to)-284(the)-283(n)27(u)1(m)27(b)-27(e)-1(r)-283(of)-284(o)28(v)28(erlap)]TJ -121.51 -11.955 Td [(elemen)28(ts.)]TJ 0 g 0 G - -79.452 -174.885 Td [(101)]TJ + 141.968 -220.714 Td [(96)]TJ 0 g 0 G ET endstream endobj -1520 0 obj +1509 0 obj << -/Length 4355 +/Length 5783 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ +/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ ET q -1 0 0 1 171.761 706.328 cm +1 0 0 1 120.951 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(exit)-375(|)-375(Exit)-375(from)-375(PSBLAS)-375(parallel)-375(en)31(vironmen)31(t)]TJ -0 g 0 G -0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_exit\050icontxt\051)]TJ 0 -11.956 Td [(call)-525(psb_exit\050icontxt,close\051)]TJ/F8 9.9626 Tf 14.944 -21.917 Td [(This)-333(subroutine)-334(exits)-333(from)-333(the)-334(PS)1(B)-1(LAS)-333(parallel)-333(virtual)-333(mac)27(hin)1(e)-1(.)]TJ -0 g 0 G -/F27 9.9626 Tf -14.944 -19.926 Td [(T)32(yp)-32(e:)]TJ -0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ -0 g 0 G -/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ -0 g 0 G -0 g 0 G - 0 -19.925 Td [(icon)32(txt)]TJ -0 g 0 G -/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyi)1(ng)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(ariable.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -19.925 Td [(close)]TJ -0 g 0 G -/F8 9.9626 Tf 28.754 0 Td [(Whether)-401(to)-401(c)-1(lose)-401(all)-401(data)-401(structures)-402(related)-401(to)-401(the)-401(virtual)-401(parallel)-402(ma-)]TJ -3.847 -11.955 Td [(c)28(hine,)-333(b)-28(esides)-334(those)-333(asso)-28(ciated)-333(with)-334(icon)28(txt.)]TJ 0 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-334(logical)-333(v)55(ariabl)1(e)-1(,)-333(default)-333(v)55(al)1(ue:)-445(true.)]TJ/F16 11.9552 Tf -24.907 -19.925 Td [(Notes)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(sp)]TJ +ET +q +1 0 0 1 138.57 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 142.605 706.129 Td [(getro)31(w)-375(|)-375(Extract)-375(ro)31(w\050s\051)-375(from)-375(a)-375(sparse)-375(matrix)]TJ 0 g 0 G -/F8 9.9626 Tf 12.177 -19.926 Td [(1.)]TJ 0 g 0 G - [-500(This)-241(routine)-241(ma)28(y)-241(b)-28(e)-241(called)-241(ev)28(en)-241(if)-241(a)-241(previous)-241(call)-241(to)]TJ/F30 9.9626 Tf 233.304 0 Td [(psb_info)]TJ/F8 9.9626 Tf 44.244 0 Td [(has)-241(returned)]TJ -264.818 -11.955 Td [(with)]TJ/F11 9.9626 Tf 22.962 0 Td [(iam)]TJ/F8 9.9626 Tf 20.663 0 Td [(=)]TJ/F14 9.9626 Tf 10.966 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1;)-374(indeed,)-367(it)-360(it)-361(is)-360(the)-361(only)-360(routine)-360(that)-361(ma)28(y)-360(b)-28(e)-361(called)-360(with)]TJ -62.34 -11.955 Td [(argumen)28(t)]TJ/F30 9.9626 Tf 44.583 0 Td [(icontxt)]TJ/F8 9.9626 Tf 39.933 0 Td [(in)-333(this)-334(situation)1(.)]TJ +/F30 9.9626 Tf -42.71 -18.647 Td [(call)-525(psb_sp_getrow\050row,)-525(a,)-525(nz,)-525(ia,)-525(ja,)-525(val,)-525(info,)-525(&)]TJ 73.225 -11.955 Td [(&)-525(append,)-525(nzin,)-525(lrw\051)]TJ 0 g 0 G - -97.246 -19.925 Td [(2.)]TJ +/F27 9.9626 Tf -73.225 -22.334 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G - [-500(A)-305(call)-306(to)-305(this)-305(routine)-305(with)]TJ/F30 9.9626 Tf 128.752 0 Td [(close=.true.)]TJ/F8 9.9626 Tf 65.806 0 Td [(implies)-305(a)-306(call)-305(to)]TJ/F30 9.9626 Tf 71.445 0 Td [(MPI_Finalize)]TJ/F8 9.9626 Tf 62.764 0 Td [(,)]TJ -316.037 -11.956 Td [(after)-333(whic)28(h)-334(no)-333(parallel)-333(routine)-334(ma)28(y)-333(b)-28(e)-333(called.)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G - -12.73 -19.925 Td [(3.)]TJ +/F27 9.9626 Tf -33.797 -20.479 Td [(On)-383(En)32(try)]TJ 0 g 0 G - [-500(If)-391(the)-390(user)-391(whishes)-391(to)-390(use)-391(m)28(ultiple)-391(comm)28(unication)-391(con)28(texts)-391(in)-390(the)-391(same)]TJ 12.73 -11.955 Td [(program,)-485(or)-455(to)-455(en)28(ter)-455(and)-454(exit)-455(m)27(u)1(ltiple)-455(times)-455(in)28(to)-455(the)-455(parallel)-455(en)28(viron-)]TJ 0 -11.955 Td [(men)28(t,)-494(this)-462(routine)-462(ma)28(y)-462(b)-28(e)-462(called)-462(to)-462(selectiv)28(ely)-462(close)-462(the)-462(con)27(texts)-462(with)]TJ/F30 9.9626 Tf 0 -11.955 Td [(close=.false.)]TJ/F8 9.9626 Tf 67.994 0 Td [(,)-244(while)-223(on)-222(the)-222(last)-222(call)-223(it)-222(should)-222(b)-28(e)-222(called)-222(with)]TJ/F30 9.9626 Tf 194.327 0 Td [(close=.true.)]TJ/F8 9.9626 Tf -262.321 -11.955 Td [(to)-333(sh)27(u)1(tdo)27(wn)-333(in)-333(a)-334(clean)-333(w)28(a)28(y)-334(the)-333(en)28(tire)-334(parallel)-333(en)28(vironmen)28(t.)]TJ 0 g 0 G - 139.477 -212.744 Td [(102)]TJ + 0 -20.479 Td [(ro)32(w)]TJ 0 g 0 G -ET - -endstream -endobj -1527 0 obj -<< -/Length 2161 ->> -stream +/F8 9.9626 Tf 23.385 0 Td [(The)-333(\050\014rst\051)-334(ro)28(w)-333(to)-334(b)-27(e)-334(extracted.)]TJ 1.522 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.951 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf -25.183 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)]TJ/F11 9.9626 Tf 104.691 0 Td [(>)]TJ/F8 9.9626 Tf 10.516 0 Td [(0.)]TJ 0 g 0 G +/F27 9.9626 Tf -140.114 -20.479 Td [(a)]TJ 0 g 0 G -BT -/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ +/F8 9.9626 Tf 10.551 0 Td [(the)-333(matrix)-334(from)-333(whic)28(h)-333(to)-334(get)-333(ro)28(ws.)]TJ 14.356 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.951 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf -25.183 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 120.951 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +1 0 0 1 312.036 496.313 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(get)]TJ +/F30 9.9626 Tf 315.174 496.114 Td [(Tspmat)]TJ ET q -1 0 0 1 143.885 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +1 0 0 1 347.183 496.313 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F16 11.9552 Tf 147.92 706.129 Td [(mpicomm)-375(|)-375(Get)-375(the)-375(MPI)-375(comm)31(unicator)]TJ +/F30 9.9626 Tf 350.322 496.114 Td [(type)]TJ 0 g 0 G +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F30 9.9626 Tf -48.025 -18.389 Td [(call)-525(psb_get_mpicomm\050icontxt,)-525(icomm\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-335(subroutine)-335(returns)-335(the)-336(MPI)-335(comm)28(unicator)-335(asso)-28(ciated)-335(with)-335(a)-336(P)1(SBLAS)]TJ -14.944 -11.955 Td [(con)28(text)]TJ +/F27 9.9626 Tf -271.348 -20.479 Td [(app)-32(end)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -19.926 Td [(T)32(yp)-32(e:)]TJ +/F8 9.9626 Tf 41.58 0 Td [(Whether)-333(to)-334(app)-27(end)-334(or)-333(o)28(v)28(erwrite)-334(existing)-333(output.)]TJ -16.673 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.951 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf -25.183 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(logical)-333(v)55(alue)-333(default:)-444(false)-334(\050o)28(v)28(erwrite\051.)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +/F27 9.9626 Tf -24.907 -20.479 Td [(nzin)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ +/F8 9.9626 Tf 25.986 0 Td [(Input)-333(size)-334(to)-333(b)-28(e)-333(app)-28(ended)-333(to.)]TJ -1.079 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.951 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf -25.183 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-398(as:)-573(an)-398(in)28(teger)]TJ/F11 9.9626 Tf 107.907 0 Td [(>)]TJ/F8 9.9626 Tf 11.589 0 Td [(0.)-638(When)-398(app)-28(end)-398(i)1(s)-398(true,)-414(sp)-28(eci\014es)-398(ho)28(w)-398(man)27(y)]TJ -119.496 -11.955 Td [(en)28(tries)-334(in)-333(the)-333(output)-333(v)27(ectors)-333(are)-333(already)-334(\014lled.)]TJ 0 g 0 G +/F27 9.9626 Tf -24.907 -20.479 Td [(lrw)]TJ 0 g 0 G - 0 -19.925 Td [(icon)32(txt)]TJ +/F8 9.9626 Tf 21.157 0 Td [(The)-333(last)-334(ro)28(w)-333(to)-334(b)-27(e)-334(extracted.)]TJ 3.75 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -27.951 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf -25.183 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)]TJ/F11 9.9626 Tf 104.691 0 Td [(>)]TJ/F8 9.9626 Tf 10.516 0 Td [(0,)-333(default:)]TJ/F11 9.9626 Tf 48.43 0 Td [(r)-28(ow)]TJ/F8 9.9626 Tf 17.001 0 Td [(.)]TJ 0 g 0 G -/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyin)1(g)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable.)]TJ +/F27 9.9626 Tf -205.545 -22.334 Td [(On)-383(Return)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -21.918 Td [(On)-383(Return)]TJ 0 g 0 G + 0 -20.479 Td [(nz)]TJ 0 g 0 G - 0 -19.925 Td [(icomm)]TJ +/F8 9.9626 Tf 16.439 0 Td [(the)-333(n)28(um)27(b)-27(er)-334(of)-333(elemen)28(ts)-334(returned)-333(b)28(y)-334(th)1(is)-334(call.)]TJ 8.468 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.956 Td [(Returned)-333(as:)-445(an)-333(in)28(teger)-334(scalar.)]TJ 0 g 0 G -/F8 9.9626 Tf 38.08 0 Td [(The)-377(MPI)-378(comm)28(unicator)-377(as)-1(so)-27(ciated)-378(with)-377(the)-378(PSBLAS)-377(virtual)-377(parallel)]TJ -13.173 -11.955 Td [(mac)28(hine.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ +/F27 9.9626 Tf -24.907 -20.479 Td [(ia)]TJ +0 g 0 G +/F8 9.9626 Tf 13.734 0 Td [(the)-333(ro)28(w)-334(indices.)]TJ 11.173 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)-333(with)-333(the)]TJ/F30 9.9626 Tf 170.611 0 Td [(ALLOCATABLE)]TJ/F8 9.9626 Tf 60.854 0 Td [(attribute.)]TJ 0 g 0 G - 89.442 -366.168 Td [(103)]TJ + -89.497 -29.887 Td [(97)]TJ 0 g 0 G ET endstream endobj -1532 0 obj +1514 0 obj << -/Length 3025 +/Length 3711 >> stream 0 g 0 G 0 g 0 G -BT -/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ -ET -q -1 0 0 1 171.761 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 175.796 706.129 Td [(get)]TJ -ET -q -1 0 0 1 194.695 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 198.729 706.129 Td [(rank)-375(|)-375(Get)-375(the)-375(MPI)-375(rank)]TJ -0 g 0 G 0 g 0 G -/F30 9.9626 Tf -48.024 -18.389 Td [(call)-525(psb_get_rank\050rank,)-525(icontxt,)-525(id\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-333(subroutine)-334(retu)1(rns)-334(the)-333(MPI)-333(rank)-334(of)-333(the)-333(PSBLAS)-334(pr)1(o)-28(cess)]TJ/F11 9.9626 Tf 274.665 0 Td [(id)]TJ -0 g 0 G -/F27 9.9626 Tf -289.609 -19.926 Td [(T)32(yp)-32(e:)]TJ +BT +/F27 9.9626 Tf 150.705 706.129 Td [(ja)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +/F8 9.9626 Tf 14.051 0 Td [(the)-333(column)-334(indices)-333(of)-333(the)-334(elemen)28(ts)-333(to)-334(b)-27(e)-334(inserted.)]TJ 10.855 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)-333(with)-333(the)]TJ/F30 9.9626 Tf 170.611 0 Td [(ALLOCATABLE)]TJ/F8 9.9626 Tf 60.855 0 Td [(attribute.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -256.372 -19.925 Td [(v)64(al)]TJ 0 g 0 G +/F8 9.9626 Tf 19.143 0 Td [(the)-333(elemen)27(ts)-333(to)-333(b)-28(e)-333(inse)-1(r)1(te)-1(d)1(.)]TJ 5.763 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -51.024 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(real)-333(arra)28(y)-334(with)-333(the)]TJ/F30 9.9626 Tf 151.516 0 Td [(ALLOCATABLE)]TJ/F8 9.9626 Tf 60.854 0 Td [(attribute.)]TJ 0 g 0 G - 0 -19.925 Td [(icon)32(txt)]TJ +/F27 9.9626 Tf -237.276 -19.925 Td [(info)]TJ 0 g 0 G -/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyi)1(ng)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(ariable.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(te)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(t)1(e)-1(d.)]TJ/F16 11.9552 Tf -24.906 -21.918 Td [(Notes)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.925 Td [(id)]TJ +/F8 9.9626 Tf 12.176 -19.925 Td [(1.)]TJ 0 g 0 G -/F8 9.9626 Tf 14.529 0 Td [(Iden)28(ti\014er)-333(of)-334(a)-333(pro)-28(cess)-333(in)-334(the)-333(PSBLAS)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ 10.378 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.451 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(alue.)-444(0)]TJ/F14 9.9626 Tf 142.05 0 Td [(\024)]TJ/F11 9.9626 Tf 10.516 0 Td [(id)]TJ/F14 9.9626 Tf 11.385 0 Td [(\024)]TJ/F11 9.9626 Tf 10.516 0 Td [(np)]TJ/F14 9.9626 Tf 13.207 0 Td [(\000)]TJ/F8 9.9626 Tf 9.962 0 Td [(1)]TJ + [-500(The)-368(output)]TJ/F11 9.9626 Tf 66.553 0 Td [(nz)]TJ/F8 9.9626 Tf 14.716 0 Td [(is)-368(alw)28(a)28(ys)-368(the)-368(size)-368(of)-368(the)-368(output)-368(generated)-367(b)27(y)-367(the)-368(curren)27(t)]TJ -68.539 -11.955 Td [(call;)-314(th)28(us,)-309(if)]TJ/F30 9.9626 Tf 54.124 0 Td [(append=.true.)]TJ/F8 9.9626 Tf 67.994 0 Td [(,)-310(the)-303(total)-304(output)-304(size)-304(will)-303(b)-28(e)]TJ/F11 9.9626 Tf 128.95 0 Td [(nz)-44(in)]TJ/F8 9.9626 Tf 22.088 0 Td [(+)]TJ/F11 9.9626 Tf 9.373 0 Td [(nz)]TJ/F8 9.9626 Tf 11.051 0 Td [(,)-310(with)]TJ -293.58 -11.955 Td [(the)-372(newly)-372(extracted)-372(co)-28(e\016cien)28(ts)-372(stored)-372(in)-372(en)28(tries)]TJ/F30 9.9626 Tf 216.307 0 Td [(nzin+1:nzin+nz)]TJ/F8 9.9626 Tf 76.93 0 Td [(of)-372(the)]TJ -293.237 -11.955 Td [(arra)28(y)-334(ar)1(gume)-1(n)28(ts;)]TJ 0 g 0 G -/F27 9.9626 Tf -222.543 -21.918 Td [(On)-383(Return)]TJ + -12.73 -19.926 Td [(2.)]TJ 0 g 0 G + [-500(When)]TJ/F30 9.9626 Tf 41.788 0 Td [(append=.true.)]TJ/F8 9.9626 Tf 71.315 0 Td [(the)-333(output)-334(arra)28(ys)-333(are)-333(reallo)-28(cated)-334(as)-333(necessary;)]TJ 0 g 0 G - 0 -19.925 Td [(rank)]TJ + -113.103 -19.925 Td [(3.)]TJ 0 g 0 G -/F8 9.9626 Tf 27.681 0 Td [(The)-333(MPI)-334(rank)-333(asso)-28(ciated)-333(with)-333(the)-334(PSBLAS)-333(pro)-28(cess)]TJ/F11 9.9626 Tf 230.248 0 Td [(id)]TJ/F8 9.9626 Tf 8.617 0 Td [(.)]TJ -241.639 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.451 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ + [-500(The)-253(ro)28(w)-252(and)-253(column)-253(indices)-252(are)-253(returned)-252(in)-253(the)-253(lo)-27(cal)-253(n)28(um)28(b)-28(ering)-253(sc)28(heme;)-280(if)]TJ 12.73 -11.955 Td [(the)-222(global)-222(n)27(um)28(b)-28(erin)1(g)-223(is)-222(desired,)-244(the)-223(user)-222(ma)28(y)-222(emplo)27(y)-222(the)]TJ/F30 9.9626 Tf 243.172 0 Td [(psb_loc_to_glob)]TJ/F8 9.9626 Tf -243.172 -11.955 Td [(routine)-333(on)-334(the)-333(output.)]TJ 0 g 0 G - 89.442 -322.333 Td [(104)]TJ + 141.968 -290.909 Td [(98)]TJ 0 g 0 G ET endstream endobj -1536 0 obj +1524 0 obj << -/Length 1181 +/Length 4123 >> stream 0 g 0 G @@ -18643,121 +18286,329 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(wtime)-375(|)-375(W)94(all)-375(clo)-32(c)32(k)-375(timing)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(sizeof)-375(|)-375(Memory)-375(o)-31(ccupation)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-333(function)-334(computes)-333(the)-333(memory)-334(o)-28(ccupation)-333(of)-333(a)-333(PSBLAS)-334(ob)-55(ject.)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(time)-525(=)-525(psb_wtime\050\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-474(function)-473(returns)-474(a)-473(w)27(all)-473(clo)-28(c)28(k)-474(timer.)-865(The)-474(resolution)-473(of)-474(the)-473(timer)-474(is)]TJ -14.944 -11.955 Td [(dep)-28(enden)28(t)-333(on)-334(the)-333(underlying)-333(parallel)-333(en)27(vir)1(onme)-1(n)28(t)-333(implemen)28(tation.)]TJ +/F30 9.9626 Tf 0 -21.918 Td [(isz)-525(=)-525(psb_sizeof\050a\051)]TJ 0 -11.955 Td [(isz)-525(=)-525(psb_sizeof\050desc_a\051)]TJ 0 -11.956 Td [(isz)-525(=)-525(psb_sizeof\050prec\051)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -19.926 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf 0 -21.917 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(Exit)]TJ +/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.551 0 Td [(A)-333(sparse)-334(matrix)]TJ/F11 9.9626 Tf 73.226 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(.)]TJ -66.342 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ +ET +q +1 0 0 1 312.036 532.522 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 315.174 532.322 Td [(Tspmat)]TJ +ET +q +1 0 0 1 347.183 532.522 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 350.322 532.322 Td [(type)]TJ +0 g 0 G +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -271.348 -19.925 Td [(desc)]TJ +ET +q +1 0 0 1 121.81 512.596 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 125.247 512.397 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.551 0 Td [(Comm)28(unication)-334(d)1(e)-1(scriptor)1(.)]TJ -10.996 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ +ET +q +1 0 0 1 312.036 464.776 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 315.174 464.576 Td [(desc)]TJ +ET +q +1 0 0 1 336.723 464.776 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 339.861 464.576 Td [(type)]TJ +0 g 0 G +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -260.887 -19.925 Td [(prec)]TJ +0 g 0 G +/F8 9.9626 Tf 26.408 0 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -33.88 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(preconditioner)-333(data)-333(structure)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 197.537 0 Td [(psb)]TJ +ET +q +1 0 0 1 338.658 408.985 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 341.796 408.786 Td [(prec)]TJ +ET +q +1 0 0 1 363.345 408.985 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 366.483 408.786 Td [(type)]TJ +0 g 0 G +/F8 9.9626 Tf 20.922 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -287.51 -19.926 Td [(On)-383(Return)]TJ 0 g 0 G 0 g 0 G 0 -19.925 Td [(F)96(unction)-384(v)64(alue)]TJ 0 g 0 G -/F8 9.9626 Tf 78.387 0 Td [(the)-333(elapsed)-334(time)-333(in)-333(seconds.)]TJ -53.48 -11.955 Td [(Returned)-333(as:)-445(a)]TJ/F30 9.9626 Tf 68.3 0 Td [(real\050psb_dpk_\051)]TJ/F8 9.9626 Tf 76.545 0 Td [(v)56(ariable.)]TJ +/F8 9.9626 Tf 78.387 0 Td [(The)-332(memory)-331(o)-28(ccupation)-332(of)-331(the)-332(ob)-55(ject)-332(sp)-28(eci\014ed)-332(in)-331(the)-332(calling)]TJ -53.48 -11.955 Td [(sequence,)-333(in)-334(b)28(ytes.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(Returned)-333(as:)-445(an)]TJ/F30 9.9626 Tf 73.834 0 Td [(integer\050psb_long_int_k_\051)]TJ/F8 9.9626 Tf 128.849 0 Td [(n)28(um)28(b)-28(er.)]TJ 0 g 0 G - -5.368 -491.698 Td [(105)]TJ + -60.715 -242.632 Td [(99)]TJ 0 g 0 G ET endstream endobj -1540 0 obj +1528 0 obj << -/Length 1474 +/Length 5774 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ +/F16 11.9552 Tf 150.705 706.129 Td [(Sorting)-375(utilities)-375(|)]TJ 0 -19.593 Td [(psb)]TJ ET q -1 0 0 1 171.761 706.328 cm +1 0 0 1 171.761 686.736 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 175.796 686.536 Td [(msort)-375(|)-375(Sorting)-375(b)31(y)-375(the)-375(Merge-sort)-375(algorithm)]TJ -25.091 -12.601 Td [(psb)]TJ +ET +q +1 0 0 1 171.761 674.134 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 175.796 673.935 Td [(qsort)-375(|)-375(Sorting)-375(b)31(y)-375(the)-375(Quic)31(ksort)-375(algorithm)]TJ -25.091 -12.602 Td [(psb)]TJ +ET +q +1 0 0 1 171.761 661.532 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(barrier)-375(|)-375(Sinc)31(hronization)-375(p)-31(oin)31(t)-375(parallel)-375(en)32(vironmen)31(t)]TJ +/F16 11.9552 Tf 175.796 661.333 Td [(hsort)-375(|)-375(Sorting)-375(b)31(y)-375(the)-375(Heapsort)-375(algorithm)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_barrier\050icontxt\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-398(subroutine)-397(acts)-398(as)-398(an)-398(explicit)-398(sync)28(hronization)-397(p)-28(oin)28(t)-398(for)-398(the)-398(PSBLAS)]TJ -14.944 -11.955 Td [(parallel)-333(virtual)-333(mac)27(hine.)]TJ +/F30 9.9626 Tf -25.091 -22.511 Td [(call)-525(psb_msort\050x,ix,dir,flag\051)]TJ 0 -11.955 Td [(call)-525(psb_qsort\050x,ix,dir,flag\051)]TJ 0 -11.955 Td [(call)-525(psb_hsort\050x,ix,dir,flag\051)]TJ/F8 9.9626 Tf 14.944 -21.865 Td [(These)-332(serial)-332(r)1(outines)-332(sort)-332(a)-332(sequence)]TJ/F11 9.9626 Tf 162.708 0 Td [(X)]TJ/F8 9.9626 Tf 12.34 0 Td [(in)28(to)-332(ascending)-332(or)-331(descending)-332(order.)]TJ -189.992 -11.955 Td [(The)-320(argumen)28(t)-321(meaning)-320(is)-320(iden)28(tical)-320(for)-320(the)-321(th)1(ree)-321(calls;)-324(the)-320(only)-321(di\013erence)-320(is)-320(the)]TJ 0 -11.955 Td [(algorithm)-333(used)-334(to)-333(accomplish)-333(the)-334(task)-333(\050see)-333(Us)-1(age)-333(Notes)-333(b)-28(elo)28(w\051.)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -19.926 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf 0 -21.865 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -33.797 -22.511 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(icon)32(txt)]TJ + 0 -22.511 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyi)1(ng)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(ariable.)]TJ +/F8 9.9626 Tf 11.028 0 Td [(The)-333(sequence)-334(to)-333(b)-28(e)-333(sorted.)]TJ 13.879 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.081 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger,)-333(real)-334(or)-333(complex)-333(arra)27(y)-333(of)-333(rank)-333(1.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -22.511 Td [(ix)]TJ +0 g 0 G +/F8 9.9626 Tf 14.21 0 Td [(A)-333(v)27(ector)-333(of)-333(indices.)]TJ 10.697 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-1(n)-333(in)28(teger)-333(arra)27(y)-333(of)-333(\050at)-333(leas)-1(t\051)-333(the)-333(same)-334(size)-333(as)]TJ/F11 9.9626 Tf 258.558 0 Td [(X)]TJ/F8 9.9626 Tf 9.036 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -292.501 -22.511 Td [(dir)]TJ +0 g 0 G +/F8 9.9626 Tf 19.247 0 Td [(The)-333(desired)-334(ordering.)]TJ 5.66 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue:)]TJ +0 g 0 G +/F27 9.9626 Tf 0 -22.511 Td [(In)32(teger)-383(and)-384(real)-383(data:)]TJ +0 g 0 G +/F30 9.9626 Tf 114.396 0 Td [(psb_sort_up_)]TJ/F8 9.9626 Tf 62.764 0 Td [(,)]TJ/F30 9.9626 Tf 5.203 0 Td [(psb_sort_down_)]TJ/F8 9.9626 Tf 73.225 0 Td [(,)]TJ/F30 9.9626 Tf 5.203 0 Td [(psb_asort_up_)]TJ/F8 9.9626 Tf 67.994 0 Td [(,)]TJ/F30 9.9626 Tf -306.868 -11.955 Td [(psb_asort_down_)]TJ/F8 9.9626 Tf 78.456 0 Td [(;)-333(default)]TJ/F30 9.9626 Tf 39.573 0 Td [(psb_sort_up_)]TJ/F8 9.9626 Tf 62.765 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -202.711 -17.233 Td [(Complex)-383(data:)]TJ +0 g 0 G +/F30 9.9626 Tf 78.337 0 Td [(psb_lsort_up_)]TJ/F8 9.9626 Tf 67.995 0 Td [(,)]TJ/F30 9.9626 Tf 5.203 0 Td [(psb_lsort_down_)]TJ/F8 9.9626 Tf 78.455 0 Td [(,)]TJ/F30 9.9626 Tf 5.202 0 Td [(psb_asort_up_)]TJ/F8 9.9626 Tf 67.995 0 Td [(,)]TJ/F30 9.9626 Tf 5.203 0 Td [(psb_asort_down_)]TJ/F8 9.9626 Tf 78.455 0 Td [(;)]TJ -364.928 -11.955 Td [(default)]TJ/F30 9.9626 Tf 33.486 0 Td [(psb_lsort_up_)]TJ/F8 9.9626 Tf 67.995 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -148.305 -22.511 Td [(\015ag)]TJ +0 g 0 G +/F8 9.9626 Tf 22.644 0 Td [(Whether)-333(to)-334(k)28(eep)-333(the)-334(origi)1(nal)-334(v)56(alues)-334(in)]TJ/F11 9.9626 Tf 170.583 0 Td [(I)-78(X)]TJ/F8 9.9626 Tf 14.197 0 Td [(.)]TJ -182.517 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.956 Td [(Sp)-28(eci\014ed)-222(as:)-389(an)-222(in)28(teger)-222(v)55(alue)]TJ/F30 9.9626 Tf 125.446 0 Td [(psb_sort_ovw_idx_)]TJ/F8 9.9626 Tf 91.13 0 Td [(or)]TJ/F30 9.9626 Tf 11.097 0 Td [(psb_sort_keep_idx_)]TJ/F8 9.9626 Tf 94.146 0 Td [(;)]TJ -321.819 -11.955 Td [(default)]TJ/F30 9.9626 Tf 33.485 0 Td [(psb_sort_ovw_idx_)]TJ/F8 9.9626 Tf 88.916 0 Td [(.)]TJ 0 g 0 G - 139.476 -455.832 Td [(106)]TJ +/F27 9.9626 Tf -147.308 -24.503 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G + 0 -22.511 Td [(x)]TJ +0 g 0 G +/F8 9.9626 Tf 11.028 0 Td [(The)-333(sequence)-334(of)-333(v)55(alu)1(e)-1(s,)-333(in)-333(the)-334(c)28(hosen)-333(ordering.)]TJ 13.879 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.081 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger,)-333(real)-334(or)-333(complex)-333(arra)27(y)-333(of)-333(rank)-333(1.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -22.511 Td [(ix)]TJ +0 g 0 G +/F8 9.9626 Tf 14.211 0 Td [(A)-333(v)28(e)-1(ctor)-333(of)-333(indices.)]TJ 10.696 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(Optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(An)-332(in)27(teger)-332(arra)28(y)-333(of)-332(rank)-332(1,)-333(whose)-333(en)28(tries)-332(are)-333(mo)28(v)28(ed)-333(to)-332(the)-333(same)-332(p)-28(osition)]TJ 0 -11.955 Td [(as)-333(the)-334(corresp)-27(onding)-334(en)28(tries)-333(in)]TJ/F11 9.9626 Tf 136.958 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ +0 g 0 G + -3.175 -43.727 Td [(100)]TJ 0 g 0 G ET endstream endobj -1544 0 obj +1532 0 obj << -/Length 1360 +/Length 6995 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ +/F16 11.9552 Tf 99.895 706.129 Td [(Notes)]TJ +0 g 0 G +/F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ +0 g 0 G + [-500(F)83(or)-466(in)28(tege)-1(r)-466(or)-467(real)-466(data)-467(the)-467(sorting)-466(can)-467(b)-28(e)-466(p)-28(erformed)-467(in)-466(the)-467(up/do)28(wn)]TJ 12.73 -11.956 Td [(direction,)-333(on)-334(th)1(e)-334(natural)-333(or)-333(absolute)-334(v)56(alues;)]TJ +0 g 0 G + -12.73 -19.925 Td [(2.)]TJ +0 g 0 G + [-500(F)83(or)-397(complex)-398(data)-398(the)-397(sorting)-398(can)-398(b)-27(e)-398(done)-398(in)-397(a)-398(lexicographic)-398(order)-397(\050i.e.:)]TJ 12.73 -11.955 Td [(sort)-316(on)-316(the)-315(real)-316(part)-316(with)-316(ties)-316(br)1(ok)27(en)-316(accordin)1(g)-316(to)-316(the)-316(imaginary)-316(part\051)-315(or)]TJ 0 -11.955 Td [(on)-333(the)-334(absolute)-333(v)56(alues;)]TJ +0 g 0 G + -12.73 -19.925 Td [(3.)]TJ +0 g 0 G + [-500(The)-257(routines)-258(retur)1(n)-258(the)-257(items)-257(in)-258(the)-257(c)28(hosen)-257(ordering;)-283(the)-257(output)-257(di\013erence)]TJ 12.73 -11.956 Td [(is)-259(the)-259(handling)-259(of)-259(ties)-259(\050i.e.)-419(items)-259(with)-259(an)-259(equal)-259(v)56(alue\051)-259(in)-259(the)-259(original)-259(input.)]TJ 0 -11.955 Td [(With)-493(the)-493(merge-sort)-493(algorithm)-493(ties)-493(are)-493(preserv)27(ed)-493(in)-493(the)-493(same)-493(relativ)28(e)]TJ 0 -11.955 Td [(order)-405(as)-406(they)-405(had)-406(in)-405(the)-405(original)-406(sequence,)-423(while)-406(this)-405(is)-406(not)-405(guaran)28(teed)]TJ 0 -11.955 Td [(for)-333(quic)28(ksort)-334(or)-333(heapsort;)]TJ +0 g 0 G + -12.73 -19.925 Td [(4.)]TJ +0 g 0 G + [-500(If)]TJ/F11 9.9626 Tf 21.889 0 Td [(f)-108(l)-19(ag)]TJ/F8 9.9626 Tf 22.262 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(psb)]TJ ET q -1 0 0 1 120.951 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +1 0 0 1 181.295 542.941 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F11 9.9626 Tf 184.284 542.742 Td [(sor)-28(t)]TJ +ET +q +1 0 0 1 202.749 542.941 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F11 9.9626 Tf 205.738 542.742 Td [(ov)-36(w)]TJ +ET +q +1 0 0 1 223.752 542.941 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F11 9.9626 Tf 226.741 542.742 Td [(idx)]TJ +ET +q +1 0 0 1 241.65 542.941 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(ab)-31(ort)-375(|)-375(Ab)-32(ort)-375(a)-374(computation)]TJ +/F8 9.9626 Tf 247.157 542.742 Td [(then)-253(the)-252(en)27(tries)-252(in)]TJ/F11 9.9626 Tf 80.169 0 Td [(ix)]TJ/F8 9.9626 Tf 9.126 0 Td [(\0501)-278(:)]TJ/F11 9.9626 Tf 17.158 0 Td [(n)]TJ/F8 9.9626 Tf 5.979 0 Td [(\051)-253(where)]TJ/F11 9.9626 Tf 34.398 0 Td [(n)]TJ/F8 9.9626 Tf 8.497 0 Td [(is)-253(the)-252(s)-1(i)1(z)-1(e)]TJ -277.682 -11.956 Td [(of)]TJ/F11 9.9626 Tf 11.91 0 Td [(x)]TJ/F8 9.9626 Tf 9.579 0 Td [(are)-390(initialized)-390(to)]TJ/F11 9.9626 Tf 76.44 0 Td [(ix)]TJ/F8 9.9626 Tf 9.126 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.433 0 Td [(\051)]TJ/F14 9.9626 Tf 7.581 0 Td [(\040)]TJ/F11 9.9626 Tf 13.67 0 Td [(i)]TJ/F8 9.9626 Tf 3.433 0 Td [(;)-418(th)28(us,)-404(up)-28(on)-390(return)-390(from)-390(the)-390(subroutine,)]TJ -139.046 -11.955 Td [(for)-333(eac)28(h)-334(index)]TJ/F11 9.9626 Tf 64.505 0 Td [(i)]TJ/F8 9.9626 Tf 6.751 0 Td [(w)28(e)-334(ha)28(v)28(e)-333(in)]TJ/F11 9.9626 Tf 49.257 0 Td [(ix)]TJ/F8 9.9626 Tf 9.126 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)-333(the)-333(p)-28(osition)-333(that)-334(th)1(e)-334(item)]TJ/F11 9.9626 Tf 123.751 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(\050)]TJ/F11 9.9626 Tf 3.875 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(\051)-333(o)-28(ccupied)]TJ -273.697 -11.955 Td [(in)-333(the)-334(original)-333(data)-333(sequence;)]TJ 0 g 0 G + -12.73 -19.925 Td [(5.)]TJ 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_abort\050icontxt\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-333(subroutine)-334(ab)-27(orts)-334(computation)-333(on)-333(the)-334(paral)1(le)-1(l)-333(virtual)-333(mac)28(hine.)]TJ + [-500(If)]TJ/F11 9.9626 Tf 23.404 0 Td [(f)-108(l)-19(ag)]TJ/F8 9.9626 Tf 23.446 0 Td [(=)]TJ/F11 9.9626 Tf 11.701 0 Td [(psb)]TJ +ET +q +1 0 0 1 185.179 487.15 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F11 9.9626 Tf 188.168 486.951 Td [(sor)-28(t)]TJ +ET +q +1 0 0 1 206.634 487.15 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F11 9.9626 Tf 209.622 486.951 Td [(k)-32(eep)]TJ +ET +q +1 0 0 1 230.011 487.15 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F11 9.9626 Tf 232.999 486.951 Td [(idx)]TJ +ET +q +1 0 0 1 247.909 487.15 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 254.929 486.951 Td [(the)-405(routine)-404(will)-405(assume)-405(that)-404(the)-405(en)28(tries)-405(in)]TJ/F11 9.9626 Tf -130.127 -11.955 Td [(ix)]TJ/F8 9.9626 Tf 9.126 0 Td [(\050:\051)-333(ha)28(v)27(e)-333(already)-333(b)-28(een)-333(initialized)-334(b)28(y)-333(the)-334(user;)]TJ 0 g 0 G -/F27 9.9626 Tf -14.944 -19.926 Td [(T)32(yp)-32(e:)]TJ + -21.856 -19.926 Td [(6.)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ + [-500(The)-376(three)-375(sorting)-376(algorithms)-376(ha)28(v)28(e)-376(a)-375(s)-1(imilar)]TJ/F11 9.9626 Tf 208.295 0 Td [(O)]TJ/F8 9.9626 Tf 7.876 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(n)]TJ/F8 9.9626 Tf 7.641 0 Td [(log)]TJ/F11 9.9626 Tf 14.528 0 Td [(n)]TJ/F8 9.9626 Tf 5.98 0 Td [(\051)-376(exp)-27(e)-1(cted)-375(running)]TJ -235.464 -11.955 Td [(time;)-349(in)-343(the)-344(a)28(v)28(erage)-344(case)-343(quic)27(ksort)-343(will)-344(b)-27(e)-344(the)-344(fastest)-343(and)-344(merge-sort)-343(the)]TJ 0 -11.955 Td [(slo)28(w)28(e)-1(st.)-444(Ho)28(w)28(e)-1(v)28(er)-333(note)-333(that:)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ + 4.206 -19.925 Td [(\050a\051)]TJ 0 g 0 G + [-500(The)-419(w)28(orst)-419(case)-419(runn)1(ing)-419(time)-419(for)-419(quic)28(ksort)-419(is)]TJ/F11 9.9626 Tf 221.059 0 Td [(O)]TJ/F8 9.9626 Tf 7.876 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(n)]TJ/F7 6.9738 Tf 5.98 3.615 Td [(2)]TJ/F8 9.9626 Tf 4.47 -3.615 Td [(\051;)-461(the)-419(algorithm)]TJ -225.547 -11.955 Td [(implemen)28(ted)-319(here)-319(follo)28(ws)-319(the)-319(w)27(ell-kno)28(wn)-319(median-of-three)-319(heuristics,)]TJ 0 -11.956 Td [(but)-333(the)-334(w)28(orst)-333(case)-334(ma)28(y)-333(still)-334(ap)1(ply;)]TJ 0 g 0 G - 0 -19.925 Td [(icon)32(txt)]TJ + -18.265 -15.94 Td [(\050b\051)]TJ 0 g 0 G -/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyin)1(g)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable.)]TJ + [-500(The)-222(w)28(orst)-223(case)-222(running)-222(time)-222(for)-222(m)-1(erge-sort)-222(and)-222(heap-sort)-222(is)]TJ/F11 9.9626 Tf 273.309 0 Td [(O)]TJ/F8 9.9626 Tf 7.876 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(n)]TJ/F8 9.9626 Tf 7.64 0 Td [(log)]TJ/F11 9.9626 Tf 14.529 0 Td [(n)]TJ/F8 9.9626 Tf 5.98 0 Td [(\051)]TJ -294.943 -11.955 Td [(as)-333(the)-334(a)28(v)28(erage)-334(case;)]TJ +0 g 0 G + -17.158 -15.94 Td [(\050c\051)]TJ +0 g 0 G + [-500(The)-358(merge-sort)-358(algorithm)-357(is)-358(implemen)28(ted)-358(to)-358(tak)28(e)-358(adv)56(an)28(tage)-358(of)-358(sub-)]TJ 17.158 -11.955 Td [(sequences)-401(that)-400(ma)28(y)-401(b)-28(e)-400(already)-401(in)-400(the)-401(d)1(e)-1(sired)-400(ordering)-400(prior)-401(to)-400(the)]TJ 0 -11.956 Td [(subroutine)-246(call;)-275(this)-246(situation)-246(is)-247(relativ)28(ely)-246(common)-246(when)-246(dealing)-246(with)]TJ 0 -11.955 Td [(groups)-301(of)-301(indices)-301(of)-302(sparse)-301(matrix)-301(en)28(tries,)-308(th)28(us)-301(merge-sort)-301(is)-302(the)-301(pre-)]TJ 0 -11.955 Td [(ferred)-249(c)28(hoice)-249(when)-249(a)-249(sorting)-248(is)-249(needed)-249(b)28(y)-249(other)-249(routines)-249(in)-248(the)-249(library)83(.)]TJ 0 g 0 G - 139.477 -467.787 Td [(107)]TJ + 117.559 -205.23 Td [(101)]TJ 0 g 0 G ET endstream endobj -1548 0 obj +1545 0 obj << -/Length 4533 +/Length 187 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ +/F16 14.3462 Tf 150.705 706.129 Td [(7)-1125(P)31(arallel)-375(en)32(v)-1(ironmen)32(t)-375(routines)]TJ +0 g 0 G +/F8 9.9626 Tf 164.383 -615.691 Td [(102)]TJ +0 g 0 G +ET + +endstream +endobj +1549 0 obj +<< +/Length 5567 +>> +stream +0 g 0 G +0 g 0 G +BT +/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ ET q -1 0 0 1 171.761 706.328 cm +1 0 0 1 120.951 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(b)-31(cast)-375(|)-375(Broadcast)-375(data)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(init)-375(|)-375(Initializes)-375(PSBLAS)-375(parallel)-375(en)31(vironmen)31(t)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_bcast\050icontxt,)-525(dat,)-525(root\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-338(subroutine)-338(implemen)27(ts)-338(a)-338(broadcast)-338(op)-28(eration)-338(based)-339(on)-338(the)-338(underlying)]TJ -14.944 -11.955 Td [(comm)28(unication)-334(lib)1(rary)83(.)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_init\050icontxt,)-525(np,)-525(basectxt,)-525(ids\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-294(subroutine)-294(initializes)-294(th)1(e)-294(PSBLAS)-294(parallel)-294(en)28(vironmen)28(t,)-302(de\014ning)-294(a)-294(vir-)]TJ -14.944 -11.955 Td [(tual)-333(parallel)-334(mac)28(hine.)]TJ 0 g 0 G /F27 9.9626 Tf 0 -19.926 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G @@ -18766,86 +18617,104 @@ BT /F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(icon)32(txt)]TJ + 0 -19.925 Td [(np)]TJ 0 g 0 G -/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyi)1(ng)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(ariable.)]TJ +/F8 9.9626 Tf 17.712 0 Td [(Num)28(b)-28(er)-333(of)-334(pr)1(o)-28(cesses)-334(in)-333(the)-333(PSBLAS)-334(virtual)-333(parallel)-333(mac)27(h)1(ine.)]TJ 7.195 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)-778(Default)1(:)-445(use)-333(all)-334(a)28(v)56(ailable)-334(p)1(ro)-28(cesses)-1(.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.925 Td [(dat)]TJ +/F27 9.9626 Tf -24.907 -19.925 Td [(basectxt)]TJ +0 g 0 G +/F8 9.9626 Tf 46.736 0 Td [(the)-356(initial)-357(comm)28(unication)-356(con)28(text.)-514(The)-356(new)-357(con)28(text)-356(will)-357(b)-27(e)-357(de\014ned)]TJ -21.829 -11.955 Td [(from)-333(the)-334(pro)-27(cess)-1(es)-333(participating)-333(in)-333(the)-334(initial)-333(one.)]TJ 0 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)-778(Default)1(:)-445(use)-333(MPI)]TJ +ET +q +1 0 0 1 339.182 466.768 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 342.171 466.569 Td [(COMM)]TJ +ET +q +1 0 0 1 375.977 466.768 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 378.966 466.569 Td [(W)28(ORLD.)]TJ 0 g 0 G -/F8 9.9626 Tf 21.371 0 Td [(On)-333(the)-334(ro)-27(ot)-334(pro)-27(ces)-1(s,)-333(the)-333(data)-334(to)-333(b)-28(e)-333(broadcast.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(tege)-1(r,)-341(real)-339(or)-340(complex)-340(v)56(ariable,)-342(whic)28(h)-339(m)-1(a)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-403(a)-403(rank)-404(1)-403(or)-403(2)-403(arra)28(y)83(,)-421(or)-403(a)-403(c)28(haracter)-404(or)-403(logical)-403(v)56(ariable,)-421(whic)28(h)-403(ma)27(y)-403(b)-28(e)]TJ 0 -11.955 Td [(a)-426(s)-1(calar)-426(or)-426(rank)-427(1)-426(arra)27(y)84(.)-1151(T)28(yp)-28(e,)-449(kind,)-450(rank)-427(and)-426(size)-427(m)28(ust)-426(agree)-427(on)-426(all)]TJ 0 -11.955 Td [(pro)-28(cesses.)]TJ +/F27 9.9626 Tf -279.071 -19.925 Td [(ids)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.926 Td [(ro)-32(ot)]TJ +/F8 9.9626 Tf 19.048 0 Td [(Iden)28(tities)-497(of)-497(the)-497(pro)-28(cesses)-497(to)-497(use)-497(for)-497(the)-498(n)1(e)-1(w)-497(con)28(text;)-579(the)-497(argumen)28(t)-497(is)]TJ 5.859 -11.956 Td [(ignored)-428(when)]TJ/F30 9.9626 Tf 63.346 0 Td [(np)]TJ/F8 9.9626 Tf 14.722 0 Td [(is)-428(not)-428(sp)-27(eci\014ed.)-728(This)-428(allo)28(ws)-428(the)-428(pro)-27(ce)-1(sses)-427(in)-428(the)-428(new)]TJ -78.068 -11.955 Td [(en)28(vironmen)28(t)-334(to)-333(b)-28(e)-333(in)-333(an)-334(order)-333(di\013eren)28(t)-334(fr)1(om)-334(the)-333(original)-333(one.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)84(.)-778(Default:)-444(use)-334(the)-333(indices)-333(\0500)]TJ/F11 9.9626 Tf 254.158 0 Td [(:)-167(:)-166(:)-167(np)]TJ/F14 9.9626 Tf 26.49 0 Td [(\000)]TJ/F8 9.9626 Tf 9.963 0 Td [(1\051.)]TJ +0 g 0 G +/F27 9.9626 Tf -315.518 -21.918 Td [(On)-383(Return)]TJ 0 g 0 G -/F8 9.9626 Tf 25.93 0 Td [(Ro)-28(ot)-333(pro)-28(cess)-333(holding)-334(data)-333(to)-333(b)-28(e)-333(broadcast.)]TJ -1.023 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(alue)-333(0)]TJ/F11 9.9626 Tf 138.176 0 Td [(<)]TJ/F8 9.9626 Tf 7.749 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(r)-28(oot)-278(<)]TJ/F8 9.9626 Tf 28.543 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(np)]TJ/F14 9.9626 Tf 13.207 0 Td [(\000)]TJ/F8 9.9626 Tf 9.962 0 Td [(1,)-333(default)-334(0)]TJ 0 g 0 G -/F27 9.9626 Tf -243.576 -21.918 Td [(On)-383(Return)]TJ + 0 -19.925 Td [(icon)32(txt)]TJ 0 g 0 G +/F8 9.9626 Tf 39.989 0 Td [(the)-458(comm)28(unication)-457(con)27(text)-457(iden)28(tifying)-458(the)-457(virtual)-458(paral)1(le)-1(l)-457(mac)28(hine.)]TJ -15.082 -11.956 Td [(Note)-335(that)-335(this)-335(is)-336(alw)28(a)28(ys)-335(a)-335(duplicate)-335(of)]TJ/F30 9.9626 Tf 169.952 0 Td [(basectxt)]TJ/F8 9.9626 Tf 41.843 0 Td [(,)-336(so)-335(that)-335(library)-335(comm)28(u-)]TJ -211.795 -11.955 Td [(nications)-305(are)-305(completely)-305(s)-1(eparated)-305(from)-305(other)-305(comm)28(unication)-305(op)-28(erations.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable.)]TJ/F16 11.9552 Tf -24.907 -21.917 Td [(Notes)]TJ 0 g 0 G - 0 -19.926 Td [(dat)]TJ +/F8 9.9626 Tf 12.177 -19.926 Td [(1.)]TJ +0 g 0 G + [-500(A)-333(call)-334(to)-333(this)-333(routine)-334(m)28(ust)-333(precede)-334(an)28(y)-333(other)-333(PSBLAS)-334(call.)]TJ +0 g 0 G + 0 -19.925 Td [(2.)]TJ 0 g 0 G -/F8 9.9626 Tf 21.371 0 Td [(On)-333(pro)-28(cesses)-334(other)-333(than)-333(ro)-28(ot,)-333(the)-334(dat)1(a)-334(to)-333(b)-28(e)-333(broadcast.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(tege)-1(r,)-341(real)-339(or)-340(complex)-340(v)56(ariable,)-342(whic)28(h)-339(m)-1(a)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-346(a)-346(rank)-347(1)-346(or)-346(2)-346(arra)28(y)83(,)-349(or)-347(a)-346(c)28(haracter)-346(or)-346(logical)-347(scalar.)-829(T)28(yp)-28(e,)-349(kind,)-350(rank)]TJ 0 -11.956 Td [(and)-333(size)-334(m)28(ust)-333(agree)-334(on)-333(all)-333(pro)-28(cesses.)]TJ + [-500(It)-262(is)-262(an)-262(error)-262(to)-262(sp)-28(ecify)-262(a)-262(v)56(alue)-262(for)]TJ/F11 9.9626 Tf 159.869 0 Td [(np)]TJ/F8 9.9626 Tf 13.603 0 Td [(greater)-262(than)-262(the)-262(n)28(um)28(b)-28(er)-262(of)-262(pro)-28(cesses)]TJ -160.742 -11.955 Td [(a)28(v)55(ailable)-333(in)-333(the)-334(un)1(derlying)-334(base)-333(parallel)-333(en)27(vir)1(onme)-1(n)28(t.)]TJ 0 g 0 G - 139.477 -170.9 Td [(108)]TJ + 139.477 -97.177 Td [(103)]TJ 0 g 0 G ET endstream endobj -1552 0 obj +1556 0 obj << -/Length 5146 +/Length 4639 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ +/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ ET q -1 0 0 1 120.951 706.328 cm +1 0 0 1 171.761 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(sum)-375(|)-375(Global)-375(sum)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(info)-306(|)-307(Return)-306(information)-306(ab)-31(out)-307(PSBLAS)-306(parallel)-306(en-)]TJ -25.091 -13.948 Td [(vironmen)31(t)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_sum\050icontxt,)-525(dat,)-525(root\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-318(subroutine)-319(implemen)28(ts)-318(a)-319(sum)-318(reduction)-318(op)-28(eration)-318(based)-319(on)-318(the)-318(under-)]TJ -14.944 -11.955 Td [(lying)-333(comm)27(unication)-333(library)84(.)]TJ +/F30 9.9626 Tf 0 -18.389 Td [(call)-525(psb_info\050icontxt,)-525(iam,)-525(np\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-456(subroutine)-456(returns)-456(in)1(formation)-456(ab)-28(out)-456(the)-456(PSBLAS)-456(p)1(arallel)-456(en)27(viron)1(-)]TJ -14.944 -11.955 Td [(men)28(t,)-334(de\014n)1(ing)-334(a)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -19.926 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf 0 -19.925 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G 0 -19.925 Td [(icon)32(txt)]TJ 0 g 0 G -/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyin)1(g)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -19.925 Td [(dat)]TJ -0 g 0 G -/F8 9.9626 Tf 21.371 0 Td [(The)-333(lo)-28(cal)-334(con)28(tribution)-333(to)-333(the)-334(global)-333(sum.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(te)-1(ger,)-341(real)-340(or)-339(complex)-340(v)56(ariable,)-342(whic)28(h)-340(ma)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-464(a)-464(rank)-463(1)-464(or)-464(2)-464(arra)28(y)83(.)-1299(T)28(yp)-28(e,)-497(kind,)-496(rank)-464(and)-463(size)-464(m)27(ust)-463(agree)-464(on)-464(all)]TJ 0 -11.955 Td [(pro)-28(cesses.)]TJ +/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyi)1(ng)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(ariable.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.926 Td [(ro)-32(ot)]TJ +/F27 9.9626 Tf -24.907 -21.918 Td [(On)-383(Return)]TJ 0 g 0 G -/F8 9.9626 Tf 25.931 0 Td [(Pro)-28(cess)-310(to)-309(hold)-310(the)-310(\014nal)-310(sum,)-314(or)]TJ/F14 9.9626 Tf 144.053 0 Td [(\000)]TJ/F8 9.9626 Tf 7.748 0 Td [(1)-310(to)-310(mak)28(e)-310(it)-309(a)27(v)56(ailable)-310(on)-310(all)-309(pro)-28(cesses.)]TJ -152.825 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue)]TJ/F14 9.9626 Tf 130.428 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)]TJ/F11 9.9626 Tf 7.748 0 Td [(<)]TJ/F8 9.9626 Tf 7.749 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(r)-28(oot)-278(<)]TJ/F8 9.9626 Tf 28.543 0 Td [(=)]TJ/F11 9.9626 Tf 10.517 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.962 0 Td [(1,)-333(default)-334(-1.)]TJ 0 g 0 G -/F27 9.9626 Tf -251.325 -21.918 Td [(On)-383(Return)]TJ + 0 -19.925 Td [(iam)]TJ 0 g 0 G +/F8 9.9626 Tf 23.281 0 Td [(Iden)28(ti\014er)-333(of)-334(curren)28(t)-333(pro)-28(cess)-333(in)-334(the)-333(PSBLAS)-333(virtual)-334(p)1(arallel)-334(mac)28(hine.)]TJ 1.626 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.451 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(alue.)]TJ/F14 9.9626 Tf 134.302 0 Td [(\000)]TJ/F8 9.9626 Tf 7.748 0 Td [(1)]TJ/F14 9.9626 Tf 7.749 0 Td [(\024)]TJ/F11 9.9626 Tf 10.516 0 Td [(iam)]TJ/F14 9.9626 Tf 20.213 0 Td [(\024)]TJ/F11 9.9626 Tf 10.516 0 Td [(np)]TJ/F14 9.9626 Tf 13.207 0 Td [(\000)]TJ/F8 9.9626 Tf 9.962 0 Td [(1)]TJ 0 g 0 G - 0 -19.925 Td [(dat)]TJ +/F27 9.9626 Tf -239.12 -19.926 Td [(np)]TJ 0 g 0 G -/F8 9.9626 Tf 21.372 0 Td [(On)-333(destination)-333(pro)-28(cess\050es\051,)-334(the)-333(result)-333(of)-334(the)-333(sum)-333(op)-28(eration.)]TJ 3.535 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -71.51 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(te)-1(ger,)-341(real)-340(or)-339(complex)-340(v)56(ariable,)-342(whic)28(h)-340(ma)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-333(a)-334(rank)-333(1)-333(or)-334(2)-333(arra)28(y)83(.)]TJ 0 -11.955 Td [(T)28(yp)-28(e,)-333(kind,)-334(r)1(ank)-334(and)-333(size)-333(m)27(ust)-333(agree)-333(on)-334(all)-333(pro)-28(cesses.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ +/F8 9.9626 Tf 17.711 0 Td [(Num)28(b)-28(er)-333(of)-334(pro)-27(cess)-1(es)-333(in)-333(the)-334(PS)1(BL)-1(AS)-333(virtual)-333(parallel)-333(mac)27(hin)1(e)-1(.)]TJ 7.196 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(ariable.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ 0 g 0 G -/F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ +/F8 9.9626 Tf 12.176 -19.926 Td [(1.)]TJ 0 g 0 G - [-500(The)]TJ/F30 9.9626 Tf 32.469 0 Td [(dat)]TJ/F8 9.9626 Tf 18.273 0 Td [(argumen)28(t)-259(is)-259(b)-28(oth)-259(input)-259(and)-259(output,)-274(and)-259(its)-259(v)55(alue)-259(ma)28(y)-259(b)-28(e)-259(c)28(hanged)]TJ -38.012 -11.956 Td [(ev)28(en)-334(on)-333(pro)-28(cesses)-333(di\013eren)28(t)-334(from)-333(the)-333(\014nal)-334(result)-333(destination.)]TJ + [-500(F)83(or)-500(pro)-27(cess)-1(es)-500(in)-500(the)-500(vir)1(tual)-500(parallel)-500(mac)27(hine)-500(the)-500(iden)28(ti\014er)-500(will)-500(satisfy)]TJ 12.731 -11.955 Td [(0)]TJ/F14 9.9626 Tf 7.748 0 Td [(\024)]TJ/F11 9.9626 Tf 10.516 0 Td [(iam)]TJ/F14 9.9626 Tf 20.213 0 Td [(\024)]TJ/F11 9.9626 Tf 10.516 0 Td [(np)]TJ/F14 9.9626 Tf 13.207 0 Td [(\000)]TJ/F8 9.9626 Tf 9.962 0 Td [(1;)]TJ 0 g 0 G - -12.73 -19.925 Td [(2.)]TJ + -84.893 -19.925 Td [(2.)]TJ 0 g 0 G - [-500(The)]TJ/F30 9.9626 Tf 33.209 0 Td [(dat)]TJ/F8 9.9626 Tf 19.012 0 Td [(argumen)28(t)-333(m)-1(a)28(y)-333(also)-333(b)-28(e)-334(a)-333(long)-333(in)28(teger)-334(scalar.)]TJ + [-500(If)-432(the)-433(user)-432(has)-433(requested)-432(on)]TJ/F30 9.9626 Tf 143.131 0 Td [(psb_init)]TJ/F8 9.9626 Tf 46.15 0 Td [(a)-432(n)27(um)28(b)-28(er)-432(of)-432(pro)-28(cesses)-433(less)-432(than)]TJ -176.551 -11.955 Td [(the)-417(total)-416(a)28(v)55(ailable)-416(in)-417(the)-416(parallel)-417(execution)-416(en)28(vironmen)28(t,)-438(the)-416(remaining)]TJ 0 -11.955 Td [(pro)-28(cesses)-359(will)-359(ha)28(v)28(e)-359(on)-359(return)]TJ/F11 9.9626 Tf 130.487 0 Td [(iam)]TJ/F8 9.9626 Tf 20.638 0 Td [(=)]TJ/F14 9.9626 Tf 10.942 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1;)-372(the)-359(only)-359(call)-359(i)1(n)27(v)28(olving)]TJ/F30 9.9626 Tf 112.377 0 Td [(icontxt)]TJ/F8 9.9626 Tf -282.192 -11.956 Td [(that)-333(an)28(y)-334(suc)28(h)-333(pro)-28(cess)-334(ma)28(y)-333(execute)-334(is)-333(to)]TJ/F30 9.9626 Tf 177.086 0 Td [(psb_exit)]TJ/F8 9.9626 Tf 41.842 0 Td [(.)]TJ 0 g 0 G - 99.986 -109.132 Td [(109)]TJ + -79.452 -174.885 Td [(104)]TJ 0 g 0 G ET @@ -18855,35 +18724,23 @@ endobj << /Type /ObjStm /N 100 -/First 969 -/Length 9533 +/First 974 +/Length 10043 >> stream -1447 0 372 58 1448 115 1444 173 1453 292 1451 431 1455 576 376 635 1456 693 1457 752 -1452 811 1460 917 1458 1056 1462 1202 380 1260 1463 1317 1464 1375 1459 1433 1467 1539 1465 1678 -1469 1822 384 1881 1466 1939 1471 2058 1473 2176 1474 2234 1475 2292 1476 2350 1470 2408 1481 2527 -1477 2684 1478 2828 1479 2974 1483 3119 388 3178 1480 3236 1485 3355 1487 3473 392 3531 1484 3588 -1490 3707 1492 3825 1493 3884 1494 3943 1495 4002 1496 4061 1497 4120 1498 4179 1499 4237 1500 4296 -1501 4355 1489 4414 1503 4532 1505 4650 396 4708 1502 4765 1507 4845 1509 4963 400 5022 1510 5080 -1511 5139 1506 5198 1513 5330 1515 5448 405 5506 1516 5563 1517 5620 1512 5678 1519 5810 1521 5928 -409 5987 1522 6045 1523 6104 1524 6163 1518 6222 1526 6354 1528 6472 413 6530 1525 6587 1531 6693 -1533 6811 417 6870 1530 6928 1535 7060 1537 7178 421 7236 1534 7293 1539 7399 1541 7517 425 7576 -1538 7634 1543 7740 1545 7858 429 7916 1542 7973 1547 8079 1549 8197 433 8256 1546 8314 1551 8446 -% 1447 0 obj -<< -/D [1445 0 R /XYZ 98.895 753.953 null] ->> -% 372 0 obj -<< -/D [1445 0 R /XYZ 99.895 720.077 null] ->> -% 1448 0 obj -<< -/D [1445 0 R /XYZ 99.895 259.346 null] ->> -% 1444 0 obj -<< -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R /F11 750 0 R >> +1446 0 1453 132 1451 271 1455 416 352 475 1452 533 1457 652 1459 770 1460 828 1461 886 +1456 944 1464 1024 1462 1163 1466 1309 356 1368 1463 1426 1469 1545 1467 1684 1471 1831 360 1889 +1472 1946 1468 2004 1476 2123 1474 2262 1478 2408 364 2467 1479 2525 1475 2584 1482 2703 1480 2842 +1484 2989 368 3047 1485 3104 1481 3162 1488 3281 1486 3420 1490 3566 372 3625 1491 3683 1487 3742 +1494 3861 1492 4000 1496 4146 376 4204 1497 4261 1498 4319 1493 4377 1501 4483 1499 4622 1503 4767 +380 4826 1504 4884 1505 4943 1500 5002 1508 5108 1506 5247 1510 5392 384 5450 1507 5507 1513 5626 +1515 5744 1516 5803 1517 5862 1518 5921 1512 5980 1523 6099 1519 6256 1520 6401 1521 6548 1525 6693 +388 6751 1522 6808 1527 6927 1529 7045 392 7104 1526 7162 1531 7281 1533 7399 1534 7457 1535 7515 +1536 7573 1537 7631 1538 7689 1539 7747 1540 7804 1541 7862 1542 7920 1530 7978 1544 8096 1546 8214 +396 8273 1543 8331 1548 8411 1550 8529 400 8587 1551 8644 1552 8702 1547 8760 1555 8892 1557 9010 +% 1446 0 obj +<< +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R /F11 755 0 R /F10 771 0 R >> /ProcSet [ /PDF /Text ] >> % 1453 0 obj @@ -18892,7 +18749,7 @@ stream /Contents 1454 0 R /Resources 1452 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1449 0 R +/Parent 1439 0 R /Annots [ 1451 0 R ] >> % 1451 0 obj @@ -18900,295 +18757,317 @@ stream /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.53 574.94 412.588 586.065] +/Rect [345.53 484.86 412.588 495.985] /A << /S /GoTo /D (descdata) >> >> % 1455 0 obj << /D [1453 0 R /XYZ 149.705 753.953 null] >> -% 376 0 obj +% 352 0 obj << /D [1453 0 R /XYZ 150.705 720.077 null] >> -% 1456 0 obj +% 1452 0 obj << -/D [1453 0 R /XYZ 150.705 370.928 null] +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R /F11 755 0 R >> +/ProcSet [ /PDF /Text ] >> % 1457 0 obj << -/D [1453 0 R /XYZ 150.705 327.092 null] +/Type /Page +/Contents 1458 0 R +/Resources 1456 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1439 0 R >> -% 1452 0 obj +% 1459 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R >> -/ProcSet [ /PDF /Text ] +/D [1457 0 R /XYZ 98.895 753.953 null] >> % 1460 0 obj << +/D [1457 0 R /XYZ 99.895 716.092 null] +>> +% 1461 0 obj +<< +/D [1457 0 R /XYZ 99.895 688.251 null] +>> +% 1456 0 obj +<< +/Font << /F8 561 0 R /F30 769 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1464 0 obj +<< /Type /Page -/Contents 1461 0 R -/Resources 1459 0 R +/Contents 1465 0 R +/Resources 1463 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1449 0 R -/Annots [ 1458 0 R ] +/Parent 1439 0 R +/Annots [ 1462 0 R ] >> -% 1458 0 obj +% 1462 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 574.94 361.779 586.065] +/Rect [345.53 483.284 412.588 494.409] /A << /S /GoTo /D (descdata) >> >> -% 1462 0 obj +% 1466 0 obj << -/D [1460 0 R /XYZ 98.895 753.953 null] +/D [1464 0 R /XYZ 149.705 753.953 null] >> -% 380 0 obj +% 356 0 obj << -/D [1460 0 R /XYZ 99.895 720.077 null] +/D [1464 0 R /XYZ 150.705 720.077 null] >> % 1463 0 obj << -/D [1460 0 R /XYZ 99.895 370.928 null] ->> -% 1464 0 obj -<< -/D [1460 0 R /XYZ 99.895 339.047 null] ->> -% 1459 0 obj -<< -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R /F11 755 0 R >> /ProcSet [ /PDF /Text ] >> -% 1467 0 obj +% 1469 0 obj << /Type /Page -/Contents 1468 0 R -/Resources 1466 0 R +/Contents 1470 0 R +/Resources 1468 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1449 0 R -/Annots [ 1465 0 R ] +/Parent 1473 0 R +/Annots [ 1467 0 R ] >> -% 1465 0 obj +% 1467 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.53 492.904 423.049 504.029] -/A << /S /GoTo /D (spdata) >> +/Rect [294.721 495.239 361.779 506.364] +/A << /S /GoTo /D (descdata) >> >> -% 1469 0 obj +% 1471 0 obj << -/D [1467 0 R /XYZ 149.705 753.953 null] +/D [1469 0 R /XYZ 98.895 753.953 null] >> -% 384 0 obj +% 360 0 obj << -/D [1467 0 R /XYZ 150.705 720.077 null] +/D [1469 0 R /XYZ 99.895 720.077 null] >> -% 1466 0 obj +% 1472 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R /F11 750 0 R >> +/D [1469 0 R /XYZ 99.895 382.883 null] +>> +% 1468 0 obj +<< +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R /F11 755 0 R >> /ProcSet [ /PDF /Text ] >> -% 1471 0 obj +% 1476 0 obj << /Type /Page -/Contents 1472 0 R -/Resources 1470 0 R +/Contents 1477 0 R +/Resources 1475 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1449 0 R +/Parent 1473 0 R +/Annots [ 1474 0 R ] >> -% 1473 0 obj +% 1474 0 obj << -/D [1471 0 R /XYZ 98.895 753.953 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [345.53 495.239 412.588 506.364] +/A << /S /GoTo /D (descdata) >> >> -% 1474 0 obj +% 1478 0 obj << -/D [1471 0 R /XYZ 99.895 496.913 null] +/D [1476 0 R /XYZ 149.705 753.953 null] >> -% 1475 0 obj +% 364 0 obj << -/D [1471 0 R /XYZ 99.895 439.185 null] +/D [1476 0 R /XYZ 150.705 720.077 null] >> -% 1476 0 obj +% 1479 0 obj << -/D [1471 0 R /XYZ 99.895 418.983 null] +/D [1476 0 R /XYZ 150.705 259.346 null] >> -% 1470 0 obj +% 1475 0 obj << -/Font << /F27 556 0 R /F8 557 0 R /F30 764 0 R /F16 554 0 R /F11 750 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R /F11 755 0 R >> /ProcSet [ /PDF /Text ] >> -% 1481 0 obj +% 1482 0 obj << /Type /Page -/Contents 1482 0 R -/Resources 1480 0 R +/Contents 1483 0 R +/Resources 1481 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1449 0 R -/Annots [ 1477 0 R 1478 0 R 1479 0 R ] ->> -% 1477 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.53 529.112 423.049 540.237] -/A << /S /GoTo /D (spdata) >> +/Parent 1473 0 R +/Annots [ 1480 0 R ] >> -% 1478 0 obj +% 1480 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.53 461.366 412.588 472.491] +/Rect [294.721 495.239 361.779 506.364] /A << /S /GoTo /D (descdata) >> >> -% 1479 0 obj +% 1484 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [372.153 405.575 439.211 416.7] -/A << /S /GoTo /D (precdata) >> +/D [1482 0 R /XYZ 98.895 753.953 null] >> -% 1483 0 obj +% 368 0 obj << -/D [1481 0 R /XYZ 149.705 753.953 null] +/D [1482 0 R /XYZ 99.895 720.077 null] >> -% 388 0 obj +% 1485 0 obj << -/D [1481 0 R /XYZ 150.705 720.077 null] +/D [1482 0 R /XYZ 99.895 382.883 null] >> -% 1480 0 obj +% 1481 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F30 764 0 R /F27 556 0 R /F11 750 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R /F11 755 0 R >> /ProcSet [ /PDF /Text ] >> -% 1485 0 obj +% 1488 0 obj << /Type /Page -/Contents 1486 0 R -/Resources 1484 0 R +/Contents 1489 0 R +/Resources 1487 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1488 0 R ->> -% 1487 0 obj -<< -/D [1485 0 R /XYZ 98.895 753.953 null] +/Parent 1473 0 R +/Annots [ 1486 0 R ] >> -% 392 0 obj +% 1486 0 obj << -/D [1485 0 R /XYZ 99.895 720.077 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [345.53 495.239 412.588 506.364] +/A << /S /GoTo /D (descdata) >> >> -% 1484 0 obj +% 1490 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F11 750 0 R /F27 556 0 R >> -/ProcSet [ /PDF /Text ] +/D [1488 0 R /XYZ 149.705 753.953 null] >> -% 1490 0 obj +% 372 0 obj << -/Type /Page -/Contents 1491 0 R -/Resources 1489 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1488 0 R +/D [1488 0 R /XYZ 150.705 720.077 null] >> -% 1492 0 obj +% 1491 0 obj << -/D [1490 0 R /XYZ 149.705 753.953 null] +/D [1488 0 R /XYZ 150.705 259.346 null] >> -% 1493 0 obj +% 1487 0 obj << -/D [1490 0 R /XYZ 150.705 702.144 null] +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R /F11 755 0 R >> +/ProcSet [ /PDF /Text ] >> % 1494 0 obj << -/D [1490 0 R /XYZ 150.705 668.326 null] +/Type /Page +/Contents 1495 0 R +/Resources 1493 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1473 0 R +/Annots [ 1492 0 R ] >> -% 1495 0 obj +% 1492 0 obj << -/D [1490 0 R /XYZ 150.705 624.491 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [294.721 574.94 361.779 586.065] +/A << /S /GoTo /D (descdata) >> >> % 1496 0 obj << -/D [1490 0 R /XYZ 150.705 556.745 null] +/D [1494 0 R /XYZ 98.895 753.953 null] >> -% 1497 0 obj +% 376 0 obj << -/D [1490 0 R /XYZ 150.705 500.954 null] +/D [1494 0 R /XYZ 99.895 720.077 null] >> -% 1498 0 obj +% 1497 0 obj << -/D [1490 0 R /XYZ 150.705 468.52 null] +/D [1494 0 R /XYZ 99.895 370.928 null] >> -% 1499 0 obj +% 1498 0 obj << -/D [1490 0 R /XYZ 150.705 425.182 null] +/D [1494 0 R /XYZ 99.895 327.092 null] >> -% 1500 0 obj +% 1493 0 obj << -/D [1490 0 R /XYZ 150.705 383.395 null] +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R >> +/ProcSet [ /PDF /Text ] >> % 1501 0 obj << -/D [1490 0 R /XYZ 150.705 355.499 null] +/Type /Page +/Contents 1502 0 R +/Resources 1500 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1473 0 R +/Annots [ 1499 0 R ] >> -% 1489 0 obj +% 1499 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F11 750 0 R /F14 767 0 R /F7 765 0 R >> -/ProcSet [ /PDF /Text ] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [345.53 574.94 412.588 586.065] +/A << /S /GoTo /D (descdata) >> >> % 1503 0 obj << -/Type /Page -/Contents 1504 0 R -/Resources 1502 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1488 0 R +/D [1501 0 R /XYZ 149.705 753.953 null] >> -% 1505 0 obj +% 380 0 obj << -/D [1503 0 R /XYZ 98.895 753.953 null] +/D [1501 0 R /XYZ 150.705 720.077 null] >> -% 396 0 obj +% 1504 0 obj << -/D [1503 0 R /XYZ 99.895 716.092 null] +/D [1501 0 R /XYZ 150.705 370.928 null] >> -% 1502 0 obj +% 1505 0 obj +<< +/D [1501 0 R /XYZ 150.705 339.047 null] +>> +% 1500 0 obj << -/Font << /F16 554 0 R /F8 557 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 1507 0 obj +% 1508 0 obj << /Type /Page -/Contents 1508 0 R -/Resources 1506 0 R +/Contents 1509 0 R +/Resources 1507 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1488 0 R ->> -% 1509 0 obj -<< -/D [1507 0 R /XYZ 149.705 753.953 null] +/Parent 1511 0 R +/Annots [ 1506 0 R ] >> -% 400 0 obj +% 1506 0 obj << -/D [1507 0 R /XYZ 150.705 720.077 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [294.721 492.904 372.239 504.029] +/A << /S /GoTo /D (spdata) >> >> % 1510 0 obj << -/D [1507 0 R /XYZ 150.705 235.436 null] +/D [1508 0 R /XYZ 98.895 753.953 null] >> -% 1511 0 obj +% 384 0 obj << -/D [1507 0 R /XYZ 150.705 213.573 null] +/D [1508 0 R /XYZ 99.895 720.077 null] >> -% 1506 0 obj +% 1507 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F27 556 0 R /F11 750 0 R /F14 767 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R /F11 755 0 R >> /ProcSet [ /PDF /Text ] >> % 1513 0 obj @@ -19197,81 +19076,94 @@ stream /Contents 1514 0 R /Resources 1512 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1488 0 R +/Parent 1511 0 R >> % 1515 0 obj << -/D [1513 0 R /XYZ 98.895 753.953 null] ->> -% 405 0 obj -<< -/D [1513 0 R /XYZ 99.895 720.077 null] +/D [1513 0 R /XYZ 149.705 753.953 null] >> % 1516 0 obj << -/D [1513 0 R /XYZ 99.895 349.01 null] +/D [1513 0 R /XYZ 150.705 496.913 null] >> % 1517 0 obj << -/D [1513 0 R /XYZ 99.895 315.192 null] +/D [1513 0 R /XYZ 150.705 439.185 null] +>> +% 1518 0 obj +<< +/D [1513 0 R /XYZ 150.705 418.983 null] >> % 1512 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F27 556 0 R /F14 767 0 R /F11 750 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F30 769 0 R /F16 558 0 R /F11 755 0 R >> /ProcSet [ /PDF /Text ] >> -% 1519 0 obj +% 1523 0 obj << /Type /Page -/Contents 1520 0 R -/Resources 1518 0 R +/Contents 1524 0 R +/Resources 1522 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1488 0 R +/Parent 1511 0 R +/Annots [ 1519 0 R 1520 0 R 1521 0 R ] >> -% 1521 0 obj +% 1519 0 obj << -/D [1519 0 R /XYZ 149.705 753.953 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [294.721 529.112 372.239 540.237] +/A << /S /GoTo /D (spdata) >> >> -% 409 0 obj +% 1520 0 obj << -/D [1519 0 R /XYZ 150.705 720.077 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [294.721 461.366 361.779 472.491] +/A << /S /GoTo /D (descdata) >> >> -% 1522 0 obj +% 1521 0 obj << -/D [1519 0 R /XYZ 150.705 442.659 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [321.343 405.575 388.401 416.7] +/A << /S /GoTo /D (precdata) >> >> -% 1523 0 obj +% 1525 0 obj << -/D [1519 0 R /XYZ 150.705 396.886 null] +/D [1523 0 R /XYZ 98.895 753.953 null] >> -% 1524 0 obj +% 388 0 obj << -/D [1519 0 R /XYZ 150.705 365.005 null] +/D [1523 0 R /XYZ 99.895 720.077 null] >> -% 1518 0 obj +% 1522 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F27 556 0 R /F11 750 0 R /F14 767 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F30 769 0 R /F27 560 0 R /F11 755 0 R >> /ProcSet [ /PDF /Text ] >> -% 1526 0 obj +% 1527 0 obj << /Type /Page -/Contents 1527 0 R -/Resources 1525 0 R +/Contents 1528 0 R +/Resources 1526 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1529 0 R +/Parent 1511 0 R >> -% 1528 0 obj +% 1529 0 obj << -/D [1526 0 R /XYZ 98.895 753.953 null] +/D [1527 0 R /XYZ 149.705 753.953 null] >> -% 413 0 obj +% 392 0 obj << -/D [1526 0 R /XYZ 99.895 720.077 null] +/D [1527 0 R /XYZ 150.705 720.077 null] >> -% 1525 0 obj +% 1526 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F27 556 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F11 755 0 R /F27 560 0 R >> /ProcSet [ /PDF /Text ] >> % 1531 0 obj @@ -19280,137 +19172,139 @@ stream /Contents 1532 0 R /Resources 1530 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1529 0 R +/Parent 1511 0 R >> % 1533 0 obj << -/D [1531 0 R /XYZ 149.705 753.953 null] +/D [1531 0 R /XYZ 98.895 753.953 null] >> -% 417 0 obj +% 1534 0 obj << -/D [1531 0 R /XYZ 150.705 720.077 null] +/D [1531 0 R /XYZ 99.895 702.144 null] >> -% 1530 0 obj +% 1535 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F11 750 0 R /F27 556 0 R /F14 767 0 R >> -/ProcSet [ /PDF /Text ] +/D [1531 0 R /XYZ 99.895 668.326 null] >> -% 1535 0 obj +% 1536 0 obj << -/Type /Page -/Contents 1536 0 R -/Resources 1534 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1529 0 R +/D [1531 0 R /XYZ 99.895 624.491 null] >> % 1537 0 obj << -/D [1535 0 R /XYZ 98.895 753.953 null] +/D [1531 0 R /XYZ 99.895 556.745 null] >> -% 421 0 obj +% 1538 0 obj << -/D [1535 0 R /XYZ 99.895 720.077 null] +/D [1531 0 R /XYZ 99.895 500.954 null] >> -% 1534 0 obj +% 1539 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F27 556 0 R >> -/ProcSet [ /PDF /Text ] +/D [1531 0 R /XYZ 99.895 468.52 null] >> -% 1539 0 obj +% 1540 0 obj << -/Type /Page -/Contents 1540 0 R -/Resources 1538 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1529 0 R +/D [1531 0 R /XYZ 99.895 425.182 null] >> % 1541 0 obj << -/D [1539 0 R /XYZ 149.705 753.953 null] +/D [1531 0 R /XYZ 99.895 383.395 null] >> -% 425 0 obj +% 1542 0 obj << -/D [1539 0 R /XYZ 150.705 720.077 null] +/D [1531 0 R /XYZ 99.895 355.499 null] >> -% 1538 0 obj +% 1530 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F27 556 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F11 755 0 R /F14 772 0 R /F7 770 0 R >> /ProcSet [ /PDF /Text ] >> -% 1543 0 obj +% 1544 0 obj << /Type /Page -/Contents 1544 0 R -/Resources 1542 0 R +/Contents 1545 0 R +/Resources 1543 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1529 0 R +/Parent 1511 0 R >> -% 1545 0 obj +% 1546 0 obj << -/D [1543 0 R /XYZ 98.895 753.953 null] +/D [1544 0 R /XYZ 149.705 753.953 null] >> -% 429 0 obj +% 396 0 obj << -/D [1543 0 R /XYZ 99.895 720.077 null] +/D [1544 0 R /XYZ 150.705 716.092 null] >> -% 1542 0 obj +% 1543 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F27 556 0 R >> +/Font << /F16 558 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 1547 0 obj +% 1548 0 obj << /Type /Page -/Contents 1548 0 R -/Resources 1546 0 R +/Contents 1549 0 R +/Resources 1547 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1529 0 R +/Parent 1553 0 R >> -% 1549 0 obj +% 1550 0 obj << -/D [1547 0 R /XYZ 149.705 753.953 null] +/D [1548 0 R /XYZ 98.895 753.953 null] >> -% 433 0 obj +% 400 0 obj << -/D [1547 0 R /XYZ 150.705 720.077 null] +/D [1548 0 R /XYZ 99.895 720.077 null] >> -% 1546 0 obj +% 1551 0 obj +<< +/D [1548 0 R /XYZ 99.895 235.436 null] +>> +% 1552 0 obj +<< +/D [1548 0 R /XYZ 99.895 213.573 null] +>> +% 1547 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F27 556 0 R /F11 750 0 R /F14 767 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F27 560 0 R /F11 755 0 R /F14 772 0 R >> /ProcSet [ /PDF /Text ] >> -% 1551 0 obj +% 1555 0 obj << /Type /Page -/Contents 1552 0 R -/Resources 1550 0 R +/Contents 1556 0 R +/Resources 1554 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1556 0 R +/Parent 1553 0 R +>> +% 1557 0 obj +<< +/D [1555 0 R /XYZ 149.705 753.953 null] >> endstream endobj -1560 0 obj +1563 0 obj << -/Length 5185 +/Length 4356 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ +/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ ET q -1 0 0 1 171.761 706.328 cm +1 0 0 1 120.951 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(max)-375(|)-375(Global)-375(maxim)31(um)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(exit)-375(|)-375(Exit)-375(from)-375(PSBLAS)-375(parallel)-375(en)31(vironmen)31(t)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_max\050icontxt,)-525(dat,)-525(root\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-326(subroutine)-326(implemen)28(ts)-326(a)-326(maxim)27(um)-326(v)56(aluereduction)-326(op)-28(eration)-326(based)-326(on)]TJ -14.944 -11.955 Td [(the)-333(underlying)-333(com)-1(m)28(unication)-333(library)83(.)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_exit\050icontxt\051)]TJ 0 -11.956 Td [(call)-525(psb_exit\050icontxt,close\051)]TJ/F8 9.9626 Tf 14.944 -21.917 Td [(This)-333(subroutine)-334(exits)-333(from)-333(the)-334(PSBLAS)-333(parallel)-333(virtual)-333(mac)27(hine.)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -19.926 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf -14.944 -19.926 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G @@ -19419,100 +19313,139 @@ BT 0 g 0 G 0 -19.925 Td [(icon)32(txt)]TJ 0 g 0 G -/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyi)1(ng)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(ariable.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -19.925 Td [(dat)]TJ -0 g 0 G -/F8 9.9626 Tf 21.371 0 Td [(The)-333(lo)-28(cal)-333(c)-1(on)28(tribution)-333(to)-333(the)-334(gl)1(obal)-334(maxim)28(um.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.451 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-326(as:)-442(an)-326(in)27(teger)-326(or)-327(real)-327(v)56(ariable,)-328(whic)28(h)-327(ma)28(y)-327(b)-28(e)-327(a)-326(s)-1(calar,)-328(or)-326(a)-327(rank)]TJ 0 -11.955 Td [(1)-333(or)-334(2)-333(arra)28(y)83(.)-778(T)28(yp)-27(e)-1(,)-333(kind,)-333(rank)-333(and)-334(size)-333(m)28(ust)-334(agree)-333(on)-333(all)-334(pro)-27(cesse)-1(s.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -19.925 Td [(ro)-32(ot)]TJ -0 g 0 G -/F8 9.9626 Tf 25.93 0 Td [(Pro)-28(cess)-305(to)-306(hold)-305(the)-305(\014nal)-305(m)-1(ax)1(im)27(um,)-311(or)]TJ/F14 9.9626 Tf 169.158 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)-305(to)-306(mak)28(e)-305(it)-306(a)28(v)56(ailable)-306(on)-305(all)-305(pro-)]TJ -177.93 -11.956 Td [(cesses.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue)]TJ/F14 9.9626 Tf 130.427 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)]TJ/F11 9.9626 Tf 7.749 0 Td [(<)]TJ/F8 9.9626 Tf 7.749 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(r)-28(oot)-278(<)]TJ/F8 9.9626 Tf 28.543 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.963 0 Td [(1,)-333(default)-334(-1.)]TJ +/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyin)1(g)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable.)]TJ 0 g 0 G -/F27 9.9626 Tf -251.325 -33.873 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf -24.907 -19.925 Td [(close)]TJ 0 g 0 G +/F8 9.9626 Tf 28.755 0 Td [(Whether)-401(to)-401(clos)-1(e)-401(all)-401(data)-401(structures)-401(relate)-1(d)-401(to)-401(the)-401(virtual)-401(parallel)-401(m)-1(a-)]TJ -3.848 -11.955 Td [(c)28(hine,)-334(b)-27(esides)-334(those)-333(asso)-28(ciated)-333(with)-334(icon)28(txt.)]TJ 0 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(logical)-333(v)55(ariable,)-333(default)-333(v)55(alu)1(e)-1(:)-444(true.)]TJ/F16 11.9552 Tf -24.907 -19.925 Td [(Notes)]TJ 0 g 0 G - 0 -19.926 Td [(dat)]TJ +/F8 9.9626 Tf 12.177 -19.926 Td [(1.)]TJ 0 g 0 G -/F8 9.9626 Tf 21.371 0 Td [(On)-333(destination)-334(pr)1(o)-28(cess\050es)-1(\051,)-333(the)-333(result)-333(of)-334(the)-333(maxim)28(um)-334(op)-27(eration.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-326(as)-1(:)-441(an)-326(in)27(teger)-326(or)-327(real)-327(v)56(ariable,)-328(whic)28(h)-327(ma)28(y)-327(b)-28(e)-327(a)-326(s)-1(calar,)-328(or)-326(a)-327(rank)]TJ 0 -11.955 Td [(1)-333(or)-334(2)-333(arra)28(y)83(.)-778(T)28(yp)-27(e)-1(,)-333(kind,)-333(rank)-333(and)-334(size)-333(m)28(ust)-334(agree)-333(on)-333(all)-334(pro)-27(cesse)-1(s.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ + [-500(This)-241(routine)-241(ma)28(y)-241(b)-28(e)-241(called)-241(ev)28(en)-241(if)-241(a)-241(previous)-241(call)-241(to)]TJ/F30 9.9626 Tf 233.305 0 Td [(psb_info)]TJ/F8 9.9626 Tf 44.244 0 Td [(has)-241(returned)]TJ -264.819 -11.955 Td [(with)]TJ/F11 9.9626 Tf 22.963 0 Td [(iam)]TJ/F8 9.9626 Tf 20.662 0 Td [(=)]TJ/F14 9.9626 Tf 10.966 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1;)-374(indeed,)-367(it)-360(it)-361(is)-360(the)-361(only)-360(routine)-360(that)-361(ma)28(y)-360(b)-28(e)-361(called)-360(with)]TJ -62.34 -11.955 Td [(argumen)28(t)]TJ/F30 9.9626 Tf 44.583 0 Td [(icontxt)]TJ/F8 9.9626 Tf 39.933 0 Td [(in)-333(this)-334(situation.)]TJ 0 g 0 G -/F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ + -97.246 -19.925 Td [(2.)]TJ 0 g 0 G - [-500(The)]TJ/F30 9.9626 Tf 32.469 0 Td [(dat)]TJ/F8 9.9626 Tf 18.272 0 Td [(argumen)28(t)-259(is)-259(b)-28(oth)-259(input)-259(and)-259(output,)-274(and)-259(its)-259(v)55(alue)-259(ma)28(y)-259(b)-28(e)-259(c)28(hanged)]TJ -38.011 -11.956 Td [(ev)28(en)-334(on)-333(pro)-28(cesses)-333(di\013eren)28(t)-334(from)-333(the)-333(\014nal)-334(result)-333(destination.)]TJ + [-500(A)-305(call)-306(to)-305(this)-305(routine)-305(with)]TJ/F30 9.9626 Tf 128.752 0 Td [(close=.true.)]TJ/F8 9.9626 Tf 65.806 0 Td [(implies)-305(a)-306(call)-305(to)]TJ/F30 9.9626 Tf 71.445 0 Td [(MPI_Finalize)]TJ/F8 9.9626 Tf 62.764 0 Td [(,)]TJ -316.037 -11.956 Td [(after)-333(whic)27(h)-333(no)-333(parallel)-333(routine)-334(ma)28(y)-333(b)-28(e)-333(called.)]TJ 0 g 0 G - -12.73 -19.925 Td [(2.)]TJ + -12.73 -19.925 Td [(3.)]TJ 0 g 0 G - [-500(The)]TJ/F30 9.9626 Tf 33.208 0 Td [(dat)]TJ/F8 9.9626 Tf 19.012 0 Td [(argumen)28(t)-334(ma)28(y)-333(also)-334(b)-27(e)-334(a)-333(long)-333(in)28(teger)-334(scalar.)]TJ + [-500(If)-391(the)-390(user)-391(whishes)-391(to)-390(use)-391(m)28(ultiple)-391(comm)28(unication)-391(con)28(texts)-391(in)-390(the)-391(same)]TJ 12.73 -11.955 Td [(program,)-485(or)-455(to)-455(en)28(ter)-455(and)-454(e)-1(xi)1(t)-455(m)27(ul)1(tiple)-455(times)-455(in)28(to)-455(the)-455(parallel)-455(en)28(viron-)]TJ 0 -11.955 Td [(men)28(t,)-494(this)-462(routine)-462(ma)28(y)-462(b)-28(e)-462(called)-462(to)-462(selectiv)28(ely)-462(close)-463(th)1(e)-462(c)-1(on)28(texts)-462(with)]TJ/F30 9.9626 Tf 0 -11.955 Td [(close=.false.)]TJ/F8 9.9626 Tf 67.994 0 Td [(,)-244(while)-223(on)-222(the)-222(last)-222(call)-223(it)-222(should)-222(b)-28(e)-222(called)-222(with)]TJ/F30 9.9626 Tf 194.328 0 Td [(close=.true.)]TJ/F8 9.9626 Tf -262.322 -11.955 Td [(to)-333(sh)27(utd)1(o)27(wn)-333(in)-333(a)-334(clean)-333(w)28(a)28(y)-334(the)-333(en)28(tire)-334(parallel)-333(en)28(vironmen)28(t.)]TJ 0 g 0 G - 99.987 -109.132 Td [(110)]TJ + 139.477 -212.744 Td [(105)]TJ 0 g 0 G ET endstream endobj -1566 0 obj +1570 0 obj << -/Length 5160 +/Length 2160 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ +/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ ET q -1 0 0 1 120.951 706.328 cm +1 0 0 1 171.761 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 175.796 706.129 Td [(get)]TJ +ET +q +1 0 0 1 194.695 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(min)-375(|)-375(Global)-375(minim)31(um)]TJ +/F16 11.9552 Tf 198.729 706.129 Td [(mpicomm)-375(|)-375(Get)-375(the)-375(MPI)-375(comm)31(unicator)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_min\050icontxt,)-525(dat,)-525(root\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-311(subroutine)-312(implemen)28(ts)-311(a)-312(minim)28(um)-312(v)56(alue)-311(reduction)-312(op)-27(eration)-312(based)-311(on)]TJ -14.944 -11.955 Td [(the)-333(underlying)-334(comm)28(unication)-333(library)83(.)]TJ +/F30 9.9626 Tf -48.024 -18.389 Td [(call)-525(psb_get_mpicomm\050icontxt,)-525(icomm\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-335(subroutine)-335(returns)-335(the)-336(M)1(PI)-336(comm)28(unicator)-335(asso)-28(ciated)-335(with)-335(a)-335(PSBLAS)]TJ -14.944 -11.955 Td [(con)28(text)]TJ 0 g 0 G /F27 9.9626 Tf 0 -19.926 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G /F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G 0 -19.925 Td [(icon)32(txt)]TJ 0 g 0 G -/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyin)1(g)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable.)]TJ +/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyi)1(ng)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(ariable.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.925 Td [(dat)]TJ +/F27 9.9626 Tf -24.907 -21.918 Td [(On)-383(Return)]TJ 0 g 0 G -/F8 9.9626 Tf 21.371 0 Td [(The)-333(lo)-28(cal)-334(con)28(tribution)-333(to)-333(the)-334(global)-333(minim)28(um.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-326(as)-1(:)-441(an)-326(in)27(teger)-326(or)-327(real)-327(v)56(ariable,)-328(whic)28(h)-327(ma)28(y)-327(b)-28(e)-327(a)-327(scalar,)-328(or)-326(a)-327(rank)]TJ 0 -11.955 Td [(1)-333(or)-334(2)-333(arra)28(y)83(.)-778(T)28(yp)-28(e,)-333(kind,)-333(rank)-333(and)-334(size)-333(m)28(ust)-334(agree)-333(on)-333(all)-334(pro)-27(cess)-1(es.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.925 Td [(ro)-32(ot)]TJ + 0 -19.925 Td [(icomm)]TJ 0 g 0 G -/F8 9.9626 Tf 25.931 0 Td [(Pro)-28(cess)-276(to)-276(hold)-276(the)-276(\014nal)-275(v)55(alue,)-287(or)]TJ/F14 9.9626 Tf 146.411 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)-276(to)-276(mak)28(e)-276(it)-276(a)28(v)55(ailable)-276(on)-276(all)-276(p)1(ro)-28(cesses.)]TJ -155.184 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue)]TJ/F14 9.9626 Tf 130.428 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)]TJ/F11 9.9626 Tf 7.748 0 Td [(<)]TJ/F8 9.9626 Tf 7.749 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(r)-28(oot)-278(<)]TJ/F8 9.9626 Tf 28.543 0 Td [(=)]TJ/F11 9.9626 Tf 10.517 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.962 0 Td [(1,)-333(default)-334(-1.)]TJ +/F8 9.9626 Tf 38.079 0 Td [(The)-377(MPI)-378(comm)28(unicator)-378(asso)-27(ciated)-378(with)-377(the)-378(PSBLAS)-377(virtual)-377(parallel)]TJ -13.172 -11.955 Td [(mac)28(hine.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -251.325 -33.873 Td [(On)-383(Return)]TJ + 89.442 -366.168 Td [(106)]TJ 0 g 0 G +ET + +endstream +endobj +1574 0 obj +<< +/Length 3020 +>> +stream 0 g 0 G - 0 -19.925 Td [(dat)]TJ 0 g 0 G -/F8 9.9626 Tf 21.372 0 Td [(On)-333(destination)-333(pro)-28(cess\050es\051,)-334(the)-333(result)-333(of)-334(the)-333(minim)28(um)-334(op)-27(eration.)]TJ 3.535 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -71.51 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-326(as)-1(:)-441(an)-326(in)27(teger)-326(or)-327(real)-327(v)56(ariable,)-328(whic)28(h)-327(ma)28(y)-327(b)-28(e)-327(a)-327(scalar,)-328(or)-326(a)-327(rank)]TJ 0 -11.955 Td [(1)-333(or)-334(2)-333(arra)28(y)83(.)]TJ 0 -11.955 Td [(T)28(yp)-28(e,)-333(kind,)-334(r)1(ank)-334(and)-333(size)-333(m)27(ust)-333(agree)-333(on)-334(all)-333(pro)-28(cesses.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ +BT +/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ +ET +q +1 0 0 1 120.951 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 124.986 706.129 Td [(get)]TJ +ET +q +1 0 0 1 143.885 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 147.92 706.129 Td [(rank)-375(|)-375(Get)-375(the)-375(MPI)-375(rank)]TJ 0 g 0 G -/F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ 0 g 0 G - [-500(The)]TJ/F30 9.9626 Tf 32.469 0 Td [(dat)]TJ/F8 9.9626 Tf 18.273 0 Td [(argumen)28(t)-259(is)-259(b)-28(oth)-259(input)-259(and)-259(output,)-274(and)-259(its)-259(v)55(alue)-259(ma)28(y)-259(b)-28(e)-259(c)28(hanged)]TJ -38.012 -11.956 Td [(ev)28(en)-334(on)-333(pro)-28(cesses)-333(di\013eren)28(t)-334(from)-333(the)-333(\014nal)-334(result)-333(destination.)]TJ +/F30 9.9626 Tf -48.025 -18.389 Td [(call)-525(psb_get_rank\050rank,)-525(icontxt,)-525(id\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-333(subroutine)-334(return)1(s)-334(the)-333(MPI)-333(rank)-334(of)-333(the)-333(PSBLAS)-334(pro)-27(cess)]TJ/F11 9.9626 Tf 274.665 0 Td [(id)]TJ 0 g 0 G - -12.73 -19.925 Td [(2.)]TJ +/F27 9.9626 Tf -289.609 -19.926 Td [(T)32(yp)-32(e:)]TJ +0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +0 g 0 G +/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(icon)32(txt)]TJ +0 g 0 G +/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyin)1(g)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.925 Td [(id)]TJ +0 g 0 G +/F8 9.9626 Tf 14.529 0 Td [(Iden)28(ti\014er)-333(of)-334(a)-333(pro)-28(cess)-333(in)-334(the)-333(PSBLAS)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ 10.378 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)-444(0)]TJ/F14 9.9626 Tf 142.051 0 Td [(\024)]TJ/F11 9.9626 Tf 10.516 0 Td [(id)]TJ/F14 9.9626 Tf 11.385 0 Td [(\024)]TJ/F11 9.9626 Tf 10.516 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.963 0 Td [(1)]TJ +0 g 0 G +/F27 9.9626 Tf -222.544 -21.918 Td [(On)-383(Return)]TJ 0 g 0 G - [-500(The)]TJ/F30 9.9626 Tf 33.209 0 Td [(dat)]TJ/F8 9.9626 Tf 19.012 0 Td [(argumen)28(t)-333(m)-1(a)28(y)-333(also)-333(b)-28(e)-334(a)-333(long)-333(in)28(teger)-334(scalar.)]TJ 0 g 0 G - 99.986 -109.132 Td [(111)]TJ + 0 -19.925 Td [(rank)]TJ +0 g 0 G +/F8 9.9626 Tf 27.681 0 Td [(The)-333(MPI)-334(rank)-333(asso)-28(ciated)-333(with)-333(the)-334(PSBLAS)-333(pro)-28(cess)]TJ/F11 9.9626 Tf 230.248 0 Td [(id)]TJ/F8 9.9626 Tf 8.618 0 Td [(.)]TJ -241.64 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ +0 g 0 G + 89.442 -322.333 Td [(107)]TJ 0 g 0 G ET endstream endobj -1572 0 obj +1578 0 obj << -/Length 5277 +/Length 1202 >> stream 0 g 0 G @@ -19525,10 +19458,47 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(amx)-375(|)-375(Global)-375(maxim)31(um)-375(absolute)-375(v)63(alue)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(wtime)-375(|)-375(W)94(all)-375(clo)-31(c)31(k)-375(timing)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_amx\050icontxt,)-525(dat,)-525(root\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-312(subroutine)-312(implemen)28(ts)-313(a)-312(maxim)28(um)-312(absolute)-312(v)55(alue)-312(reduction)-312(op)-28(eration)]TJ -14.944 -11.955 Td [(based)-333(on)-334(the)-333(underlying)-333(comm)28(unication)-334(library)84(.)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(time)-525(=)-525(psb_wtime\050\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-474(fun)1(c)-1(ti)1(o)-1(n)-473(returns)-474(a)-473(w)28(all)-474(clo)-28(c)28(k)-474(timer.)-865(The)-474(resolution)-473(of)-474(the)-473(timer)-474(is)]TJ -14.944 -11.955 Td [(dep)-28(enden)28(t)-333(on)-334(th)1(e)-334(underlying)-333(parallel)-333(en)28(vironmen)27(t)-333(implemen)28(tation.)]TJ +0 g 0 G +/F27 9.9626 Tf 0 -19.926 Td [(T)32(yp)-32(e:)]TJ +0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +0 g 0 G +/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(Exit)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(F)96(unction)-384(v)64(alue)]TJ +0 g 0 G +/F8 9.9626 Tf 78.386 0 Td [(the)-333(elapsed)-334(time)-333(in)-333(sec)-1(on)1(ds.)]TJ -53.479 -11.955 Td [(Returned)-333(as:)-445(a)]TJ/F30 9.9626 Tf 68.299 0 Td [(real\050psb_dpk_\051)]TJ/F8 9.9626 Tf 76.546 0 Td [(v)56(ariable.)]TJ +0 g 0 G + -5.369 -491.698 Td [(108)]TJ +0 g 0 G +ET + +endstream +endobj +1582 0 obj +<< +/Length 1484 +>> +stream +0 g 0 G +0 g 0 G +BT +/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ +ET +q +1 0 0 1 120.951 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 124.986 706.129 Td [(barrier)-375(|)-375(Sinc)31(hronization)-375(p)-31(oin)31(t)-375(parallel)-375(en)32(vironmen)31(t)]TJ +0 g 0 G +0 g 0 G +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_barrier\050icontxt\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-398(subroutine)-397(ac)-1(t)1(s)-398(as)-398(an)-398(explicit)-398(sync)28(hronization)-397(p)-28(oin)28(t)-398(for)-398(the)-398(PSBLAS)]TJ -14.944 -11.955 Td [(parallel)-333(virtual)-333(m)-1(ac)28(hine.)]TJ 0 g 0 G /F27 9.9626 Tf 0 -19.926 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G @@ -19539,40 +19509,54 @@ BT 0 g 0 G 0 -19.925 Td [(icon)32(txt)]TJ 0 g 0 G -/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyi)1(ng)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(ariable.)]TJ +/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyin)1(g)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.925 Td [(dat)]TJ + 139.477 -455.832 Td [(109)]TJ 0 g 0 G -/F8 9.9626 Tf 21.371 0 Td [(The)-333(lo)-28(cal)-333(c)-1(on)28(tribution)-333(to)-333(the)-334(gl)1(obal)-334(maxim)28(um.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.451 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(tege)-1(r,)-341(real)-339(or)-340(complex)-340(v)56(ariable,)-342(whic)28(h)-339(m)-1(a)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-464(a)-464(ran)1(k)-464(1)-464(or)-464(2)-464(arra)28(y)83(.)-1299(T)28(yp)-28(e,)-497(kind)1(,)-497(rank)-464(and)-463(size)-464(m)27(ust)-463(agree)-464(on)-464(all)]TJ 0 -11.955 Td [(pro)-28(cesses.)]TJ +ET + +endstream +endobj +1587 0 obj +<< +/Length 1357 +>> +stream 0 g 0 G -/F27 9.9626 Tf -24.907 -19.926 Td [(ro)-32(ot)]TJ 0 g 0 G -/F8 9.9626 Tf 25.93 0 Td [(Pro)-28(cess)-276(to)-276(hold)-276(the)-276(\014nal)-276(v)56(alue,)-287(or)]TJ/F14 9.9626 Tf 146.411 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)-276(to)-276(mak)28(e)-276(it)-276(a)28(v)55(ailable)-276(on)-276(all)-276(pr)1(o)-28(cesses)-1(.)]TJ -155.183 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(alue)]TJ/F14 9.9626 Tf 130.427 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)]TJ/F11 9.9626 Tf 7.749 0 Td [(<)]TJ/F8 9.9626 Tf 7.748 0 Td [(=)]TJ/F11 9.9626 Tf 10.517 0 Td [(r)-28(oot)-278(<)]TJ/F8 9.9626 Tf 28.543 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.963 0 Td [(1,)-333(default)-334(-1.)]TJ +BT +/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ +ET +q +1 0 0 1 171.761 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 175.796 706.129 Td [(ab)-31(ort)-375(|)-375(Ab)-31(ort)-375(a)-375(computation)]TJ 0 g 0 G -/F27 9.9626 Tf -251.325 -33.873 Td [(On)-383(Return)]TJ 0 g 0 G +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_abort\050icontxt\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-333(subroutine)-334(ab)-27(orts)-334(computation)-333(on)-333(the)-334(p)1(arallel)-334(virtual)-333(mac)28(hine.)]TJ 0 g 0 G - 0 -19.926 Td [(dat)]TJ +/F27 9.9626 Tf -14.944 -19.926 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 21.371 0 Td [(On)-333(destination)-334(p)1(ro)-28(cess\050es)-1(\051)1(,)-334(the)-333(result)-333(of)-334(the)-333(maxim)28(um)-334(op)-27(eration.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(tege)-1(r,)-341(real)-339(or)-340(complex)-340(v)56(ariable,)-342(whic)28(h)-339(m)-1(a)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-464(a)-464(ran)1(k)-464(1)-464(or)-464(2)-464(arra)28(y)83(.)-1299(T)28(yp)-28(e,)-497(kind)1(,)-497(rank)-464(and)-463(size)-464(m)27(ust)-463(agree)-464(on)-464(all)]TJ 0 -11.956 Td [(pro)-28(cesses.)]TJ/F16 11.9552 Tf -24.907 -21.917 Td [(Notes)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G -/F8 9.9626 Tf 12.177 -19.926 Td [(1.)]TJ +/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G - [-500(The)]TJ/F30 9.9626 Tf 32.469 0 Td [(dat)]TJ/F8 9.9626 Tf 18.272 0 Td [(argumen)28(t)-259(is)-259(b)-28(oth)-259(input)-259(and)-259(output,)-274(and)-259(its)-259(v)55(alue)-259(ma)28(y)-259(b)-28(e)-259(c)28(hanged)]TJ -38.011 -11.955 Td [(ev)28(en)-334(on)-333(pro)-28(cesses)-333(di\013eren)28(t)-334(from)-333(the)-333(\014nal)-334(result)-333(destination.)]TJ 0 g 0 G - -12.73 -19.925 Td [(2.)]TJ + 0 -19.925 Td [(icon)32(txt)]TJ 0 g 0 G - [-500(The)]TJ/F30 9.9626 Tf 33.208 0 Td [(dat)]TJ/F8 9.9626 Tf 19.012 0 Td [(argumen)28(t)-334(ma)28(y)-333(also)-334(b)-27(e)-334(a)-333(long)-333(in)28(teger)-334(scalar.)]TJ +/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyi)1(ng)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(ariable.)]TJ 0 g 0 G - 99.987 -97.177 Td [(112)]TJ + 139.476 -467.787 Td [(110)]TJ 0 g 0 G ET endstream endobj -1578 0 obj +1591 0 obj << -/Length 5248 +/Length 4552 >> stream 0 g 0 G @@ -19585,10 +19569,10 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(amn)-375(|)-375(Global)-375(minim)31(um)-375(absolute)-375(v)63(alue)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(b)-31(cast)-375(|)-375(Broadcast)-375(data)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_amn\050icontxt,)-525(dat,)-525(root\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-336(s)-1(u)1(broutine)-337(implemen)28(ts)-337(a)-336(minim)28(um)-337(absolute)-336(v)55(alue)-336(reduction)-336(op)-28(eration)]TJ -14.944 -11.955 Td [(based)-333(on)-334(the)-333(underlying)-333(comm)28(unication)-334(library)84(.)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_bcast\050icontxt,)-525(dat,)-525(root\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-338(subroutine)-338(impleme)-1(n)28(ts)-338(a)-338(broadcast)-339(op)-27(eration)-338(base)-1(d)-338(on)-338(the)-338(underlying)]TJ -14.944 -11.955 Td [(comm)28(unication)-334(libr)1(ary)83(.)]TJ 0 g 0 G /F27 9.9626 Tf 0 -19.926 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G @@ -19603,36 +19587,28 @@ BT 0 g 0 G /F27 9.9626 Tf -24.907 -19.925 Td [(dat)]TJ 0 g 0 G -/F8 9.9626 Tf 21.371 0 Td [(The)-333(lo)-28(cal)-334(con)28(tribution)-333(to)-333(the)-334(global)-333(minim)28(um.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(te)-1(ger,)-341(real)-340(or)-339(complex)-340(v)56(ariable,)-342(whic)28(h)-340(ma)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-464(a)-464(rank)-463(1)-464(or)-464(2)-464(arra)28(y)83(.)-1299(T)28(yp)-28(e,)-497(kind,)-496(rank)-464(and)-463(size)-464(m)27(ust)-463(agree)-464(on)-464(all)]TJ 0 -11.955 Td [(pro)-28(cesses.)]TJ +/F8 9.9626 Tf 21.371 0 Td [(On)-333(the)-334(ro)-27(ot)-334(pro)-27(ce)-1(ss,)-333(the)-333(data)-334(to)-333(b)-28(e)-333(broadcast.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(te)-1(ger,)-341(real)-340(or)-339(complex)-340(v)56(ariable,)-342(whic)28(h)-340(ma)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-403(a)-403(rank)-404(1)-403(or)-403(2)-403(arra)28(y)83(,)-421(or)-403(a)-403(c)28(haracter)-404(or)-403(logical)-403(v)56(ariable,)-421(whic)28(h)-403(ma)27(y)-403(b)-28(e)]TJ 0 -11.955 Td [(a)-427(scalar)-426(or)-427(ran)1(k)-427(1)-426(arra)27(y)84(.)-1151(T)28(yp)-28(e,)-450(ki)1(nd,)-450(rank)-427(and)-426(size)-427(m)28(ust)-426(agree)-427(on)-426(all)]TJ 0 -11.955 Td [(pro)-28(cesses.)]TJ 0 g 0 G /F27 9.9626 Tf -24.907 -19.926 Td [(ro)-32(ot)]TJ 0 g 0 G -/F8 9.9626 Tf 25.931 0 Td [(Pro)-28(cess)-276(to)-276(hold)-276(the)-276(\014nal)-275(v)55(alue,)-287(or)]TJ/F14 9.9626 Tf 146.411 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)-276(to)-276(mak)28(e)-276(it)-276(a)28(v)55(ailable)-276(on)-276(all)-276(p)1(ro)-28(cesses.)]TJ -155.184 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue)]TJ/F14 9.9626 Tf 130.428 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)]TJ/F11 9.9626 Tf 7.748 0 Td [(<)]TJ/F8 9.9626 Tf 7.749 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(r)-28(oot)-278(<)]TJ/F8 9.9626 Tf 28.543 0 Td [(=)]TJ/F11 9.9626 Tf 10.517 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.962 0 Td [(1,)-333(default)-334(-1.)]TJ +/F8 9.9626 Tf 25.931 0 Td [(Ro)-28(ot)-333(pro)-28(cess)-333(holding)-334(d)1(ata)-334(to)-333(b)-28(e)-333(broadcast.)]TJ -1.024 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue)-333(0)]TJ/F11 9.9626 Tf 138.176 0 Td [(<)]TJ/F8 9.9626 Tf 7.749 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(r)-28(oot)-278(<)]TJ/F8 9.9626 Tf 28.544 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.963 0 Td [(1,)-333(default)-334(0)]TJ 0 g 0 G -/F27 9.9626 Tf -251.325 -33.873 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf -243.577 -21.918 Td [(On)-383(Return)]TJ 0 g 0 G 0 g 0 G 0 -19.926 Td [(dat)]TJ 0 g 0 G -/F8 9.9626 Tf 21.372 0 Td [(On)-333(destination)-333(pro)-28(cess\050es\051,)-334(the)-333(result)-333(of)-334(the)-333(minim)28(um)-334(op)-27(eration.)]TJ 3.535 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -71.51 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(te)-1(ger,)-341(real)-340(or)-339(complex)-340(v)56(ariable,)-342(whic)28(h)-340(ma)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-333(a)-334(rank)-333(1)-333(or)-334(2)-333(arra)28(y)83(.)]TJ 0 -11.956 Td [(T)28(yp)-28(e,)-333(kind,)-334(r)1(ank)-334(and)-333(size)-333(m)27(ust)-333(agree)-333(on)-334(all)-333(pro)-28(cesses.)]TJ/F16 11.9552 Tf -24.907 -21.917 Td [(Notes)]TJ -0 g 0 G -/F8 9.9626 Tf 12.177 -19.926 Td [(1.)]TJ -0 g 0 G - [-500(The)]TJ/F30 9.9626 Tf 32.469 0 Td [(dat)]TJ/F8 9.9626 Tf 18.273 0 Td [(argumen)28(t)-259(is)-259(b)-28(oth)-259(input)-259(and)-259(output,)-274(and)-259(its)-259(v)55(alue)-259(ma)28(y)-259(b)-28(e)-259(c)28(hanged)]TJ -38.012 -11.955 Td [(ev)28(en)-334(on)-333(pro)-28(cesses)-333(di\013eren)28(t)-334(from)-333(the)-333(\014nal)-334(result)-333(destination.)]TJ -0 g 0 G - -12.73 -19.925 Td [(2.)]TJ -0 g 0 G - [-500(The)]TJ/F30 9.9626 Tf 33.209 0 Td [(dat)]TJ/F8 9.9626 Tf 19.012 0 Td [(argumen)28(t)-333(m)-1(a)28(y)-333(also)-333(b)-28(e)-334(a)-333(long)-333(in)28(teger)-334(scalar.)]TJ +/F8 9.9626 Tf 21.372 0 Td [(On)-333(pro)-28(cesses)-334(oth)1(e)-1(r)-333(than)-333(ro)-28(ot,)-333(the)-333(data)-334(to)-333(b)-28(e)-333(broadcast.)]TJ 3.535 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(te)-1(ger,)-341(real)-340(or)-339(complex)-340(v)56(ariable,)-342(whic)28(h)-340(ma)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-346(a)-346(rank)-347(1)-346(or)-346(2)-346(arra)28(y)83(,)-349(or)-347(a)-346(c)28(haracter)-346(or)-347(l)1(ogic)-1(al)-346(scalar.)-829(T)28(yp)-28(e,)-350(k)1(ind,)-350(rank)]TJ 0 -11.956 Td [(and)-333(size)-334(m)28(ust)-333(agree)-334(on)-333(all)-333(pro)-28(cesses.)]TJ 0 g 0 G - 99.986 -97.177 Td [(113)]TJ + 139.477 -170.9 Td [(111)]TJ 0 g 0 G ET endstream endobj -1584 0 obj +1595 0 obj << -/Length 5369 +/Length 5199 >> stream 0 g 0 G @@ -19645,51 +19621,54 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 175.796 706.129 Td [(snd)-375(|)-375(Send)-375(data)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(sum)-375(|)-375(Global)-375(sum)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_snd\050icontxt,)-525(dat,)-525(dst,)-525(m\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-333(subroutine)-334(sends)-333(a)-333(pac)28(k)27(et)-333(of)-333(data)-334(to)-333(a)-333(destination.)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_sum\050icontxt,)-525(dat,)-525(root\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-318(subroutine)-319(impl)1(e)-1(men)28(ts)-318(a)-318(s)-1(u)1(m)-319(reduction)-318(op)-28(eration)-318(based)-318(on)-319(the)-318(under-)]TJ -14.944 -11.955 Td [(lying)-333(comm)27(un)1(ic)-1(ati)1(on)-334(library)84(.)]TJ 0 g 0 G -/F27 9.9626 Tf -14.944 -19.926 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf 0 -19.926 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous:)-444(s)-1(ee)-333(usage)-333(notes.)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G /F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G 0 -19.925 Td [(icon)32(txt)]TJ 0 g 0 G -/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyi)1(ng)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(ariable.)]TJ +/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyi)1(ng)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(ariable.)]TJ 0 g 0 G /F27 9.9626 Tf -24.907 -19.925 Td [(dat)]TJ 0 g 0 G -/F8 9.9626 Tf 21.371 0 Td [(The)-333(data)-334(to)-333(b)-28(e)-333(sen)28(t.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.451 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(tege)-1(r,)-341(real)-339(or)-340(complex)-340(v)56(ariable,)-342(whic)28(h)-339(m)-1(a)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-381(a)-381(rank)-381(1)-381(or)-381(2)-381(arra)28(y)83(,)-393(or)-381(a)-381(c)28(haracte)-1(r)-381(or)-381(logical)-381(scalar.)-968(T)27(yp)-27(e,)-393(kind)-381(and)]TJ 0 -11.955 Td [(rank)-327(m)27(ust)-327(agree)-328(on)-327(sender)-328(and)-327(receiv)28(e)-1(r)-327(pro)-28(cess;)-329(if)]TJ/F11 9.9626 Tf 220.724 0 Td [(m)]TJ/F8 9.9626 Tf 12.01 0 Td [(is)-328(n)1(o)-1(t)-327(sp)-28(eci\014ed,)-328(s)-1(ize)]TJ -232.734 -11.955 Td [(m)28(ust)-334(agree)-333(as)-333(w)27(ell.)]TJ +/F8 9.9626 Tf 21.371 0 Td [(The)-333(lo)-28(cal)-333(c)-1(on)28(tribution)-333(to)-333(the)-334(gl)1(obal)-334(sum.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(tege)-1(r,)-341(real)-339(or)-340(complex)-340(v)56(ariable,)-342(whic)28(h)-339(m)-1(a)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-464(a)-464(ran)1(k)-464(1)-464(or)-464(2)-464(arra)28(y)83(.)-1299(T)28(yp)-28(e,)-497(kind)1(,)-497(rank)-464(and)-463(size)-464(m)27(ust)-463(agree)-464(on)-464(all)]TJ 0 -11.955 Td [(pro)-28(cesses.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.926 Td [(dst)]TJ +/F27 9.9626 Tf -24.907 -19.926 Td [(ro)-32(ot)]TJ 0 g 0 G -/F8 9.9626 Tf 20.321 0 Td [(Destination)-333(pro)-28(cess.)]TJ 4.586 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-1(n)-333(in)28(teger)-333(v)55(alue)-333(0)]TJ/F11 9.9626 Tf 138.176 0 Td [(<)]TJ/F8 9.9626 Tf 7.749 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(dst)-278(<)]TJ/F8 9.9626 Tf 23.969 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.963 0 Td [(1.)]TJ +/F8 9.9626 Tf 25.93 0 Td [(Pro)-28(cess)-310(to)-309(hold)-310(the)-310(\014nal)-310(sum,)-314(or)]TJ/F14 9.9626 Tf 144.053 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)-310(to)-310(mak)28(e)-310(it)-309(a)27(v)56(ailable)-310(on)-310(al)1(l)-310(pro)-28(cesses.)]TJ -152.825 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(alue)]TJ/F14 9.9626 Tf 130.427 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)]TJ/F11 9.9626 Tf 7.749 0 Td [(<)]TJ/F8 9.9626 Tf 7.749 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(r)-28(oot)-278(<)]TJ/F8 9.9626 Tf 28.543 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.963 0 Td [(1,)-333(default)-334(-1.)]TJ 0 g 0 G -/F27 9.9626 Tf -239.002 -31.881 Td [(m)]TJ +/F27 9.9626 Tf -251.325 -21.918 Td [(On)-383(Return)]TJ 0 g 0 G -/F8 9.9626 Tf 14.529 0 Td [(Num)28(b)-28(er)-333(of)-334(ro)28(ws.)]TJ 10.378 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(Optional)]TJ/F8 9.9626 Tf 43.455 0 Td [(.)]TJ -73.066 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue)-333(0)]TJ/F11 9.9626 Tf 138.176 0 Td [(<)]TJ/F8 9.9626 Tf 7.749 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(m)-278(<)]TJ/F8 9.9626 Tf 19.263 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(siz)-44(e)]TJ/F8 9.9626 Tf 17.813 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(dat;)]TJ/F8 9.9626 Tf 18.477 0 Td [(1\051.)]TJ -226.384 -11.956 Td [(When)]TJ/F11 9.9626 Tf 29.071 0 Td [(dat)]TJ/F8 9.9626 Tf 17.383 0 Td [(is)-335(a)-334(rank)-335(2)-335(arra)28(y)84(,)-335(sp)-28(eci\014es)-335(the)-335(n)28(um)28(b)-28(er)-334(of)-335(ro)28(ws)-335(to)-335(b)-27(e)-335(sen)28(t)-335(inde-)]TJ -46.454 -11.955 Td [(p)-28(enden)28(tly)-285(of)-285(the)-286(leadin)1(g)-286(dimension)]TJ/F11 9.9626 Tf 153.741 0 Td [(siz)-44(e)]TJ/F8 9.9626 Tf 17.813 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(dat;)]TJ/F8 9.9626 Tf 18.477 0 Td [(1\051;)-301(m)27(u)1(s)-1(t)-285(ha)28(v)28(e)-285(the)-286(same)-285(v)55(al)1(ue)]TJ -193.905 -11.955 Td [(on)-333(sending)-334(and)-333(receiving)-333(pro)-28(cesses.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -21.918 Td [(On)-383(Return)]TJ + 0 -19.925 Td [(dat)]TJ 0 g 0 G -/F16 11.9552 Tf 0 -21.918 Td [(Notes)]TJ +/F8 9.9626 Tf 21.371 0 Td [(On)-333(destination)-334(pr)1(o)-28(cess\050es)-1(\051,)-333(the)-333(result)-333(of)-334(the)-333(sum)-333(op)-28(eration.)]TJ 3.536 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(tege)-1(r,)-341(real)-339(o)-1(r)-339(complex)-340(v)56(ariable,)-342(whic)28(h)-339(m)-1(a)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-333(a)-334(rank)-333(1)-333(or)-333(2)-334(arra)28(y)83(.)]TJ 0 -11.955 Td [(T)28(yp)-28(e,)-333(kind,)-333(rank)-334(and)-333(size)-333(m)27(ust)-333(agree)-333(on)-334(all)-333(pro)-28(cesses.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ 0 g 0 G /F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ 0 g 0 G - [-500(This)-402(subroutine)-403(implies)-402(a)-402(sync)27(hronization,)-419(but)-403(on)1(ly)-403(b)-28(et)28(w)28(een)-403(th)1(e)-403(calling)]TJ 12.73 -11.955 Td [(pro)-28(cess)-333(and)-333(the)-334(destination)-333(pro)-28(cess)]TJ/F11 9.9626 Tf 157.52 0 Td [(dst)]TJ/F8 9.9626 Tf 13.453 0 Td [(.)]TJ + [-500(The)]TJ/F30 9.9626 Tf 32.469 0 Td [(dat)]TJ/F8 9.9626 Tf 18.272 0 Td [(argumen)28(t)-259(is)-259(b)-28(oth)-259(input)-259(and)-259(output,)-274(and)-259(its)-259(v)55(alue)-259(ma)28(y)-259(b)-28(e)-259(c)28(hanged)]TJ -38.011 -11.956 Td [(ev)28(en)-334(on)-333(pro)-28(cesses)-333(di\013eren)28(t)-334(from)-333(the)-333(\014nal)-334(result)-333(destination.)]TJ +0 g 0 G + -12.73 -19.925 Td [(2.)]TJ +0 g 0 G + [-500(The)]TJ/F30 9.9626 Tf 33.208 0 Td [(dat)]TJ/F8 9.9626 Tf 19.012 0 Td [(argumen)28(t)-334(ma)28(y)-333(also)-334(b)-27(e)-334(a)-333(long)-333(in)28(teger)-334(scalar.)]TJ 0 g 0 G - -31.496 -105.147 Td [(114)]TJ + 99.987 -109.132 Td [(112)]TJ 0 g 0 G ET endstream endobj -1589 0 obj +1601 0 obj << -/Length 5352 +/Length 5151 >> stream 0 g 0 G @@ -19702,652 +19681,698 @@ q []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 124.986 706.129 Td [(rcv)-375(|)-375(Receiv)31(e)-375(data)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(max)-375(|)-375(Global)-375(maxim)31(um)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_rcv\050icontxt,)-525(dat,)-525(src,)-525(m\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-333(subroutine)-334(receiv)28(es)-333(a)-334(pac)28(k)28(et)-333(of)-334(data)-333(to)-333(a)-334(destination.)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_max\050icontxt,)-525(dat,)-525(root\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-326(subroutine)-326(implemen)28(ts)-326(a)-326(maxim)27(um)-326(v)56(aluereduction)-326(op)-28(eration)-326(based)-326(on)]TJ -14.944 -11.955 Td [(the)-333(underlying)-334(comm)28(unication)-333(library)83(.)]TJ 0 g 0 G -/F27 9.9626 Tf -14.944 -19.926 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf 0 -19.926 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous:)-445(see)-333(usage)-333(notes.)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G /F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G 0 -19.925 Td [(icon)32(txt)]TJ 0 g 0 G -/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyin)1(g)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable.)]TJ +/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyin)1(g)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.925 Td [(src)]TJ +/F27 9.9626 Tf -24.907 -19.925 Td [(dat)]TJ 0 g 0 G -/F8 9.9626 Tf 19.311 0 Td [(Source)-333(pro)-28(cess.)]TJ 5.596 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue)-333(0)]TJ/F11 9.9626 Tf 138.176 0 Td [(<)]TJ/F8 9.9626 Tf 7.749 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(sr)-28(c)-277(<)]TJ/F8 9.9626 Tf 24.269 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.963 0 Td [(1.)]TJ +/F8 9.9626 Tf 21.371 0 Td [(The)-333(lo)-28(cal)-334(con)28(tribution)-333(to)-333(the)-334(global)-333(maxim)28(um.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-326(as)-1(:)-441(an)-326(in)27(teger)-326(or)-327(real)-327(v)56(ariable,)-328(whic)28(h)-327(ma)28(y)-327(b)-28(e)-327(a)-327(scalar,)-328(or)-326(a)-327(rank)]TJ 0 -11.955 Td [(1)-333(or)-334(2)-333(arra)28(y)83(.)-778(T)28(yp)-28(e,)-333(kind,)-333(rank)-333(and)-334(size)-333(m)28(ust)-334(agree)-333(on)-333(all)-334(pro)-27(cess)-1(es.)]TJ 0 g 0 G -/F27 9.9626 Tf -239.302 -31.88 Td [(m)]TJ +/F27 9.9626 Tf -24.907 -19.925 Td [(ro)-32(ot)]TJ 0 g 0 G -/F8 9.9626 Tf 14.529 0 Td [(Num)28(b)-28(er)-333(of)-334(ro)28(ws.)]TJ 10.378 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(Optional)]TJ/F8 9.9626 Tf 43.455 0 Td [(.)]TJ -73.066 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue)-333(0)]TJ/F11 9.9626 Tf 138.176 0 Td [(<)]TJ/F8 9.9626 Tf 7.749 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(m)-278(<)]TJ/F8 9.9626 Tf 19.264 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(siz)-44(e)]TJ/F8 9.9626 Tf 17.812 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(dat;)]TJ/F8 9.9626 Tf 18.477 0 Td [(1\051.)]TJ -226.384 -11.955 Td [(When)]TJ/F11 9.9626 Tf 29.071 0 Td [(dat)]TJ/F8 9.9626 Tf 17.383 0 Td [(is)-335(a)-334(rank)-335(2)-335(arra)28(y)84(,)-335(sp)-28(eci\014es)-335(the)-335(n)28(um)28(b)-28(er)-334(of)-335(ro)28(ws)-335(to)-335(b)-27(e)-335(sen)28(t)-335(inde-)]TJ -46.454 -11.955 Td [(p)-28(enden)28(tly)-285(of)-285(the)-286(leading)-285(dimension)]TJ/F11 9.9626 Tf 153.742 0 Td [(siz)-44(e)]TJ/F8 9.9626 Tf 17.812 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(dat;)]TJ/F8 9.9626 Tf 18.477 0 Td [(1\051;)-301(m)27(ust)-285(ha)28(v)28(e)-285(the)-286(same)-285(v)55(alu)1(e)]TJ -193.905 -11.955 Td [(on)-333(sending)-334(and)-333(receiving)-333(pro)-28(cesses.)]TJ +/F8 9.9626 Tf 25.931 0 Td [(Pro)-28(cess)-305(to)-306(hold)-305(the)-305(\014nal)-305(maxim)27(um,)-311(or)]TJ/F14 9.9626 Tf 169.157 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)-305(to)-306(mak)28(e)-305(it)-306(a)28(v)56(ailable)-306(on)-305(all)-305(pro-)]TJ -177.93 -11.956 Td [(cesses.)]TJ 0 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue)]TJ/F14 9.9626 Tf 130.428 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)]TJ/F11 9.9626 Tf 7.748 0 Td [(<)]TJ/F8 9.9626 Tf 7.749 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(r)-28(oot)-278(<)]TJ/F8 9.9626 Tf 28.543 0 Td [(=)]TJ/F11 9.9626 Tf 10.517 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.962 0 Td [(1,)-333(default)-334(-1.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -21.918 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf -251.325 -33.873 Td [(On)-383(Return)]TJ 0 g 0 G 0 g 0 G 0 -19.926 Td [(dat)]TJ 0 g 0 G -/F8 9.9626 Tf 21.371 0 Td [(The)-333(data)-334(to)-333(b)-28(e)-333(receiv)28(ed.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(te)-1(ger,)-341(real)-340(or)-339(complex)-340(v)56(ariable,)-342(whic)28(h)-340(ma)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-381(a)-381(rank)-381(1)-381(or)-381(2)-381(arra)27(y)84(,)-393(or)-381(a)-381(c)27(har)1(ac)-1(ter)-381(or)-381(logical)-381(scalar.)-969(T)28(yp)-27(e)-1(,)-393(ki)1(nd)-381(and)]TJ 0 -11.956 Td [(rank)-327(m)27(ust)-327(agree)-328(on)-327(sender)-328(and)-327(receiv)27(er)-327(pro)-28(cess;)-329(if)]TJ/F11 9.9626 Tf 220.724 0 Td [(m)]TJ/F8 9.9626 Tf 12.01 0 Td [(is)-328(not)-327(sp)-28(eci\014ed,)-329(size)]TJ -232.734 -11.955 Td [(m)28(ust)-334(agree)-333(as)-333(w)27(ell.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ +/F8 9.9626 Tf 21.372 0 Td [(On)-333(destination)-333(pro)-28(cess\050es\051,)-334(the)-333(result)-333(of)-334(the)-333(maxim)28(um)-334(op)-27(eration.)]TJ 3.535 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -71.51 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-326(as)-1(:)-441(an)-326(in)27(teger)-326(or)-327(real)-327(v)56(ariable,)-328(whic)28(h)-327(ma)28(y)-327(b)-28(e)-327(a)-327(scalar,)-328(or)-326(a)-327(rank)]TJ 0 -11.955 Td [(1)-333(or)-334(2)-333(arra)28(y)83(.)-778(T)28(yp)-28(e,)-333(kind,)-333(rank)-333(and)-334(size)-333(m)28(ust)-334(agree)-333(on)-333(all)-334(pro)-27(cess)-1(es.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ 0 g 0 G /F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ 0 g 0 G - [-500(This)-402(subroutine)-403(implies)-402(a)-402(s)-1(yn)1(c)27(hronization,)-419(but)-403(onl)1(y)-403(b)-28(et)28(w)28(een)-403(the)-402(calling)]TJ 12.73 -11.955 Td [(pro)-28(cess)-333(and)-333(the)-334(source)-333(pro)-28(cess)]TJ/F11 9.9626 Tf 136.516 0 Td [(sr)-28(c)]TJ/F8 9.9626 Tf 13.753 0 Td [(.)]TJ + [-500(The)]TJ/F30 9.9626 Tf 32.469 0 Td [(dat)]TJ/F8 9.9626 Tf 18.273 0 Td [(argumen)28(t)-259(is)-259(b)-28(oth)-259(input)-259(and)-259(output,)-274(and)-259(its)-259(v)55(alue)-259(ma)28(y)-259(b)-28(e)-259(c)28(hanged)]TJ -38.012 -11.956 Td [(ev)28(en)-334(on)-333(pro)-28(cesses)-333(di\013eren)28(t)-334(from)-333(the)-333(\014nal)-334(result)-333(destination.)]TJ +0 g 0 G + -12.73 -19.925 Td [(2.)]TJ +0 g 0 G + [-500(The)]TJ/F30 9.9626 Tf 33.209 0 Td [(dat)]TJ/F8 9.9626 Tf 19.012 0 Td [(argumen)28(t)-333(m)-1(a)28(y)-333(also)-333(b)-28(e)-334(a)-333(long)-333(in)28(teger)-334(scalar.)]TJ 0 g 0 G - -10.792 -105.147 Td [(115)]TJ + 99.986 -109.132 Td [(113)]TJ 0 g 0 G ET endstream endobj -1597 0 obj +1607 0 obj << -/Length 6407 +/Length 5183 >> stream 0 g 0 G 0 g 0 G BT -/F16 14.3462 Tf 150.705 706.129 Td [(8)-1125(Error)-375(handling)]TJ/F8 9.9626 Tf 0 -21.821 Td [(The)-446(PSBLAS)-446(library)-446(error)-446(handling)-446(p)-28(olicy)-446(has)-446(b)-28(een)-446(completely)-446(rewritten)-446(in)]TJ 0 -11.955 Td [(v)28(ersion)-448(2.0.)-788(The)-448(idea)-448(b)-27(ehind)-448(the)-448(design)-448(of)-447(this)-448(new)-448(error)-448(handling)-447(strategy)]TJ 0 -11.955 Td [(is)-491(to)-492(k)28(eep)-491(error)-491(mes)-1(sages)-491(on)-491(a)-492(stac)28(k)-491(allo)28(wing)-492(th)1(e)-492(user)-491(to)-491(trace)-492(bac)28(k)-491(up)-492(t)1(o)]TJ 0 -11.956 Td [(the)-401(p)-27(oin)28(t)-401(where)-401(the)-400(\014rst)-401(error)-400(mes)-1(sage)-400(has)-401(b)-28(een)-400(generated.)-646(Ev)27(ery)-400(routine)-401(in)]TJ 0 -11.955 Td [(the)-442(P)1(SBLAS-2.0)-442(library)-441(has,)-469(as)-442(l)1(as)-1(t)-441(non-optional)-441(argumen)27(t,)-468(an)-442(in)28(teger)]TJ/F30 9.9626 Tf 322.79 0 Td [(info)]TJ/F8 9.9626 Tf -322.79 -11.955 Td [(v)56(ariable;)-385(whenev)28(er,)-376(inside)-368(the)-367(routine,)-376(an)-368(error)-367(is)-368(detected,)-376(this)-367(v)55(ariab)1(le)-368(is)-368(set)]TJ 0 -11.955 Td [(to)-381(a)-380(v)55(alu)1(e)-381(corresp)-28(onding)-380(to)-381(a)-380(sp)-28(eci\014c)-381(error)-380(co)-28(de.)-586(Then)-381(this)-380(error)-381(co)-28(de)-380(is)-381(also)]TJ 0 -11.955 Td [(pushed)-245(on)-245(the)-245(error)-245(stac)28(k)-245(and)-245(then)-245(either)-245(con)27(tr)1(ol)-245(is)-246(retur)1(ned)-245(to)-246(th)1(e)-246(caller)-245(routin)1(e)]TJ 0 -11.955 Td [(or)-372(the)-371(e)-1(xecution)-371(is)-372(ab)-28(orted,)-381(dep)-28(ending)-372(on)-371(the)-372(users)-372(c)28(hoice.)-560(A)28(t)-372(the)-372(time)-371(when)]TJ 0 -11.956 Td [(the)-364(execution)-363(is)-364(ab)-28(orted,)-371(an)-364(error)-364(message)-363(is)-364(prin)28(ted)-364(on)-364(standard)-363(output)-364(with)]TJ 0 -11.955 Td [(a)-448(lev)28(el)-448(of)-447(v)27(erb)-27(osit)27(y)-447(than)-448(can)-448(b)-27(e)-448(c)28(hosen)-448(b)28(y)-448(the)-448(user.)-787(If)-448(the)-448(execution)-447(is)-448(not)]TJ 0 -11.955 Td [(ab)-28(orted,)-328(then,)-329(the)-328(caller)-327(routine)-328(c)28(hec)28(ks)-328(the)-327(v)55(alue)-327(returned)-328(in)-327(the)]TJ/F30 9.9626 Tf 285.459 0 Td [(info)]TJ/F8 9.9626 Tf 24.185 0 Td [(v)56(ariable)]TJ -309.644 -11.955 Td [(and,)-359(if)-354(not)-354(zero,)-359(an)-353(error)-354(condition)-354(is)-354(raised.)-506(This)-354(pro)-28(cess)-354(con)28(tin)28(ues)-354(on)-354(all)-354(th)1(e)]TJ 0 -11.955 Td [(lev)28(els)-297(of)-296(nes)-1(ted)-296(calls)-297(un)28(til)-297(the)-296(lev)28(el)-297(where)-297(the)-296(user)-297(decides)-297(to)-296(ab)-28(ort)-297(the)-296(program)]TJ 0 -11.955 Td [(execution.)]TJ 14.944 -11.956 Td [(Figure)]TJ -0 0 1 rg 0 0 1 RG - [-353(9)]TJ +/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ +ET +q +1 0 0 1 171.761 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 175.796 706.129 Td [(min)-375(|)-375(Global)-375(minim)31(um)]TJ 0 g 0 G - [-353(sho)28(ws)-353(the)-353(la)28(y)27(out)-353(of)-352(a)-353(ge)-1(n)1(e)-1(ri)1(c)]TJ/F30 9.9626 Tf 170.683 0 Td [(psb_foo)]TJ/F8 9.9626 Tf 40.129 0 Td [(routine)-353(with)-353(resp)-28(ect)-353(to)-353(the)]TJ -225.756 -11.955 Td [(PSBLAS-2.0)-326(error)-326(hand)1(ling)-326(p)-28(olicy)83(.)-442(It)-325(is)-326(p)-28(ossible)-326(to)-326(see)-326(ho)28(w,)-327(whenev)28(e)-1(r)-325(an)-326(error)]TJ 0 -11.955 Td [(condition)-379(is)-378(detected,)-390(the)]TJ/F30 9.9626 Tf 115.439 0 Td [(info)]TJ/F8 9.9626 Tf 24.694 0 Td [(v)56(ariable)-379(is)-379(set)-379(to)-378(the)-379(corresp)-28(onding)-378(error)-379(co)-28(de)]TJ -140.133 -11.955 Td [(whic)28(h)-376(is,)-387(then,)-386(pushed)-376(on)-376(top)-376(of)-376(the)-376(stac)28(k)-376(b)28(y)-376(means)-376(of)-376(the)]TJ/F30 9.9626 Tf 264.702 0 Td [(psb_errpush)]TJ/F8 9.9626 Tf 57.534 0 Td [(.)-572(An)]TJ -322.236 -11.955 Td [(error)-331(condition)-331(ma)28(y)-331(b)-28(e)-331(directly)-331(detected)-331(inside)-331(a)-331(routine)-331(or)-331(indirectly)-331(c)27(h)1(e)-1(c)28(king)]TJ 0 -11.956 Td [(the)-461(e)-1(rr)1(or)-462(co)-28(de)-461(returned)-462(returned)-461(b)28(y)-462(a)-461(called)-462(routine.)-829(Whenev)28(er)-461(an)-462(error)-461(is)]TJ 0 -11.955 Td [(encoun)28(tered,)-459(after)-434(it)-434(has)-433(b)-28(een)-434(pushed)-434(on)-434(stac)28(k,)-459(the)-434(program)-433(execution)-434(skips)]TJ 0 -11.955 Td [(to)-356(a)-356(p)-27(oin)28(t)-356(where)-356(the)-356(error)-355(condition)-356(is)-356(handled;)-367(the)-355(error)-356(condition)-356(is)-356(han)1(dled)]TJ 0 -11.955 Td [(either)-392(b)28(y)-392(returning)-392(con)28(trol)-392(to)-392(the)-392(caller)-391(routine)-392(or)-392(b)28(y)-392(calling)-392(the)]TJ/F30 9.9626 Tf 291.408 0 Td [(psb\134_error)]TJ/F8 9.9626 Tf -291.408 -11.955 Td [(routine)-478(whic)28(h)-479(pr)1(in)27(ts)-478(the)-478(con)28(ten)27(t)-478(of)-478(the)-478(error)-478(s)-1(tac)28(k)-478(and)-478(ab)-28(orts)-478(the)-478(program)]TJ 0 -11.955 Td [(execution,)-329(ac)-1(cord)1(ing)-329(to)-328(the)-329(c)28(hoice)-329(made)-328(b)27(y)-328(the)-329(user)-328(with)]TJ/F30 9.9626 Tf 252.028 0 Td [(psb_set_erraction)]TJ/F8 9.9626 Tf 88.916 0 Td [(.)]TJ -340.944 -11.956 Td [(The)-347(default)-346(is)-347(to)-346(prin)28(t)-347(the)-347(error)-346(and)-347(terminate)-346(the)-347(program,)-350(but)-346(the)-347(user)-346(ma)27(y)]TJ 0 -11.955 Td [(c)28(ho)-28(ose)-333(to)-334(handle)-333(the)-333(error)-334(explicitly)84(.)]TJ 14.944 -11.955 Td [(Figure)]TJ -0 0 1 rg 0 0 1 RG - [-479(10)]TJ 0 g 0 G - [-479(rep)-28(orts)-479(a)-479(sample)-480(error)-479(message)-479(generated)-479(b)28(y)-480(the)-479(PSBLAS-2.0)]TJ -14.944 -11.955 Td [(library)83(.)-451(This)-335(error)-336(has)-335(b)-28(een)-336(generated)-335(b)27(y)-335(the)-336(fact)-335(that)-336(the)-335(use)-1(r)-335(has)-336(c)28(hosen)-336(th)1(e)]TJ 0 -11.955 Td [(in)28(v)55(alid)-367(\134F)28(OO")-368(storage)-367(format)-368(to)-367(represen)27(t)-367(the)-368(sparse)-367(matrix.)-547(F)83(rom)-367(this)-368(error)]TJ 0 -11.955 Td [(message)-248(it)-248(is)-248(p)-27(oss)-1(i)1(ble)-248(to)-248(see)-248(that)-248(the)-248(error)-247(has)-248(b)-28(een)-248(detected)-248(inside)-248(th)1(e)]TJ/F30 9.9626 Tf 301.868 0 Td [(psb_cest)]TJ/F8 9.9626 Tf -301.868 -11.956 Td [(subroutine)-333(called)-334(b)28(y)]TJ/F30 9.9626 Tf 91.407 0 Td [(psb_spasb)]TJ/F8 9.9626 Tf 50.394 0 Td [(...)-444(b)27(y)-333(pro)-28(cess)-333(0)-333(\050i.e.)-445(the)-333(ro)-28(ot)-333(pro)-28(cess\051.)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_min\050icontxt,)-525(dat,)-525(root\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-311(subroutine)-312(implemen)28(ts)-311(a)-312(minim)28(um)-311(v)55(alue)-311(reduction)-312(op)-27(eration)-312(based)-311(on)]TJ -14.944 -11.955 Td [(the)-333(underlying)-333(com)-1(m)28(unication)-333(library)83(.)]TJ +0 g 0 G +/F27 9.9626 Tf 0 -19.926 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G - 22.583 -211.304 Td [(116)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ +0 g 0 G +/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(icon)32(txt)]TJ +0 g 0 G +/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyi)1(ng)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(ariable.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.925 Td [(dat)]TJ +0 g 0 G +/F8 9.9626 Tf 21.371 0 Td [(The)-333(lo)-28(cal)-333(c)-1(on)28(tribution)-333(to)-333(the)-334(gl)1(obal)-334(minim)28(um.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.451 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-326(as:)-442(an)-326(in)27(teger)-326(or)-327(real)-327(v)56(ariable,)-328(whic)28(h)-327(ma)28(y)-327(b)-28(e)-327(a)-326(s)-1(calar,)-328(or)-326(a)-327(rank)]TJ 0 -11.955 Td [(1)-333(or)-334(2)-333(arra)28(y)83(.)-778(T)28(yp)-27(e)-1(,)-333(kind,)-333(rank)-333(and)-334(size)-333(m)28(ust)-334(agree)-333(on)-333(all)-334(pro)-27(cesse)-1(s.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.925 Td [(ro)-32(ot)]TJ +0 g 0 G +/F8 9.9626 Tf 25.93 0 Td [(Pro)-28(cess)-276(to)-276(hold)-276(the)-276(\014nal)-276(v)56(alue,)-287(or)]TJ/F14 9.9626 Tf 146.411 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)-276(to)-276(mak)28(e)-276(it)-276(a)28(v)55(ailable)-276(on)-276(all)-276(pr)1(o)-28(cesses)-1(.)]TJ -155.183 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(alue)]TJ/F14 9.9626 Tf 130.427 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)]TJ/F11 9.9626 Tf 7.749 0 Td [(<)]TJ/F8 9.9626 Tf 7.748 0 Td [(=)]TJ/F11 9.9626 Tf 10.517 0 Td [(r)-28(oot)-278(<)]TJ/F8 9.9626 Tf 28.543 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.963 0 Td [(1,)-333(default)-334(-1.)]TJ +0 g 0 G +/F27 9.9626 Tf -251.325 -33.873 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(dat)]TJ +0 g 0 G +/F8 9.9626 Tf 21.371 0 Td [(On)-333(destination)-334(p)1(ro)-28(cess\050es)-1(\051)1(,)-334(the)-333(result)-333(of)-334(the)-333(minim)28(um)-334(op)-27(eration.)]TJ 3.536 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-326(as:)-442(an)-326(in)27(teger)-326(or)-327(real)-327(v)56(ariable,)-328(whic)28(h)-327(ma)28(y)-327(b)-28(e)-327(a)-326(s)-1(calar,)-328(or)-326(a)-327(rank)]TJ 0 -11.955 Td [(1)-333(or)-334(2)-333(arra)28(y)83(.)]TJ 0 -11.955 Td [(T)28(yp)-28(e,)-333(kind,)-333(rank)-334(and)-333(size)-333(m)27(ust)-333(agree)-333(on)-334(all)-333(pro)-28(cesses.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ +0 g 0 G +/F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ +0 g 0 G + [-500(The)]TJ/F30 9.9626 Tf 32.469 0 Td [(dat)]TJ/F8 9.9626 Tf 18.272 0 Td [(argumen)28(t)-259(is)-259(b)-28(oth)-259(input)-259(and)-259(output,)-274(and)-259(its)-259(v)55(alue)-259(ma)28(y)-259(b)-28(e)-259(c)28(hanged)]TJ -38.011 -11.956 Td [(ev)28(en)-334(on)-333(pro)-28(cesses)-333(di\013eren)28(t)-334(from)-333(the)-333(\014nal)-334(result)-333(destination.)]TJ +0 g 0 G + -12.73 -19.925 Td [(2.)]TJ +0 g 0 G + [-500(The)]TJ/F30 9.9626 Tf 33.208 0 Td [(dat)]TJ/F8 9.9626 Tf 19.012 0 Td [(argumen)28(t)-334(ma)28(y)-333(also)-334(b)-27(e)-334(a)-333(long)-333(in)28(teger)-334(scalar.)]TJ +0 g 0 G + 99.987 -109.132 Td [(114)]TJ 0 g 0 G ET endstream endobj -1603 0 obj +1613 0 obj << -/Length 7220 +/Length 5239 >> stream 0 g 0 G 0 g 0 G -0 g 0 G -0 g 0 G -0 g 0 G -BT -/F53 8.9664 Tf 108.801 680.066 Td [(s)-60(u)-60(b)-60(r)-59(o)-60(u)-60(t)-60(i)-60(n)-60(e)]TJ/F46 8.9664 Tf 61.47 0 Td [(p)-132(s)-132(b)]TJ -ET -q -1 0 0 1 188.254 680.265 cm -[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S -Q -BT -/F46 8.9664 Tf 192.204 680.066 Td [(f)-132(o)-132(o)-241(\050)-155(s)-47(o)-47(m)-47(e)-768(a)-105(r)-106(g)-105(s)-376(,)-939(i)-156(n)-157(f)-156(o)-265(\051)]TJ -65.125 -10.959 Td [(.)-248(.)-249(.)]TJ/F53 8.9664 Tf -0.604 -10.959 Td [(i)-181(f)]TJ/F46 8.9664 Tf 10.408 0 Td [(\050)-260(e)-151(r)-151(r)-151(o)-151(r)-897(d)-129(e)-129(t)-130(e)-129(c)-129(t)-129(e)-130(d)-237(\051)]TJ/F53 8.9664 Tf 93.292 0 Td [(t)-30(h)-29(e)-30(n)]TJ/F46 8.9664 Tf -87.332 -10.959 Td [(i)-156(n)-157(f)-156(o)-65(=)-38(e)-129(r)-128(r)-129(c)-129(o)-129(d)-129(e)-129(1)]TJ/F53 8.9664 Tf -0.133 -10.959 Td [(c)-142(a)-141(l)-142(l)]TJ/F46 8.9664 Tf 27.487 0 Td [(p)-124(s)-124(b)]TJ -ET -q -1 0 0 1 187.956 636.429 cm -[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S -Q BT -/F46 8.9664 Tf 191.831 636.23 Td [(e)-124(r)-124(r)-124(p)-123(u)-124(s)-124(h)-233(\050)-329(')-242(p)-133(s)-132(b)]TJ -ET -q -1 0 0 1 260.135 636.429 cm -[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S -Q -BT -/F46 8.9664 Tf 264.085 636.23 Td [(f)-132(o)-132(o)-353(')-332(,)-855(e)-129(r)-129(r)-129(c)-129(o)-128(d)-129(e)-129(1)-237(\051)]TJ/F53 8.9664 Tf -122.23 -10.959 Td [(g)-46(o)-47(t)-46(o)]TJ/F46 8.9664 Tf 27.968 0 Td [(9)-82(9)-82(9)-83(9)]TJ/F53 8.9664 Tf -44.989 -10.959 Td [(e)2(n)2(d)-796(i)-181(f)]TJ/F46 8.9664 Tf 2.245 -10.959 Td [(.)-248(.)-249(.)]TJ/F53 8.9664 Tf -0.957 -10.959 Td [(c)-142(a)-141(l)-142(l)]TJ/F46 8.9664 Tf 27.399 0 Td [(p)-114(s)-114(b)]TJ +/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ ET q -1 0 0 1 171.016 592.594 cm -[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S +1 0 0 1 120.951 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F46 8.9664 Tf 174.803 592.394 Td [(b)-114(a)-114(r)-223(\050)-155(s)-47(o)-46(m)-47(e)-769(a)-105(r)-105(g)-105(s)-377(,)-938(i)-157(n)-156(f)-157(o)-265(\051)]TJ/F53 8.9664 Tf -48.328 -10.958 Td [(i)-181(f)]TJ/F46 8.9664 Tf 10.408 0 Td [(\050)-265(i)-156(n)-157(f)-156(o)-939(.)]TJ/F53 8.9664 Tf 37.831 0 Td [(n)-11(e)]TJ/F46 8.9664 Tf 12.445 0 Td [(.)-910(z)-127(e)-127(r)-128(o)-235(\051)]TJ/F53 8.9664 Tf 43.016 0 Td [(t)-30(h)-29(e)-30(n)]TJ/F46 8.9664 Tf -87.332 -10.959 Td [(i)-156(n)-157(f)-156(o)-65(=)-38(e)-129(r)-128(r)-129(c)-129(o)-129(d)-129(e)-129(2)]TJ/F53 8.9664 Tf -0.133 -10.959 Td [(c)-142(a)-141(l)-142(l)]TJ/F46 8.9664 Tf 27.487 0 Td [(p)-124(s)-124(b)]TJ -ET -q -1 0 0 1 187.956 559.717 cm -[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S -Q -BT -/F46 8.9664 Tf 191.831 559.518 Td [(e)-124(r)-124(r)-124(p)-123(u)-124(s)-124(h)-233(\050)-329(')-242(p)-133(s)-132(b)]TJ -ET -q -1 0 0 1 260.135 559.717 cm -[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S -Q -BT -/F46 8.9664 Tf 264.085 559.518 Td [(f)-132(o)-132(o)-353(')-332(,)-855(e)-129(r)-129(r)-129(c)-129(o)-128(d)-129(e)-129(2)-237(\051)]TJ/F53 8.9664 Tf -122.23 -10.959 Td [(g)-46(o)-47(t)-46(o)]TJ/F46 8.9664 Tf 27.968 0 Td [(9)-82(9)-82(9)-83(9)]TJ/F53 8.9664 Tf -44.989 -10.959 Td [(e)2(n)2(d)-796(i)-181(f)]TJ/F46 8.9664 Tf 2.245 -10.959 Td [(.)-248(.)-249(.)]TJ -18.078 -10.959 Td [(9)-82(9)-82(9)-83(9)]TJ/F53 8.9664 Tf 27.419 0 Td [(c)-57(o)-57(n)-57(t)-56(i)-57(n)-57(u)-57(e)]TJ -9.945 -10.959 Td [(i)-181(f)]TJ/F46 8.9664 Tf 15.937 0 Td [(\050)-273(e)-164(r)-165(r)]TJ -ET -q -1 0 0 1 164.726 504.923 cm -[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S -Q -BT -/F46 8.9664 Tf 168.965 504.723 Td [(a)-164(c)-165(t)-946(.)]TJ/F53 8.9664 Tf 27.964 0 Td [(e)-22(q)]TJ/F46 8.9664 Tf 12.347 0 Td [(.)-923(a)-141(c)-141(t)]TJ -ET -q -1 0 0 1 236.744 504.923 cm -[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S -Q -BT -/F46 8.9664 Tf 240.772 504.723 Td [(a)-141(b)-141(o)-141(r)-141(t)-249(\051)]TJ/F53 8.9664 Tf 39.166 0 Td [(t)-30(h)-30(e)-29(n)]TJ -142.758 -10.959 Td [(c)-142(a)-141(l)-142(l)]TJ/F46 8.9664 Tf 27.682 0 Td [(p)-146(s)-145(b)]TJ -ET -q -1 0 0 1 183.205 493.964 cm -[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S -Q -BT -/F46 8.9664 Tf 187.274 493.764 Td [(e)-146(r)-145(r)-146(o)-145(r)-254(\050)-252(i)-144(c)-143(o)-144(n)-143(t)-143(x)-144(t)-252(\051)]TJ/F53 8.9664 Tf -50.844 -10.959 Td [(r)-58(e)-58(t)-58(u)-58(r)-58(n)]TJ -10.529 -10.958 Td [(e)-117(l)-117(s)-117(e)]TJ 10.529 -10.959 Td [(r)-58(e)-58(t)-58(u)-58(r)-58(n)]TJ -11.596 -10.959 Td [(e)2(n)2(d)-796(i)-181(f)]TJ -16.587 -21.918 Td [(e)2(n)2(d)-675(s)-59(u)-60(b)-60(r)-60(o)-60(u)-60(t)-60(i)-60(n)-59(e)]TJ/F46 8.9664 Tf 84.141 0 Td [(p)-132(s)-132(b)]TJ -ET -q -1 0 0 1 210.371 428.21 cm -[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S -Q -BT -/F46 8.9664 Tf 214.321 428.011 Td [(f)-132(o)-132(o)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(amx)-375(|)-375(Global)-375(maxim)31(um)-375(absolute)-375(v)63(alue)]TJ 0 g 0 G 0 g 0 G -ET -q -1 0 0 1 99.895 701.884 cm -[]0 d 0 J 0.398 w 0 0 m 346.583 0 l S -Q -q -1 0 0 1 100.095 410.576 cm -[]0 d 0 J 0.398 w 0 0 m 0 291.308 l S -Q -q -1 0 0 1 446.279 410.576 cm -[]0 d 0 J 0.398 w 0 0 m 0 291.308 l S -Q -q -1 0 0 1 99.895 410.576 cm -[]0 d 0 J 0.398 w 0 0 m 346.583 0 l S -Q -BT -/F8 9.9626 Tf 99.895 382.537 Td [(Figure)-329(9:)-443(The)-329(la)27(y)28(out)-329(of)-330(a)-329(generic)]TJ/F30 9.9626 Tf 147.445 0 Td [(psb)]TJ -ET -q -1 0 0 1 263.659 382.736 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 266.797 382.537 Td [(foo)]TJ/F8 9.9626 Tf 18.973 0 Td [(routine)-329(with)-330(resp)-28(ect)-329(to)-330(PS)1(B)-1(LAS)1(-)-1(2.)1(0)]TJ -185.875 -11.955 Td [(error)-333(handling)-333(p)-28(olicy)83(.)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_amx\050icontxt,)-525(dat,)-525(root\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-312(subroutine)-312(implemen)28(ts)-313(a)-312(maxim)28(um)-312(absolute)-312(v)55(alue)-312(reduction)-312(op)-28(eration)]TJ -14.944 -11.955 Td [(based)-333(on)-334(the)-333(underlying)-333(comm)28(unication)-334(library)84(.)]TJ 0 g 0 G +/F27 9.9626 Tf 0 -19.926 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G +/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G + 0 -19.925 Td [(icon)32(txt)]TJ 0 g 0 G -/F30 9.9626 Tf 8.369 -39.475 Td [(==========================================================)]TJ 0 -11.955 Td [(Process:)-525(0.)-1050(PSBLAS)-525(Error)-525(\0504010\051)-525(in)-525(subroutine:)-525(df_sample)]TJ 0 -11.955 Td [(Error)-525(from)-525(call)-525(to)-525(subroutine)-525(mat)-525(dist)]TJ 0 -11.955 Td [(==========================================================)]TJ 0 -11.955 Td [(Process:)-525(0.)-1050(PSBLAS)-525(Error)-525(\0504010\051)-525(in)-525(subroutine:)-525(mat_distv)]TJ 0 -11.956 Td [(Error)-525(from)-525(call)-525(to)-525(subroutine)-525(psb_spasb)]TJ 0 -11.955 Td [(==========================================================)]TJ 0 -11.955 Td [(Process:)-525(0.)-1050(PSBLAS)-525(Error)-525(\0504010\051)-525(in)-525(subroutine:)-525(psb_spasb)]TJ 0 -11.955 Td [(Error)-525(from)-525(call)-525(to)-525(subroutine)-525(psb_cest)]TJ 0 -11.955 Td [(==========================================================)]TJ 0 -11.955 Td [(Process:)-525(0.)-1050(PSBLAS)-525(Error)-525(\050136\051)-525(in)-525(subroutine:)-525(psb_cest)]TJ 0 -11.956 Td [(Format)-525(FOO)-525(is)-525(unknown)]TJ 0 -11.955 Td [(==========================================================)]TJ 0 -11.955 Td [(Aborting...)]TJ -ET -q -1 0 0 1 99.895 343.417 cm -[]0 d 0 J 0.398 w 0 0 m 346.583 0 l S -Q -q -1 0 0 1 100.095 165.307 cm -[]0 d 0 J 0.398 w 0 0 m 0 178.111 l S -Q -q -1 0 0 1 446.279 165.307 cm -[]0 d 0 J 0.398 w 0 0 m 0 178.111 l S -Q -q -1 0 0 1 99.895 165.307 cm -[]0 d 0 J 0.398 w 0 0 m 346.583 0 l S -Q -BT -/F8 9.9626 Tf 99.895 137.267 Td [(Figure)-386(10:)-551(A)-386(sample)-386(PSBLAS-2.0)-387(error)-386(message.)-603(Pro)-28(cess)-387(0)-386(detected)-386(an)-387(error)]TJ 0 -11.955 Td [(condition)-333(inside)-334(the)-333(psb)]TJ -ET -q -1 0 0 1 204.658 125.512 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F8 9.9626 Tf 207.647 125.312 Td [(cest)-333(s)-1(u)1(broutine)]TJ +/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyin)1(g)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.925 Td [(dat)]TJ +0 g 0 G +/F8 9.9626 Tf 21.371 0 Td [(The)-333(lo)-28(cal)-334(con)28(tribution)-333(to)-333(the)-334(global)-333(maxim)28(um.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(te)-1(ger,)-341(real)-340(or)-339(complex)-340(v)56(ariable,)-342(whic)28(h)-340(ma)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-464(a)-464(rank)-463(1)-464(or)-464(2)-464(arra)28(y)83(.)-1299(T)28(yp)-28(e,)-497(kind,)-496(rank)-464(and)-463(size)-464(m)27(ust)-463(agree)-464(on)-464(all)]TJ 0 -11.955 Td [(pro)-28(cesses.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.926 Td [(ro)-32(ot)]TJ +0 g 0 G +/F8 9.9626 Tf 25.931 0 Td [(Pro)-28(cess)-276(to)-276(hold)-276(the)-276(\014nal)-275(v)55(alue,)-287(or)]TJ/F14 9.9626 Tf 146.411 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)-276(to)-276(mak)28(e)-276(it)-276(a)28(v)55(ailable)-276(on)-276(all)-276(p)1(ro)-28(cesses.)]TJ -155.184 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue)]TJ/F14 9.9626 Tf 130.428 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)]TJ/F11 9.9626 Tf 7.748 0 Td [(<)]TJ/F8 9.9626 Tf 7.749 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(r)-28(oot)-278(<)]TJ/F8 9.9626 Tf 28.543 0 Td [(=)]TJ/F11 9.9626 Tf 10.517 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.962 0 Td [(1,)-333(default)-334(-1.)]TJ +0 g 0 G +/F27 9.9626 Tf -251.325 -33.873 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G + 0 -19.926 Td [(dat)]TJ +0 g 0 G +/F8 9.9626 Tf 21.372 0 Td [(On)-333(destination)-333(pro)-28(cess\050es\051,)-334(the)-333(result)-333(of)-334(the)-333(maxim)28(um)-334(op)-27(eration.)]TJ 3.535 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -71.51 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(te)-1(ger,)-341(real)-340(or)-339(complex)-340(v)56(ariable,)-342(whic)28(h)-340(ma)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-464(a)-464(rank)-463(1)-464(or)-464(2)-464(arra)28(y)83(.)-1299(T)28(yp)-28(e,)-497(kind,)-496(rank)-464(and)-463(size)-464(m)27(ust)-463(agree)-464(on)-464(all)]TJ 0 -11.956 Td [(pro)-28(cesses.)]TJ/F16 11.9552 Tf -24.907 -21.917 Td [(Notes)]TJ 0 g 0 G +/F8 9.9626 Tf 12.177 -19.926 Td [(1.)]TJ +0 g 0 G + [-500(The)]TJ/F30 9.9626 Tf 32.469 0 Td [(dat)]TJ/F8 9.9626 Tf 18.273 0 Td [(argumen)28(t)-259(is)-259(b)-28(oth)-259(input)-259(and)-259(output,)-274(and)-259(its)-259(v)55(alue)-259(ma)28(y)-259(b)-28(e)-259(c)28(hanged)]TJ -38.012 -11.955 Td [(ev)28(en)-334(on)-333(pro)-28(cesses)-333(di\013eren)28(t)-334(from)-333(the)-333(\014nal)-334(result)-333(destination.)]TJ +0 g 0 G + -12.73 -19.925 Td [(2.)]TJ +0 g 0 G + [-500(The)]TJ/F30 9.9626 Tf 33.209 0 Td [(dat)]TJ/F8 9.9626 Tf 19.012 0 Td [(argumen)28(t)-333(m)-1(a)28(y)-333(also)-333(b)-28(e)-334(a)-333(long)-333(in)28(teger)-334(scalar.)]TJ 0 g 0 G - 56.632 -34.874 Td [(117)]TJ + 99.986 -97.177 Td [(115)]TJ 0 g 0 G ET endstream endobj -1633 0 obj +1620 0 obj << -/Length 3723 +/Length 5273 >> stream 0 g 0 G 0 g 0 G -0 g 0 G -0 g 0 G -BT -/F16 14.3462 Tf 150.705 680.226 Td [(psb)]TJ -ET -q -1 0 0 1 175.972 680.425 cm -[]0 d 0 J 0.398 w 0 0 m 4.842 0 l S -Q -BT -/F16 14.3462 Tf 180.814 680.226 Td [(errpush|Pushes)-375(an)-375(error)-375(co)-31(de)-375(on)31(to)-375(the)]TJ -30.109 -17.933 Td [(error)-375(stac)31(k)]TJ/F27 9.9626 Tf 1.377 -35.768 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.711 0 Td [(p)-120(s)-121(b)]TJ -ET -q -1 0 0 1 200.991 626.724 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F8 9.9626 Tf 205.18 626.525 Td [(e)-120(r)-121(r)-120(p)-121(u)-120(s)-121(h)-226(\050)-244(e)-138(r)-138(r)]TJ -ET -q -1 0 0 1 270.664 626.724 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F8 9.9626 Tf 275.03 626.525 Td [(c)-438(,)-825(r)]TJ -ET -q -1 0 0 1 299.951 626.724 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F8 9.9626 Tf 303.581 626.525 Td [(n)-64(a)-65(m)-64(e)-290(,)-923(i)]TJ -ET -q -1 0 0 1 348.584 626.724 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q BT -/F8 9.9626 Tf 353.187 626.525 Td [(e)-162(r)-162(r)-485(,)-914(a)]TJ +/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ ET q -1 0 0 1 392.442 626.724 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 171.761 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F8 9.9626 Tf 396.945 626.525 Td [(e)-152(r)-152(r)-258(\051)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(amn)-375(|)-375(Global)-375(minim)31(um)-375(absolute)-375(v)63(alue)]TJ 0 g 0 G 0 g 0 G +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_amn\050icontxt,)-525(dat,)-525(root\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-336(subroutine)-337(implemen)28(ts)-337(a)-336(minim)28(um)-337(absolute)-336(v)55(al)1(ue)-337(reduction)-336(op)-28(eration)]TJ -14.944 -11.955 Td [(based)-333(on)-334(the)-333(underlying)-333(comm)28(unication)-334(library)84(.)]TJ 0 g 0 G -/F27 9.9626 Tf -246.24 -17.933 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf 0 -19.926 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G /F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.926 Td [(err)]TJ -ET -q -1 0 0 1 166.08 568.941 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 169.517 568.741 Td [(c)]TJ + 0 -19.925 Td [(icon)32(txt)]TJ 0 g 0 G -/F8 9.9626 Tf 10.074 0 Td [(the)-333(error)-334(co)-27(de)]TJ -3.98 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger.)]TJ +/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyi)1(ng)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(ariable.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -19.926 Td [(r)]TJ -ET -q -1 0 0 1 156.111 501.195 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 159.548 500.995 Td [(name)]TJ +/F27 9.9626 Tf -24.907 -19.925 Td [(dat)]TJ 0 g 0 G -/F8 9.9626 Tf 31.714 0 Td [(the)-333(soutine)-334(where)-333(the)-333(error)-334(has)-333(b)-28(een)-333(caugh)28(t.)]TJ -15.651 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(string.)]TJ +/F8 9.9626 Tf 21.371 0 Td [(The)-333(lo)-28(cal)-333(c)-1(on)28(tribution)-333(to)-333(the)-334(gl)1(obal)-334(minim)28(um.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.451 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(tege)-1(r,)-341(real)-339(or)-340(complex)-340(v)56(ariable,)-342(whic)28(h)-339(m)-1(a)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-464(a)-464(ran)1(k)-464(1)-464(or)-464(2)-464(arra)28(y)83(.)-1299(T)28(yp)-28(e,)-497(kind)1(,)-497(rank)-464(and)-463(size)-464(m)27(ust)-463(agree)-464(on)-464(all)]TJ 0 -11.955 Td [(pro)-28(cesses.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -31.881 Td [(i)]TJ -ET -q -1 0 0 1 154.575 421.494 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 158.012 421.294 Td [(err)]TJ +/F27 9.9626 Tf -24.907 -19.926 Td [(ro)-32(ot)]TJ 0 g 0 G -/F8 9.9626 Tf 19.669 0 Td [(addional)-333(info)-333(for)-334(error)-333(co)-28(de)]TJ -2.07 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)]TJ +/F8 9.9626 Tf 25.93 0 Td [(Pro)-28(cess)-276(to)-276(hold)-276(the)-276(\014nal)-276(v)56(alue,)-287(or)]TJ/F14 9.9626 Tf 146.411 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)-276(to)-276(mak)28(e)-276(it)-276(a)28(v)55(ailable)-276(on)-276(all)-276(pr)1(o)-28(cesses)-1(.)]TJ -155.183 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(alue)]TJ/F14 9.9626 Tf 130.427 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)]TJ/F11 9.9626 Tf 7.749 0 Td [(<)]TJ/F8 9.9626 Tf 7.748 0 Td [(=)]TJ/F11 9.9626 Tf 10.517 0 Td [(r)-28(oot)-278(<)]TJ/F8 9.9626 Tf 28.543 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.963 0 Td [(1,)-333(default)-334(-1.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -31.881 Td [(a)]TJ -ET -q -1 0 0 1 156.962 353.748 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 160.399 353.548 Td [(err)]TJ +/F27 9.9626 Tf -251.325 -33.873 Td [(On)-383(Return)]TJ 0 g 0 G -/F8 9.9626 Tf 19.669 0 Td [(addional)-333(info)-333(for)-334(error)-333(co)-28(de)]TJ -4.457 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(string.)]TJ 0 g 0 G - 139.477 -227.245 Td [(118)]TJ + 0 -19.926 Td [(dat)]TJ +0 g 0 G +/F8 9.9626 Tf 21.371 0 Td [(On)-333(destination)-334(p)1(ro)-28(cess\050es)-1(\051)1(,)-334(the)-333(result)-333(of)-334(the)-333(minim)28(um)-334(op)-27(eration.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(tege)-1(r,)-341(real)-339(or)-340(complex)-340(v)56(ariable,)-342(whic)28(h)-339(m)-1(a)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-333(a)-334(rank)-333(1)-333(or)-333(2)-334(arra)28(y)83(.)]TJ 0 -11.956 Td [(T)28(yp)-28(e,)-333(kind,)-333(rank)-334(and)-333(size)-333(m)27(ust)-333(agree)-333(on)-334(all)-333(pro)-28(cesses.)]TJ/F16 11.9552 Tf -24.907 -21.917 Td [(Notes)]TJ +0 g 0 G +/F8 9.9626 Tf 12.177 -19.926 Td [(1.)]TJ +0 g 0 G + [-500(The)]TJ/F30 9.9626 Tf 32.469 0 Td [(dat)]TJ/F8 9.9626 Tf 18.272 0 Td [(argumen)28(t)-259(is)-259(b)-28(oth)-259(input)-259(and)-259(output,)-274(and)-259(its)-259(v)55(alue)-259(ma)28(y)-259(b)-28(e)-259(c)28(hanged)]TJ -38.011 -11.955 Td [(ev)28(en)-334(on)-333(pro)-28(cesses)-333(di\013eren)28(t)-334(from)-333(the)-333(\014nal)-334(result)-333(destination.)]TJ +0 g 0 G + -12.73 -19.925 Td [(2.)]TJ +0 g 0 G + [-500(The)]TJ/F30 9.9626 Tf 33.208 0 Td [(dat)]TJ/F8 9.9626 Tf 19.012 0 Td [(argumen)28(t)-334(ma)28(y)-333(also)-334(b)-27(e)-334(a)-333(long)-333(in)28(teger)-334(scalar.)]TJ +0 g 0 G + 99.987 -97.177 Td [(116)]TJ 0 g 0 G ET endstream endobj -1639 0 obj +1626 0 obj << -/Length 1398 +/Length 6189 >> stream 0 g 0 G 0 g 0 G -0 g 0 G -0 g 0 G -BT -/F16 14.3462 Tf 99.895 680.226 Td [(psb)]TJ -ET -q -1 0 0 1 125.163 680.425 cm -[]0 d 0 J 0.398 w 0 0 m 4.842 0 l S -Q BT -/F16 14.3462 Tf 130.004 680.226 Td [(error|Prin)31(ts)-375(the)-375(error)-375(stac)32(k)-375(con)31(ten)31(t)-375(and)]TJ -30.109 -17.933 Td [(ab)-31(orts)-375(execution)]TJ/F27 9.9626 Tf 1.377 -35.768 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.921 0 Td [(p)-141(s)-142(b)]TJ +/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ ET q -1 0 0 1 151.02 626.724 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 120.951 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F8 9.9626 Tf 155.418 626.525 Td [(e)-142(r)-141(r)-142(o)-141(r)-247(\050)-245(i)-140(c)-139(o)-140(n)-140(t)-139(x)-140(t)-245(\051)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(nrm2)-375(|)-375(Global)-375(2-norm)-375(reduction)]TJ 0 g 0 G 0 g 0 G +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_nrm2\050icontxt,)-525(dat,)-525(root\051)]TJ/F8 9.9626 Tf 14.944 -19.604 Td [(This)-425(subroutine)-426(imp)1(le)-1(men)28(ts)-425(a)-425(2-norm)-426(v)56(alue)-425(reduction)-426(op)-27(eration)-426(based)-425(on)]TJ -14.944 -11.955 Td [(the)-333(underlying)-334(comm)28(unication)-333(library)83(.)]TJ 0 g 0 G -/F27 9.9626 Tf -55.523 -17.933 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf 0 -18.074 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -33.797 -19 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.926 Td [(icon)32(txt)]TJ + 0 -19 Td [(icon)32(txt)]TJ 0 g 0 G -/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger.)]TJ +/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyin)1(g)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable.)]TJ 0 g 0 G - 139.477 -430.483 Td [(119)]TJ +/F27 9.9626 Tf -24.907 -19 Td [(dat)]TJ 0 g 0 G -ET - -endstream -endobj -1645 0 obj -<< -/Length 1632 ->> -stream +/F8 9.9626 Tf 21.371 0 Td [(The)-333(lo)-28(cal)-334(con)28(tribution)-333(to)-333(the)-334(global)-333(minim)28(um.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-421(as:)-619(a)-421(real)-421(v)55(ariable,)-443(whic)28(h)-421(ma)28(y)-421(b)-28(e)-421(a)-421(scalar,)-443(or)-421(a)-420(rank)-421(1)-421(arra)28(y)83(.)]TJ 0 -11.955 Td [(Kind,)-333(rank)-333(and)-334(size)-333(m)28(ust)-334(agree)-333(on)-333(all)-334(pro)-27(ce)-1(sses.)]TJ 0 g 0 G +/F27 9.9626 Tf -24.907 -19 Td [(ro)-32(ot)]TJ 0 g 0 G +/F8 9.9626 Tf 25.931 0 Td [(Pro)-28(cess)-276(to)-276(hold)-276(the)-276(\014nal)-275(v)55(alue,)-287(or)]TJ/F14 9.9626 Tf 146.411 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)-276(to)-276(mak)28(e)-276(it)-276(a)28(v)55(ailable)-276(on)-276(all)-276(p)1(ro)-28(cesses.)]TJ -155.184 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue)]TJ/F14 9.9626 Tf 130.428 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1)]TJ/F11 9.9626 Tf 7.748 0 Td [(<)]TJ/F8 9.9626 Tf 7.749 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(r)-28(oot)-278(<)]TJ/F8 9.9626 Tf 28.543 0 Td [(=)]TJ/F11 9.9626 Tf 10.517 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.962 0 Td [(1,)-333(default)-334(-1.)]TJ 0 g 0 G +/F27 9.9626 Tf -251.325 -31.559 Td [(On)-383(Return)]TJ 0 g 0 G -BT -/F16 14.3462 Tf 150.705 680.226 Td [(psb)]TJ +0 g 0 G + 0 -19 Td [(dat)]TJ +0 g 0 G +/F8 9.9626 Tf 21.372 0 Td [(On)-333(destination)-333(pro)-28(cess\050es\051,)-334(the)-333(result)-333(of)-334(the)-333(2-norm)-333(reduction.)]TJ 3.535 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -71.51 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(real)-333(v)55(ariable,)-333(whic)28(h)-333(ma)27(y)-333(b)-28(e)-333(a)-333(sc)-1(alar)1(,)-334(or)-333(a)-333(rank)-334(1)-333(arra)28(y)83(.)]TJ 0 -11.955 Td [(Kind,)-333(rank)-333(and)-334(size)-333(m)28(ust)-334(agree)-333(on)-333(all)-334(pro)-27(ce)-1(sses.)]TJ/F16 11.9552 Tf -24.907 -19.603 Td [(Notes)]TJ +0 g 0 G +/F8 9.9626 Tf 12.177 -18.075 Td [(1.)]TJ +0 g 0 G + [-500(This)-416(reduction)-416(is)-416(appropriate)-416(to)-416(compute)-416(the)-417(results)-416(of)-416(m)28(ultiple)-416(\050lo)-28(cal\051)]TJ 12.73 -11.955 Td [(NRM2)-333(op)-28(erations)-333(at)-334(the)-333(same)-334(ti)1(m)-1(e.)]TJ +0 g 0 G + -12.73 -18.999 Td [(2.)]TJ +0 g 0 G + [-500(Denoting)-283(b)28(y)]TJ/F11 9.9626 Tf 68.601 0 Td [(dat)]TJ/F10 6.9738 Tf 14.05 -1.495 Td [(i)]TJ/F8 9.9626 Tf 6.138 1.495 Td [(the)-283(v)55(alue)-283(of)-283(the)-283(v)55(ariable)]TJ/F11 9.9626 Tf 106.29 0 Td [(dat)]TJ/F8 9.9626 Tf 16.87 0 Td [(on)-283(pro)-28(cess)]TJ/F11 9.9626 Tf 47.57 0 Td [(i)]TJ/F8 9.9626 Tf 3.432 0 Td [(,)-293(the)-283(output)]TJ/F11 9.9626 Tf 54.503 0 Td [(r)-28(es)]TJ/F8 9.9626 Tf -304.724 -11.956 Td [(is)-333(equiv)55(alen)28(t)-333(to)-334(the)-333(computation)-333(of)]TJ/F11 9.9626 Tf 122.071 -25.714 Td [(r)-28(es)]TJ/F8 9.9626 Tf 16.847 0 Td [(=)]TJ/F1 9.9626 Tf 10.516 14.335 Td [(s)]TJ ET q -1 0 0 1 175.972 680.425 cm -[]0 d 0 J 0.398 w 0 0 m 4.842 0 l S +1 0 0 1 284.199 204.589 cm +[]0 d 0 J 0.398 w 0 0 m 34.569 0 l S Q BT -/F16 14.3462 Tf 180.814 680.226 Td [(set)]TJ +/F1 9.9626 Tf 284.199 199.519 Td [(X)]TJ/F10 6.9738 Tf 5.786 -21.219 Td [(i)]TJ/F11 9.9626 Tf 10.265 11.754 Td [(dat)]TJ/F7 6.9738 Tf 14.049 3.432 Td [(2)]TJ/F10 6.9738 Tf 0 -6.209 Td [(i)]TJ/F11 9.9626 Tf 4.469 2.777 Td [(;)]TJ/F8 9.9626 Tf -193.966 -30.717 Td [(with)-333(care)-334(tak)28(en)-333(to)-334(a)28(v)28(oid)-333(unnecessary)-334(o)28(v)28(er\015o)28(w.)]TJ +0 g 0 G + -12.73 -19 Td [(3.)]TJ +0 g 0 G + [-500(The)]TJ/F30 9.9626 Tf 32.469 0 Td [(dat)]TJ/F8 9.9626 Tf 18.273 0 Td [(argumen)28(t)-259(is)-259(b)-28(oth)-259(input)-259(and)-259(output,)-274(and)-259(its)-259(v)55(alue)-259(ma)28(y)-259(b)-28(e)-259(c)28(hanged)]TJ -38.012 -11.955 Td [(ev)28(en)-334(on)-333(pro)-28(cesses)-333(di\013eren)28(t)-334(from)-333(the)-333(\014nal)-334(result)-333(destination.)]TJ +0 g 0 G + 139.477 -37.944 Td [(117)]TJ +0 g 0 G ET -q -1 0 0 1 201.789 680.425 cm -[]0 d 0 J 0.398 w 0 0 m 4.842 0 l S -Q + +endstream +endobj +1634 0 obj +<< +/Length 5369 +>> +stream +0 g 0 G +0 g 0 G BT -/F16 14.3462 Tf 206.631 680.226 Td [(errv)31(erb)-31(osit)31(y|Sets)-375(the)-375(v)31(erb)-31(osit)32(y)-376(of)-375(error)]TJ -55.926 -17.933 Td [(messages.)]TJ/F27 9.9626 Tf 1.377 -35.768 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 30.082 0 Td [(p)-158(s)-157(b)]TJ +/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ ET q -1 0 0 1 202.473 626.724 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 171.761 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F8 9.9626 Tf 207.032 626.525 Td [(s)-158(e)-157(t)]TJ +/F16 11.9552 Tf 175.796 706.129 Td [(snd)-375(|)-375(Send)-375(data)]TJ +0 g 0 G +0 g 0 G +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_snd\050icontxt,)-525(dat,)-525(dst,)-525(m\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-333(subroutine)-334(sends)-333(a)-333(pac)28(k)27(et)-333(of)-333(data)-334(to)-333(a)-333(destination.)]TJ +0 g 0 G +/F27 9.9626 Tf -14.944 -19.926 Td [(T)32(yp)-32(e:)]TJ +0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous:)-444(s)-1(ee)-333(usage)-333(notes.)]TJ +0 g 0 G +/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(icon)32(txt)]TJ +0 g 0 G +/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyi)1(ng)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.134 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(ariable.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.925 Td [(dat)]TJ +0 g 0 G +/F8 9.9626 Tf 21.371 0 Td [(The)-333(data)-334(to)-333(b)-28(e)-333(sen)28(t.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.451 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(tege)-1(r,)-341(real)-339(or)-340(complex)-340(v)56(ariable,)-342(whic)28(h)-339(m)-1(a)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-381(a)-381(rank)-381(1)-381(or)-381(2)-381(arra)28(y)83(,)-393(or)-381(a)-381(c)28(haracte)-1(r)-381(or)-381(logical)-381(scalar.)-968(T)27(yp)-27(e,)-393(kind)-381(and)]TJ 0 -11.955 Td [(rank)-327(m)27(ust)-327(agree)-328(on)-327(sender)-328(and)-327(receiv)28(e)-1(r)-327(pro)-28(cess;)-329(if)]TJ/F11 9.9626 Tf 220.724 0 Td [(m)]TJ/F8 9.9626 Tf 12.01 0 Td [(is)-328(n)1(o)-1(t)-327(sp)-28(eci\014ed,)-328(s)-1(ize)]TJ -232.734 -11.955 Td [(m)28(ust)-334(agree)-333(as)-333(w)27(ell.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.926 Td [(dst)]TJ +0 g 0 G +/F8 9.9626 Tf 20.321 0 Td [(Destination)-333(pro)-28(cess.)]TJ 4.586 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-1(n)-333(in)28(teger)-333(v)55(alue)-333(0)]TJ/F11 9.9626 Tf 138.176 0 Td [(<)]TJ/F8 9.9626 Tf 7.749 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(dst)-278(<)]TJ/F8 9.9626 Tf 23.969 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.963 0 Td [(1.)]TJ +0 g 0 G +/F27 9.9626 Tf -239.002 -31.881 Td [(m)]TJ +0 g 0 G +/F8 9.9626 Tf 14.529 0 Td [(Num)28(b)-28(er)-333(of)-334(ro)28(ws.)]TJ 10.378 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(global)]TJ/F8 9.9626 Tf 29.757 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(Optional)]TJ/F8 9.9626 Tf 43.455 0 Td [(.)]TJ -73.066 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue)-333(0)]TJ/F11 9.9626 Tf 138.176 0 Td [(<)]TJ/F8 9.9626 Tf 7.749 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(m)-278(<)]TJ/F8 9.9626 Tf 19.263 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(siz)-44(e)]TJ/F8 9.9626 Tf 17.813 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(dat;)]TJ/F8 9.9626 Tf 18.477 0 Td [(1\051.)]TJ -226.384 -11.956 Td [(When)]TJ/F11 9.9626 Tf 29.071 0 Td [(dat)]TJ/F8 9.9626 Tf 17.383 0 Td [(is)-335(a)-334(rank)-335(2)-335(arra)28(y)84(,)-335(sp)-28(eci\014es)-335(the)-335(n)28(um)28(b)-28(er)-334(of)-335(ro)28(ws)-335(to)-335(b)-27(e)-335(sen)28(t)-335(inde-)]TJ -46.454 -11.955 Td [(p)-28(enden)28(tly)-285(of)-285(the)-286(leadin)1(g)-286(dimension)]TJ/F11 9.9626 Tf 153.741 0 Td [(siz)-44(e)]TJ/F8 9.9626 Tf 17.813 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(dat;)]TJ/F8 9.9626 Tf 18.477 0 Td [(1\051;)-301(m)27(u)1(s)-1(t)-285(ha)28(v)28(e)-285(the)-286(same)-285(v)55(al)1(ue)]TJ -193.905 -11.955 Td [(on)-333(sending)-334(and)-333(receiving)-333(pro)-28(cesses.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -21.918 Td [(On)-383(Return)]TJ +0 g 0 G +/F16 11.9552 Tf 0 -21.918 Td [(Notes)]TJ +0 g 0 G +/F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ +0 g 0 G + [-500(This)-402(subroutine)-403(implies)-402(a)-402(sync)27(hronization,)-419(but)-403(on)1(ly)-403(b)-28(et)28(w)28(een)-403(th)1(e)-403(calling)]TJ 12.73 -11.955 Td [(pro)-28(cess)-333(and)-333(the)-334(destination)-333(pro)-28(cess)]TJ/F11 9.9626 Tf 157.52 0 Td [(dst)]TJ/F8 9.9626 Tf 13.453 0 Td [(.)]TJ +0 g 0 G + -31.496 -105.147 Td [(118)]TJ +0 g 0 G +ET + +endstream +endobj +1639 0 obj +<< +/Length 5352 +>> +stream +0 g 0 G +0 g 0 G +BT +/F16 11.9552 Tf 99.895 706.129 Td [(psb)]TJ ET q -1 0 0 1 224.574 626.724 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 120.951 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F8 9.9626 Tf 229.133 626.525 Td [(e)-158(r)-157(r)-158(v)-158(e)-157(r)-158(b)-157(o)-158(s)-158(i)-157(t)-158(y)-263(\050)-142(v)-142(\051)]TJ +/F16 11.9552 Tf 124.986 706.129 Td [(rcv)-375(|)-375(Receiv)31(e)-375(data)]TJ 0 g 0 G 0 g 0 G +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_rcv\050icontxt,)-525(dat,)-525(src,)-525(m\051)]TJ/F8 9.9626 Tf 14.944 -21.918 Td [(This)-333(subroutine)-334(receiv)28(es)-333(a)-334(pac)28(k)28(et)-333(of)-334(data)-333(to)-333(a)-334(destination.)]TJ 0 g 0 G -/F27 9.9626 Tf -78.428 -17.933 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf -14.944 -19.926 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous:)-445(see)-333(usage)-333(notes.)]TJ 0 g 0 G /F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.926 Td [(v)]TJ + 0 -19.925 Td [(icon)32(txt)]TJ 0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(the)-333(v)27(erb)-27(osit)27(y)-333(lev)28(el)]TJ 13.878 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger.)]TJ +/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text)-333(iden)27(tifyin)1(g)-334(the)-333(virtual)-333(parallel)-334(mac)28(hine.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.925 Td [(src)]TJ +0 g 0 G +/F8 9.9626 Tf 19.311 0 Td [(Source)-333(pro)-28(cess.)]TJ 5.596 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue)-333(0)]TJ/F11 9.9626 Tf 138.176 0 Td [(<)]TJ/F8 9.9626 Tf 7.749 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(sr)-28(c)-277(<)]TJ/F8 9.9626 Tf 24.269 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(np)]TJ/F14 9.9626 Tf 13.206 0 Td [(\000)]TJ/F8 9.9626 Tf 9.963 0 Td [(1.)]TJ +0 g 0 G +/F27 9.9626 Tf -239.302 -31.88 Td [(m)]TJ +0 g 0 G +/F8 9.9626 Tf 14.529 0 Td [(Num)28(b)-28(er)-333(of)-334(ro)28(ws.)]TJ 10.378 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -62.135 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(Optional)]TJ/F8 9.9626 Tf 43.455 0 Td [(.)]TJ -73.066 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue)-333(0)]TJ/F11 9.9626 Tf 138.176 0 Td [(<)]TJ/F8 9.9626 Tf 7.749 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(m)-278(<)]TJ/F8 9.9626 Tf 19.264 0 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(siz)-44(e)]TJ/F8 9.9626 Tf 17.812 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(dat;)]TJ/F8 9.9626 Tf 18.477 0 Td [(1\051.)]TJ -226.384 -11.955 Td [(When)]TJ/F11 9.9626 Tf 29.071 0 Td [(dat)]TJ/F8 9.9626 Tf 17.383 0 Td [(is)-335(a)-334(rank)-335(2)-335(arra)28(y)84(,)-335(sp)-28(eci\014es)-335(the)-335(n)28(um)28(b)-28(er)-334(of)-335(ro)28(ws)-335(to)-335(b)-27(e)-335(sen)28(t)-335(inde-)]TJ -46.454 -11.955 Td [(p)-28(enden)28(tly)-285(of)-285(the)-286(leading)-285(dimension)]TJ/F11 9.9626 Tf 153.742 0 Td [(siz)-44(e)]TJ/F8 9.9626 Tf 17.812 0 Td [(\050)]TJ/F11 9.9626 Tf 3.874 0 Td [(dat;)]TJ/F8 9.9626 Tf 18.477 0 Td [(1\051;)-301(m)27(ust)-285(ha)28(v)28(e)-285(the)-286(same)-285(v)55(alu)1(e)]TJ -193.905 -11.955 Td [(on)-333(sending)-334(and)-333(receiving)-333(pro)-28(cesses.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -21.918 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G + 0 -19.926 Td [(dat)]TJ 0 g 0 G - 139.477 -430.483 Td [(120)]TJ +/F8 9.9626 Tf 21.371 0 Td [(The)-333(data)-334(to)-333(b)-28(e)-333(receiv)28(ed.)]TJ 3.536 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -71.509 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-339(as:)-458(an)-339(in)28(te)-1(ger,)-341(real)-340(or)-339(complex)-340(v)56(ariable,)-342(whic)28(h)-340(ma)28(y)-339(b)-28(e)-340(a)-340(scalar,)]TJ 0 -11.955 Td [(or)-381(a)-381(rank)-381(1)-381(or)-381(2)-381(arra)27(y)84(,)-393(or)-381(a)-381(c)27(har)1(ac)-1(ter)-381(or)-381(logical)-381(scalar.)-969(T)28(yp)-27(e)-1(,)-393(ki)1(nd)-381(and)]TJ 0 -11.956 Td [(rank)-327(m)27(ust)-327(agree)-328(on)-327(sender)-328(and)-327(receiv)27(er)-327(pro)-28(cess;)-329(if)]TJ/F11 9.9626 Tf 220.724 0 Td [(m)]TJ/F8 9.9626 Tf 12.01 0 Td [(is)-328(not)-327(sp)-28(eci\014ed,)-329(size)]TJ -232.734 -11.955 Td [(m)28(ust)-334(agree)-333(as)-333(w)27(ell.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ +0 g 0 G +/F8 9.9626 Tf 12.177 -19.925 Td [(1.)]TJ +0 g 0 G + [-500(This)-402(subroutine)-403(implies)-402(a)-402(s)-1(yn)1(c)27(hronization,)-419(but)-403(onl)1(y)-403(b)-28(et)28(w)28(een)-403(the)-402(calling)]TJ 12.73 -11.955 Td [(pro)-28(cess)-333(and)-333(the)-334(source)-333(pro)-28(cess)]TJ/F11 9.9626 Tf 136.516 0 Td [(sr)-28(c)]TJ/F8 9.9626 Tf 13.753 0 Td [(.)]TJ +0 g 0 G + -10.792 -105.147 Td [(119)]TJ 0 g 0 G ET endstream endobj -1651 0 obj +1646 0 obj << -/Length 2103 +/Length 6407 +>> +stream +0 g 0 G +0 g 0 G +BT +/F16 14.3462 Tf 150.705 706.129 Td [(8)-1125(Error)-375(handling)]TJ/F8 9.9626 Tf 0 -21.821 Td [(The)-446(PSBLAS)-446(library)-446(error)-446(handling)-446(p)-28(olicy)-446(has)-446(b)-28(een)-446(completely)-446(rewritten)-446(in)]TJ 0 -11.955 Td [(v)28(ersion)-448(2.0.)-788(The)-448(idea)-448(b)-27(ehind)-448(the)-448(design)-448(of)-447(this)-448(new)-448(error)-448(handling)-447(strategy)]TJ 0 -11.955 Td [(is)-491(to)-492(k)28(eep)-491(error)-491(mes)-1(sages)-491(on)-491(a)-492(stac)28(k)-491(allo)28(wing)-492(th)1(e)-492(user)-491(to)-491(trace)-492(bac)28(k)-491(up)-492(t)1(o)]TJ 0 -11.956 Td [(the)-401(p)-27(oin)28(t)-401(where)-401(the)-400(\014rst)-401(error)-400(mes)-1(sage)-400(has)-401(b)-28(een)-400(generated.)-646(Ev)27(ery)-400(routine)-401(in)]TJ 0 -11.955 Td [(the)-442(P)1(SBLAS-2.0)-442(library)-441(has,)-469(as)-442(l)1(as)-1(t)-441(non-optional)-441(argumen)27(t,)-468(an)-442(in)28(teger)]TJ/F30 9.9626 Tf 322.79 0 Td [(info)]TJ/F8 9.9626 Tf -322.79 -11.955 Td [(v)56(ariable;)-385(whenev)28(er,)-376(inside)-368(the)-367(routine,)-376(an)-368(error)-367(is)-368(detected,)-376(this)-367(v)55(ariab)1(le)-368(is)-368(set)]TJ 0 -11.955 Td [(to)-381(a)-380(v)55(alu)1(e)-381(corresp)-28(onding)-380(to)-381(a)-380(sp)-28(eci\014c)-381(error)-380(co)-28(de.)-586(Then)-381(this)-380(error)-381(co)-28(de)-380(is)-381(also)]TJ 0 -11.955 Td [(pushed)-245(on)-245(the)-245(error)-245(stac)28(k)-245(and)-245(then)-245(either)-245(con)27(tr)1(ol)-245(is)-246(retur)1(ned)-245(to)-246(th)1(e)-246(caller)-245(routin)1(e)]TJ 0 -11.955 Td [(or)-372(the)-371(e)-1(xecution)-371(is)-372(ab)-28(orted,)-381(dep)-28(ending)-372(on)-371(the)-372(users)-372(c)28(hoice.)-560(A)28(t)-372(the)-372(time)-371(when)]TJ 0 -11.956 Td [(the)-364(execution)-363(is)-364(ab)-28(orted,)-371(an)-364(error)-364(message)-363(is)-364(prin)28(ted)-364(on)-364(standard)-363(output)-364(with)]TJ 0 -11.955 Td [(a)-448(lev)28(el)-448(of)-447(v)27(erb)-27(osit)27(y)-447(than)-448(can)-448(b)-27(e)-448(c)28(hosen)-448(b)28(y)-448(the)-448(user.)-787(If)-448(the)-448(execution)-447(is)-448(not)]TJ 0 -11.955 Td [(ab)-28(orted,)-328(then,)-329(the)-328(caller)-327(routine)-328(c)28(hec)28(ks)-328(the)-327(v)55(alue)-327(returned)-328(in)-327(the)]TJ/F30 9.9626 Tf 285.459 0 Td [(info)]TJ/F8 9.9626 Tf 24.185 0 Td [(v)56(ariable)]TJ -309.644 -11.955 Td [(and,)-359(if)-354(not)-354(zero,)-359(an)-353(error)-354(condition)-354(is)-354(raised.)-506(This)-354(pro)-28(cess)-354(con)28(tin)28(ues)-354(on)-354(all)-354(th)1(e)]TJ 0 -11.955 Td [(lev)28(els)-297(of)-296(nes)-1(ted)-296(calls)-297(un)28(til)-297(the)-296(lev)28(el)-297(where)-297(the)-296(user)-297(decides)-297(to)-296(ab)-28(ort)-297(the)-296(program)]TJ 0 -11.955 Td [(execution.)]TJ 14.944 -11.956 Td [(Figure)]TJ +0 0 1 rg 0 0 1 RG + [-353(9)]TJ +0 g 0 G + [-353(sho)28(ws)-353(the)-353(la)28(y)27(out)-353(of)-352(a)-353(ge)-1(n)1(e)-1(ri)1(c)]TJ/F30 9.9626 Tf 170.683 0 Td [(psb_foo)]TJ/F8 9.9626 Tf 40.129 0 Td [(routine)-353(with)-353(resp)-28(ect)-353(to)-353(the)]TJ -225.756 -11.955 Td [(PSBLAS-2.0)-326(error)-326(hand)1(ling)-326(p)-28(olicy)83(.)-442(It)-325(is)-326(p)-28(ossible)-326(to)-326(see)-326(ho)28(w,)-327(whenev)28(e)-1(r)-325(an)-326(error)]TJ 0 -11.955 Td [(condition)-379(is)-378(detected,)-390(the)]TJ/F30 9.9626 Tf 115.439 0 Td [(info)]TJ/F8 9.9626 Tf 24.694 0 Td [(v)56(ariable)-379(is)-379(set)-379(to)-378(the)-379(corresp)-28(onding)-378(error)-379(co)-28(de)]TJ -140.133 -11.955 Td [(whic)28(h)-376(is,)-387(then,)-386(pushed)-376(on)-376(top)-376(of)-376(the)-376(stac)28(k)-376(b)28(y)-376(means)-376(of)-376(the)]TJ/F30 9.9626 Tf 264.702 0 Td [(psb_errpush)]TJ/F8 9.9626 Tf 57.534 0 Td [(.)-572(An)]TJ -322.236 -11.955 Td [(error)-331(condition)-331(ma)28(y)-331(b)-28(e)-331(directly)-331(detected)-331(inside)-331(a)-331(routine)-331(or)-331(indirectly)-331(c)27(h)1(e)-1(c)28(king)]TJ 0 -11.956 Td [(the)-461(e)-1(rr)1(or)-462(co)-28(de)-461(returned)-462(returned)-461(b)28(y)-462(a)-461(called)-462(routine.)-829(Whenev)28(er)-461(an)-462(error)-461(is)]TJ 0 -11.955 Td [(encoun)28(tered,)-459(after)-434(it)-434(has)-433(b)-28(een)-434(pushed)-434(on)-434(stac)28(k,)-459(the)-434(program)-433(execution)-434(skips)]TJ 0 -11.955 Td [(to)-356(a)-356(p)-27(oin)28(t)-356(where)-356(the)-356(error)-355(condition)-356(is)-356(handled;)-367(the)-355(error)-356(condition)-356(is)-356(han)1(dled)]TJ 0 -11.955 Td [(either)-392(b)28(y)-392(returning)-392(con)28(trol)-392(to)-392(the)-392(caller)-391(routine)-392(or)-392(b)28(y)-392(calling)-392(the)]TJ/F30 9.9626 Tf 291.408 0 Td [(psb\134_error)]TJ/F8 9.9626 Tf -291.408 -11.955 Td [(routine)-478(whic)28(h)-479(pr)1(in)27(ts)-478(the)-478(con)28(ten)27(t)-478(of)-478(the)-478(error)-478(s)-1(tac)28(k)-478(and)-478(ab)-28(orts)-478(the)-478(program)]TJ 0 -11.955 Td [(execution,)-329(ac)-1(cord)1(ing)-329(to)-328(the)-329(c)28(hoice)-329(made)-328(b)27(y)-328(the)-329(user)-328(with)]TJ/F30 9.9626 Tf 252.028 0 Td [(psb_set_erraction)]TJ/F8 9.9626 Tf 88.916 0 Td [(.)]TJ -340.944 -11.956 Td [(The)-347(default)-346(is)-347(to)-346(prin)28(t)-347(the)-347(error)-346(and)-347(terminate)-346(the)-347(program,)-350(but)-346(the)-347(user)-346(ma)27(y)]TJ 0 -11.955 Td [(c)28(ho)-28(ose)-333(to)-334(handle)-333(the)-333(error)-334(explicitly)84(.)]TJ 14.944 -11.955 Td [(Figure)]TJ +0 0 1 rg 0 0 1 RG + [-479(10)]TJ +0 g 0 G + [-479(rep)-28(orts)-479(a)-479(sample)-480(error)-479(message)-479(generated)-479(b)28(y)-480(the)-479(PSBLAS-2.0)]TJ -14.944 -11.955 Td [(library)83(.)-451(This)-335(error)-336(has)-335(b)-28(een)-336(generated)-335(b)27(y)-335(the)-336(fact)-335(that)-336(the)-335(use)-1(r)-335(has)-336(c)28(hosen)-336(th)1(e)]TJ 0 -11.955 Td [(in)28(v)55(alid)-367(\134F)28(OO")-368(storage)-367(format)-368(to)-367(represen)27(t)-367(the)-368(sparse)-367(matrix.)-547(F)83(rom)-367(this)-368(error)]TJ 0 -11.955 Td [(message)-248(it)-248(is)-248(p)-27(oss)-1(i)1(ble)-248(to)-248(see)-248(that)-248(the)-248(error)-247(has)-248(b)-28(een)-248(detected)-248(inside)-248(th)1(e)]TJ/F30 9.9626 Tf 301.868 0 Td [(psb_cest)]TJ/F8 9.9626 Tf -301.868 -11.956 Td [(subroutine)-333(called)-334(b)28(y)]TJ/F30 9.9626 Tf 91.407 0 Td [(psb_spasb)]TJ/F8 9.9626 Tf 50.394 0 Td [(...)-444(b)27(y)-333(pro)-28(cess)-333(0)-333(\050i.e.)-445(the)-333(ro)-28(ot)-333(pro)-28(cess\051.)]TJ +0 g 0 G + 22.583 -211.304 Td [(120)]TJ +0 g 0 G +ET + +endstream +endobj +1652 0 obj +<< +/Length 7220 >> stream 0 g 0 G 0 g 0 G 0 g 0 G 0 g 0 G +0 g 0 G BT -/F16 14.3462 Tf 99.895 680.226 Td [(psb)]TJ +/F53 8.9664 Tf 108.801 680.066 Td [(s)-60(u)-60(b)-60(r)-59(o)-60(u)-60(t)-60(i)-60(n)-60(e)]TJ/F46 8.9664 Tf 61.47 0 Td [(p)-132(s)-132(b)]TJ ET q -1 0 0 1 125.163 680.425 cm -[]0 d 0 J 0.398 w 0 0 m 4.842 0 l S +1 0 0 1 188.254 680.265 cm +[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S Q BT -/F16 14.3462 Tf 130.004 680.226 Td [(set)]TJ +/F46 8.9664 Tf 192.204 680.066 Td [(f)-132(o)-132(o)-241(\050)-155(s)-47(o)-47(m)-47(e)-768(a)-105(r)-106(g)-105(s)-376(,)-939(i)-156(n)-157(f)-156(o)-265(\051)]TJ -65.125 -10.959 Td [(.)-248(.)-249(.)]TJ/F53 8.9664 Tf -0.604 -10.959 Td [(i)-181(f)]TJ/F46 8.9664 Tf 10.408 0 Td [(\050)-260(e)-151(r)-151(r)-151(o)-151(r)-897(d)-129(e)-129(t)-130(e)-129(c)-129(t)-129(e)-130(d)-237(\051)]TJ/F53 8.9664 Tf 93.292 0 Td [(t)-30(h)-29(e)-30(n)]TJ/F46 8.9664 Tf -87.332 -10.959 Td [(i)-156(n)-157(f)-156(o)-65(=)-38(e)-129(r)-128(r)-129(c)-129(o)-129(d)-129(e)-129(1)]TJ/F53 8.9664 Tf -0.133 -10.959 Td [(c)-142(a)-141(l)-142(l)]TJ/F46 8.9664 Tf 27.487 0 Td [(p)-124(s)-124(b)]TJ ET q -1 0 0 1 150.979 680.425 cm -[]0 d 0 J 0.398 w 0 0 m 4.842 0 l S +1 0 0 1 187.956 636.429 cm +[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S Q BT -/F16 14.3462 Tf 155.821 680.226 Td [(erraction|Set)-375(the)-375(t)31(yp)-31(e)-375(of)-375(action)-375(to)-375(b)-31(e)]TJ -55.926 -17.933 Td [(tak)31(en)-375(up)-31(on)-375(error)-375(condition.)]TJ/F27 9.9626 Tf 1.377 -35.768 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 30.09 0 Td [(p)-158(s)-159(b)]TJ +/F46 8.9664 Tf 191.831 636.23 Td [(e)-124(r)-124(r)-124(p)-123(u)-124(s)-124(h)-233(\050)-329(')-242(p)-133(s)-132(b)]TJ ET q -1 0 0 1 151.695 626.724 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 260.135 636.429 cm +[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S Q BT -/F8 9.9626 Tf 156.263 626.525 Td [(s)-159(e)-158(t)]TJ +/F46 8.9664 Tf 264.085 636.23 Td [(f)-132(o)-132(o)-353(')-332(,)-855(e)-129(r)-129(r)-129(c)-129(o)-128(d)-129(e)-129(1)-237(\051)]TJ/F53 8.9664 Tf -122.23 -10.959 Td [(g)-46(o)-47(t)-46(o)]TJ/F46 8.9664 Tf 27.968 0 Td [(9)-82(9)-82(9)-83(9)]TJ/F53 8.9664 Tf -44.989 -10.959 Td [(e)2(n)2(d)-796(i)-181(f)]TJ/F46 8.9664 Tf 2.245 -10.959 Td [(.)-248(.)-249(.)]TJ/F53 8.9664 Tf -0.957 -10.959 Td [(c)-142(a)-141(l)-142(l)]TJ/F46 8.9664 Tf 27.399 0 Td [(p)-114(s)-114(b)]TJ ET q -1 0 0 1 173.829 626.724 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 171.016 592.594 cm +[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S Q BT -/F8 9.9626 Tf 178.396 626.525 Td [(e)-159(r)-158(r)-158(a)-159(c)-158(t)-159(i)-158(o)-159(n)-264(\050)-265(e)-160(r)-160(r)]TJ +/F46 8.9664 Tf 174.803 592.394 Td [(b)-114(a)-114(r)-223(\050)-155(s)-47(o)-46(m)-47(e)-769(a)-105(r)-105(g)-105(s)-377(,)-938(i)-157(n)-156(f)-157(o)-265(\051)]TJ/F53 8.9664 Tf -48.328 -10.958 Td [(i)-181(f)]TJ/F46 8.9664 Tf 10.408 0 Td [(\050)-265(i)-156(n)-157(f)-156(o)-939(.)]TJ/F53 8.9664 Tf 37.831 0 Td [(n)-11(e)]TJ/F46 8.9664 Tf 12.445 0 Td [(.)-910(z)-127(e)-127(r)-128(o)-235(\051)]TJ/F53 8.9664 Tf 43.016 0 Td [(t)-30(h)-29(e)-30(n)]TJ/F46 8.9664 Tf -87.332 -10.959 Td [(i)-156(n)-157(f)-156(o)-65(=)-38(e)-129(r)-128(r)-129(c)-129(o)-129(d)-129(e)-129(2)]TJ/F53 8.9664 Tf -0.133 -10.959 Td [(c)-142(a)-141(l)-142(l)]TJ/F46 8.9664 Tf 27.487 0 Td [(p)-124(s)-124(b)]TJ ET q -1 0 0 1 256.582 626.724 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 187.956 559.717 cm +[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S Q BT -/F8 9.9626 Tf 261.163 626.525 Td [(a)-160(c)-160(t)-265(\051)]TJ -0 g 0 G -0 g 0 G -0 g 0 G -/F27 9.9626 Tf -161.268 -17.933 Td [(T)32(yp)-32(e:)]TJ -0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ -0 g 0 G -/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ +/F46 8.9664 Tf 191.831 559.518 Td [(e)-124(r)-124(r)-124(p)-123(u)-124(s)-124(h)-233(\050)-329(')-242(p)-133(s)-132(b)]TJ +ET +q +1 0 0 1 260.135 559.717 cm +[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S +Q +BT +/F46 8.9664 Tf 264.085 559.518 Td [(f)-132(o)-132(o)-353(')-332(,)-855(e)-129(r)-129(r)-129(c)-129(o)-128(d)-129(e)-129(2)-237(\051)]TJ/F53 8.9664 Tf -122.23 -10.959 Td [(g)-46(o)-47(t)-46(o)]TJ/F46 8.9664 Tf 27.968 0 Td [(9)-82(9)-82(9)-83(9)]TJ/F53 8.9664 Tf -44.989 -10.959 Td [(e)2(n)2(d)-796(i)-181(f)]TJ/F46 8.9664 Tf 2.245 -10.959 Td [(.)-248(.)-249(.)]TJ -18.078 -10.959 Td [(9)-82(9)-82(9)-83(9)]TJ/F53 8.9664 Tf 27.419 0 Td [(c)-57(o)-57(n)-57(t)-56(i)-57(n)-57(u)-57(e)]TJ -9.945 -10.959 Td [(i)-181(f)]TJ/F46 8.9664 Tf 15.937 0 Td [(\050)-273(e)-164(r)-165(r)]TJ +ET +q +1 0 0 1 164.726 504.923 cm +[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S +Q +BT +/F46 8.9664 Tf 168.965 504.723 Td [(a)-164(c)-165(t)-946(.)]TJ/F53 8.9664 Tf 27.964 0 Td [(e)-22(q)]TJ/F46 8.9664 Tf 12.347 0 Td [(.)-923(a)-141(c)-141(t)]TJ +ET +q +1 0 0 1 236.744 504.923 cm +[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S +Q +BT +/F46 8.9664 Tf 240.772 504.723 Td [(a)-141(b)-141(o)-141(r)-141(t)-249(\051)]TJ/F53 8.9664 Tf 39.166 0 Td [(t)-30(h)-30(e)-29(n)]TJ -142.758 -10.959 Td [(c)-142(a)-141(l)-142(l)]TJ/F46 8.9664 Tf 27.682 0 Td [(p)-146(s)-145(b)]TJ +ET +q +1 0 0 1 183.205 493.964 cm +[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S +Q +BT +/F46 8.9664 Tf 187.274 493.764 Td [(e)-146(r)-145(r)-146(o)-145(r)-254(\050)-252(i)-144(c)-143(o)-144(n)-143(t)-143(x)-144(t)-252(\051)]TJ/F53 8.9664 Tf -50.844 -10.959 Td [(r)-58(e)-58(t)-58(u)-58(r)-58(n)]TJ -10.529 -10.958 Td [(e)-117(l)-117(s)-117(e)]TJ 10.529 -10.959 Td [(r)-58(e)-58(t)-58(u)-58(r)-58(n)]TJ -11.596 -10.959 Td [(e)2(n)2(d)-796(i)-181(f)]TJ -16.587 -21.918 Td [(e)2(n)2(d)-675(s)-59(u)-60(b)-60(r)-60(o)-60(u)-60(t)-60(i)-60(n)-59(e)]TJ/F46 8.9664 Tf 84.141 0 Td [(p)-132(s)-132(b)]TJ +ET +q +1 0 0 1 210.371 428.21 cm +[]0 d 0 J 0.398 w 0 0 m 2.765 0 l S +Q +BT +/F46 8.9664 Tf 214.321 428.011 Td [(f)-132(o)-132(o)]TJ 0 g 0 G 0 g 0 G - 0 -19.926 Td [(err)]TJ ET q -1 0 0 1 115.271 568.941 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +1 0 0 1 99.895 701.884 cm +[]0 d 0 J 0.398 w 0 0 m 346.583 0 l S +Q +q +1 0 0 1 100.095 410.576 cm +[]0 d 0 J 0.398 w 0 0 m 0 291.308 l S +Q +q +1 0 0 1 446.279 410.576 cm +[]0 d 0 J 0.398 w 0 0 m 0 291.308 l S +Q +q +1 0 0 1 99.895 410.576 cm +[]0 d 0 J 0.398 w 0 0 m 346.583 0 l S Q BT -/F27 9.9626 Tf 118.708 568.741 Td [(act)]TJ -0 g 0 G -/F8 9.9626 Tf 20.098 0 Td [(the)-333(t)27(yp)-27(e)-334(of)-333(action.)]TJ -14.004 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger.)-444(P)27(ossible)-333(v)56(alues)-1(:)]TJ/F30 9.9626 Tf 180.269 0 Td [(psb_act_ret)]TJ/F8 9.9626 Tf 57.533 0 Td [(,)]TJ/F30 9.9626 Tf 6.089 0 Td [(psb_act_abort)]TJ/F8 9.9626 Tf 67.994 0 Td [(.)]TJ +/F8 9.9626 Tf 99.895 382.537 Td [(Figure)-329(9:)-443(The)-329(la)27(y)28(out)-329(of)-330(a)-329(generic)]TJ/F30 9.9626 Tf 147.445 0 Td [(psb)]TJ +ET +q +1 0 0 1 263.659 382.736 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 266.797 382.537 Td [(foo)]TJ/F8 9.9626 Tf 18.973 0 Td [(routine)-329(with)-330(resp)-28(ect)-329(to)-330(PS)1(B)-1(LAS)1(-)-1(2.)1(0)]TJ -185.875 -11.955 Td [(error)-333(handling)-333(p)-28(olicy)83(.)]TJ 0 g 0 G - -172.408 -430.483 Td [(121)]TJ 0 g 0 G -ET - -endstream -endobj -1658 0 obj -<< -/Length 538 ->> -stream 0 g 0 G 0 g 0 G -BT -/F16 14.3462 Tf 150.705 706.129 Td [(9)-1125(Utilities)]TJ/F8 9.9626 Tf 0 -21.821 Td [(W)83(e)-412(ha)27(v)28(e)-412(som)-1(e)-412(utilities)-413(a)28(v)55(ai)1(lable)-413(for)-413(input)-412(and)-413(output)-412(of)-413(sparse)-413(matrices;)-452(the)]TJ 0 -11.955 Td [(in)28(terfaces)-334(to)-333(these)-333(routines)-334(are)-333(a)28(v)55(ailable)-333(in)-333(the)-334(mo)-27(dule)]TJ/F30 9.9626 Tf 241.843 0 Td [(psb_util_mod)]TJ/F8 9.9626 Tf 62.764 0 Td [(.)]TJ 0 g 0 G - -140.224 -581.915 Td [(122)]TJ +0 g 0 G +/F30 9.9626 Tf 8.369 -39.475 Td [(==========================================================)]TJ 0 -11.955 Td [(Process:)-525(0.)-1050(PSBLAS)-525(Error)-525(\0504010\051)-525(in)-525(subroutine:)-525(df_sample)]TJ 0 -11.955 Td [(Error)-525(from)-525(call)-525(to)-525(subroutine)-525(mat)-525(dist)]TJ 0 -11.955 Td [(==========================================================)]TJ 0 -11.955 Td [(Process:)-525(0.)-1050(PSBLAS)-525(Error)-525(\0504010\051)-525(in)-525(subroutine:)-525(mat_distv)]TJ 0 -11.956 Td [(Error)-525(from)-525(call)-525(to)-525(subroutine)-525(psb_spasb)]TJ 0 -11.955 Td [(==========================================================)]TJ 0 -11.955 Td [(Process:)-525(0.)-1050(PSBLAS)-525(Error)-525(\0504010\051)-525(in)-525(subroutine:)-525(psb_spasb)]TJ 0 -11.955 Td [(Error)-525(from)-525(call)-525(to)-525(subroutine)-525(psb_cest)]TJ 0 -11.955 Td [(==========================================================)]TJ 0 -11.955 Td [(Process:)-525(0.)-1050(PSBLAS)-525(Error)-525(\050136\051)-525(in)-525(subroutine:)-525(psb_cest)]TJ 0 -11.956 Td [(Format)-525(FOO)-525(is)-525(unknown)]TJ 0 -11.955 Td [(==========================================================)]TJ 0 -11.955 Td [(Aborting...)]TJ +ET +q +1 0 0 1 99.895 343.417 cm +[]0 d 0 J 0.398 w 0 0 m 346.583 0 l S +Q +q +1 0 0 1 100.095 165.307 cm +[]0 d 0 J 0.398 w 0 0 m 0 178.111 l S +Q +q +1 0 0 1 446.279 165.307 cm +[]0 d 0 J 0.398 w 0 0 m 0 178.111 l S +Q +q +1 0 0 1 99.895 165.307 cm +[]0 d 0 J 0.398 w 0 0 m 346.583 0 l S +Q +BT +/F8 9.9626 Tf 99.895 137.267 Td [(Figure)-386(10:)-551(A)-386(sample)-386(PSBLAS-2.0)-387(error)-386(message.)-603(Pro)-28(cess)-387(0)-386(detected)-386(an)-387(error)]TJ 0 -11.955 Td [(condition)-333(inside)-334(the)-333(psb)]TJ +ET +q +1 0 0 1 204.658 125.512 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 207.647 125.312 Td [(cest)-333(s)-1(u)1(broutine)]TJ +0 g 0 G +0 g 0 G + 56.632 -34.874 Td [(121)]TJ 0 g 0 G ET endstream endobj -1557 0 obj +1560 0 obj << /Type /ObjStm /N 100 -/First 972 -/Length 8536 +/First 967 +/Length 9161 >> stream -1553 0 437 58 1554 115 1555 173 1550 231 1559 363 1561 481 441 540 1562 598 1563 657 -1558 716 1565 848 1567 966 445 1024 1568 1081 1569 1139 1564 1197 1571 1329 1573 1447 449 1506 -1574 1564 1575 1623 1570 1682 1577 1814 1579 1932 453 1990 1580 2047 1581 2105 1576 2163 1583 2295 -1585 2413 457 2472 1586 2530 1582 2588 1588 2720 1590 2838 461 2896 1591 2953 1587 3010 1596 3142 -1593 3290 1594 3435 1598 3582 465 3641 1595 3699 1602 3792 1604 3910 1605 3968 1606 4027 1608 4086 -1609 4145 1610 4204 1611 4263 1612 4322 1613 4380 1614 4439 1615 4498 1616 4557 1617 4616 1618 4675 -1619 4734 1620 4793 1621 4852 1622 4909 1623 4968 1624 5027 1625 5086 1626 5145 1627 5204 1628 5263 -1629 5322 1630 5381 1599 5439 1600 5498 1601 5557 1632 5665 1634 5783 469 5842 1635 5900 1636 5958 -1631 6016 1638 6109 1640 6227 473 6285 1641 6342 1642 6399 1637 6456 1644 6549 1646 6667 477 6726 -1647 6784 1648 6842 1643 6900 1650 6993 1652 7111 481 7169 1653 7226 1654 7283 1649 7340 1657 7446 -% 1553 0 obj -<< -/D [1551 0 R /XYZ 98.895 753.953 null] ->> -% 437 0 obj +405 0 1558 58 1559 116 1554 175 1562 307 1564 425 409 483 1565 540 1566 598 1567 656 +1561 714 1569 846 1571 964 413 1023 1568 1081 1573 1187 1575 1305 417 1363 1572 1420 1577 1552 +1579 1670 421 1729 1576 1787 1581 1893 1583 2011 425 2069 1580 2126 1586 2232 1588 2350 429 2409 +1585 2467 1590 2573 1592 2691 433 2749 1589 2806 1594 2938 1596 3056 437 3115 1597 3173 1598 3232 +1593 3291 1600 3423 1602 3541 441 3599 1603 3656 1604 3714 1599 3772 1606 3904 1608 4022 445 4081 +1609 4139 1610 4198 1605 4257 1612 4389 1614 4507 449 4565 1615 4622 1616 4680 1611 4738 1619 4870 +1621 4988 453 5047 1622 5105 1623 5164 1618 5223 1625 5355 1627 5473 457 5531 1628 5588 1629 5646 +1631 5704 1624 5762 1633 5932 1635 6050 461 6109 1636 6167 1632 6225 1638 6357 1640 6475 465 6533 +1641 6590 1637 6647 1645 6779 1642 6927 1643 7072 1647 7219 469 7278 1644 7336 1651 7429 1653 7547 +1654 7605 1655 7664 1657 7723 1658 7782 1659 7841 1660 7900 1661 7959 1662 8017 1663 8076 1664 8135 +% 405 0 obj << -/D [1551 0 R /XYZ 99.895 720.077 null] +/D [1555 0 R /XYZ 150.705 720.077 null] >> -% 1554 0 obj +% 1558 0 obj << -/D [1551 0 R /XYZ 99.895 247.391 null] +/D [1555 0 R /XYZ 150.705 349.01 null] >> -% 1555 0 obj +% 1559 0 obj << -/D [1551 0 R /XYZ 99.895 213.573 null] +/D [1555 0 R /XYZ 150.705 315.192 null] >> -% 1550 0 obj +% 1554 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F27 556 0 R /F14 767 0 R /F11 750 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F27 560 0 R /F14 772 0 R /F11 755 0 R >> /ProcSet [ /PDF /Text ] >> -% 1559 0 obj +% 1562 0 obj << /Type /Page -/Contents 1560 0 R -/Resources 1558 0 R +/Contents 1563 0 R +/Resources 1561 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1556 0 R +/Parent 1553 0 R >> -% 1561 0 obj +% 1564 0 obj << -/D [1559 0 R /XYZ 149.705 753.953 null] +/D [1562 0 R /XYZ 98.895 753.953 null] >> -% 441 0 obj +% 409 0 obj << -/D [1559 0 R /XYZ 150.705 720.077 null] +/D [1562 0 R /XYZ 99.895 720.077 null] >> -% 1562 0 obj +% 1565 0 obj << -/D [1559 0 R /XYZ 150.705 247.391 null] +/D [1562 0 R /XYZ 99.895 442.659 null] >> -% 1563 0 obj +% 1566 0 obj << -/D [1559 0 R /XYZ 150.705 213.573 null] +/D [1562 0 R /XYZ 99.895 396.886 null] >> -% 1558 0 obj +% 1567 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F27 556 0 R /F14 767 0 R /F11 750 0 R >> +/D [1562 0 R /XYZ 99.895 365.005 null] +>> +% 1561 0 obj +<< +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F27 560 0 R /F11 755 0 R /F14 772 0 R >> /ProcSet [ /PDF /Text ] >> -% 1565 0 obj +% 1569 0 obj << /Type /Page -/Contents 1566 0 R -/Resources 1564 0 R +/Contents 1570 0 R +/Resources 1568 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1556 0 R +/Parent 1553 0 R >> -% 1567 0 obj +% 1571 0 obj << -/D [1565 0 R /XYZ 98.895 753.953 null] +/D [1569 0 R /XYZ 149.705 753.953 null] >> -% 445 0 obj +% 413 0 obj << -/D [1565 0 R /XYZ 99.895 720.077 null] +/D [1569 0 R /XYZ 150.705 720.077 null] >> % 1568 0 obj << -/D [1565 0 R /XYZ 99.895 247.391 null] ->> -% 1569 0 obj -<< -/D [1565 0 R /XYZ 99.895 213.573 null] ->> -% 1564 0 obj -<< -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F27 556 0 R /F14 767 0 R /F11 750 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F27 560 0 R >> /ProcSet [ /PDF /Text ] >> -% 1571 0 obj +% 1573 0 obj << /Type /Page -/Contents 1572 0 R -/Resources 1570 0 R +/Contents 1574 0 R +/Resources 1572 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1556 0 R ->> -% 1573 0 obj -<< -/D [1571 0 R /XYZ 149.705 753.953 null] +/Parent 1553 0 R >> -% 449 0 obj -<< -/D [1571 0 R /XYZ 150.705 720.077 null] ->> -% 1574 0 obj +% 1575 0 obj << -/D [1571 0 R /XYZ 150.705 235.436 null] +/D [1573 0 R /XYZ 98.895 753.953 null] >> -% 1575 0 obj +% 417 0 obj << -/D [1571 0 R /XYZ 150.705 201.618 null] +/D [1573 0 R /XYZ 99.895 720.077 null] >> -% 1570 0 obj +% 1572 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F27 556 0 R /F14 767 0 R /F11 750 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F11 755 0 R /F27 560 0 R /F14 772 0 R >> /ProcSet [ /PDF /Text ] >> % 1577 0 obj @@ -20356,269 +20381,285 @@ stream /Contents 1578 0 R /Resources 1576 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1556 0 R +/Parent 1553 0 R >> % 1579 0 obj << -/D [1577 0 R /XYZ 98.895 753.953 null] +/D [1577 0 R /XYZ 149.705 753.953 null] >> -% 453 0 obj +% 421 0 obj << -/D [1577 0 R /XYZ 99.895 720.077 null] +/D [1577 0 R /XYZ 150.705 720.077 null] >> -% 1580 0 obj +% 1576 0 obj << -/D [1577 0 R /XYZ 99.895 235.436 null] +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F27 560 0 R >> +/ProcSet [ /PDF /Text ] >> % 1581 0 obj << -/D [1577 0 R /XYZ 99.895 201.618 null] +/Type /Page +/Contents 1582 0 R +/Resources 1580 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1584 0 R >> -% 1576 0 obj +% 1583 0 obj +<< +/D [1581 0 R /XYZ 98.895 753.953 null] +>> +% 425 0 obj +<< +/D [1581 0 R /XYZ 99.895 720.077 null] +>> +% 1580 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F27 556 0 R /F14 767 0 R /F11 750 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F27 560 0 R >> /ProcSet [ /PDF /Text ] >> -% 1583 0 obj +% 1586 0 obj << /Type /Page -/Contents 1584 0 R -/Resources 1582 0 R +/Contents 1587 0 R +/Resources 1585 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1556 0 R ->> -% 1585 0 obj -<< -/D [1583 0 R /XYZ 149.705 753.953 null] +/Parent 1584 0 R >> -% 457 0 obj +% 1588 0 obj << -/D [1583 0 R /XYZ 150.705 720.077 null] +/D [1586 0 R /XYZ 149.705 753.953 null] >> -% 1586 0 obj +% 429 0 obj << -/D [1583 0 R /XYZ 150.705 223.48 null] +/D [1586 0 R /XYZ 150.705 720.077 null] >> -% 1582 0 obj +% 1585 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F27 556 0 R /F11 750 0 R /F14 767 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F27 560 0 R >> /ProcSet [ /PDF /Text ] >> -% 1588 0 obj +% 1590 0 obj << /Type /Page -/Contents 1589 0 R -/Resources 1587 0 R +/Contents 1591 0 R +/Resources 1589 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1592 0 R ->> -% 1590 0 obj -<< -/D [1588 0 R /XYZ 98.895 753.953 null] +/Parent 1584 0 R >> -% 461 0 obj +% 1592 0 obj << -/D [1588 0 R /XYZ 99.895 720.077 null] +/D [1590 0 R /XYZ 98.895 753.953 null] >> -% 1591 0 obj +% 433 0 obj << -/D [1588 0 R /XYZ 99.895 223.48 null] +/D [1590 0 R /XYZ 99.895 720.077 null] >> -% 1587 0 obj +% 1589 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F8 557 0 R /F27 556 0 R /F11 750 0 R /F14 767 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F27 560 0 R /F11 755 0 R /F14 772 0 R >> /ProcSet [ /PDF /Text ] >> -% 1596 0 obj +% 1594 0 obj << /Type /Page -/Contents 1597 0 R -/Resources 1595 0 R +/Contents 1595 0 R +/Resources 1593 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1592 0 R -/Annots [ 1593 0 R 1594 0 R ] +/Parent 1584 0 R >> -% 1593 0 obj +% 1596 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [196.286 501.77 203.26 512.895] -/A << /S /GoTo /D (figure.9) >> +/D [1594 0 R /XYZ 149.705 753.953 null] >> -% 1594 0 obj +% 437 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [197.543 346.63 209.498 357.478] -/A << /S /GoTo /D (figure.10) >> +/D [1594 0 R /XYZ 150.705 720.077 null] >> -% 1598 0 obj +% 1597 0 obj << -/D [1596 0 R /XYZ 149.705 753.953 null] +/D [1594 0 R /XYZ 150.705 247.391 null] >> -% 465 0 obj +% 1598 0 obj << -/D [1596 0 R /XYZ 150.705 716.092 null] +/D [1594 0 R /XYZ 150.705 213.573 null] >> -% 1595 0 obj +% 1593 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F30 764 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F27 560 0 R /F14 772 0 R /F11 755 0 R >> /ProcSet [ /PDF /Text ] >> -% 1602 0 obj +% 1600 0 obj << /Type /Page -/Contents 1603 0 R -/Resources 1601 0 R +/Contents 1601 0 R +/Resources 1599 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1592 0 R +/Parent 1584 0 R +>> +% 1602 0 obj +<< +/D [1600 0 R /XYZ 98.895 753.953 null] +>> +% 441 0 obj +<< +/D [1600 0 R /XYZ 99.895 720.077 null] +>> +% 1603 0 obj +<< +/D [1600 0 R /XYZ 99.895 247.391 null] >> % 1604 0 obj << -/D [1602 0 R /XYZ 98.895 753.953 null] +/D [1600 0 R /XYZ 99.895 213.573 null] >> -% 1605 0 obj +% 1599 0 obj << -/D [1602 0 R /XYZ 108.264 687.737 null] +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F27 560 0 R /F14 772 0 R /F11 755 0 R >> +/ProcSet [ /PDF /Text ] >> % 1606 0 obj << -/D [1602 0 R /XYZ 108.264 691.025 null] +/Type /Page +/Contents 1607 0 R +/Resources 1605 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1584 0 R >> % 1608 0 obj << -/D [1602 0 R /XYZ 108.264 680.066 null] +/D [1606 0 R /XYZ 149.705 753.953 null] +>> +% 445 0 obj +<< +/D [1606 0 R /XYZ 150.705 720.077 null] >> % 1609 0 obj << -/D [1602 0 R /XYZ 108.264 669.107 null] +/D [1606 0 R /XYZ 150.705 247.391 null] >> % 1610 0 obj << -/D [1602 0 R /XYZ 108.264 658.148 null] +/D [1606 0 R /XYZ 150.705 213.573 null] >> -% 1611 0 obj +% 1605 0 obj << -/D [1602 0 R /XYZ 108.264 647.189 null] +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F27 560 0 R /F14 772 0 R /F11 755 0 R >> +/ProcSet [ /PDF /Text ] >> % 1612 0 obj << -/D [1602 0 R /XYZ 108.264 636.23 null] +/Type /Page +/Contents 1613 0 R +/Resources 1611 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1617 0 R >> -% 1613 0 obj +% 1614 0 obj << -/D [1602 0 R /XYZ 108.264 625.271 null] +/D [1612 0 R /XYZ 98.895 753.953 null] >> -% 1614 0 obj +% 449 0 obj << -/D [1602 0 R /XYZ 108.264 614.312 null] +/D [1612 0 R /XYZ 99.895 720.077 null] >> % 1615 0 obj << -/D [1602 0 R /XYZ 108.264 603.353 null] +/D [1612 0 R /XYZ 99.895 235.436 null] >> % 1616 0 obj << -/D [1602 0 R /XYZ 108.264 592.394 null] ->> -% 1617 0 obj -<< -/D [1602 0 R /XYZ 108.264 581.436 null] +/D [1612 0 R /XYZ 99.895 201.618 null] >> -% 1618 0 obj +% 1611 0 obj << -/D [1602 0 R /XYZ 108.264 570.477 null] +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F27 560 0 R /F14 772 0 R /F11 755 0 R >> +/ProcSet [ /PDF /Text ] >> % 1619 0 obj << -/D [1602 0 R /XYZ 108.264 559.518 null] +/Type /Page +/Contents 1620 0 R +/Resources 1618 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1617 0 R >> -% 1620 0 obj +% 1621 0 obj << -/D [1602 0 R /XYZ 108.264 548.559 null] +/D [1619 0 R /XYZ 149.705 753.953 null] >> -% 1621 0 obj +% 453 0 obj << -/D [1602 0 R /XYZ 108.264 537.6 null] +/D [1619 0 R /XYZ 150.705 720.077 null] >> % 1622 0 obj << -/D [1602 0 R /XYZ 108.264 526.641 null] +/D [1619 0 R /XYZ 150.705 235.436 null] >> % 1623 0 obj << -/D [1602 0 R /XYZ 108.264 515.682 null] +/D [1619 0 R /XYZ 150.705 201.618 null] >> -% 1624 0 obj +% 1618 0 obj << -/D [1602 0 R /XYZ 108.264 504.723 null] +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F27 560 0 R /F14 772 0 R /F11 755 0 R >> +/ProcSet [ /PDF /Text ] >> % 1625 0 obj << -/D [1602 0 R /XYZ 108.264 493.764 null] +/Type /Page +/Contents 1626 0 R +/Resources 1624 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1617 0 R >> -% 1626 0 obj +% 1627 0 obj << -/D [1602 0 R /XYZ 108.264 482.805 null] +/D [1625 0 R /XYZ 98.895 753.953 null] >> -% 1627 0 obj +% 457 0 obj << -/D [1602 0 R /XYZ 108.264 471.847 null] +/D [1625 0 R /XYZ 99.895 720.077 null] >> % 1628 0 obj << -/D [1602 0 R /XYZ 108.264 460.888 null] +/D [1625 0 R /XYZ 99.895 274.156 null] >> % 1629 0 obj << -/D [1602 0 R /XYZ 108.264 449.929 null] +/D [1625 0 R /XYZ 99.895 241.264 null] >> -% 1630 0 obj -<< -/D [1602 0 R /XYZ 108.264 438.97 null] ->> -% 1599 0 obj -<< -/D [1602 0 R /XYZ 143.452 394.492 null] ->> -% 1600 0 obj +% 1631 0 obj << -/D [1602 0 R /XYZ 150.074 149.223 null] +/D [1625 0 R /XYZ 99.895 153.877 null] >> -% 1601 0 obj +% 1624 0 obj << -/Font << /F53 1607 0 R /F46 1170 0 R /F8 557 0 R /F30 764 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F27 560 0 R /F14 772 0 R /F11 755 0 R /F10 771 0 R /F1 1630 0 R /F7 770 0 R >> /ProcSet [ /PDF /Text ] >> -% 1632 0 obj +% 1633 0 obj << /Type /Page -/Contents 1633 0 R -/Resources 1631 0 R +/Contents 1634 0 R +/Resources 1632 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1592 0 R ->> -% 1634 0 obj -<< -/D [1632 0 R /XYZ 149.705 753.953 null] +/Parent 1617 0 R >> -% 469 0 obj +% 1635 0 obj << -/D [1632 0 R /XYZ 150.705 724.062 null] +/D [1633 0 R /XYZ 149.705 753.953 null] >> -% 1635 0 obj +% 461 0 obj << -/D [1632 0 R /XYZ 150.705 638.48 null] +/D [1633 0 R /XYZ 150.705 720.077 null] >> % 1636 0 obj << -/D [1632 0 R /XYZ 150.705 638.48 null] +/D [1633 0 R /XYZ 150.705 223.48 null] >> -% 1631 0 obj +% 1632 0 obj << -/Font << /F16 554 0 R /F27 556 0 R /F8 557 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F27 560 0 R /F11 755 0 R /F14 772 0 R >> /ProcSet [ /PDF /Text ] >> % 1638 0 obj @@ -20627,925 +20668,1780 @@ stream /Contents 1639 0 R /Resources 1637 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1592 0 R +/Parent 1617 0 R >> % 1640 0 obj << /D [1638 0 R /XYZ 98.895 753.953 null] >> -% 473 0 obj +% 465 0 obj << -/D [1638 0 R /XYZ 99.895 724.062 null] +/D [1638 0 R /XYZ 99.895 720.077 null] >> % 1641 0 obj << -/D [1638 0 R /XYZ 99.895 638.48 null] ->> -% 1642 0 obj -<< -/D [1638 0 R /XYZ 99.895 638.48 null] +/D [1638 0 R /XYZ 99.895 223.48 null] >> % 1637 0 obj << -/Font << /F16 554 0 R /F27 556 0 R /F8 557 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F8 561 0 R /F27 560 0 R /F11 755 0 R /F14 772 0 R >> /ProcSet [ /PDF /Text ] >> -% 1644 0 obj +% 1645 0 obj << /Type /Page -/Contents 1645 0 R -/Resources 1643 0 R +/Contents 1646 0 R +/Resources 1644 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1592 0 R +/Parent 1617 0 R +/Annots [ 1642 0 R 1643 0 R ] >> -% 1646 0 obj +% 1642 0 obj << -/D [1644 0 R /XYZ 149.705 753.953 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [196.286 501.77 203.26 512.895] +/A << /S /GoTo /D (figure.9) >> >> -% 477 0 obj +% 1643 0 obj << -/D [1644 0 R /XYZ 150.705 724.062 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [197.543 346.63 209.498 357.478] +/A << /S /GoTo /D (figure.10) >> >> % 1647 0 obj << -/D [1644 0 R /XYZ 150.705 635.69 null] +/D [1645 0 R /XYZ 149.705 753.953 null] >> -% 1648 0 obj +% 469 0 obj << -/D [1644 0 R /XYZ 150.705 638.48 null] +/D [1645 0 R /XYZ 150.705 716.092 null] >> -% 1643 0 obj +% 1644 0 obj << -/Font << /F16 554 0 R /F27 556 0 R /F8 557 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 1650 0 obj +% 1651 0 obj << /Type /Page -/Contents 1651 0 R -/Resources 1649 0 R +/Contents 1652 0 R +/Resources 1650 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1655 0 R +/Parent 1680 0 R >> -% 1652 0 obj +% 1653 0 obj << -/D [1650 0 R /XYZ 98.895 753.953 null] +/D [1651 0 R /XYZ 98.895 753.953 null] >> -% 481 0 obj +% 1654 0 obj << -/D [1650 0 R /XYZ 99.895 724.062 null] +/D [1651 0 R /XYZ 108.264 687.737 null] >> -% 1653 0 obj +% 1655 0 obj << -/D [1650 0 R /XYZ 99.895 635.69 null] +/D [1651 0 R /XYZ 108.264 691.025 null] >> -% 1654 0 obj +% 1657 0 obj << -/D [1650 0 R /XYZ 99.895 638.48 null] +/D [1651 0 R /XYZ 108.264 680.066 null] >> -% 1649 0 obj +% 1658 0 obj << -/Font << /F16 554 0 R /F27 556 0 R /F8 557 0 R /F30 764 0 R >> -/ProcSet [ /PDF /Text ] +/D [1651 0 R /XYZ 108.264 669.107 null] >> -% 1657 0 obj +% 1659 0 obj << -/Type /Page -/Contents 1658 0 R -/Resources 1656 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1655 0 R +/D [1651 0 R /XYZ 108.264 658.148 null] +>> +% 1660 0 obj +<< +/D [1651 0 R /XYZ 108.264 647.189 null] +>> +% 1661 0 obj +<< +/D [1651 0 R /XYZ 108.264 636.23 null] +>> +% 1662 0 obj +<< +/D [1651 0 R /XYZ 108.264 625.271 null] +>> +% 1663 0 obj +<< +/D [1651 0 R /XYZ 108.264 614.312 null] +>> +% 1664 0 obj +<< +/D [1651 0 R /XYZ 108.264 603.353 null] >> endstream endobj -1664 0 obj +1684 0 obj << -/Length 4792 +/Length 3723 >> stream 0 g 0 G 0 g 0 G +0 g 0 G +0 g 0 G BT -/F16 11.9552 Tf 103.166 706.129 Td [(h)31(b)]TJ +/F16 14.3462 Tf 150.705 680.226 Td [(psb)]TJ ET q -1 0 0 1 118.544 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +1 0 0 1 175.972 680.425 cm +[]0 d 0 J 0.398 w 0 0 m 4.842 0 l S Q BT -/F16 11.9552 Tf 122.579 706.129 Td [(read)-274(|)-273(Read)-274(a)-273(sparse)-274(matrix)-274(from)-273(a)-274(\014le)-273(in)-274(the)-274(Harw)32(ell{)]TJ -22.684 -13.948 Td [(Bo)-31(eing)-375(format)]TJ/F27 9.9626 Tf 1.377 -24.367 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.554 0 Td [(h)-105(b)]TJ +/F16 14.3462 Tf 180.814 680.226 Td [(errpush|Pushes)-375(an)-375(error)-375(co)-31(de)-375(on)31(to)-375(the)]TJ -30.109 -17.933 Td [(error)-375(stac)31(k)]TJ/F27 9.9626 Tf 1.377 -35.768 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.711 0 Td [(p)-120(s)-121(b)]TJ ET q -1 0 0 1 144.579 668.014 cm +1 0 0 1 200.991 626.724 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 148.61 667.814 Td [(r)-105(e)-104(a)-105(d)-210(\050)-139(a)-228(,)-911(i)-149(r)-150(e)-149(t)-460(,)-896(i)-135(u)-135(n)-135(i)-135(t)-431(,)-877(f)-116(i)-116(l)-116(e)-117(n)-116(a)-116(m)-116(e)-393(,)-776(b)-191(,)-902(m)-142(t)-141(i)-141(t)-141(l)-142(e)-247(\051)]TJ +/F8 9.9626 Tf 205.18 626.525 Td [(e)-120(r)-121(r)-120(p)-121(u)-120(s)-121(h)-226(\050)-244(e)-138(r)-138(r)]TJ +ET +q +1 0 0 1 270.664 626.724 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 275.03 626.525 Td [(c)-438(,)-825(r)]TJ +ET +q +1 0 0 1 299.951 626.724 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 303.581 626.525 Td [(n)-64(a)-65(m)-64(e)-290(,)-923(i)]TJ +ET +q +1 0 0 1 348.584 626.724 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 353.187 626.525 Td [(e)-162(r)-162(r)-485(,)-914(a)]TJ +ET +q +1 0 0 1 392.442 626.724 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 396.945 626.525 Td [(e)-152(r)-152(r)-258(\051)]TJ 0 g 0 G 0 g 0 G 0 g 0 G -/F27 9.9626 Tf -48.715 -17.933 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf -246.24 -17.933 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G /F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(\014lename)]TJ -0 g 0 G -/F8 9.9626 Tf 46.513 0 Td [(The)-333(name)-334(of)-333(the)-333(\014le)-334(to)-333(b)-28(e)-333(read.)]TJ -21.606 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-435(as:)-648(a)-435(c)27(h)1(arac)-1(ter)-435(v)56(ariable)-435(con)28(taining)-436(a)-435(v)56(alid)-435(\014le)-435(name,)-461(or)]TJ/F30 9.9626 Tf 297.915 0 Td [(-)]TJ/F8 9.9626 Tf 5.231 0 Td [(,)-461(in)]TJ -303.146 -11.956 Td [(whic)28(h)-302(cas)-1(e)-302(the)-302(default)-302(input)-302(unit)-302(5)-303(\050i.e.)-434(standard)-302(input)-302(in)-302(Unix)-302(jargon\051)-302(is)]TJ 0 -11.955 Td [(used.)-444(Default:)]TJ/F30 9.9626 Tf 66.058 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -96.195 -19.925 Td [(iunit)]TJ -0 g 0 G -/F8 9.9626 Tf 28.532 0 Td [(The)-333(F)83(ortran)-333(\014le)-334(un)1(it)-334(n)28(um)28(b)-28(er.)]TJ -3.625 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)-444(Only)-333(me)-1(ani)1(ngful)-334(if)-333(\014lename)-333(is)-334(not)]TJ/F30 9.9626 Tf 286.288 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -316.425 -21.918 Td [(On)-383(Return)]TJ -0 g 0 G -0 g 0 G - 0 -19.925 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(sparse)-334(matrix)-333(read)-333(from)-334(\014le.)]TJ 14.356 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ + 0 -19.926 Td [(err)]TJ ET q -1 0 0 1 312.036 452.82 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 166.08 568.941 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F30 9.9626 Tf 315.174 452.621 Td [(Tspmat)]TJ +/F27 9.9626 Tf 169.517 568.741 Td [(c)]TJ +0 g 0 G +/F8 9.9626 Tf 10.074 0 Td [(the)-333(error)-334(co)-27(de)]TJ -3.98 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.906 -19.926 Td [(r)]TJ ET q -1 0 0 1 347.183 452.82 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 156.111 501.195 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S Q BT -/F30 9.9626 Tf 350.322 452.621 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -271.348 -19.925 Td [(b)]TJ +/F27 9.9626 Tf 159.548 500.995 Td [(name)]TJ 0 g 0 G -/F8 9.9626 Tf 11.347 0 Td [(Rigth)-333(hand)-333(s)-1(i)1(de\050s)-1(\051.)]TJ 13.56 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(Optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(An)-282(ar)1(ra)27(y)-281(of)-282(t)28(yp)-28(e)-281(real)-282(or)-281(complex,)-292(rank)-282(2)-281(and)-282(ha)28(ving)-281(the)-282(ALLOCA)83(T)84(ABLE)]TJ 0 -11.956 Td [(attribute;)-409(will)-384(b)-28(e)-384(allo)-28(cated)-384(an)1(d)-384(\014lled)-384(in)-384(if)-384(the)-384(input)-384(\014le)-384(con)28(tains)-384(a)-384(righ)28(t)]TJ 0 -11.955 Td [(hand)-333(side,)-334(otherwise)-333(will)-333(b)-28(e)-333(left)-334(in)-333(the)-333(UNALLOCA)83(TED)-333(state.)]TJ +/F8 9.9626 Tf 31.714 0 Td [(the)-333(soutine)-334(where)-333(the)-333(error)-334(has)-333(b)-28(een)-333(caugh)28(t.)]TJ -15.651 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(string.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.925 Td [(m)32(title)]TJ +/F27 9.9626 Tf -24.906 -31.881 Td [(i)]TJ +ET +q +1 0 0 1 154.575 421.494 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 158.012 421.294 Td [(err)]TJ 0 g 0 G -/F8 9.9626 Tf 34.738 0 Td [(Matrix)-333(title.)]TJ -9.831 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(Optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(A)-405(c)28(harac)28(h)28(ter)-405(v)56(ariable)-405(of)-405(length)-404(72)-405(holding)-405(a)-404(cop)27(y)-404(of)-405(the)-405(matrix)-404(title)-405(as)]TJ 0 -11.956 Td [(sp)-28(eci\014ed)-333(b)28(y)-334(the)-333(Harw)28(ell-Bo)-28(eing)-333(format)-334(and)-333(con)28(tained)-333(in)-334(the)-333(input)-333(\014le.)]TJ +/F8 9.9626 Tf 19.669 0 Td [(addional)-333(info)-333(for)-334(error)-333(co)-28(de)]TJ -2.07 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(arra)27(y)]TJ 0 g 0 G -/F27 9.9626 Tf -24.907 -19.925 Td [(iret)]TJ +/F27 9.9626 Tf -24.906 -31.881 Td [(a)]TJ +ET +q +1 0 0 1 156.962 353.748 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 160.399 353.548 Td [(err)]TJ 0 g 0 G -/F8 9.9626 Tf 22.589 0 Td [(Error)-333(co)-28(de.)]TJ 2.318 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ +/F8 9.9626 Tf 19.669 0 Td [(addional)-333(info)-333(for)-334(error)-333(co)-28(de)]TJ -4.457 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(string.)]TJ 0 g 0 G - 139.477 -194.811 Td [(123)]TJ + 139.477 -227.245 Td [(122)]TJ 0 g 0 G ET endstream endobj -1671 0 obj +1690 0 obj << -/Length 5239 +/Length 1398 >> stream 0 g 0 G 0 g 0 G +0 g 0 G +0 g 0 G BT -/F16 11.9552 Tf 150.705 706.129 Td [(h)31(b)]TJ +/F16 14.3462 Tf 99.895 680.226 Td [(psb)]TJ ET q -1 0 0 1 166.082 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +1 0 0 1 125.163 680.425 cm +[]0 d 0 J 0.398 w 0 0 m 4.842 0 l S Q BT -/F16 11.9552 Tf 170.117 706.129 Td [(write)-357(|)-357(W)93(rite)-357(a)-357(sparse)-357(matrix)-358(to)-357(a)-357(\014le)-357(in)-357(the)-357(Harw)31(ell{)]TJ -19.412 -13.948 Td [(Bo)-31(eing)-375(format)]TJ/F27 9.9626 Tf 1.377 -24.367 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.733 0 Td [(h)-123(b)]TJ +/F16 14.3462 Tf 130.004 680.226 Td [(error|Prin)31(ts)-375(the)-375(error)-375(stac)32(k)-375(con)31(ten)31(t)-375(and)]TJ -30.109 -17.933 Td [(ab)-31(orts)-375(execution)]TJ/F27 9.9626 Tf 1.377 -35.768 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.921 0 Td [(p)-141(s)-142(b)]TJ ET q -1 0 0 1 195.926 668.014 cm +1 0 0 1 151.02 626.724 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 200.137 667.814 Td [(w)-123(r)-122(i)-123(t)-123(e)-228(\050)-139(a)-228(,)-910(i)-150(r)-149(e)-150(t)-460(,)-896(i)-135(u)-135(n)-135(i)-135(t)-431(,)-877(f)-116(i)-116(l)-116(e)-116(n)-116(a)-116(m)-117(e)-393(,)-821(k)-60(e)-60(y)-281(,)-853(r)-92(h)-91(s)-345(,)-902(m)-141(t)-142(i)-141(t)-141(l)-141(e)-247(\051)]TJ +/F8 9.9626 Tf 155.418 626.525 Td [(e)-142(r)-141(r)-142(o)-141(r)-247(\050)-245(i)-140(c)-139(o)-140(n)-140(t)-139(x)-140(t)-245(\051)]TJ 0 g 0 G 0 g 0 G 0 g 0 G -/F27 9.9626 Tf -49.432 -17.933 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf -55.523 -17.933 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G /F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(sparse)-334(matrix)-333(to)-333(b)-28(e)-333(written.)]TJ 14.355 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ -ET -q -1 0 0 1 362.845 586.32 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 365.983 586.121 Td [(Tspmat)]TJ -ET -q -1 0 0 1 397.993 586.32 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 401.131 586.121 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -271.347 -19.926 Td [(b)]TJ -0 g 0 G -/F8 9.9626 Tf 11.346 0 Td [(Rigth)-333(hand)-334(sid)1(e)-1(.)]TJ 13.56 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(Optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(An)-282(arr)1(a)27(y)-281(of)-282(t)28(yp)-28(e)-281(real)-282(or)-281(complex,)-292(rank)-282(1)-281(and)-282(ha)28(ving)-281(the)-282(ALLOCA)83(T)84(ABLE)]TJ 0 -11.955 Td [(attribute;)-409(will)-384(b)-28(e)-384(allo)-28(cated)-384(and)-383(\014lled)-384(in)-384(if)-384(the)-384(input)-384(\014le)-384(con)28(tains)-384(a)-384(righ)28(t)]TJ 0 -11.955 Td [(hand)-333(side.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.906 -19.926 Td [(\014lename)]TJ -0 g 0 G -/F8 9.9626 Tf 46.513 0 Td [(The)-333(name)-334(of)-333(the)-333(\014le)-334(to)-333(b)-28(e)-333(written)-333(to.)]TJ -21.607 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.761 -11.955 Td [(Sp)-28(eci\014ed)-435(as:)-648(a)-435(c)27(haracter)-435(v)56(ariable)-435(con)27(tain)1(ing)-436(a)-435(v)56(alid)-435(\014le)-435(name)-1(,)-460(or)]TJ/F30 9.9626 Tf 297.916 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(,)-461(in)]TJ -303.146 -11.955 Td [(whic)28(h)-281(case)-280(the)-281(d)1(e)-1(f)1(ault)-281(output)-280(unit)-280(6)-281(\050i.e.)-427(stand)1(ard)-281(output)-280(in)-280(Unix)-281(jargon\051)]TJ 0 -11.955 Td [(is)-333(used.)-445(Default:)]TJ/F30 9.9626 Tf 76.076 0 Td [(-)]TJ/F8 9.9626 Tf 5.231 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -106.213 -19.926 Td [(iunit)]TJ -0 g 0 G -/F8 9.9626 Tf 28.532 0 Td [(The)-333(F)83(ortran)-333(\014le)-334(u)1(nit)-334(n)28(um)28(b)-28(er.)]TJ -3.626 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.761 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)-444(Only)-334(meaningf)1(ul)-334(if)-333(\014lename)-333(is)-334(not)]TJ/F30 9.9626 Tf 286.289 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -316.425 -19.925 Td [(k)32(ey)]TJ -0 g 0 G -/F8 9.9626 Tf 22.008 0 Td [(Matrix)-333(k)28(ey)83(.)]TJ 2.899 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(Optional)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(A)-385(c)28(harac)28(h)28(ter)-385(v)56(ariable)-385(of)-385(length)-384(8)-385(holding)-385(the)-384(matrix)-385(k)28(ey)-385(as)-385(sp)-28(eci\014ed)-384(b)27(y)]TJ 0 -11.955 Td [(the)-333(Harw)27(ell-Bo)-27(eing)-334(format)-333(and)-333(to)-334(b)-27(e)-334(written)-333(to)-333(\014le.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -19.925 Td [(m)32(title)]TJ -0 g 0 G -/F8 9.9626 Tf 34.738 0 Td [(Matrix)-333(title.)]TJ -9.831 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(Optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(A)-318(c)28(harac)28(h)28(ter)-318(v)56(ariable)-318(of)-317(length)-318(72)-317(holding)-318(the)-317(matrix)-318(title)-318(as)-317(sp)-28(eci\014ed)-318(b)28(y)]TJ 0 -11.956 Td [(the)-333(Harw)27(ell-Bo)-27(eing)-334(format)-333(and)-333(to)-334(b)-27(e)-334(written)-333(to)-333(\014le.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -21.917 Td [(On)-383(Return)]TJ -0 g 0 G -0 g 0 G - 0 -19.926 Td [(iret)]TJ + 0 -19.926 Td [(icon)32(txt)]TJ 0 g 0 G -/F8 9.9626 Tf 22.589 0 Td [(Error)-333(co)-28(de.)]TJ 2.318 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detected.)]TJ +/F8 9.9626 Tf 39.989 0 Td [(the)-333(comm)27(unication)-333(con)28(text.)]TJ -15.082 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger.)]TJ 0 g 0 G - 139.477 -139.02 Td [(124)]TJ + 139.477 -430.483 Td [(123)]TJ 0 g 0 G ET endstream endobj -1678 0 obj +1696 0 obj << -/Length 3661 +/Length 1632 >> stream 0 g 0 G 0 g 0 G +0 g 0 G +0 g 0 G BT -/F16 11.9552 Tf 99.895 706.129 Td [(mm)]TJ +/F16 14.3462 Tf 150.705 680.226 Td [(psb)]TJ ET q -1 0 0 1 123.118 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +1 0 0 1 175.972 680.425 cm +[]0 d 0 J 0.398 w 0 0 m 4.842 0 l S Q BT -/F16 11.9552 Tf 127.153 706.129 Td [(mat)]TJ +/F16 14.3462 Tf 180.814 680.226 Td [(set)]TJ ET q -1 0 0 1 150.936 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +1 0 0 1 201.789 680.425 cm +[]0 d 0 J 0.398 w 0 0 m 4.842 0 l S Q BT -/F16 11.9552 Tf 154.971 706.129 Td [(read)-467(|)-467(Read)-466(a)-467(sparse)-467(matrix)-467(from)-467(a)-467(\014le)-466(in)-467(the)]TJ -55.076 -13.948 Td [(MatrixMark)31(et)-375(format)]TJ/F27 9.9626 Tf 1.377 -24.367 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.009 0 Td [(m)-50(m)]TJ +/F16 14.3462 Tf 206.631 680.226 Td [(errv)31(erb)-31(osit)31(y|Sets)-375(the)-375(v)31(erb)-31(osit)32(y)-376(of)-375(error)]TJ -55.926 -17.933 Td [(messages.)]TJ/F27 9.9626 Tf 1.377 -35.768 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 30.082 0 Td [(p)-158(s)-157(b)]TJ ET q -1 0 0 1 148.479 668.014 cm +1 0 0 1 202.473 626.724 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 151.965 667.814 Td [(m)-50(a)-50(t)]TJ +/F8 9.9626 Tf 207.032 626.525 Td [(s)-158(e)-157(t)]TJ ET q -1 0 0 1 171.214 668.014 cm +1 0 0 1 224.574 626.724 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 174.701 667.814 Td [(r)-50(e)-50(a)-50(d)-155(\050)-139(a)-228(,)-911(i)-149(r)-150(e)-149(t)-460(,)-897(i)-134(u)-135(n)-135(i)-135(t)-431(,)-890(f)-129(i)-129(l)-129(e)-129(n)-129(a)-129(m)-129(e)-235(\051)]TJ +/F8 9.9626 Tf 229.133 626.525 Td [(e)-158(r)-157(r)-158(v)-158(e)-157(r)-158(b)-157(o)-158(s)-158(i)-157(t)-158(y)-263(\050)-142(v)-142(\051)]TJ 0 g 0 G 0 g 0 G 0 g 0 G -/F27 9.9626 Tf -74.806 -17.933 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf -78.428 -17.933 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G /F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(\014lename)]TJ -0 g 0 G -/F8 9.9626 Tf 46.513 0 Td [(The)-333(name)-334(of)-333(the)-333(\014le)-334(to)-333(b)-28(e)-333(read.)]TJ -21.606 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-435(as:)-648(a)-435(c)27(h)1(arac)-1(ter)-435(v)56(ariable)-435(con)28(taining)-436(a)-435(v)56(alid)-435(\014le)-435(name,)-461(or)]TJ/F30 9.9626 Tf 297.915 0 Td [(-)]TJ/F8 9.9626 Tf 5.231 0 Td [(,)-461(in)]TJ -303.146 -11.956 Td [(whic)28(h)-302(cas)-1(e)-302(the)-302(default)-302(input)-302(unit)-302(5)-303(\050i.e.)-434(standard)-302(input)-302(in)-302(Unix)-302(jargon\051)-302(is)]TJ 0 -11.955 Td [(used.)-444(Default:)]TJ/F30 9.9626 Tf 66.058 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -96.195 -19.925 Td [(iunit)]TJ -0 g 0 G -/F8 9.9626 Tf 28.532 0 Td [(The)-333(F)83(ortran)-333(\014le)-334(un)1(it)-334(n)28(um)28(b)-28(er.)]TJ -3.625 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)-444(Only)-333(me)-1(ani)1(ngful)-334(if)-333(\014lename)-333(is)-334(not)]TJ/F30 9.9626 Tf 286.288 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -316.425 -21.918 Td [(On)-383(Return)]TJ -0 g 0 G -0 g 0 G - 0 -19.925 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(sparse)-334(matrix)-333(read)-333(from)-334(\014le.)]TJ 14.356 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ -ET -q -1 0 0 1 312.036 452.82 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 315.174 452.621 Td [(Tspmat)]TJ -ET -q -1 0 0 1 347.183 452.82 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 350.322 452.621 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -271.348 -19.925 Td [(iret)]TJ + 0 -19.926 Td [(v)]TJ 0 g 0 G -/F8 9.9626 Tf 22.589 0 Td [(Error)-333(co)-28(de.)]TJ 2.318 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ +/F8 9.9626 Tf 11.028 0 Td [(the)-333(v)27(erb)-27(osit)27(y)-333(lev)28(el)]TJ 13.878 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger.)]TJ 0 g 0 G - 139.477 -318.348 Td [(125)]TJ + 139.477 -430.483 Td [(124)]TJ 0 g 0 G ET endstream endobj -1684 0 obj +1702 0 obj << -/Length 3696 +/Length 2103 >> stream 0 g 0 G 0 g 0 G +0 g 0 G +0 g 0 G BT -/F16 11.9552 Tf 150.705 706.129 Td [(mm)]TJ +/F16 14.3462 Tf 99.895 680.226 Td [(psb)]TJ ET q -1 0 0 1 173.928 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +1 0 0 1 125.163 680.425 cm +[]0 d 0 J 0.398 w 0 0 m 4.842 0 l S Q BT -/F16 11.9552 Tf 177.963 706.129 Td [(arra)31(y)]TJ +/F16 14.3462 Tf 130.004 680.226 Td [(set)]TJ ET q -1 0 0 1 209.557 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +1 0 0 1 150.979 680.425 cm +[]0 d 0 J 0.398 w 0 0 m 4.842 0 l S Q BT -/F16 11.9552 Tf 213.592 706.129 Td [(read)-504(|)-504(Read)-504(a)-504(dense)-504(ar)1(ra)31(y)-504(from)-504(a)-504(\014le)-504(in)-504(the)]TJ -62.887 -13.948 Td [(MatrixMark)31(et)-375(format)]TJ/F27 9.9626 Tf 1.377 -24.367 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.373 0 Td [(m)-86(m)]TJ +/F16 14.3462 Tf 155.821 680.226 Td [(erraction|Set)-375(the)-375(t)31(yp)-31(e)-375(of)-375(action)-375(to)-375(b)-31(e)]TJ -55.926 -17.933 Td [(tak)31(en)-375(up)-31(on)-375(error)-375(condition.)]TJ/F27 9.9626 Tf 1.377 -35.768 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 30.09 0 Td [(p)-158(s)-159(b)]TJ ET q -1 0 0 1 200.38 668.014 cm +1 0 0 1 151.695 626.724 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 204.23 667.814 Td [(a)-86(r)-87(r)-86(a)-87(y)]TJ +/F8 9.9626 Tf 156.263 626.525 Td [(s)-159(e)-158(t)]TJ ET q -1 0 0 1 232.16 668.014 cm +1 0 0 1 173.829 626.724 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 236.01 667.814 Td [(r)-86(e)-87(a)-86(d)-192(\050)-121(b)-191(,)-910(i)-150(r)-149(e)-150(t)-460(,)-896(i)-135(u)-135(n)-135(i)-135(t)-431(,)-890(f)-129(i)-129(l)-129(e)-129(n)-129(a)-129(m)-129(e)-234(\051)]TJ -0 g 0 G -0 g 0 G -0 g 0 G -/F27 9.9626 Tf -85.305 -17.933 Td [(T)32(yp)-32(e:)]TJ -0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +/F8 9.9626 Tf 178.396 626.525 Td [(e)-159(r)-158(r)-158(a)-159(c)-158(t)-159(i)-158(o)-159(n)-264(\050)-265(e)-160(r)-160(r)]TJ +ET +q +1 0 0 1 256.582 626.724 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 261.163 626.525 Td [(a)-160(c)-160(t)-265(\051)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(\014lename)]TJ +/F27 9.9626 Tf -161.268 -17.933 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 46.513 0 Td [(The)-333(name)-334(of)-333(the)-333(\014le)-334(to)-333(b)-28(e)-333(read.)]TJ -21.607 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-435(as:)-648(a)-435(c)28(haracte)-1(r)-435(v)56(ariable)-435(con)28(taining)-435(a)-436(v)56(alid)-435(\014le)-435(name,)-461(or)]TJ/F30 9.9626 Tf 297.915 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(,)-461(in)]TJ -303.145 -11.956 Td [(whic)28(h)-302(case)-303(the)-302(default)-302(input)-302(unit)-302(5)-303(\050i.e.)-434(standard)-302(input)-302(in)-302(Unix)-302(jargon\051)-302(is)]TJ 0 -11.955 Td [(used.)-444(Default:)]TJ/F30 9.9626 Tf 66.057 0 Td [(-)]TJ/F8 9.9626 Tf 5.231 0 Td [(.)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -96.195 -19.925 Td [(iunit)]TJ +/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G -/F8 9.9626 Tf 28.532 0 Td [(The)-333(F)83(ortran)-333(\014le)-334(u)1(nit)-334(n)28(um)28(b)-28(er.)]TJ -3.625 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(alue.)-444(Only)-333(me)-1(an)1(ingful)-334(if)-333(\014lename)-333(is)-334(not)]TJ/F30 9.9626 Tf 286.288 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -316.425 -21.918 Td [(On)-383(Return)]TJ + 0 -19.926 Td [(err)]TJ +ET +q +1 0 0 1 115.271 568.941 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 118.708 568.741 Td [(act)]TJ 0 g 0 G +/F8 9.9626 Tf 20.098 0 Td [(the)-333(t)27(yp)-27(e)-334(of)-333(action.)]TJ -14.004 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger.)-444(P)27(ossible)-333(v)56(alues)-1(:)]TJ/F30 9.9626 Tf 180.269 0 Td [(psb_act_ret)]TJ/F8 9.9626 Tf 57.533 0 Td [(,)]TJ/F30 9.9626 Tf 6.089 0 Td [(psb_act_abort)]TJ/F8 9.9626 Tf 67.994 0 Td [(.)]TJ 0 g 0 G - 0 -19.925 Td [(b)]TJ + -172.408 -430.483 Td [(125)]TJ 0 g 0 G -/F8 9.9626 Tf 11.346 0 Td [(Rigth)-333(hand)-334(side\050s\051.)]TJ 13.561 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(An)-310(arra)28(y)-310(of)-310(t)28(yp)-28(e)-310(real)-310(or)-310(complex,)-315(ran)1(k)-310(1)-310(or)-310(2)-310(and)-310(ha)28(ving)-310(the)-310(ALLOCA)83(T-)]TJ 0 -11.955 Td [(ABLE)-334(attribute;)-334(will)-333(b)-28(e)-334(allo)-27(c)-1(ated)-333(and)-334(\014lled)-334(in)-333(if)-334(the)-334(input)-333(\014le)-334(con)28(tains)-334(a)]TJ 0 -11.955 Td [(righ)28(t)-333(hand)-334(side,)-333(otherwise)-333(will)-334(b)-27(e)-334(left)-333(in)-333(the)-334(UNALLOCA)84(TED)-334(state.)]TJ +ET + +endstream +endobj +1708 0 obj +<< +/Length 538 +>> +stream 0 g 0 G -/F27 9.9626 Tf -24.907 -19.925 Td [(iret)]TJ 0 g 0 G -/F8 9.9626 Tf 22.589 0 Td [(Error)-333(co)-28(de.)]TJ 2.318 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detected.)]TJ +BT +/F16 14.3462 Tf 150.705 706.129 Td [(9)-1125(Utilities)]TJ/F8 9.9626 Tf 0 -21.821 Td [(W)83(e)-412(ha)27(v)28(e)-412(som)-1(e)-412(utilities)-413(a)28(v)55(ai)1(lable)-413(for)-413(input)-412(and)-413(output)-412(of)-413(sparse)-413(matrices;)-452(the)]TJ 0 -11.955 Td [(in)28(terfaces)-334(to)-333(these)-333(routines)-334(are)-333(a)28(v)55(ailable)-333(in)-333(the)-334(mo)-27(dule)]TJ/F30 9.9626 Tf 241.843 0 Td [(psb_util_mod)]TJ/F8 9.9626 Tf 62.764 0 Td [(.)]TJ 0 g 0 G - 139.477 -294.437 Td [(126)]TJ + -140.224 -581.915 Td [(126)]TJ 0 g 0 G ET endstream endobj -1691 0 obj +1713 0 obj << -/Length 4176 +/Length 4792 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 99.895 706.129 Td [(mm)]TJ -ET -q -1 0 0 1 123.118 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 127.153 706.129 Td [(mat)]TJ +/F16 11.9552 Tf 103.166 706.129 Td [(h)31(b)]TJ ET q -1 0 0 1 150.936 706.328 cm +1 0 0 1 118.544 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 154.971 706.129 Td [(write)-531(|)-532(W)94(rite)-532(a)-531(sparse)-531(matrix)-532(to)-531(a)-532(\014le)-531(in)-531(the)]TJ -55.076 -13.948 Td [(MatrixMark)31(et)-375(format)]TJ/F27 9.9626 Tf 1.377 -24.367 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.175 0 Td [(m)-67(m)]TJ -ET -q -1 0 0 1 148.977 668.014 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F8 9.9626 Tf 152.63 667.814 Td [(m)-67(a)-66(t)]TJ +/F16 11.9552 Tf 122.579 706.129 Td [(read)-274(|)-273(Read)-274(a)-273(sparse)-274(matrix)-274(from)-273(a)-274(\014le)-273(in)-274(the)-274(Harw)32(ell{)]TJ -22.684 -13.948 Td [(Bo)-31(eing)-375(format)]TJ/F27 9.9626 Tf 1.377 -24.367 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.554 0 Td [(h)-105(b)]TJ ET q -1 0 0 1 172.377 668.014 cm +1 0 0 1 144.579 668.014 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 176.029 667.814 Td [(w)-67(r)-66(i)-67(t)-67(e)-172(\050)-139(a)-227(,)-885(m)-124(t)-123(i)-124(t)-124(l)-123(e)-409(,)-910(i)-150(r)-149(e)-150(t)-460(,)-896(i)-135(u)-135(n)-135(i)-135(t)-431(,)-890(f)-129(i)-129(l)-129(e)-129(n)-129(a)-129(m)-129(e)-234(\051)]TJ +/F8 9.9626 Tf 148.61 667.814 Td [(r)-105(e)-104(a)-105(d)-210(\050)-139(a)-228(,)-911(i)-149(r)-150(e)-149(t)-460(,)-896(i)-135(u)-135(n)-135(i)-135(t)-431(,)-877(f)-116(i)-116(l)-116(e)-117(n)-116(a)-116(m)-116(e)-393(,)-776(b)-191(,)-902(m)-142(t)-141(i)-141(t)-141(l)-142(e)-247(\051)]TJ 0 g 0 G 0 g 0 G 0 g 0 G -/F27 9.9626 Tf -76.134 -17.933 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf -48.715 -17.933 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G /F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G +0 g 0 G + 0 -19.925 Td [(\014lename)]TJ +0 g 0 G +/F8 9.9626 Tf 46.513 0 Td [(The)-333(name)-334(of)-333(the)-333(\014le)-334(to)-333(b)-28(e)-333(read.)]TJ -21.606 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-435(as:)-648(a)-435(c)27(h)1(arac)-1(ter)-435(v)56(ariable)-435(con)28(taining)-436(a)-435(v)56(alid)-435(\014le)-435(name,)-461(or)]TJ/F30 9.9626 Tf 297.915 0 Td [(-)]TJ/F8 9.9626 Tf 5.231 0 Td [(,)-461(in)]TJ -303.146 -11.956 Td [(whic)28(h)-302(cas)-1(e)-302(the)-302(default)-302(input)-302(unit)-302(5)-303(\050i.e.)-434(standard)-302(input)-302(in)-302(Unix)-302(jargon\051)-302(is)]TJ 0 -11.955 Td [(used.)-444(Default:)]TJ/F30 9.9626 Tf 66.058 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -96.195 -19.925 Td [(iunit)]TJ +0 g 0 G +/F8 9.9626 Tf 28.532 0 Td [(The)-333(F)83(ortran)-333(\014le)-334(un)1(it)-334(n)28(um)28(b)-28(er.)]TJ -3.625 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)-444(Only)-333(me)-1(ani)1(ngful)-334(if)-333(\014lename)-333(is)-334(not)]TJ/F30 9.9626 Tf 286.288 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -316.425 -21.918 Td [(On)-383(Return)]TJ +0 g 0 G 0 g 0 G 0 -19.925 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(sparse)-334(matrix)-333(to)-333(b)-28(e)-333(written.)]TJ 14.356 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +/F8 9.9626 Tf 10.551 0 Td [(the)-333(sparse)-334(matrix)-333(read)-333(from)-334(\014le.)]TJ 14.356 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG /F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 312.036 586.32 cm +1 0 0 1 312.036 452.82 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 315.174 586.121 Td [(Tspmat)]TJ +/F30 9.9626 Tf 315.174 452.621 Td [(Tspmat)]TJ ET q -1 0 0 1 347.183 586.32 cm +1 0 0 1 347.183 452.82 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 350.322 586.121 Td [(type)]TJ +/F30 9.9626 Tf 350.322 452.621 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -271.348 -19.926 Td [(m)32(title)]TJ -0 g 0 G -/F8 9.9626 Tf 34.738 0 Td [(Matrix)-333(title.)]TJ -9.831 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(A)-299(c)28(harac)28(h)28(ter)-299(v)55(ariable)-299(h)1(olding)-299(a)-299(descriptiv)28(e)-299(title)-299(for)-299(the)-299(matrix)-298(to)-299(b)-28(e)-299(writ-)]TJ 0 -11.955 Td [(ten)-333(to)-334(\014le.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -19.925 Td [(\014lename)]TJ -0 g 0 G -/F8 9.9626 Tf 46.513 0 Td [(The)-333(name)-334(of)-333(the)-333(\014le)-334(to)-333(b)-28(e)-333(written)-333(to.)]TJ -21.606 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-435(as:)-648(a)-435(c)27(h)1(arac)-1(ter)-435(v)56(ariable)-435(con)28(taining)-436(a)-435(v)56(alid)-435(\014le)-435(name,)-461(or)]TJ/F30 9.9626 Tf 297.915 0 Td [(-)]TJ/F8 9.9626 Tf 5.231 0 Td [(,)-461(in)]TJ -303.146 -11.955 Td [(whic)28(h)-281(case)-280(the)-280(default)-281(output)-280(unit)-280(6)-281(\050i.e.)-426(s)-1(t)1(andard)-281(output)-280(in)-280(Unix)-281(jargon\051)]TJ 0 -11.955 Td [(is)-333(used.)-445(Default:)]TJ/F30 9.9626 Tf 76.076 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -106.213 -19.925 Td [(iunit)]TJ +/F27 9.9626 Tf -271.348 -19.925 Td [(b)]TJ 0 g 0 G -/F8 9.9626 Tf 28.532 0 Td [(The)-333(F)83(ortran)-333(\014le)-334(un)1(it)-334(n)28(um)28(b)-28(er.)]TJ -3.625 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)-444(Only)-333(me)-1(ani)1(ngful)-334(if)-333(\014lename)-333(is)-334(not)]TJ/F30 9.9626 Tf 286.288 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(.)]TJ +/F8 9.9626 Tf 11.347 0 Td [(Rigth)-333(hand)-333(s)-1(i)1(de\050s)-1(\051.)]TJ 13.56 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(Optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(An)-282(ar)1(ra)27(y)-281(of)-282(t)28(yp)-28(e)-281(real)-282(or)-281(complex,)-292(rank)-282(2)-281(and)-282(ha)28(ving)-281(the)-282(ALLOCA)83(T)84(ABLE)]TJ 0 -11.956 Td [(attribute;)-409(will)-384(b)-28(e)-384(allo)-28(cated)-384(an)1(d)-384(\014lled)-384(in)-384(if)-384(the)-384(input)-384(\014le)-384(con)28(tains)-384(a)-384(righ)28(t)]TJ 0 -11.955 Td [(hand)-333(side,)-334(otherwise)-333(will)-333(b)-28(e)-333(left)-334(in)-333(the)-333(UNALLOCA)83(TED)-333(state.)]TJ 0 g 0 G -/F27 9.9626 Tf -316.425 -21.918 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf -24.907 -19.925 Td [(m)32(title)]TJ 0 g 0 G +/F8 9.9626 Tf 34.738 0 Td [(Matrix)-333(title.)]TJ -9.831 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(Optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(A)-405(c)28(harac)28(h)28(ter)-405(v)56(ariable)-405(of)-405(length)-404(72)-405(holding)-405(a)-404(cop)27(y)-404(of)-405(the)-405(matrix)-404(title)-405(as)]TJ 0 -11.956 Td [(sp)-28(eci\014ed)-333(b)28(y)-334(the)-333(Harw)28(ell-Bo)-28(eing)-333(format)-334(and)-333(con)28(tained)-333(in)-334(the)-333(input)-333(\014le.)]TJ 0 g 0 G - 0 -19.925 Td [(iret)]TJ +/F27 9.9626 Tf -24.907 -19.925 Td [(iret)]TJ 0 g 0 G -/F8 9.9626 Tf 22.589 0 Td [(Error)-333(co)-28(de.)]TJ 2.318 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detected.)]TJ +/F8 9.9626 Tf 22.589 0 Td [(Error)-333(co)-28(de.)]TJ 2.318 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ 0 g 0 G - 139.477 -262.557 Td [(127)]TJ + 139.477 -194.811 Td [(127)]TJ 0 g 0 G ET endstream endobj -1698 0 obj +1721 0 obj << -/Length 3364 +/Length 5239 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 150.705 706.129 Td [(mm)]TJ -ET -q -1 0 0 1 173.928 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 177.963 706.129 Td [(arra)31(y)]TJ +/F16 11.9552 Tf 150.705 706.129 Td [(h)31(b)]TJ ET q -1 0 0 1 209.557 706.328 cm +1 0 0 1 166.082 706.328 cm []0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F16 11.9552 Tf 213.592 706.129 Td [(write)-438(|)-438(W)93(rite)-438(a)-438(dense)-438(arra)31(y)-438(from)-438(a)-438(\014le)-439(in)-438(the)]TJ -62.887 -13.948 Td [(MatrixMark)31(et)-375(format)]TJ/F27 9.9626 Tf 1.377 -24.367 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.492 0 Td [(m)-99(m)]TJ -ET -q -1 0 0 1 200.739 668.014 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S -Q -BT -/F8 9.9626 Tf 204.709 667.814 Td [(a)-98(r)-99(r)-98(a)-99(y)]TJ +/F16 11.9552 Tf 170.117 706.129 Td [(write)-357(|)-357(W)93(rite)-357(a)-357(sparse)-357(matrix)-358(to)-357(a)-357(\014le)-357(in)-357(the)-357(Harw)31(ell{)]TJ -19.412 -13.948 Td [(Bo)-31(eing)-375(format)]TJ/F27 9.9626 Tf 1.377 -24.367 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.733 0 Td [(h)-123(b)]TJ ET q -1 0 0 1 233.237 668.014 cm +1 0 0 1 195.926 668.014 cm []0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F8 9.9626 Tf 237.207 667.814 Td [(w)-99(r)-98(i)-98(t)-99(e)-204(\050)-120(b)-191(,)-911(i)-149(r)-150(e)-149(t)-461(,)-896(i)-134(u)-135(n)-135(i)-135(t)-431(,)-890(f)-129(i)-129(l)-129(e)-129(n)-129(a)-129(m)-129(e)-235(\051)]TJ +/F8 9.9626 Tf 200.137 667.814 Td [(w)-123(r)-122(i)-123(t)-123(e)-228(\050)-139(a)-228(,)-910(i)-150(r)-149(e)-150(t)-460(,)-896(i)-135(u)-135(n)-135(i)-135(t)-431(,)-877(f)-116(i)-116(l)-116(e)-116(n)-116(a)-116(m)-117(e)-393(,)-821(k)-60(e)-60(y)-281(,)-853(r)-92(h)-91(s)-345(,)-902(m)-141(t)-142(i)-141(t)-141(l)-141(e)-247(\051)]TJ 0 g 0 G 0 g 0 G 0 g 0 G -/F27 9.9626 Tf -86.502 -17.933 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf -49.432 -17.933 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G /F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(b)]TJ -0 g 0 G -/F8 9.9626 Tf 11.346 0 Td [(Rigth)-333(hand)-334(side\050s\051.)]TJ 13.56 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(An)-333(arra)27(y)-333(of)-333(t)28(yp)-28(e)-333(real)-334(or)-333(complex,)-333(rank)-334(1)-333(or)-333(2;)-334(will)-333(b)-28(e)-333(written..)]TJ + 0 -19.925 Td [(a)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -19.926 Td [(\014lename)]TJ +/F8 9.9626 Tf 10.551 0 Td [(the)-333(sparse)-334(matrix)-333(to)-333(b)-28(e)-333(written.)]TJ 14.355 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(required)]TJ/F8 9.9626 Tf 41.898 0 Td [(.)]TJ -67.082 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ +ET +q +1 0 0 1 362.845 586.32 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 365.983 586.121 Td [(Tspmat)]TJ +ET +q +1 0 0 1 397.993 586.32 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 401.131 586.121 Td [(type)]TJ 0 g 0 G -/F8 9.9626 Tf 46.513 0 Td [(The)-333(name)-334(of)-333(the)-333(\014le)-334(to)-333(b)-28(e)-333(written.)]TJ -21.607 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-435(as:)-648(a)-435(c)28(haracte)-1(r)-435(v)56(ariable)-435(con)28(taining)-435(a)-436(v)56(alid)-435(\014le)-435(name,)-461(or)]TJ/F30 9.9626 Tf 297.915 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(,)-461(in)]TJ -303.145 -11.955 Td [(whic)28(h)-302(case)-303(the)-302(default)-302(input)-302(unit)-302(5)-303(\050i.e.)-434(standard)-302(input)-302(in)-302(Unix)-302(jargon\051)-302(is)]TJ 0 -11.955 Td [(used.)-444(Default:)]TJ/F30 9.9626 Tf 66.057 0 Td [(-)]TJ/F8 9.9626 Tf 5.231 0 Td [(.)]TJ +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -96.195 -19.926 Td [(iunit)]TJ +/F27 9.9626 Tf -271.347 -19.926 Td [(b)]TJ 0 g 0 G -/F8 9.9626 Tf 28.532 0 Td [(The)-333(F)83(ortran)-333(\014le)-334(u)1(nit)-334(n)28(um)28(b)-28(er.)]TJ -3.625 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(alue.)-444(Only)-333(me)-1(an)1(ingful)-334(if)-333(\014lename)-333(is)-334(not)]TJ/F30 9.9626 Tf 286.288 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(.)]TJ +/F8 9.9626 Tf 11.346 0 Td [(Rigth)-333(hand)-334(sid)1(e)-1(.)]TJ 13.56 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(Optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(An)-282(arr)1(a)27(y)-281(of)-282(t)28(yp)-28(e)-281(real)-282(or)-281(complex,)-292(rank)-282(1)-281(and)-282(ha)28(ving)-281(the)-282(ALLOCA)83(T)84(ABLE)]TJ 0 -11.955 Td [(attribute;)-409(will)-384(b)-28(e)-384(allo)-28(cated)-384(and)-383(\014lled)-384(in)-384(if)-384(the)-384(input)-384(\014le)-384(con)28(tains)-384(a)-384(righ)28(t)]TJ 0 -11.955 Td [(hand)-333(side.)]TJ 0 g 0 G -/F27 9.9626 Tf -316.425 -21.918 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf -24.906 -19.926 Td [(\014lename)]TJ 0 g 0 G +/F8 9.9626 Tf 46.513 0 Td [(The)-333(name)-334(of)-333(the)-333(\014le)-334(to)-333(b)-28(e)-333(written)-333(to.)]TJ -21.607 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.761 -11.955 Td [(Sp)-28(eci\014ed)-435(as:)-648(a)-435(c)27(haracter)-435(v)56(ariable)-435(con)27(tain)1(ing)-436(a)-435(v)56(alid)-435(\014le)-435(name)-1(,)-460(or)]TJ/F30 9.9626 Tf 297.916 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(,)-461(in)]TJ -303.146 -11.955 Td [(whic)28(h)-281(case)-280(the)-281(d)1(e)-1(f)1(ault)-281(output)-280(unit)-280(6)-281(\050i.e.)-427(stand)1(ard)-281(output)-280(in)-280(Unix)-281(jargon\051)]TJ 0 -11.955 Td [(is)-333(used.)-445(Default:)]TJ/F30 9.9626 Tf 76.076 0 Td [(-)]TJ/F8 9.9626 Tf 5.231 0 Td [(.)]TJ 0 g 0 G - 0 -19.925 Td [(iret)]TJ +/F27 9.9626 Tf -106.213 -19.926 Td [(iunit)]TJ 0 g 0 G -/F8 9.9626 Tf 22.589 0 Td [(Error)-333(co)-28(de.)]TJ 2.318 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detected.)]TJ +/F8 9.9626 Tf 28.532 0 Td [(The)-333(F)83(ortran)-333(\014le)-334(u)1(nit)-334(n)28(um)28(b)-28(er.)]TJ -3.626 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.761 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)-444(Only)-334(meaningf)1(ul)-334(if)-333(\014lename)-333(is)-334(not)]TJ/F30 9.9626 Tf 286.289 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(.)]TJ 0 g 0 G - 139.477 -318.348 Td [(128)]TJ +/F27 9.9626 Tf -316.425 -19.925 Td [(k)32(ey)]TJ 0 g 0 G -ET - -endstream -endobj -1704 0 obj -<< -/Length 1212 ->> -stream +/F8 9.9626 Tf 22.008 0 Td [(Matrix)-333(k)28(ey)83(.)]TJ 2.899 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(Optional)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(A)-385(c)28(harac)28(h)28(ter)-385(v)56(ariable)-385(of)-385(length)-384(8)-385(holding)-385(the)-384(matrix)-385(k)28(ey)-385(as)-385(sp)-28(eci\014ed)-384(b)27(y)]TJ 0 -11.955 Td [(the)-333(Harw)27(ell-Bo)-27(eing)-334(format)-333(and)-333(to)-334(b)-27(e)-334(written)-333(to)-333(\014le.)]TJ 0 g 0 G +/F27 9.9626 Tf -24.907 -19.925 Td [(m)32(title)]TJ 0 g 0 G -BT -/F16 14.3462 Tf 99.895 706.129 Td [(10)-1125(Preconditioner)-375(routines)]TJ/F8 9.9626 Tf 0 -21.821 Td [(The)-310(base)-310(PSBLAS)-310(library)-310(con)28(tains)-310(the)-310(implemen)28(tation)-310(of)-310(t)28(w)27(o)-310(simple)-310(precondi-)]TJ 0 -11.955 Td [(tioning)-333(tec)27(hn)1(iques:)]TJ +/F8 9.9626 Tf 34.738 0 Td [(Matrix)-333(title.)]TJ -9.831 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(Optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(A)-318(c)28(harac)28(h)28(ter)-318(v)56(ariable)-318(of)-317(length)-318(72)-317(holding)-318(the)-317(matrix)-318(title)-318(as)-317(sp)-28(eci\014ed)-318(b)28(y)]TJ 0 -11.956 Td [(the)-333(Harw)27(ell-Bo)-27(eing)-334(format)-333(and)-333(to)-334(b)-27(e)-334(written)-333(to)-333(\014le.)]TJ 0 g 0 G -/F14 9.9626 Tf 14.944 -19.925 Td [(\017)]TJ +/F27 9.9626 Tf -24.907 -21.917 Td [(On)-383(Return)]TJ 0 g 0 G -/F8 9.9626 Tf 9.963 0 Td [(Diagonal)-333(Scaling)]TJ 0 g 0 G -/F14 9.9626 Tf -9.963 -19.926 Td [(\017)]TJ + 0 -19.926 Td [(iret)]TJ 0 g 0 G -/F8 9.9626 Tf 9.963 0 Td [(Blo)-28(c)28(k)-333(Jacobi)-334(with)-333(ILU\0500\051)-333(factorization)]TJ -24.907 -19.925 Td [(The)-364(supp)-27(orting)-364(data)-364(t)28(yp)-27(e)-364(and)-364(subroutine)-363(in)28(terfaces)-364(are)-364(de\014ned)-363(in)-364(the)-364(mo)-27(dule)]TJ/F30 9.9626 Tf 0 -11.955 Td [(psb_prec_mod)]TJ/F8 9.9626 Tf 62.764 0 Td [(.)-844(The)-466(old)-466(in)27(terfaces)]TJ/F30 9.9626 Tf 96.595 0 Td [(psb_precinit)]TJ/F8 9.9626 Tf 67.41 0 Td [(and)]TJ/F30 9.9626 Tf 20.698 0 Td [(psb_precbld)]TJ/F8 9.9626 Tf 62.18 0 Td [(are)-466(still)]TJ -309.647 -11.955 Td [(supp)-28(orted)-333(for)-333(bac)27(kw)28(ard)-333(compatibilit)28(y)]TJ +/F8 9.9626 Tf 22.589 0 Td [(Error)-333(co)-28(de.)]TJ 2.318 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detected.)]TJ 0 g 0 G - 164.384 -498.229 Td [(129)]TJ + 139.477 -139.02 Td [(128)]TJ 0 g 0 G ET endstream endobj -1710 0 obj +1728 0 obj << -/Length 4508 +/Length 3661 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 150.705 706.129 Td [(init)-375(|)-375(Initialize)-375(a)-375(preconditioner)]TJ +/F16 11.9552 Tf 99.895 706.129 Td [(mm)]TJ +ET +q +1 0 0 1 123.118 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 127.153 706.129 Td [(mat)]TJ +ET +q +1 0 0 1 150.936 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 154.971 706.129 Td [(read)-467(|)-467(Read)-466(a)-467(sparse)-467(matrix)-467(from)-467(a)-467(\014le)-466(in)-467(the)]TJ -55.076 -13.948 Td [(MatrixMark)31(et)-375(format)]TJ/F27 9.9626 Tf 1.377 -24.367 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.009 0 Td [(m)-50(m)]TJ +ET +q +1 0 0 1 148.479 668.014 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 151.965 667.814 Td [(m)-50(a)-50(t)]TJ +ET +q +1 0 0 1 171.214 668.014 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 174.701 667.814 Td [(r)-50(e)-50(a)-50(d)-155(\050)-139(a)-228(,)-911(i)-149(r)-150(e)-149(t)-460(,)-897(i)-134(u)-135(n)-135(i)-135(t)-431(,)-890(f)-129(i)-129(l)-129(e)-129(n)-129(a)-129(m)-129(e)-235(\051)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf 0 -18.389 Td [(call)-525(prec%init\050ptype,)-525(info\051)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ +/F27 9.9626 Tf -74.806 -17.933 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G /F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G 0 g 0 G - 0 -19.925 Td [(pt)32(yp)-32(e)]TJ + 0 -19.925 Td [(\014lename)]TJ 0 g 0 G -/F8 9.9626 Tf 33.465 0 Td [(the)-333(t)28(yp)-28(e)-334(of)-333(preconditioner.)-444(Scop)-28(e:)]TJ/F27 9.9626 Tf 153.092 0 Td [(global)]TJ/F8 9.9626 Tf -161.651 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(c)28(haracter)-334(stri)1(ng,)-334(see)-333(usage)-334(notes.)]TJ +/F8 9.9626 Tf 46.513 0 Td [(The)-333(name)-334(of)-333(the)-333(\014le)-334(to)-333(b)-28(e)-333(read.)]TJ -21.606 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-435(as:)-648(a)-435(c)27(h)1(arac)-1(ter)-435(v)56(ariable)-435(con)28(taining)-436(a)-435(v)56(alid)-435(\014le)-435(name,)-461(or)]TJ/F30 9.9626 Tf 297.915 0 Td [(-)]TJ/F8 9.9626 Tf 5.231 0 Td [(,)-461(in)]TJ -303.146 -11.956 Td [(whic)28(h)-302(cas)-1(e)-302(the)-302(default)-302(input)-302(unit)-302(5)-303(\050i.e.)-434(standard)-302(input)-302(in)-302(Unix)-302(jargon\051)-302(is)]TJ 0 -11.955 Td [(used.)-444(Default:)]TJ/F30 9.9626 Tf 66.058 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -19.926 Td [(On)-383(Exit)]TJ +/F27 9.9626 Tf -96.195 -19.925 Td [(iunit)]TJ +0 g 0 G +/F8 9.9626 Tf 28.532 0 Td [(The)-333(F)83(ortran)-333(\014le)-334(un)1(it)-334(n)28(um)28(b)-28(er.)]TJ -3.625 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)-444(Only)-333(me)-1(ani)1(ngful)-334(if)-333(\014lename)-333(is)-334(not)]TJ/F30 9.9626 Tf 286.288 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(.)]TJ 0 g 0 G +/F27 9.9626 Tf -316.425 -21.918 Td [(On)-383(Return)]TJ 0 g 0 G - 0 -19.925 Td [(prec)]TJ 0 g 0 G -/F8 9.9626 Tf 26.408 0 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -33.88 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.583 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(preconditioner)-333(data)-333(structure)]TJ + 0 -19.925 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.551 0 Td [(the)-333(sparse)-334(matrix)-333(read)-333(from)-334(\014le.)]TJ 14.356 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 197.538 0 Td [(psb)]TJ +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 389.467 514.589 cm +1 0 0 1 312.036 452.82 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 392.606 514.39 Td [(prec)]TJ +/F30 9.9626 Tf 315.174 452.621 Td [(Tspmat)]TJ ET q -1 0 0 1 414.155 514.589 cm +1 0 0 1 347.183 452.82 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 417.293 514.39 Td [(type)]TJ +/F30 9.9626 Tf 350.322 452.621 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -287.509 -19.926 Td [(info)]TJ -0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -31.23 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.034 -11.955 Td [(Error)-333(co)-28(de:)-444(if)-334(no)-333(error,)-333(0)-334(is)-333(returned.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ/F8 9.9626 Tf 37.058 0 Td [(Legal)-316(inputs)-315(to)-316(this)-316(subroutine)-315(are)-316(in)28(terpreted)-316(dep)-28(ending)-315(on)-316(the)]TJ/F11 9.9626 Tf 283.15 0 Td [(pty)-36(pe)]TJ/F8 9.9626 Tf -320.208 -11.955 Td [(string)-333(as)-334(follo)28(ws)]TJ -0 0 1 rg 0 0 1 RG -/F7 6.9738 Tf 69.932 3.615 Td [(4)]TJ -0 g 0 G -/F8 9.9626 Tf 4.47 -3.615 Td [(:)]TJ -0 g 0 G -/F27 9.9626 Tf -74.402 -19.925 Td [(NONE)]TJ -0 g 0 G -/F8 9.9626 Tf 39.048 0 Td [(No)-333(preconditioning,)-333(i.e.)-445(the)-333(preconditioner)-333(is)-334(just)-333(a)-333(cop)27(y)-333(op)-28(erator.)]TJ -0 g 0 G -/F27 9.9626 Tf -39.048 -19.926 Td [(DIA)32(G)]TJ -0 g 0 G -/F8 9.9626 Tf 35.464 0 Td [(Diagonal)-441(scaling;)-496(eac)28(h)-442(en)28(try)-441(of)-441(the)-442(input)-441(v)28(ector)-442(is)-441(m)27(ulti)1(plied)-442(b)28(y)-441(the)]TJ -10.557 -11.955 Td [(recipro)-28(cal)-346(of)-346(the)-346(sum)-345(of)-346(the)-346(absolute)-346(v)55(alues)-346(of)-346(th)1(e)-346(c)-1(o)-27(e\016cien)27(ts)-346(in)-345(the)-346(cor-)]TJ 0 -11.955 Td [(resp)-28(onding)-333(ro)28(w)-334(of)-333(matrix)]TJ/F11 9.9626 Tf 113.602 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(;)]TJ -0 g 0 G -/F27 9.9626 Tf -145.981 -19.925 Td [(BJA)32(C)]TJ -0 g 0 G -/F8 9.9626 Tf 35.672 0 Td [(Precondition)-249(b)28(y)-249(a)-249(factorization)-248(of)-249(the)-249(blo)-28(c)28(k-diagonal)-249(of)-249(matrix)]TJ/F11 9.9626 Tf 269.664 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(,)-266(where)]TJ -287.901 -11.956 Td [(blo)-28(c)28(k)-457(b)-28(oundaries)-457(are)-457(determined)-457(b)28(y)-457(the)-457(data)-457(allo)-28(cation)-457(b)-28(oundaries)-457(for)]TJ 0 -11.955 Td [(eac)28(h)-347(pro)-27(c)-1(ess;)-353(requires)-346(no)-347(comm)28(unication.)-484(Only)-347(the)-346(incomplete)-347(factoriza-)]TJ 0 -11.955 Td [(tion)]TJ/F11 9.9626 Tf 20.478 0 Td [(I)-78(LU)]TJ/F8 9.9626 Tf 19.83 0 Td [(\0500\051)-333(is)-334(curren)28(tly)-333(implemen)28(ted.)]TJ -0 g 0 G -ET -q -1 0 0 1 150.705 129.78 cm -[]0 d 0 J 0.398 w 0 0 m 137.482 0 l S -Q -BT -/F32 5.9776 Tf 161.797 123.138 Td [(4)]TJ/F31 7.9701 Tf 4.151 -2.812 Td [(The)-354(string)-354(is)-354(c)-1(a)1(se)-1(-)1(i)-1(nsensitiv)30(e)]TJ +/F27 9.9626 Tf -271.348 -19.925 Td [(iret)]TJ 0 g 0 G +/F8 9.9626 Tf 22.589 0 Td [(Error)-333(co)-28(de.)]TJ 2.318 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ 0 g 0 G -/F8 9.9626 Tf 149.14 -29.888 Td [(130)]TJ + 139.477 -318.348 Td [(129)]TJ 0 g 0 G ET endstream endobj -1719 0 obj +1734 0 obj << -/Length 7751 +/Length 3696 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 99.895 706.129 Td [(build)-375(|)-375(Builds)-375(a)-375(preconditioner)]TJ -0 g 0 G -0 g 0 G -/F30 9.9626 Tf 0 -19.764 Td [(call)-525(prec%build\050a,)-525(desc_a,)-525(info[,amold,vmold,imold]\051)]TJ -0 g 0 G -/F27 9.9626 Tf 0 -24.132 Td [(T)32(yp)-32(e:)]TJ -0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ -0 g 0 G -/F27 9.9626 Tf -33.797 -22.879 Td [(On)-383(En)32(try)]TJ -0 g 0 G -0 g 0 G - 0 -22.879 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(system)-334(sparse)-333(matrix.)-445(Scop)-27(e:)]TJ/F27 9.9626 Tf 148.886 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -134.53 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(,)-333(target.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(sparse)-333(matrix)-334(data)-333(structure)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 194.05 0 Td [(psb)]TJ +/F16 11.9552 Tf 150.705 706.129 Td [(mm)]TJ ET q -1 0 0 1 335.171 580.809 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 173.928 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F30 9.9626 Tf 338.309 580.61 Td [(Tspmat)]TJ +/F16 11.9552 Tf 177.963 706.129 Td [(arra)31(y)]TJ ET q -1 0 0 1 370.319 580.809 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 209.557 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F30 9.9626 Tf 373.457 580.61 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -294.484 -22.879 Td [(prec)]TJ -0 g 0 G -/F8 9.9626 Tf 26.408 0 Td [(the)-333(preconditioner.)]TJ -1.501 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-222(as:)-389(an)-222(already)-222(initialized)-222(precondtioner)-222(data)-223(structure)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 273.115 0 Td [(psb)]TJ +/F16 11.9552 Tf 213.592 706.129 Td [(read)-504(|)-504(Read)-504(a)-504(dense)-504(ar)1(ra)31(y)-504(from)-504(a)-504(\014le)-504(in)-504(the)]TJ -62.887 -13.948 Td [(MatrixMark)31(et)-375(format)]TJ/F27 9.9626 Tf 1.377 -24.367 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.373 0 Td [(m)-86(m)]TJ ET q -1 0 0 1 414.236 510.11 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 200.38 668.014 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F30 9.9626 Tf 417.374 509.91 Td [(prec)]TJ +/F8 9.9626 Tf 204.23 667.814 Td [(a)-86(r)-87(r)-86(a)-87(y)]TJ ET q -1 0 0 1 438.923 510.11 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 232.16 668.014 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F30 9.9626 Tf 442.061 509.91 Td [(type)]TJ +/F8 9.9626 Tf 236.01 667.814 Td [(r)-86(e)-87(a)-86(d)-192(\050)-121(b)-191(,)-910(i)-150(r)-149(e)-150(t)-460(,)-896(i)-135(u)-135(n)-135(i)-135(t)-431(,)-890(f)-129(i)-129(l)-129(e)-129(n)-129(a)-129(m)-129(e)-234(\051)]TJ 0 g 0 G 0 g 0 G -/F27 9.9626 Tf -342.166 -34.833 Td [(desc)]TJ -ET -q -1 0 0 1 121.81 475.276 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 125.247 475.077 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(the)-333(problem)-334(comm)28(unication)-333(descriptor.)-445(Scop)-27(e:)]TJ/F27 9.9626 Tf 208.247 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -219.243 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(,)-333(target.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(comm)28(unication)-333(desc)-1(ri)1(ptor)-334(data)-333(structure)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 247.683 0 Td [(psb)]TJ -ET -q -1 0 0 1 388.803 439.41 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 391.942 439.211 Td [(desc)]TJ -ET -q -1 0 0 1 413.491 439.41 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 416.629 439.211 Td [(type)]TJ +/F27 9.9626 Tf -85.305 -17.933 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ 0 g 0 G -/F27 9.9626 Tf -337.655 -22.879 Td [(amold)]TJ +/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ 0 g 0 G -/F8 9.9626 Tf 35.374 0 Td [(The)-333(desired)-334(dynamic)-333(t)28(yp)-28(e)-333(for)-334(the)-333(in)28(ternal)-333(matrix)-334(storage.)]TJ -10.467 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(a)-333(class)-334(deriv)28(ed)-333(from)]TJ/F30 9.9626 Tf 203.349 0 Td [(psb)]TJ +0 g 0 G + 0 -19.925 Td [(\014lename)]TJ +0 g 0 G +/F8 9.9626 Tf 46.513 0 Td [(The)-333(name)-334(of)-333(the)-333(\014le)-334(to)-333(b)-28(e)-333(read.)]TJ -21.607 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-435(as:)-648(a)-435(c)28(haracte)-1(r)-435(v)56(ariable)-435(con)28(taining)-435(a)-436(v)56(alid)-435(\014le)-435(name,)-461(or)]TJ/F30 9.9626 Tf 297.915 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(,)-461(in)]TJ -303.145 -11.956 Td [(whic)28(h)-302(case)-303(the)-302(default)-302(input)-302(unit)-302(5)-303(\050i.e.)-434(standard)-302(input)-302(in)-302(Unix)-302(jargon\051)-302(is)]TJ 0 -11.955 Td [(used.)-444(Default:)]TJ/F30 9.9626 Tf 66.057 0 Td [(-)]TJ/F8 9.9626 Tf 5.231 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -96.195 -19.925 Td [(iunit)]TJ +0 g 0 G +/F8 9.9626 Tf 28.532 0 Td [(The)-333(F)83(ortran)-333(\014le)-334(u)1(nit)-334(n)28(um)28(b)-28(er.)]TJ -3.625 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(alue.)-444(Only)-333(me)-1(an)1(ingful)-334(if)-333(\014lename)-333(is)-334(not)]TJ/F30 9.9626 Tf 286.288 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -316.425 -21.918 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(b)]TJ +0 g 0 G +/F8 9.9626 Tf 11.346 0 Td [(Rigth)-333(hand)-334(side\050s\051.)]TJ 13.561 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(An)-310(arra)28(y)-310(of)-310(t)28(yp)-28(e)-310(real)-310(or)-310(complex,)-315(ran)1(k)-310(1)-310(or)-310(2)-310(and)-310(ha)28(ving)-310(the)-310(ALLOCA)83(T-)]TJ 0 -11.955 Td [(ABLE)-334(attribute;)-334(will)-333(b)-28(e)-334(allo)-27(c)-1(ated)-333(and)-334(\014lled)-334(in)-333(if)-334(the)-334(input)-333(\014le)-334(con)28(tains)-334(a)]TJ 0 -11.955 Td [(righ)28(t)-333(hand)-334(side,)-333(otherwise)-333(will)-334(b)-27(e)-334(left)-333(in)-333(the)-334(UNALLOCA)84(TED)-334(state.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.925 Td [(iret)]TJ +0 g 0 G +/F8 9.9626 Tf 22.589 0 Td [(Error)-333(co)-28(de.)]TJ 2.318 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detected.)]TJ +0 g 0 G + 139.477 -294.437 Td [(130)]TJ +0 g 0 G +ET + +endstream +endobj +1741 0 obj +<< +/Length 4176 +>> +stream +0 g 0 G +0 g 0 G +BT +/F16 11.9552 Tf 99.895 706.129 Td [(mm)]TJ ET q -1 0 0 1 344.47 368.711 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 123.118 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F30 9.9626 Tf 347.608 368.512 Td [(T)]TJ +/F16 11.9552 Tf 127.153 706.129 Td [(mat)]TJ ET q -1 0 0 1 353.466 368.711 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 150.936 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F30 9.9626 Tf 356.604 368.512 Td [(base)]TJ +/F16 11.9552 Tf 154.971 706.129 Td [(write)-531(|)-532(W)94(rite)-532(a)-531(sparse)-531(matrix)-532(to)-531(a)-532(\014le)-531(in)-531(the)]TJ -55.076 -13.948 Td [(MatrixMark)31(et)-375(format)]TJ/F27 9.9626 Tf 1.377 -24.367 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.175 0 Td [(m)-67(m)]TJ ET q -1 0 0 1 378.153 368.711 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 148.977 668.014 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F30 9.9626 Tf 381.291 368.512 Td [(sparse)]TJ +/F8 9.9626 Tf 152.63 667.814 Td [(m)-67(a)-66(t)]TJ ET q -1 0 0 1 413.301 368.711 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 172.377 668.014 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F30 9.9626 Tf 416.439 368.512 Td [(mat)]TJ/F8 9.9626 Tf 15.691 0 Td [(.)]TJ +/F8 9.9626 Tf 176.029 667.814 Td [(w)-67(r)-66(i)-67(t)-67(e)-172(\050)-139(a)-227(,)-885(m)-124(t)-123(i)-124(t)-124(l)-123(e)-409(,)-910(i)-150(r)-149(e)-150(t)-460(,)-896(i)-135(u)-135(n)-135(i)-135(t)-431(,)-890(f)-129(i)-129(l)-129(e)-129(n)-129(a)-129(m)-129(e)-234(\051)]TJ 0 g 0 G -/F27 9.9626 Tf -332.235 -22.879 Td [(vmold)]TJ 0 g 0 G -/F8 9.9626 Tf 35.852 0 Td [(The)-333(desired)-334(dynamic)-333(t)28(yp)-28(e)-333(for)-334(the)-333(in)28(ternal)-333(v)27(ector)-333(storage.)]TJ -10.945 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(a)-333(class)-334(deriv)28(ed)-333(from)]TJ/F30 9.9626 Tf 203.349 0 Td [(psb)]TJ +0 g 0 G +/F27 9.9626 Tf -76.134 -17.933 Td [(T)32(yp)-32(e:)]TJ +0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +0 g 0 G +/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.551 0 Td [(the)-333(sparse)-334(matrix)-333(to)-333(b)-28(e)-333(written.)]TJ 14.356 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(required)]TJ/F8 9.9626 Tf 41.899 0 Td [(.)]TJ -67.082 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 344.47 298.012 cm +1 0 0 1 312.036 586.32 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 347.608 297.812 Td [(T)]TJ +/F30 9.9626 Tf 315.174 586.121 Td [(Tspmat)]TJ ET q -1 0 0 1 353.466 298.012 cm +1 0 0 1 347.183 586.32 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 356.604 297.812 Td [(base)]TJ +/F30 9.9626 Tf 350.322 586.121 Td [(type)]TJ +0 g 0 G +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -271.348 -19.926 Td [(m)32(title)]TJ +0 g 0 G +/F8 9.9626 Tf 34.738 0 Td [(Matrix)-333(title.)]TJ -9.831 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(A)-299(c)28(harac)28(h)28(ter)-299(v)55(ariable)-299(h)1(olding)-299(a)-299(descriptiv)28(e)-299(title)-299(for)-299(the)-299(matrix)-298(to)-299(b)-28(e)-299(writ-)]TJ 0 -11.955 Td [(ten)-333(to)-334(\014le.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.925 Td [(\014lename)]TJ +0 g 0 G +/F8 9.9626 Tf 46.513 0 Td [(The)-333(name)-334(of)-333(the)-333(\014le)-334(to)-333(b)-28(e)-333(written)-333(to.)]TJ -21.606 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-435(as:)-648(a)-435(c)27(h)1(arac)-1(ter)-435(v)56(ariable)-435(con)28(taining)-436(a)-435(v)56(alid)-435(\014le)-435(name,)-461(or)]TJ/F30 9.9626 Tf 297.915 0 Td [(-)]TJ/F8 9.9626 Tf 5.231 0 Td [(,)-461(in)]TJ -303.146 -11.955 Td [(whic)28(h)-281(case)-280(the)-280(default)-281(output)-280(unit)-280(6)-281(\050i.e.)-426(s)-1(t)1(andard)-281(output)-280(in)-280(Unix)-281(jargon\051)]TJ 0 -11.955 Td [(is)-333(used.)-445(Default:)]TJ/F30 9.9626 Tf 76.076 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -106.213 -19.925 Td [(iunit)]TJ +0 g 0 G +/F8 9.9626 Tf 28.532 0 Td [(The)-333(F)83(ortran)-333(\014le)-334(un)1(it)-334(n)28(um)28(b)-28(er.)]TJ -3.625 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(alue.)-444(Only)-333(me)-1(ani)1(ngful)-334(if)-333(\014lename)-333(is)-334(not)]TJ/F30 9.9626 Tf 286.288 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -316.425 -21.918 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(iret)]TJ +0 g 0 G +/F8 9.9626 Tf 22.589 0 Td [(Error)-333(co)-28(de.)]TJ 2.318 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detected.)]TJ +0 g 0 G + 139.477 -262.557 Td [(131)]TJ +0 g 0 G ET -q -1 0 0 1 378.153 298.012 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q + +endstream +endobj +1747 0 obj +<< +/Length 3364 +>> +stream +0 g 0 G +0 g 0 G BT -/F30 9.9626 Tf 381.291 297.812 Td [(vect)]TJ +/F16 11.9552 Tf 150.705 706.129 Td [(mm)]TJ ET q -1 0 0 1 402.84 298.012 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 173.928 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F30 9.9626 Tf 405.978 297.812 Td [(type)]TJ/F8 9.9626 Tf 20.922 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -327.005 -22.878 Td [(imold)]TJ -0 g 0 G -/F8 9.9626 Tf 32.988 0 Td [(The)-333(desired)-334(dynamic)-333(t)28(yp)-28(e)-333(for)-334(th)1(e)-334(in)28(ternal)-333(in)28(te)-1(ger)-333(v)28(ector)-333(s)-1(t)1(o)-1(r)1(age)-1(.)]TJ -8.081 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-222(as:)-389(an)-222(ob)-56(ject)-222(of)-222(a)-222(class)-223(deriv)28(ed)-222(from)-222(\050in)28(teger\051)]TJ/F30 9.9626 Tf 233.541 0 Td [(psb)]TJ +/F16 11.9552 Tf 177.963 706.129 Td [(arra)31(y)]TJ ET q -1 0 0 1 374.662 227.312 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 209.557 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S Q BT -/F30 9.9626 Tf 377.8 227.113 Td [(T)]TJ +/F16 11.9552 Tf 213.592 706.129 Td [(write)-438(|)-438(W)93(rite)-438(a)-438(dense)-438(arra)31(y)-438(from)-438(a)-438(\014le)-439(in)-438(the)]TJ -62.887 -13.948 Td [(MatrixMark)31(et)-375(format)]TJ/F27 9.9626 Tf 1.377 -24.367 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.492 0 Td [(m)-99(m)]TJ ET q -1 0 0 1 383.658 227.312 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 200.739 668.014 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S Q BT -/F30 9.9626 Tf 386.796 227.113 Td [(base)]TJ +/F8 9.9626 Tf 204.709 667.814 Td [(a)-98(r)-99(r)-98(a)-99(y)]TJ ET q -1 0 0 1 408.345 227.312 cm +1 0 0 1 233.237 668.014 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 237.207 667.814 Td [(w)-99(r)-98(i)-98(t)-99(e)-204(\050)-120(b)-191(,)-911(i)-149(r)-150(e)-149(t)-461(,)-896(i)-134(u)-135(n)-135(i)-135(t)-431(,)-890(f)-129(i)-129(l)-129(e)-129(n)-129(a)-129(m)-129(e)-235(\051)]TJ +0 g 0 G +0 g 0 G +0 g 0 G +/F27 9.9626 Tf -86.502 -17.933 Td [(T)32(yp)-32(e:)]TJ +0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +0 g 0 G +/F27 9.9626 Tf -33.797 -19.925 Td [(On)-383(En)32(try)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(b)]TJ +0 g 0 G +/F8 9.9626 Tf 11.346 0 Td [(Rigth)-333(hand)-334(side\050s\051.)]TJ 13.56 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(An)-333(arra)27(y)-333(of)-333(t)28(yp)-28(e)-333(real)-334(or)-333(complex,)-333(rank)-334(1)-333(or)-333(2;)-334(will)-333(b)-28(e)-333(written..)]TJ +0 g 0 G +/F27 9.9626 Tf -24.906 -19.926 Td [(\014lename)]TJ +0 g 0 G +/F8 9.9626 Tf 46.513 0 Td [(The)-333(name)-334(of)-333(the)-333(\014le)-334(to)-333(b)-28(e)-333(written.)]TJ -21.607 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.184 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-435(as:)-648(a)-435(c)28(haracte)-1(r)-435(v)56(ariable)-435(con)28(taining)-435(a)-436(v)56(alid)-435(\014le)-435(name,)-461(or)]TJ/F30 9.9626 Tf 297.915 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(,)-461(in)]TJ -303.145 -11.955 Td [(whic)28(h)-302(case)-303(the)-302(default)-302(input)-302(unit)-302(5)-303(\050i.e.)-434(standard)-302(input)-302(in)-302(Unix)-302(jargon\051)-302(is)]TJ 0 -11.955 Td [(used.)-444(Default:)]TJ/F30 9.9626 Tf 66.057 0 Td [(-)]TJ/F8 9.9626 Tf 5.231 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -96.195 -19.926 Td [(iunit)]TJ +0 g 0 G +/F8 9.9626 Tf 28.532 0 Td [(The)-333(F)83(ortran)-333(\014le)-334(u)1(nit)-334(n)28(um)28(b)-28(er.)]TJ -3.625 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-444(an)-334(in)28(teger)-333(v)55(alue.)-444(Only)-333(me)-1(an)1(ingful)-334(if)-333(\014lename)-333(is)-334(not)]TJ/F30 9.9626 Tf 286.288 0 Td [(-)]TJ/F8 9.9626 Tf 5.23 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -316.425 -21.918 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(iret)]TJ +0 g 0 G +/F8 9.9626 Tf 22.589 0 Td [(Error)-333(co)-28(de.)]TJ 2.318 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detected.)]TJ +0 g 0 G + 139.477 -318.348 Td [(132)]TJ +0 g 0 G +ET + +endstream +endobj +1753 0 obj +<< +/Length 1212 +>> +stream +0 g 0 G +0 g 0 G +BT +/F16 14.3462 Tf 99.895 706.129 Td [(10)-1125(Preconditioner)-375(routines)]TJ/F8 9.9626 Tf 0 -21.821 Td [(The)-310(base)-310(PSBLAS)-310(library)-310(con)28(tains)-310(the)-310(implemen)28(tation)-310(of)-310(t)28(w)27(o)-310(simple)-310(precondi-)]TJ 0 -11.955 Td [(tioning)-333(tec)27(hn)1(iques:)]TJ +0 g 0 G +/F14 9.9626 Tf 14.944 -19.925 Td [(\017)]TJ +0 g 0 G +/F8 9.9626 Tf 9.963 0 Td [(Diagonal)-333(Scaling)]TJ +0 g 0 G +/F14 9.9626 Tf -9.963 -19.926 Td [(\017)]TJ +0 g 0 G +/F8 9.9626 Tf 9.963 0 Td [(Blo)-28(c)28(k)-333(Jacobi)-334(with)-333(ILU\0500\051)-333(factorization)]TJ -24.907 -19.925 Td [(The)-364(supp)-27(orting)-364(data)-364(t)28(yp)-27(e)-364(and)-364(subroutine)-363(in)28(terfaces)-364(are)-364(de\014ned)-363(in)-364(the)-364(mo)-27(dule)]TJ/F30 9.9626 Tf 0 -11.955 Td [(psb_prec_mod)]TJ/F8 9.9626 Tf 62.764 0 Td [(.)-844(The)-466(old)-466(in)27(terfaces)]TJ/F30 9.9626 Tf 96.595 0 Td [(psb_precinit)]TJ/F8 9.9626 Tf 67.41 0 Td [(and)]TJ/F30 9.9626 Tf 20.698 0 Td [(psb_precbld)]TJ/F8 9.9626 Tf 62.18 0 Td [(are)-466(still)]TJ -309.647 -11.955 Td [(supp)-28(orted)-333(for)-333(bac)27(kw)28(ard)-333(compatibilit)28(y)]TJ +0 g 0 G + 164.384 -498.229 Td [(133)]TJ +0 g 0 G +ET + +endstream +endobj +1760 0 obj +<< +/Length 4508 +>> +stream +0 g 0 G +0 g 0 G +BT +/F16 11.9552 Tf 150.705 706.129 Td [(init)-375(|)-375(Initialize)-375(a)-375(preconditioner)]TJ +0 g 0 G +0 g 0 G +/F30 9.9626 Tf 0 -18.389 Td [(call)-525(prec%init\050ptype,)-525(info\051)]TJ +0 g 0 G +/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ +0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +0 g 0 G +/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(pt)32(yp)-32(e)]TJ +0 g 0 G +/F8 9.9626 Tf 33.465 0 Td [(the)-333(t)28(yp)-28(e)-334(of)-333(preconditioner.)-444(Scop)-28(e:)]TJ/F27 9.9626 Tf 153.092 0 Td [(global)]TJ/F8 9.9626 Tf -161.651 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(c)28(haracter)-334(stri)1(ng,)-334(see)-333(usage)-334(notes.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.906 -19.926 Td [(On)-383(Exit)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(prec)]TJ +0 g 0 G +/F8 9.9626 Tf 26.408 0 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -33.88 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.583 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(preconditioner)-333(data)-333(structure)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 197.538 0 Td [(psb)]TJ +ET +q +1 0 0 1 389.467 514.589 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 411.483 227.113 Td [(vect)]TJ +/F30 9.9626 Tf 392.606 514.39 Td [(prec)]TJ ET q -1 0 0 1 433.032 227.312 cm +1 0 0 1 414.155 514.589 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 436.171 227.113 Td [(type)]TJ/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +/F30 9.9626 Tf 417.293 514.39 Td [(type)]TJ 0 g 0 G -/F27 9.9626 Tf -357.197 -24.133 Td [(On)-383(Return)]TJ +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -287.509 -19.926 Td [(info)]TJ 0 g 0 G +/F8 9.9626 Tf 23.758 0 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -31.23 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.034 -11.955 Td [(Error)-333(co)-28(de:)-444(if)-334(no)-333(error,)-333(0)-334(is)-333(returned.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ/F8 9.9626 Tf 37.058 0 Td [(Legal)-316(inputs)-315(to)-316(this)-316(subroutine)-315(are)-316(in)28(terpreted)-316(dep)-28(ending)-315(on)-316(the)]TJ/F11 9.9626 Tf 283.15 0 Td [(pty)-36(pe)]TJ/F8 9.9626 Tf -320.208 -11.955 Td [(string)-333(as)-334(follo)28(ws)]TJ +0 0 1 rg 0 0 1 RG +/F7 6.9738 Tf 69.932 3.615 Td [(4)]TJ 0 g 0 G - 0 -22.879 Td [(prec)]TJ +/F8 9.9626 Tf 4.47 -3.615 Td [(:)]TJ 0 g 0 G -/F8 9.9626 Tf 26.408 0 Td [(the)-333(preconditioner.)]TJ -1.501 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(precondtioner)-333(data)-333(structure)]TJ +/F27 9.9626 Tf -74.402 -19.925 Td [(NONE)]TJ +0 g 0 G +/F8 9.9626 Tf 39.048 0 Td [(No)-333(preconditioning,)-333(i.e.)-445(the)-333(preconditioner)-333(is)-334(just)-333(a)-333(cop)27(y)-333(op)-28(erator.)]TJ +0 g 0 G +/F27 9.9626 Tf -39.048 -19.926 Td [(DIA)32(G)]TJ +0 g 0 G +/F8 9.9626 Tf 35.464 0 Td [(Diagonal)-441(scaling;)-496(eac)28(h)-442(en)28(try)-441(of)-441(the)-442(input)-441(v)28(ector)-442(is)-441(m)27(ulti)1(plied)-442(b)28(y)-441(the)]TJ -10.557 -11.955 Td [(recipro)-28(cal)-346(of)-346(the)-346(sum)-345(of)-346(the)-346(absolute)-346(v)55(alues)-346(of)-346(th)1(e)-346(c)-1(o)-27(e\016cien)27(ts)-346(in)-345(the)-346(cor-)]TJ 0 -11.955 Td [(resp)-28(onding)-333(ro)28(w)-334(of)-333(matrix)]TJ/F11 9.9626 Tf 113.602 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(;)]TJ +0 g 0 G +/F27 9.9626 Tf -145.981 -19.925 Td [(BJA)32(C)]TJ +0 g 0 G +/F8 9.9626 Tf 35.672 0 Td [(Precondition)-249(b)28(y)-249(a)-249(factorization)-248(of)-249(the)-249(blo)-28(c)28(k-diagonal)-249(of)-249(matrix)]TJ/F11 9.9626 Tf 269.664 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(,)-266(where)]TJ -287.901 -11.956 Td [(blo)-28(c)28(k)-457(b)-28(oundaries)-457(are)-457(determined)-457(b)28(y)-457(the)-457(data)-457(allo)-28(cation)-457(b)-28(oundaries)-457(for)]TJ 0 -11.955 Td [(eac)28(h)-347(pro)-27(c)-1(ess;)-353(requires)-346(no)-347(comm)28(unication.)-484(Only)-347(the)-346(incomplete)-347(factoriza-)]TJ 0 -11.955 Td [(tion)]TJ/F11 9.9626 Tf 20.478 0 Td [(I)-78(LU)]TJ/F8 9.9626 Tf 19.83 0 Td [(\0500\051)-333(is)-334(curren)28(tly)-333(implemen)28(ted.)]TJ +0 g 0 G +ET +q +1 0 0 1 150.705 129.78 cm +[]0 d 0 J 0.398 w 0 0 m 137.482 0 l S +Q +BT +/F32 5.9776 Tf 161.797 123.138 Td [(4)]TJ/F31 7.9701 Tf 4.151 -2.812 Td [(The)-354(string)-354(is)-354(c)-1(a)1(se)-1(-)1(i)-1(nsensitiv)30(e)]TJ +0 g 0 G +0 g 0 G +/F8 9.9626 Tf 149.14 -29.888 Td [(134)]TJ +0 g 0 G +ET + +endstream +endobj +1769 0 obj +<< +/Length 7751 +>> +stream +0 g 0 G +0 g 0 G +BT +/F16 11.9552 Tf 99.895 706.129 Td [(build)-375(|)-375(Builds)-375(a)-375(preconditioner)]TJ +0 g 0 G +0 g 0 G +/F30 9.9626 Tf 0 -19.764 Td [(call)-525(prec%build\050a,)-525(desc_a,)-525(info[,amold,vmold,imold]\051)]TJ +0 g 0 G +/F27 9.9626 Tf 0 -24.132 Td [(T)32(yp)-32(e:)]TJ +0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ +0 g 0 G +/F27 9.9626 Tf -33.797 -22.879 Td [(On)-383(En)32(try)]TJ +0 g 0 G +0 g 0 G + 0 -22.879 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.551 0 Td [(the)-333(system)-334(sparse)-333(matrix.)-445(Scop)-27(e:)]TJ/F27 9.9626 Tf 148.886 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -134.53 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(,)-333(target.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(sparse)-333(matrix)-334(data)-333(structure)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 194.77 0 Td [(psb)]TJ +/F30 9.9626 Tf 194.05 0 Td [(psb)]TJ ET q -1 0 0 1 335.891 132.48 cm +1 0 0 1 335.171 580.809 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 339.029 132.281 Td [(prec)]TJ +/F30 9.9626 Tf 338.309 580.61 Td [(Tspmat)]TJ ET q -1 0 0 1 360.578 132.48 cm +1 0 0 1 370.319 580.809 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 363.716 132.281 Td [(type)]TJ +/F30 9.9626 Tf 373.457 580.61 Td [(type)]TJ +0 g 0 G +/F8 9.9626 Tf 20.922 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -294.484 -22.879 Td [(prec)]TJ +0 g 0 G +/F8 9.9626 Tf 26.408 0 Td [(the)-333(preconditioner.)]TJ -1.501 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-222(as:)-389(an)-222(already)-222(initialized)-222(precondtioner)-222(data)-223(structure)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 273.115 0 Td [(psb)]TJ +ET +q +1 0 0 1 414.236 510.11 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 417.374 509.91 Td [(prec)]TJ +ET +q +1 0 0 1 438.923 510.11 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 442.061 509.91 Td [(type)]TJ +0 g 0 G 0 g 0 G +/F27 9.9626 Tf -342.166 -34.833 Td [(desc)]TJ +ET +q +1 0 0 1 121.81 475.276 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 125.247 475.077 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.551 0 Td [(the)-333(problem)-334(comm)28(unication)-333(descriptor.)-445(Scop)-27(e:)]TJ/F27 9.9626 Tf 208.247 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -219.243 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(,)-333(target.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(comm)28(unication)-333(desc)-1(ri)1(ptor)-334(data)-333(structure)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 247.683 0 Td [(psb)]TJ +ET +q +1 0 0 1 388.803 439.41 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 391.942 439.211 Td [(desc)]TJ +ET +q +1 0 0 1 413.491 439.41 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 416.629 439.211 Td [(type)]TJ +0 g 0 G +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -337.655 -22.879 Td [(amold)]TJ +0 g 0 G +/F8 9.9626 Tf 35.374 0 Td [(The)-333(desired)-334(dynamic)-333(t)28(yp)-28(e)-333(for)-334(the)-333(in)28(ternal)-333(matrix)-334(storage.)]TJ -10.467 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(a)-333(class)-334(deriv)28(ed)-333(from)]TJ/F30 9.9626 Tf 203.349 0 Td [(psb)]TJ +ET +q +1 0 0 1 344.47 368.711 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 347.608 368.512 Td [(T)]TJ +ET +q +1 0 0 1 353.466 368.711 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 356.604 368.512 Td [(base)]TJ +ET +q +1 0 0 1 378.153 368.711 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 381.291 368.512 Td [(sparse)]TJ +ET +q +1 0 0 1 413.301 368.711 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 416.439 368.512 Td [(mat)]TJ/F8 9.9626 Tf 15.691 0 Td [(.)]TJ 0 g 0 G -/F8 9.9626 Tf -99.437 -41.843 Td [(131)]TJ +/F27 9.9626 Tf -332.235 -22.879 Td [(vmold)]TJ 0 g 0 G +/F8 9.9626 Tf 35.852 0 Td [(The)-333(desired)-334(dynamic)-333(t)28(yp)-28(e)-333(for)-334(the)-333(in)28(ternal)-333(v)27(ector)-333(storage.)]TJ -10.945 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(ob)-55(ject)-334(of)-333(a)-333(class)-334(deriv)28(ed)-333(from)]TJ/F30 9.9626 Tf 203.349 0 Td [(psb)]TJ ET +q +1 0 0 1 344.47 298.012 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 347.608 297.812 Td [(T)]TJ +ET +q +1 0 0 1 353.466 298.012 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 356.604 297.812 Td [(base)]TJ +ET +q +1 0 0 1 378.153 298.012 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 381.291 297.812 Td [(vect)]TJ +ET +q +1 0 0 1 402.84 298.012 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 405.978 297.812 Td [(type)]TJ/F8 9.9626 Tf 20.922 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -327.005 -22.878 Td [(imold)]TJ +0 g 0 G +/F8 9.9626 Tf 32.988 0 Td [(The)-333(desired)-334(dynamic)-333(t)28(yp)-28(e)-333(for)-334(th)1(e)-334(in)28(ternal)-333(in)28(te)-1(ger)-333(v)28(ector)-333(s)-1(t)1(o)-1(r)1(age)-1(.)]TJ -8.081 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.452 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-222(as:)-389(an)-222(ob)-56(ject)-222(of)-222(a)-222(class)-223(deriv)28(ed)-222(from)-222(\050in)28(teger\051)]TJ/F30 9.9626 Tf 233.541 0 Td [(psb)]TJ +ET +q +1 0 0 1 374.662 227.312 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 377.8 227.113 Td [(T)]TJ +ET +q +1 0 0 1 383.658 227.312 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 386.796 227.113 Td [(base)]TJ +ET +q +1 0 0 1 408.345 227.312 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 411.483 227.113 Td [(vect)]TJ +ET +q +1 0 0 1 433.032 227.312 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 436.171 227.113 Td [(type)]TJ/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -357.197 -24.133 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G + 0 -22.879 Td [(prec)]TJ +0 g 0 G +/F8 9.9626 Tf 26.408 0 Td [(the)-333(preconditioner.)]TJ -1.501 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(precondtioner)-333(data)-333(structure)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 194.77 0 Td [(psb)]TJ +ET +q +1 0 0 1 335.891 132.48 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 339.029 132.281 Td [(prec)]TJ +ET +q +1 0 0 1 360.578 132.48 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 363.716 132.281 Td [(type)]TJ +0 g 0 G +0 g 0 G +/F8 9.9626 Tf -99.437 -41.843 Td [(135)]TJ +0 g 0 G +ET + +endstream +endobj +1681 0 obj +<< +/Type /ObjStm +/N 100 +/First 967 +/Length 9157 +>> +stream +1665 0 1666 59 1667 118 1668 177 1669 236 1670 295 1671 352 1672 411 1673 470 1674 529 +1675 588 1676 647 1677 706 1678 765 1679 824 1648 882 1649 941 1650 1000 1683 1108 1685 1226 +473 1285 1686 1343 1687 1401 1682 1459 1689 1552 1691 1670 477 1728 1692 1785 1693 1842 1688 1899 +1695 1992 1697 2110 481 2169 1698 2227 1699 2285 1694 2343 1701 2436 1703 2554 485 2612 1704 2669 +1705 2726 1700 2783 1707 2889 1709 3007 489 3066 1706 3124 1712 3217 1710 3356 1714 3501 493 3559 +1715 3616 1716 3674 1711 3732 1720 3838 1718 3977 1722 4120 497 4179 1723 4237 1724 4296 1719 4355 +1727 4461 1725 4600 1729 4745 501 4803 1730 4860 1731 4918 1726 4976 1733 5082 1735 5200 505 5259 +1736 5317 1737 5376 1732 5435 1740 5541 1738 5680 1742 5824 509 5882 1743 5939 1744 5997 1739 6055 +1746 6161 1748 6279 513 6338 1749 6396 1750 6455 1745 6514 1752 6620 1754 6738 517 6796 1751 6853 +1759 6959 1756 7107 1757 7254 1761 7404 521 7463 1762 7521 1758 7579 1768 7736 1763 7902 1764 8045 +% 1665 0 obj +<< +/D [1651 0 R /XYZ 108.264 592.394 null] +>> +% 1666 0 obj +<< +/D [1651 0 R /XYZ 108.264 581.436 null] +>> +% 1667 0 obj +<< +/D [1651 0 R /XYZ 108.264 570.477 null] +>> +% 1668 0 obj +<< +/D [1651 0 R /XYZ 108.264 559.518 null] +>> +% 1669 0 obj +<< +/D [1651 0 R /XYZ 108.264 548.559 null] +>> +% 1670 0 obj +<< +/D [1651 0 R /XYZ 108.264 537.6 null] +>> +% 1671 0 obj +<< +/D [1651 0 R /XYZ 108.264 526.641 null] +>> +% 1672 0 obj +<< +/D [1651 0 R /XYZ 108.264 515.682 null] +>> +% 1673 0 obj +<< +/D [1651 0 R /XYZ 108.264 504.723 null] +>> +% 1674 0 obj +<< +/D [1651 0 R /XYZ 108.264 493.764 null] +>> +% 1675 0 obj +<< +/D [1651 0 R /XYZ 108.264 482.805 null] +>> +% 1676 0 obj +<< +/D [1651 0 R /XYZ 108.264 471.847 null] +>> +% 1677 0 obj +<< +/D [1651 0 R /XYZ 108.264 460.888 null] +>> +% 1678 0 obj +<< +/D [1651 0 R /XYZ 108.264 449.929 null] +>> +% 1679 0 obj +<< +/D [1651 0 R /XYZ 108.264 438.97 null] +>> +% 1648 0 obj +<< +/D [1651 0 R /XYZ 143.452 394.492 null] +>> +% 1649 0 obj +<< +/D [1651 0 R /XYZ 150.074 149.223 null] +>> +% 1650 0 obj +<< +/Font << /F53 1656 0 R /F46 1211 0 R /F8 561 0 R /F30 769 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1683 0 obj +<< +/Type /Page +/Contents 1684 0 R +/Resources 1682 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1680 0 R +>> +% 1685 0 obj +<< +/D [1683 0 R /XYZ 149.705 753.953 null] +>> +% 473 0 obj +<< +/D [1683 0 R /XYZ 150.705 724.062 null] +>> +% 1686 0 obj +<< +/D [1683 0 R /XYZ 150.705 638.48 null] +>> +% 1687 0 obj +<< +/D [1683 0 R /XYZ 150.705 638.48 null] +>> +% 1682 0 obj +<< +/Font << /F16 558 0 R /F27 560 0 R /F8 561 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1689 0 obj +<< +/Type /Page +/Contents 1690 0 R +/Resources 1688 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1680 0 R +>> +% 1691 0 obj +<< +/D [1689 0 R /XYZ 98.895 753.953 null] +>> +% 477 0 obj +<< +/D [1689 0 R /XYZ 99.895 724.062 null] +>> +% 1692 0 obj +<< +/D [1689 0 R /XYZ 99.895 638.48 null] +>> +% 1693 0 obj +<< +/D [1689 0 R /XYZ 99.895 638.48 null] +>> +% 1688 0 obj +<< +/Font << /F16 558 0 R /F27 560 0 R /F8 561 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1695 0 obj +<< +/Type /Page +/Contents 1696 0 R +/Resources 1694 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1680 0 R +>> +% 1697 0 obj +<< +/D [1695 0 R /XYZ 149.705 753.953 null] +>> +% 481 0 obj +<< +/D [1695 0 R /XYZ 150.705 724.062 null] +>> +% 1698 0 obj +<< +/D [1695 0 R /XYZ 150.705 635.69 null] +>> +% 1699 0 obj +<< +/D [1695 0 R /XYZ 150.705 638.48 null] +>> +% 1694 0 obj +<< +/Font << /F16 558 0 R /F27 560 0 R /F8 561 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1701 0 obj +<< +/Type /Page +/Contents 1702 0 R +/Resources 1700 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1680 0 R +>> +% 1703 0 obj +<< +/D [1701 0 R /XYZ 98.895 753.953 null] +>> +% 485 0 obj +<< +/D [1701 0 R /XYZ 99.895 724.062 null] +>> +% 1704 0 obj +<< +/D [1701 0 R /XYZ 99.895 635.69 null] +>> +% 1705 0 obj +<< +/D [1701 0 R /XYZ 99.895 638.48 null] +>> +% 1700 0 obj +<< +/Font << /F16 558 0 R /F27 560 0 R /F8 561 0 R /F30 769 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1707 0 obj +<< +/Type /Page +/Contents 1708 0 R +/Resources 1706 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1680 0 R +>> +% 1709 0 obj +<< +/D [1707 0 R /XYZ 149.705 753.953 null] +>> +% 489 0 obj +<< +/D [1707 0 R /XYZ 150.705 716.092 null] +>> +% 1706 0 obj +<< +/Font << /F16 558 0 R /F8 561 0 R /F30 769 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1712 0 obj +<< +/Type /Page +/Contents 1713 0 R +/Resources 1711 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1717 0 R +/Annots [ 1710 0 R ] +>> +% 1710 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [294.721 449.411 372.239 460.536] +/A << /S /GoTo /D (spdata) >> +>> +% 1714 0 obj +<< +/D [1712 0 R /XYZ 98.895 753.953 null] +>> +% 493 0 obj +<< +/D [1712 0 R /XYZ 99.895 720.077 null] +>> +% 1715 0 obj +<< +/D [1712 0 R /XYZ 99.895 677.445 null] +>> +% 1716 0 obj +<< +/D [1712 0 R /XYZ 99.895 679.769 null] +>> +% 1711 0 obj +<< +/Font << /F16 558 0 R /F27 560 0 R /F8 561 0 R /F30 769 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1720 0 obj +<< +/Type /Page +/Contents 1721 0 R +/Resources 1719 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1717 0 R +/Annots [ 1718 0 R ] +>> +% 1718 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [345.53 582.91 423.049 594.035] +/A << /S /GoTo /D (spdata) >> +>> +% 1722 0 obj +<< +/D [1720 0 R /XYZ 149.705 753.953 null] +>> +% 497 0 obj +<< +/D [1720 0 R /XYZ 150.705 720.077 null] +>> +% 1723 0 obj +<< +/D [1720 0 R /XYZ 150.705 677.445 null] +>> +% 1724 0 obj +<< +/D [1720 0 R /XYZ 150.705 679.769 null] +>> +% 1719 0 obj +<< +/Font << /F16 558 0 R /F27 560 0 R /F8 561 0 R /F30 769 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1727 0 obj +<< +/Type /Page +/Contents 1728 0 R +/Resources 1726 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1717 0 R +/Annots [ 1725 0 R ] +>> +% 1725 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [294.721 449.411 372.239 460.536] +/A << /S /GoTo /D (spdata) >> +>> +% 1729 0 obj +<< +/D [1727 0 R /XYZ 98.895 753.953 null] +>> +% 501 0 obj +<< +/D [1727 0 R /XYZ 99.895 720.077 null] +>> +% 1730 0 obj +<< +/D [1727 0 R /XYZ 99.895 679.769 null] +>> +% 1731 0 obj +<< +/D [1727 0 R /XYZ 99.895 679.769 null] +>> +% 1726 0 obj +<< +/Font << /F16 558 0 R /F27 560 0 R /F8 561 0 R /F30 769 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1733 0 obj +<< +/Type /Page +/Contents 1734 0 R +/Resources 1732 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1717 0 R +>> +% 1735 0 obj +<< +/D [1733 0 R /XYZ 149.705 753.953 null] +>> +% 505 0 obj +<< +/D [1733 0 R /XYZ 150.705 720.077 null] +>> +% 1736 0 obj +<< +/D [1733 0 R /XYZ 150.705 679.769 null] +>> +% 1737 0 obj +<< +/D [1733 0 R /XYZ 150.705 679.769 null] +>> +% 1732 0 obj +<< +/Font << /F16 558 0 R /F27 560 0 R /F8 561 0 R /F30 769 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1740 0 obj +<< +/Type /Page +/Contents 1741 0 R +/Resources 1739 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1717 0 R +/Annots [ 1738 0 R ] +>> +% 1738 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [294.721 582.91 372.239 594.035] +/A << /S /GoTo /D (spdata) >> +>> +% 1742 0 obj +<< +/D [1740 0 R /XYZ 98.895 753.953 null] +>> +% 509 0 obj +<< +/D [1740 0 R /XYZ 99.895 720.077 null] +>> +% 1743 0 obj +<< +/D [1740 0 R /XYZ 99.895 679.769 null] +>> +% 1744 0 obj +<< +/D [1740 0 R /XYZ 99.895 679.769 null] +>> +% 1739 0 obj +<< +/Font << /F16 558 0 R /F27 560 0 R /F8 561 0 R /F30 769 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1746 0 obj +<< +/Type /Page +/Contents 1747 0 R +/Resources 1745 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1717 0 R +>> +% 1748 0 obj +<< +/D [1746 0 R /XYZ 149.705 753.953 null] +>> +% 513 0 obj +<< +/D [1746 0 R /XYZ 150.705 720.077 null] +>> +% 1749 0 obj +<< +/D [1746 0 R /XYZ 150.705 679.769 null] +>> +% 1750 0 obj +<< +/D [1746 0 R /XYZ 150.705 679.769 null] +>> +% 1745 0 obj +<< +/Font << /F16 558 0 R /F27 560 0 R /F8 561 0 R /F30 769 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1752 0 obj +<< +/Type /Page +/Contents 1753 0 R +/Resources 1751 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1755 0 R +>> +% 1754 0 obj +<< +/D [1752 0 R /XYZ 98.895 753.953 null] +>> +% 517 0 obj +<< +/D [1752 0 R /XYZ 99.895 716.092 null] +>> +% 1751 0 obj +<< +/Font << /F16 558 0 R /F8 561 0 R /F14 772 0 R /F30 769 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1759 0 obj +<< +/Type /Page +/Contents 1760 0 R +/Resources 1758 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1755 0 R +/Annots [ 1756 0 R 1757 0 R ] +>> +% 1756 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [372.153 511.179 439.211 522.304] +/A << /S /GoTo /D (precdata) >> +>> +% 1757 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [219.641 421.792 226.103 433.832] +/A << /S /GoTo /D (Hfootnote.4) >> +>> +% 1761 0 obj +<< +/D [1759 0 R /XYZ 149.705 753.953 null] +>> +% 521 0 obj +<< +/D [1759 0 R /XYZ 150.705 720.077 null] +>> +% 1762 0 obj +<< +/D [1759 0 R /XYZ 165.948 129.79 null] +>> +% 1758 0 obj +<< +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R /F11 755 0 R /F7 770 0 R /F32 773 0 R /F31 775 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1768 0 obj +<< +/Type /Page +/Contents 1769 0 R +/Resources 1767 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1755 0 R +/Annots [ 1763 0 R 1764 0 R 1765 0 R 1766 0 R ] +>> +% 1763 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [317.856 577.4 395.375 588.524] +/A << /S /GoTo /D (spdata) >> +>> +% 1764 0 obj +<< +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [396.921 506.7 463.979 517.825] +/A << /S /GoTo /D (precdata) >> +>> endstream endobj -1723 0 obj +1774 0 obj << /Length 1097 >> @@ -21558,13 +22454,13 @@ BT 0 g 0 G /F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)27(t)1(e)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ -24.906 -21.918 Td [(The)]TJ/F30 9.9626 Tf 21.637 0 Td [(amold)]TJ/F8 9.9626 Tf 26.152 0 Td [(,)]TJ/F30 9.9626 Tf 7.537 0 Td [(vmold)]TJ/F8 9.9626 Tf 30.631 0 Td [(and)]TJ/F30 9.9626 Tf 20.53 0 Td [(imold)]TJ/F8 9.9626 Tf 30.631 0 Td [(argumen)28(ts)-450(ma)28(y)-450(b)-28(e)-449(emplo)28(y)27(ed)-449(to)-450(in)28(terface)-450(with)]TJ -137.118 -11.955 Td [(sp)-28(ecial)-333(devices,)-334(suc)28(h)-333(as)-334(GP)1(Us)-334(and)-333(other)-333(acc)-1(elerators.)]TJ 0 g 0 G - 164.383 -533.997 Td [(132)]TJ + 164.383 -533.997 Td [(136)]TJ 0 g 0 G ET endstream endobj -1731 0 obj +1782 0 obj << /Length 5847 >> @@ -21689,1274 +22585,1198 @@ BT /F30 9.9626 Tf 367.754 277.279 Td [(T)]TJ ET q -1 0 0 1 373.612 277.478 cm +1 0 0 1 373.612 277.478 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 376.751 277.279 Td [(vect)]TJ +ET +q +1 0 0 1 398.3 277.478 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 401.438 277.279 Td [(type)]TJ +0 g 0 G +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -322.464 -19.926 Td [(info)]TJ +0 g 0 G +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ +0 g 0 G + 139.477 -119.095 Td [(137)]TJ +0 g 0 G +ET + +endstream +endobj +1787 0 obj +<< +/Length 2936 +>> +stream +0 g 0 G +0 g 0 G +BT +/F16 11.9552 Tf 150.705 706.129 Td [(descr)-375(|)-375(Prin)31(ts)-375(a)-375(description)-375(of)-375(curren)31(t)-375(preconditioner)]TJ +0 g 0 G +0 g 0 G +/F30 9.9626 Tf 0 -18.389 Td [(call)-525(prec%descr\050\051)]TJ 0 -11.956 Td [(call)-525(prec%descr\050iout,)-525(root\051)]TJ +0 g 0 G +/F27 9.9626 Tf 0 -21.917 Td [(T)32(yp)-32(e:)]TJ +0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +0 g 0 G +/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(prec)]TJ +0 g 0 G +/F8 9.9626 Tf 26.408 0 Td [(the)-333(preconditioner.)-445(Scop)-27(e:)]TJ/F27 9.9626 Tf 119.33 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -120.832 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(preconditioner)-333(data)-333(structure)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 197.538 0 Td [(psb)]TJ +ET +q +1 0 0 1 389.467 578.35 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 392.606 578.15 Td [(prec)]TJ +ET +q +1 0 0 1 414.155 578.35 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 417.293 578.15 Td [(type)]TJ +0 g 0 G +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -287.509 -19.925 Td [(iout)]TJ +0 g 0 G +/F8 9.9626 Tf 24.713 0 Td [(output)-333(unit.)-444(Scop)-28(e:)]TJ/F27 9.9626 Tf 89.94 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -89.747 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(n)27(um)28(b)-28(er.)-444(Default:)-444(default)-334(outpu)1(t)-334(unit.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.906 -19.926 Td [(ro)-32(ot)]TJ +0 g 0 G +/F8 9.9626 Tf 25.93 0 Td [(Pro)-28(cess)-333(from)-334(whic)28(h)-333(to)-333(prin)28(t)-334(Scop)-28(e:)]TJ/F27 9.9626 Tf 157.244 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -158.268 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-478(as:)-733(an)-478(in)28(teger)-478(n)28(um)27(b)-27(er)-478(b)-28(et)28(w)28(een)-478(0)-478(and)]TJ/F11 9.9626 Tf 220.073 0 Td [(np)]TJ/F14 9.9626 Tf 14.166 0 Td [(\000)]TJ/F8 9.9626 Tf 10.922 0 Td [(1,)-514(in)-478(whic)28(h)-478(case)]TJ -245.161 -11.955 Td [(the)-410(sp)-28(eci\014ed)-410(pro)-28(cess)-410(will)-411(pri)1(n)27(t)-410(the)-410(description,)-429(or)]TJ/F14 9.9626 Tf 225 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1,)-429(in)-411(whic)28(h)-410(case)-410(all)]TJ -232.749 -11.955 Td [(pro)-28(cesses)-333(will)-334(prin)28(t.)-444(Default:)-445(0.)]TJ +0 g 0 G + 139.477 -352.221 Td [(138)]TJ +0 g 0 G +ET + +endstream +endobj +1791 0 obj +<< +/Length 989 +>> +stream +0 g 0 G +0 g 0 G +BT +/F16 11.9552 Tf 99.895 706.129 Td [(clone)-375(|)-375(clone)-375(curren)31(t)-375(preconditioner)]TJ +0 g 0 G +0 g 0 G +/F30 9.9626 Tf 0 -18.389 Td [(call)-1050(prec%clone\050precout,info\051)]TJ +0 g 0 G +/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ +0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +0 g 0 G +/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(prec)]TJ +0 g 0 G +/F8 9.9626 Tf 26.408 0 Td [(the)-333(preconditioner.)]TJ -1.501 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -80.359 -33.873 Td [(On)-383(Return)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(precout)]TJ +0 g 0 G +/F8 9.9626 Tf 42.957 0 Td [(A)-333(cop)27(y)-333(of)-333(the)-334(in)1(put)-334(ob)-55(ject.)]TJ +0 g 0 G +/F27 9.9626 Tf -42.957 -19.926 Td [(info)]TJ +0 g 0 G +/F8 9.9626 Tf 23.758 0 Td [(Return)-333(co)-28(de.)]TJ +0 g 0 G + 140.626 -449.854 Td [(139)]TJ +0 g 0 G +ET + +endstream +endobj +1798 0 obj +<< +/Length 2730 +>> +stream +0 g 0 G +0 g 0 G +BT +/F16 11.9552 Tf 150.705 706.129 Td [(free)-375(|)-375(F)94(ree)-375(a)-375(preconditioner)]TJ +0 g 0 G +0 g 0 G +/F30 9.9626 Tf 0 -18.389 Td [(call)-525(prec%free\050info\051)]TJ +0 g 0 G +/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ +0 g 0 G +/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +0 g 0 G +/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(prec)]TJ +0 g 0 G +/F8 9.9626 Tf 26.408 0 Td [(the)-333(preconditioner.)]TJ -1.501 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.451 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-334(preconditioner)-333(data)-333(structure)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 197.537 0 Td [(psb)]TJ +ET +q +1 0 0 1 389.467 578.35 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 392.606 578.15 Td [(prec)]TJ +ET +q +1 0 0 1 414.155 578.35 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 417.293 578.15 Td [(type)]TJ +0 g 0 G +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +0 g 0 G +/F27 9.9626 Tf -287.509 -19.925 Td [(On)-383(Exit)]TJ +0 g 0 G +0 g 0 G + 0 -19.925 Td [(prec)]TJ +0 g 0 G +/F8 9.9626 Tf 26.408 0 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -33.879 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-334(preconditioner)-333(data)-333(structure)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 197.537 0 Td [(psb)]TJ +ET +q +1 0 0 1 389.467 502.634 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 376.751 277.279 Td [(vect)]TJ +/F30 9.9626 Tf 392.606 502.434 Td [(prec)]TJ ET q -1 0 0 1 398.3 277.478 cm +1 0 0 1 414.155 502.634 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 401.438 277.279 Td [(type)]TJ +/F30 9.9626 Tf 417.293 502.434 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -322.464 -19.926 Td [(info)]TJ +/F27 9.9626 Tf -287.509 -19.925 Td [(info)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.149 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(tege)-1(r)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detecte)-1(d)1(.)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -31.23 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.034 -11.955 Td [(Error)-333(co)-28(de:)-444(if)-334(no)-333(error,)-333(0)-334(is)-333(returned.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ/F8 9.9626 Tf 37.234 0 Td [(Releases)-334(all)-333(in)28(ternal)-333(storage.)]TJ 0 g 0 G - 139.477 -119.095 Td [(133)]TJ + 127.149 -334.288 Td [(140)]TJ 0 g 0 G ET endstream endobj -1737 0 obj +1802 0 obj << -/Length 2936 +/Length 598 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 150.705 706.129 Td [(descr)-375(|)-375(Prin)31(ts)-375(a)-375(description)-375(of)-375(curren)31(t)-375(preconditioner)]TJ +/F16 14.3462 Tf 99.895 706.129 Td [(11)-1125(Iterativ)31(e)-375(Metho)-31(ds)]TJ/F8 9.9626 Tf 0 -21.821 Td [(In)-519(this)-518(c)28(hapter)-519(w)28(e)-519(pro)28(vide)-519(routin)1(e)-1(s)-518(for)-519(preconditioners)-518(and)-519(iterativ)28(e)-519(meth-)]TJ 0 -11.955 Td [(o)-28(ds.)-647(The)-401(in)28(terfaces)-401(for)-401(Kryl)1(o)27(v)-401(subspace)-400(m)-1(etho)-27(ds)-401(are)-401(a)28(v)55(ailable)-400(in)-401(the)-401(mo)-28(dule)]TJ/F30 9.9626 Tf 0 -11.955 Td [(psb_krylov_mod)]TJ/F8 9.9626 Tf 73.225 0 Td [(.)]TJ 0 g 0 G + 91.159 -569.96 Td [(141)]TJ 0 g 0 G -/F30 9.9626 Tf 0 -18.389 Td [(call)-525(prec%descr\050\051)]TJ 0 -11.956 Td [(call)-525(prec%descr\050iout,)-525(root\051)]TJ +ET + +endstream +endobj +1809 0 obj +<< +/Length 8299 +>> +stream 0 g 0 G -/F27 9.9626 Tf 0 -21.917 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +BT +/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ +ET +q +1 0 0 1 171.761 706.328 cm +[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S +Q +BT +/F16 11.9552 Tf 175.796 706.129 Td [(krylo)31(v)-375(|)-375(Krylo)31(v)-375(Metho)-31(ds)-375(Driv)31(er)-375(Routine)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-343(subroutine)-342(is)-343(a)-343(driv)28(er)-343(that)-342(pro)27(vi)1(des)-343(a)-343(general)-343(in)28(terface)-343(for)-342(all)-343(the)-343(Krylo)28(v-)]TJ 0 -11.956 Td [(Subspace)-333(family)-334(metho)-27(ds)-334(implemen)28(ted)-333(in)-334(PSBLAS)-333(v)28(ersion)-333(2.)]TJ 14.944 -11.955 Td [(The)-333(stopping)-334(criterion)-333(can)-333(tak)28(e)-334(the)-333(follo)28(wing)-334(v)56(alues:)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ +/F27 9.9626 Tf -14.944 -19.102 Td [(1)]TJ 0 g 0 G +/F8 9.9626 Tf 10.71 0 Td [(norm)28(wise)-334(bac)28(kw)28(ard)-333(error)-334(in)-333(the)-333(in\014nit)28(y)-334(norm;)-333(the)-333(iteration)-333(is)-334(stopp)-28(ed)-333(when)]TJ/F11 9.9626 Tf 109.582 -26.078 Td [(er)-28(r)]TJ/F8 9.9626 Tf 16.95 0 Td [(=)]TJ/F14 9.9626 Tf 38.11 6.74 Td [(k)]TJ/F11 9.9626 Tf 4.981 0 Td [(r)]TJ/F10 6.9738 Tf 4.495 -1.495 Td [(i)]TJ/F14 9.9626 Tf 3.317 1.495 Td [(k)]TJ +ET +q +1 0 0 1 299.658 621.14 cm +[]0 d 0 J 0.398 w 0 0 m 70.572 0 l S +Q +BT +/F8 9.9626 Tf 299.658 611.815 Td [(\050)]TJ/F14 9.9626 Tf 3.875 0 Td [(k)]TJ/F11 9.9626 Tf 4.981 0 Td [(A)]TJ/F14 9.9626 Tf 7.472 0 Td [(kk)]TJ/F11 9.9626 Tf 9.963 0 Td [(x)]TJ/F10 6.9738 Tf 5.693 -1.494 Td [(i)]TJ/F14 9.9626 Tf 3.317 1.494 Td [(k)]TJ/F8 9.9626 Tf 7.196 0 Td [(+)]TJ/F14 9.9626 Tf 9.962 0 Td [(k)]TJ/F11 9.9626 Tf 4.981 0 Td [(b)]TJ/F14 9.9626 Tf 4.276 0 Td [(k)]TJ/F8 9.9626 Tf 4.981 0 Td [(\051)]TJ/F11 9.9626 Tf 7.838 6.834 Td [(<)-278(eps)]TJ 0 g 0 G - 0 -19.925 Td [(prec)]TJ +/F27 9.9626 Tf -223.488 -29.952 Td [(2)]TJ 0 g 0 G -/F8 9.9626 Tf 26.408 0 Td [(the)-333(preconditioner.)-445(Scop)-27(e:)]TJ/F27 9.9626 Tf 119.33 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -120.832 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(preconditioner)-333(data)-333(structure)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 197.538 0 Td [(psb)]TJ +/F8 9.9626 Tf 10.71 0 Td [(Relativ)28(e)-334(residual)-333(in)-333(the)-333(2-norm;)-334(the)-333(iteration)-333(is)-334(stopp)-27(ed)-334(when)]TJ/F11 9.9626 Tf 135.514 -26.078 Td [(er)-28(r)]TJ/F8 9.9626 Tf 16.95 0 Td [(=)]TJ/F14 9.9626 Tf 12.178 6.74 Td [(k)]TJ/F11 9.9626 Tf 4.981 0 Td [(r)]TJ/F10 6.9738 Tf 4.495 -1.495 Td [(i)]TJ/F14 9.9626 Tf 3.317 1.495 Td [(k)]TJ ET q -1 0 0 1 389.467 578.35 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 325.59 565.11 cm +[]0 d 0 J 0.398 w 0 0 m 18.708 0 l S Q BT -/F30 9.9626 Tf 392.606 578.15 Td [(prec)]TJ +/F14 9.9626 Tf 325.59 555.785 Td [(k)]TJ/F11 9.9626 Tf 4.981 0 Td [(b)]TJ/F14 9.9626 Tf 4.276 0 Td [(k)]TJ/F7 6.9738 Tf 4.981 -1.494 Td [(2)]TJ/F11 9.9626 Tf 8.433 8.328 Td [(<)-278(eps)]TJ +0 g 0 G +/F27 9.9626 Tf -197.556 -29.952 Td [(3)]TJ +0 g 0 G +/F8 9.9626 Tf 10.71 0 Td [(Relativ)28(e)-334(residual)-333(reduction)-333(in)-333(the)-334(2-norm;)-333(the)-333(iteration)-334(is)-333(stopp)-28(ed)-333(when)]TJ/F11 9.9626 Tf 133.17 -26.078 Td [(er)-28(r)]TJ/F8 9.9626 Tf 16.949 0 Td [(=)]TJ/F14 9.9626 Tf 14.523 6.74 Td [(k)]TJ/F11 9.9626 Tf 4.981 0 Td [(r)]TJ/F10 6.9738 Tf 4.495 -1.495 Td [(i)]TJ/F14 9.9626 Tf 3.317 1.495 Td [(k)]TJ ET q -1 0 0 1 414.155 578.35 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +1 0 0 1 323.246 509.08 cm +[]0 d 0 J 0.398 w 0 0 m 23.396 0 l S Q BT -/F30 9.9626 Tf 417.293 578.15 Td [(type)]TJ +/F14 9.9626 Tf 323.246 499.755 Td [(k)]TJ/F11 9.9626 Tf 4.981 0 Td [(r)]TJ/F7 6.9738 Tf 4.495 -1.494 Td [(0)]TJ/F14 9.9626 Tf 4.469 1.494 Td [(k)]TJ/F7 6.9738 Tf 4.982 -1.494 Td [(2)]TJ/F11 9.9626 Tf 8.432 8.328 Td [(<)-278(eps)]TJ/F8 9.9626 Tf -199.9 -30.505 Td [(The)-442(b)-28(eha)28(viour)-443(is)-442(con)27(t)1(rolled)-443(b)28(y)-443(th)1(e)-443(istop)-442(argumen)27(t)-442(\050see)-443(later\051.)-771(In)-443(the)-442(ab)-28(o)28(v)28(e)]TJ 0 -11.955 Td [(form)28(ulae,)]TJ/F11 9.9626 Tf 43.127 0 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.495 Td [(i)]TJ/F8 9.9626 Tf 5.855 1.495 Td [(is)-255(the)-255(ten)28(tativ)28(e)-255(solution)-255(and)]TJ/F11 9.9626 Tf 122.118 0 Td [(r)]TJ/F10 6.9738 Tf 4.494 -1.495 Td [(i)]TJ/F8 9.9626 Tf 6.085 1.495 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(b)]TJ/F14 9.9626 Tf 4.925 0 Td [(\000)]TJ/F11 9.9626 Tf 8.399 0 Td [(Ax)]TJ/F10 6.9738 Tf 13.165 -1.495 Td [(i)]TJ/F8 9.9626 Tf 5.856 1.495 Td [(the)-255(corresp)-28(onding)-254(residual)]TJ -230.234 -11.956 Td [(at)-333(the)]TJ/F11 9.9626 Tf 29.334 0 Td [(i)]TJ/F8 9.9626 Tf 3.433 0 Td [(-th)-333(iteration.)]TJ/F27 9.9626 Tf -31.39 -17.52 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.763 0 Td [(p)-126(s)-125(b)]TJ +ET +q +1 0 0 1 201.196 434.852 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 205.436 434.653 Td [(k)-126(r)-125(y)-126(l)-125(o)-126(v)-231(\050)-146(m)-40(e)-41(t)-40(h)-40(o)-40(d)-242(,)-194(a)-228(,)-255(p)-94(r)-94(e)-94(c)-349(,)-176(b)-191(,)-185(x)-209(,)-243(e)-81(p)-81(s)-323(,)-274(d)-113(e)-112(s)-113(c)]TJ +ET +q +1 0 0 1 402.384 434.852 cm +[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +Q +BT +/F8 9.9626 Tf 406.495 434.653 Td [(a)-386(,)-288(i)-127(n)-127(f)-127(o)-302(,)-48(&)]TJ -226.787 -11.956 Td [(&)-579(i)-67(t)-67(m)-68(a)-67(x)-296(,)-311(i)-150(t)-149(e)-150(r)-460(,)]TJ/F27 9.9626 Tf 79.243 0 Td [(e)-65(r)-65(r)]TJ/F8 9.9626 Tf 18.89 0 Td [(,)-305(i)-144(t)-144(r)-144(a)-144(c)-145(e)-449(,)-319(i)-158(r)-158(s)-158(t)-476(,)-288(i)-126(s)-126(t)-126(o)-127(p)-413(,)-230(c)-69(o)-69(n)-69(d)-174(\051)]TJ 0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -287.509 -19.925 Td [(iout)]TJ 0 g 0 G -/F8 9.9626 Tf 24.713 0 Td [(output)-333(unit.)-444(Scop)-28(e:)]TJ/F27 9.9626 Tf 89.94 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -89.747 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(n)27(um)28(b)-28(er.)-444(Default:)-444(default)-334(outpu)1(t)-334(unit.)]TJ +/F27 9.9626 Tf -127.136 -26.454 Td [(T)32(yp)-32(e:)]TJ 0 g 0 G -/F27 9.9626 Tf -24.906 -19.926 Td [(ro)-32(ot)]TJ +/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ 0 g 0 G -/F8 9.9626 Tf 25.93 0 Td [(Pro)-28(cess)-333(from)-334(whic)28(h)-333(to)-333(prin)28(t)-334(Scop)-28(e:)]TJ/F27 9.9626 Tf 157.244 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -158.268 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-478(as:)-733(an)-478(in)28(teger)-478(n)28(um)27(b)-27(er)-478(b)-28(et)28(w)28(een)-478(0)-478(and)]TJ/F11 9.9626 Tf 220.073 0 Td [(np)]TJ/F14 9.9626 Tf 14.166 0 Td [(\000)]TJ/F8 9.9626 Tf 10.922 0 Td [(1,)-514(in)-478(whic)28(h)-478(case)]TJ -245.161 -11.955 Td [(the)-410(sp)-28(eci\014ed)-410(pro)-28(cess)-410(will)-411(pri)1(n)27(t)-410(the)-410(description,)-429(or)]TJ/F14 9.9626 Tf 225 0 Td [(\000)]TJ/F8 9.9626 Tf 7.749 0 Td [(1,)-429(in)-411(whic)28(h)-410(case)-410(all)]TJ -232.749 -11.955 Td [(pro)-28(cesses)-333(will)-334(prin)28(t.)-444(Default:)-445(0.)]TJ +/F27 9.9626 Tf -33.797 -19.513 Td [(On)-383(En)32(try)]TJ 0 g 0 G - 139.477 -352.221 Td [(134)]TJ 0 g 0 G -ET - -endstream -endobj -1741 0 obj -<< -/Length 989 ->> -stream + 0 -19.514 Td [(metho)-32(d)]TJ 0 g 0 G +/F8 9.9626 Tf 43.012 0 Td [(a)-235(string)-235(that)-235(de\014nes)-235(the)-236(iterativ)28(e)-235(metho)-28(d)-235(to)-235(b)-28(e)-235(used.)-412(Supp)-27(orted)-235(v)55(alues)]TJ -18.106 -11.955 Td [(are:)]TJ 0 g 0 G -BT -/F16 11.9552 Tf 99.895 706.129 Td [(clone)-375(|)-375(clone)-375(curren)31(t)-375(preconditioner)]TJ +/F27 9.9626 Tf 0 -19.513 Td [(CG:)]TJ 0 g 0 G +/F8 9.9626 Tf 25.447 0 Td [(the)-333(Conjugate)-334(Gradien)28(t)-333(metho)-28(d;)]TJ 0 g 0 G -/F30 9.9626 Tf 0 -18.389 Td [(call)-1050(prec%clone\050precout,info\051)]TJ +/F27 9.9626 Tf -25.447 -15.529 Td [(CGS:)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ +/F8 9.9626 Tf 31.812 0 Td [(the)-333(Conjugate)-334(Gradien)28(t)-333(Stabilized)-333(metho)-28(d;)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +/F27 9.9626 Tf -31.812 -15.528 Td [(GCR:)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ +/F8 9.9626 Tf 34.039 0 Td [(the)-333(Generalized)-334(Conjugate)-333(Residual)-333(metho)-28(d;)]TJ 0 g 0 G +/F27 9.9626 Tf -34.039 -15.529 Td [(F)32(CG:)]TJ 0 g 0 G - 0 -19.925 Td [(prec)]TJ +/F8 9.9626 Tf 32.337 0 Td [(the)-333(Flexible)-334(Conjugate)-333(Gradien)28(t)-333(me)-1(th)1(o)-28(d)]TJ +0 0 1 rg 0 0 1 RG +/F7 6.9738 Tf 177.626 3.616 Td [(5)]TJ 0 g 0 G -/F8 9.9626 Tf 26.408 0 Td [(the)-333(preconditioner.)]TJ -1.501 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ +/F8 9.9626 Tf 4.47 -3.616 Td [(;)]TJ 0 g 0 G -/F27 9.9626 Tf -80.359 -33.873 Td [(On)-383(Return)]TJ +/F27 9.9626 Tf -214.433 -15.528 Td [(BICG:)]TJ 0 g 0 G +/F8 9.9626 Tf 37.941 0 Td [(the)-333(Bi-Conjugate)-334(Gradien)28(t)-333(metho)-28(d;)]TJ 0 g 0 G - 0 -19.925 Td [(precout)]TJ +/F27 9.9626 Tf -37.941 -15.529 Td [(BICGST)96(AB:)]TJ 0 g 0 G -/F8 9.9626 Tf 42.957 0 Td [(A)-333(cop)27(y)-333(of)-333(the)-334(in)1(put)-334(ob)-55(ject.)]TJ +/F8 9.9626 Tf 68.133 0 Td [(the)-333(Bi-Conjugate)-334(Gradien)28(t)-333(Stabilized)-333(me)-1(th)1(o)-28(d;)]TJ 0 g 0 G -/F27 9.9626 Tf -42.957 -19.926 Td [(info)]TJ +/F27 9.9626 Tf -68.133 -15.528 Td [(BICGST)96(ABL:)]TJ +0 g 0 G +/F8 9.9626 Tf 75.024 0 Td [(the)-222(Bi-Conjugate)-222(Gradien)27(t)-222(Stabilized)-222(metho)-28(d)-222(with)-222(restart-)]TJ -53.106 -11.955 Td [(ing;)]TJ +0 g 0 G +/F27 9.9626 Tf -21.918 -15.529 Td [(R)32(GMRES:)]TJ +0 g 0 G +/F8 9.9626 Tf 58.807 0 Td [(the)-333(Generalized)-334(Minimal)-333(Residual)-333(metho)-28(d)-333(with)-334(restarting.)]TJ +0 g 0 G +/F27 9.9626 Tf -83.713 -19.513 Td [(a)]TJ +0 g 0 G +/F8 9.9626 Tf 10.55 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(sparse)-333(matrix)]TJ/F11 9.9626 Tf 178.969 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(.)]TJ -172.085 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ +ET +q +1 0 0 1 362.845 137.958 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 365.983 137.759 Td [(Tspmat)]TJ +ET +q +1 0 0 1 397.993 137.958 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 401.131 137.759 Td [(type)]TJ +0 g 0 G +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ +0 g 0 G +ET +q +1 0 0 1 150.705 129.78 cm +[]0 d 0 J 0.398 w 0 0 m 137.482 0 l S +Q +BT +/F32 5.9776 Tf 161.797 123.138 Td [(5)]TJ/F31 7.9701 Tf 4.151 -2.812 Td [(Note:)-472(the)-354(i)-1(mplemen)30(tation)-354(is)-354(for)]TJ/F33 7.9701 Tf 120.249 0 Td [(F)-148(C)-70(G)]TJ/F31 7.9701 Tf 19.733 0 Td [(\0501\051.)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Return)-333(co)-28(de.)]TJ 0 g 0 G - 140.626 -449.854 Td [(135)]TJ +/F8 9.9626 Tf 9.158 -29.888 Td [(142)]TJ 0 g 0 G ET endstream endobj -1747 0 obj +1821 0 obj << -/Length 2730 +/Length 7084 >> stream 0 g 0 G 0 g 0 G -BT -/F16 11.9552 Tf 150.705 706.129 Td [(free)-375(|)-375(F)94(ree)-375(a)-375(preconditioner)]TJ 0 g 0 G +BT +/F27 9.9626 Tf 99.895 706.129 Td [(prec)]TJ 0 g 0 G -/F30 9.9626 Tf 0 -18.389 Td [(call)-525(prec%free\050info\051)]TJ +/F8 9.9626 Tf 26.408 0 Td [(The)-333(data)-334(structure)-333(con)28(taining)-333(the)-334(preconditioner.)]TJ -1.501 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ +ET +q +1 0 0 1 312.036 658.507 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 315.174 658.308 Td [(prec)]TJ +ET +q +1 0 0 1 336.723 658.507 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 339.861 658.308 Td [(type)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -21.918 Td [(T)32(yp)-32(e:)]TJ +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Async)28(hronous.)]TJ +/F27 9.9626 Tf -260.887 -19.427 Td [(b)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.926 Td [(On)-383(En)32(try)]TJ +/F8 9.9626 Tf 11.347 0 Td [(The)-333(RHS)-334(v)28(ector.)]TJ 13.56 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-333(arra)27(y)-333(or)-333(an)-334(ob)-55(ject)-333(of)-334(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 223.496 0 Td [(psb)]TJ +ET +q +1 0 0 1 364.616 591.26 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 367.754 591.06 Td [(T)]TJ +ET +q +1 0 0 1 373.612 591.26 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 376.751 591.06 Td [(vect)]TJ +ET +q +1 0 0 1 398.3 591.26 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 401.438 591.06 Td [(type)]TJ 0 g 0 G +/F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G - 0 -19.925 Td [(prec)]TJ +/F27 9.9626 Tf -322.464 -19.427 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 26.408 0 Td [(the)-333(preconditioner.)]TJ -1.501 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf 23.073 0 Td [(.)]TJ -55.451 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-334(preconditioner)-333(data)-333(structure)]TJ +/F8 9.9626 Tf 11.028 0 Td [(The)-333(initial)-334(guess.)]TJ 13.879 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-333(arra)27(y)-333(or)-333(an)-334(ob)-55(ject)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 197.537 0 Td [(psb)]TJ +/F30 9.9626 Tf 223.496 0 Td [(psb)]TJ ET q -1 0 0 1 389.467 578.35 cm +1 0 0 1 364.616 524.012 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 392.606 578.15 Td [(prec)]TJ +/F30 9.9626 Tf 367.754 523.813 Td [(T)]TJ ET q -1 0 0 1 414.155 578.35 cm +1 0 0 1 373.612 524.012 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 417.293 578.15 Td [(type)]TJ +/F30 9.9626 Tf 376.751 523.813 Td [(vect)]TJ +ET +q +1 0 0 1 398.3 524.012 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S +Q +BT +/F30 9.9626 Tf 401.438 523.813 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -287.509 -19.925 Td [(On)-383(Exit)]TJ +/F27 9.9626 Tf -322.464 -19.428 Td [(eps)]TJ 0 g 0 G +/F8 9.9626 Tf 21.117 0 Td [(The)-333(stopping)-334(tolerance.)]TJ 3.79 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(real)-333(n)28(um)27(b)-27(er.)]TJ 0 g 0 G - 0 -19.925 Td [(prec)]TJ +/F27 9.9626 Tf -24.907 -19.427 Td [(desc)]TJ +ET +q +1 0 0 1 121.81 437.337 cm +[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S +Q +BT +/F27 9.9626 Tf 125.247 437.138 Td [(a)]TJ 0 g 0 G -/F8 9.9626 Tf 26.408 0 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.378 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -33.879 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(inout)]TJ/F8 9.9626 Tf 26.097 0 Td [(.)]TJ -59.582 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-444(a)-334(preconditioner)-333(data)-333(structure)]TJ +/F8 9.9626 Tf 10.551 0 Td [(con)28(tains)-334(d)1(ata)-334(structures)-333(for)-333(com)-1(m)28(unications.)]TJ -10.996 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ 0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 197.537 0 Td [(psb)]TJ +/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ ET q -1 0 0 1 389.467 502.634 cm +1 0 0 1 312.036 389.516 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 392.606 502.434 Td [(prec)]TJ +/F30 9.9626 Tf 315.174 389.317 Td [(desc)]TJ ET q -1 0 0 1 414.155 502.634 cm +1 0 0 1 336.723 389.516 cm []0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F30 9.9626 Tf 417.293 502.434 Td [(type)]TJ +/F30 9.9626 Tf 339.861 389.317 Td [(type)]TJ 0 g 0 G /F8 9.9626 Tf 20.921 0 Td [(.)]TJ 0 g 0 G -/F27 9.9626 Tf -287.509 -19.925 Td [(info)]TJ +/F27 9.9626 Tf -260.887 -19.427 Td [(itmax)]TJ 0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -31.23 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.485 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.034 -11.955 Td [(Error)-333(co)-28(de:)-444(if)-334(no)-333(error,)-333(0)-334(is)-333(returned.)]TJ/F16 11.9552 Tf -24.907 -21.918 Td [(Notes)]TJ/F8 9.9626 Tf 37.234 0 Td [(Releases)-334(all)-333(in)28(ternal)-333(storage.)]TJ +/F8 9.9626 Tf 33.783 0 Td [(The)-333(maxim)27(um)-333(n)28(um)28(b)-28(er)-333(of)-334(iterations)-333(to)-333(p)-28(erform.)]TJ -8.876 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Default:)]TJ/F11 9.9626 Tf 39.436 0 Td [(itmax)]TJ/F8 9.9626 Tf 29.504 0 Td [(=)-278(1000.)]TJ -68.94 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable)]TJ/F11 9.9626 Tf 142.079 0 Td [(itmax)]TJ/F14 9.9626 Tf 29.504 0 Td [(\025)]TJ/F8 9.9626 Tf 10.516 0 Td [(1.)]TJ 0 g 0 G - 127.149 -334.288 Td [(136)]TJ +/F27 9.9626 Tf -207.006 -19.427 Td [(itrace)]TJ 0 g 0 G -ET - -endstream -endobj -1751 0 obj -<< -/Length 598 ->> -stream +/F8 9.9626 Tf 33.251 0 Td [(If)]TJ/F11 9.9626 Tf 8.911 0 Td [(>)]TJ/F8 9.9626 Tf 10.517 0 Td [(0)-228(prin)28(t)-228(out)-228(an)-227(informational)-228(message)-228(ab)-28(out)-228(con)28(v)28(ergence)-228(ev)28(e)-1(r)1(y)]TJ/F11 9.9626 Tf 265.015 0 Td [(itr)-28(ace)]TJ/F8 9.9626 Tf -292.787 -11.955 Td [(iterations.)]TJ 0 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ 0 g 0 G +/F27 9.9626 Tf -67.94 -31.382 Td [(irst)]TJ 0 g 0 G -BT -/F16 14.3462 Tf 99.895 706.129 Td [(11)-1125(Iterativ)31(e)-375(Metho)-31(ds)]TJ/F8 9.9626 Tf 0 -21.821 Td [(In)-519(this)-518(c)28(hapter)-519(w)28(e)-519(pro)28(vide)-519(routin)1(e)-1(s)-518(for)-519(preconditioners)-518(and)-519(iterativ)28(e)-519(meth-)]TJ 0 -11.955 Td [(o)-28(ds.)-647(The)-401(in)28(terfaces)-401(for)-401(Kryl)1(o)27(v)-401(subspace)-400(m)-1(etho)-27(ds)-401(are)-401(a)28(v)55(ailable)-400(in)-401(the)-401(mo)-28(dule)]TJ/F30 9.9626 Tf 0 -11.955 Td [(psb_krylov_mod)]TJ/F8 9.9626 Tf 73.225 0 Td [(.)]TJ +/F8 9.9626 Tf 21.857 0 Td [(An)-333(in)28(te)-1(ger)-333(sp)-28(ecifying)-333(the)-333(restart)-334(parameter.)]TJ 3.05 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(V)83(alues:)]TJ/F11 9.9626 Tf 37.506 0 Td [(ir)-28(st)-447(>)]TJ/F8 9.9626 Tf 33.135 0 Td [(0.)-750(This)-435(is)-435(emplo)28(y)28(e)-1(d)-435(for)-435(the)-435(BiCGST)84(AB)-1(L)-435(or)-435(R)28(GMRES)]TJ -70.641 -11.955 Td [(metho)-28(ds,)-333(otherwise)-334(it)-333(is)-333(ignored.)]TJ +0 g 0 G +/F27 9.9626 Tf -24.907 -19.427 Td [(istop)]TJ +0 g 0 G +/F8 9.9626 Tf 29.232 0 Td [(An)-333(in)28(te)-1(ger)-333(sp)-28(ecifying)-333(the)-333(stopping)-334(crit)1(e)-1(ri)1(on.)]TJ -4.325 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ 0 g 0 G - 91.159 -569.96 Td [(137)]TJ +/F8 9.9626 Tf 107.098 -29.888 Td [(143)]TJ 0 g 0 G ET endstream endobj -1758 0 obj +1826 0 obj << -/Length 8299 +/Length 4414 >> stream 0 g 0 G 0 g 0 G BT -/F16 11.9552 Tf 150.705 706.129 Td [(psb)]TJ -ET -q -1 0 0 1 171.761 706.328 cm -[]0 d 0 J 0.398 w 0 0 m 4.035 0 l S -Q -BT -/F16 11.9552 Tf 175.796 706.129 Td [(krylo)31(v)-375(|)-375(Krylo)31(v)-375(Metho)-31(ds)-375(Driv)31(er)-375(Routine)]TJ/F8 9.9626 Tf -25.091 -18.389 Td [(This)-343(subroutine)-342(is)-343(a)-343(driv)28(er)-343(that)-342(pro)27(vi)1(des)-343(a)-343(general)-343(in)28(terface)-343(for)-342(all)-343(the)-343(Krylo)28(v-)]TJ 0 -11.956 Td [(Subspace)-333(family)-334(metho)-27(ds)-334(implemen)28(ted)-333(in)-334(PSBLAS)-333(v)28(ersion)-333(2.)]TJ 14.944 -11.955 Td [(The)-333(stopping)-334(criterion)-333(can)-333(tak)28(e)-334(the)-333(follo)28(wing)-334(v)56(alues:)]TJ -0 g 0 G -/F27 9.9626 Tf -14.944 -19.102 Td [(1)]TJ -0 g 0 G -/F8 9.9626 Tf 10.71 0 Td [(norm)28(wise)-334(bac)28(kw)28(ard)-333(error)-334(in)-333(the)-333(in\014nit)28(y)-334(norm;)-333(the)-333(iteration)-333(is)-334(stopp)-28(ed)-333(when)]TJ/F11 9.9626 Tf 109.582 -26.078 Td [(er)-28(r)]TJ/F8 9.9626 Tf 16.95 0 Td [(=)]TJ/F14 9.9626 Tf 38.11 6.74 Td [(k)]TJ/F11 9.9626 Tf 4.981 0 Td [(r)]TJ/F10 6.9738 Tf 4.495 -1.495 Td [(i)]TJ/F14 9.9626 Tf 3.317 1.495 Td [(k)]TJ -ET -q -1 0 0 1 299.658 621.14 cm -[]0 d 0 J 0.398 w 0 0 m 70.572 0 l S -Q -BT -/F8 9.9626 Tf 299.658 611.815 Td [(\050)]TJ/F14 9.9626 Tf 3.875 0 Td [(k)]TJ/F11 9.9626 Tf 4.981 0 Td [(A)]TJ/F14 9.9626 Tf 7.472 0 Td [(kk)]TJ/F11 9.9626 Tf 9.963 0 Td [(x)]TJ/F10 6.9738 Tf 5.693 -1.494 Td [(i)]TJ/F14 9.9626 Tf 3.317 1.494 Td [(k)]TJ/F8 9.9626 Tf 7.196 0 Td [(+)]TJ/F14 9.9626 Tf 9.962 0 Td [(k)]TJ/F11 9.9626 Tf 4.981 0 Td [(b)]TJ/F14 9.9626 Tf 4.276 0 Td [(k)]TJ/F8 9.9626 Tf 4.981 0 Td [(\051)]TJ/F11 9.9626 Tf 7.838 6.834 Td [(<)-278(eps)]TJ +/F8 9.9626 Tf 175.611 706.129 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf 40.576 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(V)83(alues:)-478(1:)-479(use)-351(the)-350(norm)28(wise)-351(bac)28(kw)28(ard)-351(error,)-354(2:)-479(use)-350(the)-351(scaled)-350(2-norm)-351(of)]TJ 0 -11.956 Td [(the)-333(residual,)-334(3:)-444(use)-333(the)-334(residual)-333(reduction)-333(in)-334(the)-333(2-norm.)-444(Default:)-445(2.)]TJ 0 g 0 G -/F27 9.9626 Tf -223.488 -29.952 Td [(2)]TJ +/F27 9.9626 Tf -24.906 -19.925 Td [(On)-383(Return)]TJ 0 g 0 G -/F8 9.9626 Tf 10.71 0 Td [(Relativ)28(e)-334(residual)-333(in)-333(the)-333(2-norm;)-334(the)-333(iteration)-333(is)-334(stopp)-27(ed)-334(when)]TJ/F11 9.9626 Tf 135.514 -26.078 Td [(er)-28(r)]TJ/F8 9.9626 Tf 16.95 0 Td [(=)]TJ/F14 9.9626 Tf 12.178 6.74 Td [(k)]TJ/F11 9.9626 Tf 4.981 0 Td [(r)]TJ/F10 6.9738 Tf 4.495 -1.495 Td [(i)]TJ/F14 9.9626 Tf 3.317 1.495 Td [(k)]TJ -ET -q -1 0 0 1 325.59 565.11 cm -[]0 d 0 J 0.398 w 0 0 m 18.708 0 l S -Q -BT -/F14 9.9626 Tf 325.59 555.785 Td [(k)]TJ/F11 9.9626 Tf 4.981 0 Td [(b)]TJ/F14 9.9626 Tf 4.276 0 Td [(k)]TJ/F7 6.9738 Tf 4.981 -1.494 Td [(2)]TJ/F11 9.9626 Tf 8.433 8.328 Td [(<)-278(eps)]TJ 0 g 0 G -/F27 9.9626 Tf -197.556 -29.952 Td [(3)]TJ + 0 -19.925 Td [(x)]TJ 0 g 0 G -/F8 9.9626 Tf 10.71 0 Td [(Relativ)28(e)-334(residual)-333(reduction)-333(in)-333(the)-334(2-norm;)-333(the)-333(iteration)-334(is)-333(stopp)-28(ed)-333(when)]TJ/F11 9.9626 Tf 133.17 -26.078 Td [(er)-28(r)]TJ/F8 9.9626 Tf 16.949 0 Td [(=)]TJ/F14 9.9626 Tf 14.523 6.74 Td [(k)]TJ/F11 9.9626 Tf 4.981 0 Td [(r)]TJ/F10 6.9738 Tf 4.495 -1.495 Td [(i)]TJ/F14 9.9626 Tf 3.317 1.495 Td [(k)]TJ +/F8 9.9626 Tf 11.028 0 Td [(The)-333(computed)-334(solution.)]TJ 13.878 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-334(ar)1(ra)27(y)-333(or)-333(an)-334(ob)-55(ject)-333(of)-334(t)28(yp)-28(e)]TJ +0 0 1 rg 0 0 1 RG +/F30 9.9626 Tf 223.496 0 Td [(psb)]TJ ET q -1 0 0 1 323.246 509.08 cm -[]0 d 0 J 0.398 w 0 0 m 23.396 0 l S +1 0 0 1 415.426 582.791 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F14 9.9626 Tf 323.246 499.755 Td [(k)]TJ/F11 9.9626 Tf 4.981 0 Td [(r)]TJ/F7 6.9738 Tf 4.495 -1.494 Td [(0)]TJ/F14 9.9626 Tf 4.469 1.494 Td [(k)]TJ/F7 6.9738 Tf 4.982 -1.494 Td [(2)]TJ/F11 9.9626 Tf 8.432 8.328 Td [(<)-278(eps)]TJ/F8 9.9626 Tf -199.9 -30.505 Td [(The)-442(b)-28(eha)28(viour)-443(is)-442(con)27(t)1(rolled)-443(b)28(y)-443(th)1(e)-443(istop)-442(argumen)27(t)-442(\050see)-443(later\051.)-771(In)-443(the)-442(ab)-28(o)28(v)28(e)]TJ 0 -11.955 Td [(form)28(ulae,)]TJ/F11 9.9626 Tf 43.127 0 Td [(x)]TJ/F10 6.9738 Tf 5.694 -1.495 Td [(i)]TJ/F8 9.9626 Tf 5.855 1.495 Td [(is)-255(the)-255(ten)28(tativ)28(e)-255(solution)-255(and)]TJ/F11 9.9626 Tf 122.118 0 Td [(r)]TJ/F10 6.9738 Tf 4.494 -1.495 Td [(i)]TJ/F8 9.9626 Tf 6.085 1.495 Td [(=)]TJ/F11 9.9626 Tf 10.516 0 Td [(b)]TJ/F14 9.9626 Tf 4.925 0 Td [(\000)]TJ/F11 9.9626 Tf 8.399 0 Td [(Ax)]TJ/F10 6.9738 Tf 13.165 -1.495 Td [(i)]TJ/F8 9.9626 Tf 5.856 1.495 Td [(the)-255(corresp)-28(onding)-254(residual)]TJ -230.234 -11.956 Td [(at)-333(the)]TJ/F11 9.9626 Tf 29.334 0 Td [(i)]TJ/F8 9.9626 Tf 3.433 0 Td [(-th)-333(iteration.)]TJ/F27 9.9626 Tf -31.39 -17.52 Td [(c)-138(a)-138(l)-139(l)]TJ/F8 9.9626 Tf 29.763 0 Td [(p)-126(s)-125(b)]TJ +/F30 9.9626 Tf 418.564 582.592 Td [(T)]TJ ET q -1 0 0 1 201.196 434.852 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 424.422 582.791 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F8 9.9626 Tf 205.436 434.653 Td [(k)-126(r)-125(y)-126(l)-125(o)-126(v)-231(\050)-146(m)-40(e)-41(t)-40(h)-40(o)-40(d)-242(,)-194(a)-228(,)-255(p)-94(r)-94(e)-94(c)-349(,)-176(b)-191(,)-185(x)-209(,)-243(e)-81(p)-81(s)-323(,)-274(d)-113(e)-112(s)-113(c)]TJ +/F30 9.9626 Tf 427.56 582.592 Td [(vect)]TJ ET q -1 0 0 1 402.384 434.852 cm -[]0 d 0 J 0.398 w 0 0 m 2.989 0 l S +1 0 0 1 449.109 582.791 cm +[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S Q BT -/F8 9.9626 Tf 406.495 434.653 Td [(a)-386(,)-288(i)-127(n)-127(f)-127(o)-302(,)-48(&)]TJ -226.787 -11.956 Td [(&)-579(i)-67(t)-67(m)-68(a)-67(x)-296(,)-311(i)-150(t)-149(e)-150(r)-460(,)]TJ/F27 9.9626 Tf 79.243 0 Td [(e)-65(r)-65(r)]TJ/F8 9.9626 Tf 18.89 0 Td [(,)-305(i)-144(t)-144(r)-144(a)-144(c)-145(e)-449(,)-319(i)-158(r)-158(s)-158(t)-476(,)-288(i)-126(s)-126(t)-126(o)-127(p)-413(,)-230(c)-69(o)-69(n)-69(d)-174(\051)]TJ +/F30 9.9626 Tf 452.247 582.592 Td [(type)]TJ 0 g 0 G +/F8 9.9626 Tf 20.922 0 Td [(.)]TJ 0 g 0 G +/F27 9.9626 Tf -322.464 -19.925 Td [(iter)]TJ 0 g 0 G -/F27 9.9626 Tf -127.136 -26.454 Td [(T)32(yp)-32(e:)]TJ +/F8 9.9626 Tf 22.589 0 Td [(The)-333(n)27(u)1(m)27(b)-27(e)-1(r)-333(of)-333(iterations)-333(p)-28(erformed.)]TJ 2.317 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Returned)-333(as:)-445(an)-333(in)28(teger)-334(v)56(ariable.)]TJ 0 g 0 G -/F8 9.9626 Tf 33.797 0 Td [(Sync)28(hronous.)]TJ +/F27 9.9626 Tf -24.906 -19.925 Td [(err)]TJ 0 g 0 G -/F27 9.9626 Tf -33.797 -19.513 Td [(On)-383(En)32(try)]TJ +/F8 9.9626 Tf 19.669 0 Td [(The)-333(con)27(v)28(ergence)-333(estimate)-334(on)-333(exit.)]TJ 5.237 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Returned)-333(as:)-445(a)-333(real)-333(n)27(um)28(b)-28(er.)]TJ 0 g 0 G +/F27 9.9626 Tf -24.906 -19.925 Td [(cond)]TJ 0 g 0 G - 0 -19.514 Td [(metho)-32(d)]TJ +/F8 9.9626 Tf 28.532 0 Td [(An)-280(estimate)-280(of)-279(the)-280(condition)-280(n)28(um)28(b)-28(er)-280(of)-279(matrix)]TJ/F11 9.9626 Tf 204.226 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(;)-298(only)-279(a)28(v)55(ailable)-280(with)-279(the)]TJ/F11 9.9626 Tf -215.324 -11.955 Td [(C)-72(G)]TJ/F8 9.9626 Tf 18.988 0 Td [(metho)-28(d)-333(on)-333(real)-334(data.)]TJ -18.988 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Returned)-287(as:)-421(a)-287(real)-287(n)28(um)28(b)-28(er.)-429(A)-287(correct)-287(result)-286(will)-287(b)-28(e)-287(greater)-287(than)-287(or)-286(equal)]TJ 0 -11.955 Td [(to)-267(one;)-288(if)-267(sp)-28(eci\014ed)-266(for)-267(non-real)-266(data,)-280(or)-266(an)-267(error)-266(o)-28(ccurred,)-280(zero)-267(is)-266(returned.)]TJ 0 g 0 G -/F8 9.9626 Tf 43.012 0 Td [(a)-235(string)-235(that)-235(de\014nes)-235(the)-236(iterativ)28(e)-235(metho)-28(d)-235(to)-235(b)-28(e)-235(used.)-412(Supp)-27(orted)-235(v)55(alues)]TJ -18.106 -11.955 Td [(are:)]TJ +/F27 9.9626 Tf -24.906 -19.925 Td [(info)]TJ 0 g 0 G -/F27 9.9626 Tf 0 -19.513 Td [(CG:)]TJ +/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(te)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ 0 g 0 G -/F8 9.9626 Tf 25.447 0 Td [(the)-333(Conjugate)-334(Gradien)28(t)-333(metho)-28(d;)]TJ + 139.477 -197.26 Td [(144)]TJ 0 g 0 G -/F27 9.9626 Tf -25.447 -15.529 Td [(CGS:)]TJ +ET + +endstream +endobj +1830 0 obj +<< +/Length 7014 +>> +stream 0 g 0 G -/F8 9.9626 Tf 31.812 0 Td [(the)-333(Conjugate)-334(Gradien)28(t)-333(Stabilized)-333(metho)-28(d;)]TJ 0 g 0 G -/F27 9.9626 Tf -31.812 -15.528 Td [(GCR:)]TJ +BT +/F16 14.3462 Tf 99.895 706.129 Td [(References)]TJ 0 g 0 G -/F8 9.9626 Tf 34.039 0 Td [(the)-333(Generalized)-334(Conjugate)-333(Residual)-333(metho)-28(d;)]TJ +/F8 9.9626 Tf 4.982 -21.821 Td [([1])]TJ 0 g 0 G -/F27 9.9626 Tf -34.039 -15.529 Td [(F)32(CG:)]TJ + [-500(D.)-441(Barbieri,)-468(V.)-441(Cardellini,)-467(S.)-441(Filipp)-28(one)-441(and)-441(D.)-441(Rouson)]TJ/F17 9.9626 Tf 267.833 0 Td [(Design)-457(Patterns)]TJ -252.336 -11.955 Td [(for)-441(S)-1(ci)1(ent)-1(i)1(\014)-1(c)-441(Computations)-442(on)-441(Sp)51(arse)-441(Matric)51(es)]TJ/F8 9.9626 Tf 210.802 0 Td [(,)-447(HPSS)-424(2011,)-447(Algorithms)]TJ -210.802 -11.955 Td [(and)-375(Programming)-374(T)83(o)-28(ols)-375(for)-374(Next-Generation)-375(High-P)28(erformance)-375(Scien)28(ti\014c)]TJ 0 -11.956 Td [(Soft)28(w)28(are,)-334(Bordeaux,)-333(Sep.)-333(2011)]TJ 0 g 0 G -/F8 9.9626 Tf 32.337 0 Td [(the)-333(Flexible)-334(Conjugate)-333(Gradien)28(t)-333(me)-1(th)1(o)-28(d)]TJ -0 0 1 rg 0 0 1 RG -/F7 6.9738 Tf 177.626 3.616 Td [(5)]TJ + -15.497 -18.666 Td [([2])]TJ 0 g 0 G -/F8 9.9626 Tf 4.47 -3.616 Td [(;)]TJ + [-500(G.)-341(Bella,)-343(S.)-341(Filipp)-28(one,)-343(A.)-341(De)-341(Maio)-341(and)-341(M.)-341(T)84(esta,)]TJ/F17 9.9626 Tf 235.488 0 Td [(A)-365(Simulation)-365(Mo)51(del)-364(for)]TJ -219.991 -11.955 Td [(F)77(or)51(est)-365(Fir)51(es)]TJ/F8 9.9626 Tf 52.03 0 Td [(,)-343(in)-341(J.)-340(Dongarra,)-343(K.)-341(Madsen,)-343(J.)-341(W)84(asniewski,)-343(editors,)-343(Pro)-28(ceed-)]TJ -52.03 -11.955 Td [(ings)-394(of)-395(P)84(ARA)-395(04)-394(W)83(orkshop)-394(on)-395(State)-394(of)-395(the)-394(Art)-394(in)-395(Scien)28(ti\014c)-394(Com)-1(p)1(uting,)]TJ 0 -11.955 Td [(pp.)-333(546{553,)-334(Lecture)-333(Notes)-333(in)-334(Computer)-333(Science,)-333(Springer,)-334(2005.)]TJ 0 g 0 G -/F27 9.9626 Tf -214.433 -15.528 Td [(BICG:)]TJ + -15.497 -18.666 Td [([3])]TJ 0 g 0 G -/F8 9.9626 Tf 37.941 0 Td [(the)-333(Bi-Conjugate)-334(Gradien)28(t)-333(metho)-28(d;)]TJ + [-500(A.)-316(Buttari,)-320(D.)-317(di)-316(Sera\014no,)-320(P)83(.)-316(D'Am)28(bra,)-320(S.)-317(Filipp)-27(one,)-100(2LEV-D2P4:)-436(a)-316(pac)28(k-)]TJ 15.497 -11.955 Td [(age)-388(of)-388(high-p)-28(erformance)-388(preconditioners,)-218(Applicable)-388(Alge)-1(b)1(ra)-389(in)-388(Engin)1(e)-1(er-)]TJ 0 -11.956 Td [(ing,)-393(Comm)27(un)1(ications)-382(and)-381(Computing,)-393(V)83(olume)-381(18,)-393(Num)27(b)-27(er)-382(3,)-393(Ma)28(y)83(,)-393(2007,)]TJ 0 -11.955 Td [(pp.)-333(223-239)]TJ 0 g 0 G -/F27 9.9626 Tf -37.941 -15.529 Td [(BICGST)96(AB:)]TJ + -15.497 -18.666 Td [([4])]TJ 0 g 0 G -/F8 9.9626 Tf 68.133 0 Td [(the)-333(Bi-Conjugate)-334(Gradien)28(t)-333(Stabilized)-333(me)-1(th)1(o)-28(d;)]TJ + [-500(P)83(.)-691(D'Am)28(bra,)-780(S.)-691(Filipp)-28(one,)-780(D.)-691(Di)-691(Sera\014no)-819(On)-691(the)-691(Dev)28(elopmen)28(t)-691(of)]TJ 15.497 -11.955 Td [(PSBLAS-based)-430(P)28(arallel)-430(Tw)28(o-lev)28(el)-430(Sc)27(h)28(w)28(arz)-430(Preconditioners)-731(Applied)-430(Nu-)]TJ 0 -11.955 Td [(merical)-245(Mathematics)-1(,)-262(Elsevier)-246(Science,)-263(V)83(ol)1(ume)-246(57,)-263(Issues)-245(11-12,)-263(No)27(v)28(em)28(b)-28(er-)]TJ 0 -11.955 Td [(Decem)28(b)-28(er)-333(2007)-1(,)-333(P)28(ages)-333(1181-1196.)]TJ 0 g 0 G -/F27 9.9626 Tf -68.133 -15.528 Td [(BICGST)96(ABL:)]TJ + -15.497 -18.667 Td [([5])]TJ 0 g 0 G -/F8 9.9626 Tf 75.024 0 Td [(the)-222(Bi-Conjugate)-222(Gradien)27(t)-222(Stabilized)-222(metho)-28(d)-222(with)-222(restart-)]TJ -53.106 -11.955 Td [(ing;)]TJ + [-500(Dongarra,)-529(J.)-490(J.,)-529(DuCroz,)-529(J.,)-529(Hammarling,)-529(S.)-490(and)-490(Hanson,)-529(R.,)-529(An)-490(Ex-)]TJ 15.497 -11.955 Td [(tended)-478(Set)-478(of)-478(F)83(ortran)-478(Basic)-478(Linear)-478(Algebra)-478(Subprograms,)-514(A)28(C)-1(M)-477(T)83(rans.)]TJ 0 -11.955 Td [(Math.)-333(Soft)28(w.)-334(v)28(ol.)-333(14,)-334(1{17,)-333(1988.)]TJ 0 g 0 G -/F27 9.9626 Tf -21.918 -15.529 Td [(R)32(GMRES:)]TJ + -15.497 -18.666 Td [([6])]TJ 0 g 0 G -/F8 9.9626 Tf 58.807 0 Td [(the)-333(Generalized)-334(Minimal)-333(Residual)-333(metho)-28(d)-333(with)-334(restarting.)]TJ + [-500(Dongarra,)-444(J.,)-444(DuCroz,)-444(J.,)-445(Hammarling,)-444(S.)-422(and)-422(Du\013,)-444(I.,)-444(A)-422(Set)-422(of)-422(lev)28(el)-422(3)]TJ 15.497 -11.955 Td [(Basic)-357(Linear)-357(Algebra)-357(Subpr)1(ogram)-1(s,)-362(A)27(CM)-356(T)83(rans.)-357(Math.)-357(Soft)28(w.)-357(v)28(ol.)-357(16,)-362(1{)]TJ 0 -11.955 Td [(17,)-333(1990.)]TJ 0 g 0 G -/F27 9.9626 Tf -83.713 -19.513 Td [(a)]TJ + -15.497 -18.666 Td [([7])]TJ 0 g 0 G -/F8 9.9626 Tf 10.55 0 Td [(the)-333(lo)-28(cal)-333(p)-28(ortion)-333(of)-334(global)-333(sparse)-333(matrix)]TJ/F11 9.9626 Tf 178.969 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(.)]TJ -172.085 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ -ET -q -1 0 0 1 362.845 137.958 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 365.983 137.759 Td [(Tspmat)]TJ -ET -q -1 0 0 1 397.993 137.958 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 401.131 137.759 Td [(type)]TJ + [-500(J.)-265(J.)-266(Dongarra)-266(and)-265(R.)-266(C.)-265(Whaley)83(,)]TJ/F17 9.9626 Tf 162.063 0 Td [(A)-295(User's)-296(Guide)-295(to)-296(the)-295(BLA)25(CS)-295(v.)-295(1.1)]TJ/F8 9.9626 Tf 156.589 0 Td [(,)-279(La-)]TJ -303.155 -11.956 Td [(pac)28(k)-291(W)84(orking)-291(Note)-290(94,)-299(T)83(ec)28(h.)-290(Rep.)-291(UT-CS-95-281,)-299(Univ)28(ersit)28(y)-290(of)-291(T)84(ennesse)-1(e,)]TJ 0 -11.955 Td [(Marc)28(h)-334(1995)-333(\050up)-28(dated)-333(Ma)28(y)-333(1997\051.)]TJ 0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ + -15.497 -18.666 Td [([8])]TJ 0 g 0 G -ET -q -1 0 0 1 150.705 129.78 cm -[]0 d 0 J 0.398 w 0 0 m 137.482 0 l S -Q -BT -/F32 5.9776 Tf 161.797 123.138 Td [(5)]TJ/F31 7.9701 Tf 4.151 -2.812 Td [(Note:)-472(the)-354(i)-1(mplemen)30(tation)-354(is)-354(for)]TJ/F33 7.9701 Tf 120.249 0 Td [(F)-148(C)-70(G)]TJ/F31 7.9701 Tf 19.733 0 Td [(\0501\051.)]TJ + [-500(I.)-488(Du\013,)-527(M.)-488(Marrone,)-526(G.)-488(Radicati)-488(and)-488(C.)-488(Vittoli,)]TJ/F17 9.9626 Tf 244.569 0 Td [(L)51(evel)-500(3)-500(Basic)-500(Line)51(ar)]TJ -229.072 -11.955 Td [(A)26(lgebr)51(a)-463(Subpr)52(o)51(gr)51(ams)-463(f)1(or)-463(Sp)51(arse)-462(Matric)51(es:)-669(a)-462(User)-462(L)51(evel)-463(Interfac)52(e)]TJ/F8 9.9626 Tf 292.206 0 Td [(,)-475(A)27(CM)]TJ -292.206 -11.955 Td [(T)83(ransactions)-333(on)-333(Mathematical)-334(Soft)28(w)28(are,)-333(23\0503\051,)-334(pp.)-333(379{401,)-333(1997.)]TJ +0 g 0 G + -15.497 -18.666 Td [([9])]TJ +0 g 0 G + [-500(I.)-358(Du\013,)-365(M.)-359(Heroux)-358(and)-359(R.)-358(P)27(ozo,)]TJ/F17 9.9626 Tf 162.007 0 Td [(A)26(n)-381(Overview)-381(of)-381(the)-381(Sp)51(arse)-381(Basic)-381(Line)51(ar)]TJ -146.51 -11.956 Td [(A)26(lgebr)51(a)-348(S)-1(u)1(bpr)51(o)51(gr)51(ams:)-455(the)-348(New)-349(Standar)51(d)-348(fr)51(om)-348(the)-348(BLAS)-348(T)76(e)51(chnic)52(al)-349(F)77(orum)]TJ/F8 9.9626 Tf 320.465 0 Td [(,)]TJ -320.465 -11.955 Td [(A)28(CM)-334(T)84(ransactions)-334(on)-333(Mathematical)-333(Soft)28(w)27(are,)-333(28\0502\051,)-333(pp.)-333(23)-1(9{267,)-333(2002.)]TJ +0 g 0 G + -20.479 -18.666 Td [([10])]TJ +0 g 0 G + [-500(S.)-451(Filipp)-28(one)-451(and)-451(M.)-451(Cola)-56(janni,)]TJ/F17 9.9626 Tf 165.708 0 Td [(PSBLAS:)-466(A)-466(Libr)51(ary)-466(for)-467(Par)51(al)-51(lel)-466(Line)51(ar)]TJ -145.229 -11.955 Td [(A)26(lgebr)51(a)-420(Computation)-420(on)-420(Sp)51(arse)-420(Matric)51(es)]TJ/F8 9.9626 Tf 181.375 0 Td [(,)-661(A)27(CM)-400(T)83(ransactions)-401(on)-401(Mathe-)]TJ -181.375 -11.955 Td [(matical)-333(Soft)27(w)28(are,)-333(26\0504\051,)-333(pp.)-334(527{550,)-333(2000.)]TJ +0 g 0 G + -20.479 -18.666 Td [([11])]TJ +0 g 0 G + [-500(S.)-425(Filipp)-27(one)-425(and)-425(A.)-425(Buttari,)]TJ/F17 9.9626 Tf 152.315 0 Td [(Obje)51(ct-Oriente)51(d)-442(T)77(e)51(chniques)-442(for)-441(Sp)51(arse)-442(Ma-)]TJ -131.836 -11.955 Td [(trix)-407(Computations)-406(in)-407(F)77(ortr)51(an)-407(2003)]TJ/F8 9.9626 Tf 153.485 0 Td [(,)-615(A)28(CM)-387(T)84(ransactions)-387(on)-386(Mathematical)]TJ -153.485 -11.956 Td [(Soft)28(w)28(are,)-334(38\0504\051,)-333(2012.)]TJ +0 g 0 G + -20.479 -18.666 Td [([12])]TJ 0 g 0 G + [-500(S.)-267(Filipp)-27(one,)-280(P)83(.)-267(D'Am)28(bra,)-280(M.)-267(Cola)-55(janni,)]TJ/F17 9.9626 Tf 197.776 0 Td [(Using)-297(a)-296(Par)51(al)-51(lel)-297(Libr)52(ary)-297(of)-296(Sp)51(arse)]TJ -177.297 -11.955 Td [(Line)51(ar)-352(A)26(lgebr)51(a)-352(in)-352(a)-352(Fluid)-352(Dynami)1(cs)-352(Applic)51(ations)-352(Co)51(de)-352(on)-352(Linux)-352(Clusters)]TJ/F8 9.9626 Tf 320.465 0 Td [(,)]TJ -320.465 -11.955 Td [(in)-398(G.)-399(Jou)1(b)-28(ert,)-415(A.)-398(Murli,)-414(F.)-399(P)28(eters,)-414(M.)-399(V)84(annesc)27(hi,)-414(editors,)-415(P)28(arallel)-398(Com-)]TJ 0 -11.955 Td [(puting)-354(-)-354(Adv)55(ances)-354(&)-354(Curren)28(t)-355(Issues,)-359(pp.)-354(441{448,)-360(Imp)-28(erial)-354(College)-354(Press,)]TJ 0 -11.955 Td [(2002.)]TJ 0 g 0 G -/F8 9.9626 Tf 9.158 -29.888 Td [(138)]TJ + 143.905 -29.888 Td [(145)]TJ 0 g 0 G ET endstream endobj -1660 0 obj +1839 0 obj << -/Type /ObjStm -/N 100 -/First 969 -/Length 10502 +/Length 3124 >> stream -1659 0 485 59 1656 117 1663 210 1661 349 1665 494 489 552 1666 609 1667 667 1662 725 -1670 831 1668 970 1672 1113 493 1172 1673 1230 1674 1289 1669 1348 1677 1454 1675 1593 1679 1738 -497 1796 1680 1853 1681 1911 1676 1969 1683 2075 1685 2193 501 2252 1686 2310 1687 2369 1682 2428 -1690 2534 1688 2673 1692 2817 505 2875 1693 2932 1694 2990 1689 3048 1697 3154 1699 3272 509 3331 -1700 3389 1701 3448 1696 3507 1703 3613 1705 3731 513 3789 1702 3846 1709 3952 1706 4100 1707 4247 -1711 4397 517 4456 1712 4514 1708 4572 1718 4729 1713 4895 1714 5038 1715 5183 1716 5330 1720 5477 -521 5535 1717 5592 1722 5698 1724 5816 1721 5875 1730 5968 1725 6134 1726 6280 1727 6423 1728 6570 -1732 6714 525 6772 1729 6829 1736 6935 1734 7074 1738 7220 529 7279 1735 7337 1740 7469 1742 7587 -533 7645 1739 7702 1746 7808 1743 7956 1744 8102 1748 8249 537 8308 1745 8366 1750 8472 1752 8590 -541 8648 1749 8705 1757 8798 1753 8946 1754 9095 1759 9239 545 9298 1760 9356 1761 9415 1762 9474 -% 1659 0 obj -<< -/D [1657 0 R /XYZ 149.705 753.953 null] ->> -% 485 0 obj -<< -/D [1657 0 R /XYZ 150.705 716.092 null] ->> -% 1656 0 obj -<< -/Font << /F16 554 0 R /F8 557 0 R /F30 764 0 R >> -/ProcSet [ /PDF /Text ] ->> -% 1663 0 obj -<< -/Type /Page -/Contents 1664 0 R -/Resources 1662 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1655 0 R -/Annots [ 1661 0 R ] ->> -% 1661 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 449.411 372.239 460.536] -/A << /S /GoTo /D (spdata) >> ->> -% 1665 0 obj -<< -/D [1663 0 R /XYZ 98.895 753.953 null] ->> -% 489 0 obj -<< -/D [1663 0 R /XYZ 99.895 720.077 null] ->> -% 1666 0 obj -<< -/D [1663 0 R /XYZ 99.895 677.445 null] ->> -% 1667 0 obj -<< -/D [1663 0 R /XYZ 99.895 679.769 null] ->> -% 1662 0 obj -<< -/Font << /F16 554 0 R /F27 556 0 R /F8 557 0 R /F30 764 0 R >> -/ProcSet [ /PDF /Text ] ->> -% 1670 0 obj +0 g 0 G +0 g 0 G +0 g 0 G +BT +/F8 9.9626 Tf 150.705 706.129 Td [([13])]TJ +0 g 0 G + [-500(Gamma,)-494(E.,)-987(Helm,)-493(R.,)-987(Johnson,)-494(R.,)-987(and)-923(Vlissides,)-494(J.)-461(1995.)]TJ/F17 9.9626 Tf 314.294 0 Td [(Design)]TJ -293.815 -11.955 Td [(Patterns:)-427(Elements)-293(of)-292(R)51(eusable)-293(Obje)51(ct-Oriente)51(d)-292(Softwar)51(e)]TJ/F8 9.9626 Tf 246.617 0 Td [(.)-262(Addison-W)83(esley)83(.)]TJ +0 g 0 G + -267.096 -19.926 Td [([14])]TJ +0 g 0 G + [-500(Karypis,)-561(G.)-515(and)-515(Kumar,)-561(V.,)]TJ/F17 9.9626 Tf 157.276 0 Td [(METIS:)-525(Unstructur)51(e)51(d)-525(Gr)51(aph)-525(Partitioning)]TJ -136.797 -11.955 Td [(and)-413(Sp)51(arse)-413(Matrix)-414(Or)51(deri)1(ng)-414(System)]TJ/F8 9.9626 Tf 158.597 0 Td [(.)-394(Minneap)-27(olis,)-409(MN)-394(55455:)-565(Univ)28(ersit)28(y)]TJ -158.597 -11.955 Td [(of)-420(Minnesota,)-441(Departmen)27(t)-420(of)-419(Computer)-420(Science,)-442(1995.)-420(In)28(ternet)-420(Address:)]TJ/F30 9.9626 Tf 0 -11.955 Td [(http://www.cs.umn.edu/~karypis)]TJ/F8 9.9626 Tf 156.91 0 Td [(.)]TJ +0 g 0 G + -177.389 -19.925 Td [([15])]TJ +0 g 0 G + [-500(La)28(wson,)-339(C.,)-339(Hanson,)-339(R.,)-339(Kincaid,)-339(D.)-338(and)-338(Krogh,)-339(F.,)-339(Basic)-338(Linear)-338(Algebra)]TJ 20.479 -11.956 Td [(Subprograms)-337(for)-336(Fortran)-337(usage,)-338(A)28(CM)-337(T)84(rans.)-337(Math.)-337(Soft)28(w.)-337(v)28(ol.)-337(5,)-337(38{329,)]TJ 0 -11.955 Td [(1979.)]TJ +0 g 0 G + -20.479 -19.925 Td [([16])]TJ +0 g 0 G + [-500(Mac)28(hiels,)-372(L.)-364(and)-364(Deville,)-372(M.)]TJ/F17 9.9626 Tf 148.97 0 Td [(F)77(ortr)51(an)-386(90:)-517(A)26(n)-387(entry)-386(to)-386(obje)51(ct-oriente)51(d)-386(pr)51(o-)]TJ -128.491 -11.955 Td [(gr)51(amming)-492(for)-492(the)-492(soluti)1(on)-492(of)-492(p)51(artial)-492(di\013er)51(ential)-492(e)51(quations.)]TJ/F8 9.9626 Tf 267.456 0 Td [(A)28(CM)-479(T)83(rans.)]TJ -267.456 -11.955 Td [(Math.)-333(Soft)28(w.)-334(v)28(ol.)-333(23,)-334(32{49.)]TJ +0 g 0 G + -20.479 -19.926 Td [([17])]TJ +0 g 0 G + [-500(Metcalf,)-434(M.,)-434(Reid,)-433(J.)-414(and)-414(Cohen,)-434(M.)]TJ/F17 9.9626 Tf 189.335 0 Td [(F)77(ortr)51(an)-432(95/2003)-432(explaine)51(d.)]TJ/F8 9.9626 Tf 123.907 0 Td [(Oxford)]TJ -292.763 -11.955 Td [(Univ)28(ersit)28(y)-334(Press,)-333(2004.)]TJ +0 g 0 G + -20.479 -19.925 Td [([18])]TJ +0 g 0 G + [-500(Rouson,)-374(D.W.I.,)-374(Xia,)-374(J.,)-374(Xu,)-373(X.:)-510(Scien)28(ti\014c)-366(Soft)28(w)28(are)-366(Design:)-510(Th)1(e)-366(Ob)-56(ject-)]TJ 20.479 -11.955 Td [(Orien)28(ted)-333(W)83(a)28(y.)-334(Cam)28(bridge)-333(Univ)28(ersit)27(y)-333(Press)-333(\0502011\051)]TJ +0 g 0 G + -20.479 -19.926 Td [([19])]TJ +0 g 0 G + [-500(M.)-443(Snir,)-471(S.)-443(Otto,)-471(S.)-443(Huss-Lederman,)-471(D.)-443(W)84(alk)27(er)-443(and)-443(J.)-443(Dongarra,)]TJ/F17 9.9626 Tf 321.124 0 Td [(MPI:)]TJ -300.645 -11.955 Td [(The)-365(Complete)-365(R)51(efer)51(enc)51(e.)-365(V)76(ol)1(ume)-366(1)-365(-)-365(The)-365(MPI)-365(Cor)51(e)]TJ/F8 9.9626 Tf 228.803 0 Td [(,)-343(sec)-1(on)1(d)-342(edition,)-343(MIT)]TJ -228.803 -11.955 Td [(Press,)-333(1998.)]TJ +0 g 0 G + 143.905 -352.677 Td [(146)]TJ +0 g 0 G +ET + +endstream +endobj +1771 0 obj << -/Type /Page -/Contents 1671 0 R -/Resources 1669 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1655 0 R -/Annots [ 1668 0 R ] +/Type /ObjStm +/N 100 +/First 973 +/Length 14915 >> -% 1668 0 obj +stream +1765 0 1766 147 1770 294 525 352 1767 409 1773 515 1775 633 1772 692 1781 785 1776 951 +1777 1097 1778 1240 1779 1387 1783 1531 529 1589 1780 1646 1786 1752 1784 1891 1788 2037 533 2096 +1785 2154 1790 2286 1792 2404 537 2462 1789 2519 1797 2625 1794 2773 1795 2919 1799 3066 541 3125 +1796 3183 1801 3289 1803 3407 545 3465 1800 3522 1808 3615 1804 3763 1805 3912 1810 4056 549 4115 +1811 4173 1812 4232 1813 4291 1814 4350 1807 4408 1820 4605 1806 4771 1816 4918 1817 5061 1818 5205 +1822 5352 1819 5410 1825 5529 1823 5668 1827 5812 1824 5871 1829 5977 1831 6095 1832 6153 739 6211 +1833 6268 790 6325 789 6382 745 6439 746 6496 762 6553 742 6610 743 6667 1834 6724 738 6782 +1835 6839 1828 6897 1838 6990 1840 7108 903 7167 777 7225 744 7283 741 7341 737 7399 740 7457 +1841 7515 1837 7574 1842 7667 1843 7712 1844 7851 1845 8038 1846 8532 1847 8861 1848 9204 1849 9333 +1850 9354 1851 9860 1852 9905 1853 10595 1854 10923 1855 11004 1856 11379 1857 12016 1858 12675 1859 13298 +% 1765 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.53 582.91 423.049 594.035] -/A << /S /GoTo /D (spdata) >> ->> -% 1672 0 obj -<< -/D [1670 0 R /XYZ 149.705 753.953 null] ->> -% 493 0 obj -<< -/D [1670 0 R /XYZ 150.705 720.077 null] ->> -% 1673 0 obj -<< -/D [1670 0 R /XYZ 150.705 677.445 null] ->> -% 1674 0 obj -<< -/D [1670 0 R /XYZ 150.705 679.769 null] ->> -% 1669 0 obj -<< -/Font << /F16 554 0 R /F27 556 0 R /F8 557 0 R /F30 764 0 R >> -/ProcSet [ /PDF /Text ] ->> -% 1677 0 obj -<< -/Type /Page -/Contents 1678 0 R -/Resources 1676 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1655 0 R -/Annots [ 1675 0 R ] +/Rect [371.488 436.001 438.546 447.126] +/A << /S /GoTo /D (descdata) >> >> -% 1675 0 obj +% 1766 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 449.411 372.239 460.536] -/A << /S /GoTo /D (spdata) >> ->> -% 1679 0 obj -<< -/D [1677 0 R /XYZ 98.895 753.953 null] ->> -% 497 0 obj -<< -/D [1677 0 R /XYZ 99.895 720.077 null] +/Rect [318.576 129.071 385.634 140.196] +/A << /S /GoTo /D (precdata) >> >> -% 1680 0 obj +% 1770 0 obj << -/D [1677 0 R /XYZ 99.895 679.769 null] +/D [1768 0 R /XYZ 98.895 753.953 null] >> -% 1681 0 obj +% 525 0 obj << -/D [1677 0 R /XYZ 99.895 679.769 null] +/D [1768 0 R /XYZ 99.895 720.077 null] >> -% 1676 0 obj +% 1767 0 obj << -/Font << /F16 554 0 R /F27 556 0 R /F8 557 0 R /F30 764 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 1683 0 obj +% 1773 0 obj << /Type /Page -/Contents 1684 0 R -/Resources 1682 0 R +/Contents 1774 0 R +/Resources 1772 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1655 0 R ->> -% 1685 0 obj -<< -/D [1683 0 R /XYZ 149.705 753.953 null] ->> -% 501 0 obj -<< -/D [1683 0 R /XYZ 150.705 720.077 null] ->> -% 1686 0 obj -<< -/D [1683 0 R /XYZ 150.705 679.769 null] +/Parent 1755 0 R >> -% 1687 0 obj +% 1775 0 obj << -/D [1683 0 R /XYZ 150.705 679.769 null] +/D [1773 0 R /XYZ 149.705 753.953 null] >> -% 1682 0 obj +% 1772 0 obj << -/Font << /F16 554 0 R /F27 556 0 R /F8 557 0 R /F30 764 0 R >> +/Font << /F27 560 0 R /F8 561 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 1690 0 obj +% 1781 0 obj << /Type /Page -/Contents 1691 0 R -/Resources 1689 0 R +/Contents 1782 0 R +/Resources 1780 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1695 0 R -/Annots [ 1688 0 R ] +/Parent 1755 0 R +/Annots [ 1776 0 R 1777 0 R 1778 0 R 1779 0 R ] >> -% 1688 0 obj +% 1776 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 582.91 372.239 594.035] -/A << /S /GoTo /D (spdata) >> ->> -% 1692 0 obj -<< -/D [1690 0 R /XYZ 98.895 753.953 null] ->> -% 505 0 obj -<< -/D [1690 0 R /XYZ 99.895 720.077 null] ->> -% 1693 0 obj -<< -/D [1690 0 R /XYZ 99.895 679.769 null] ->> -% 1694 0 obj -<< -/D [1690 0 R /XYZ 99.895 679.769 null] ->> -% 1689 0 obj -<< -/Font << /F16 554 0 R /F27 556 0 R /F8 557 0 R /F30 764 0 R >> -/ProcSet [ /PDF /Text ] ->> -% 1697 0 obj -<< -/Type /Page -/Contents 1698 0 R -/Resources 1696 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1695 0 R ->> -% 1699 0 obj -<< -/D [1697 0 R /XYZ 149.705 753.953 null] ->> -% 509 0 obj -<< -/D [1697 0 R /XYZ 150.705 720.077 null] ->> -% 1700 0 obj -<< -/D [1697 0 R /XYZ 150.705 679.769 null] ->> -% 1701 0 obj -<< -/D [1697 0 R /XYZ 150.705 679.769 null] ->> -% 1696 0 obj -<< -/Font << /F16 554 0 R /F27 556 0 R /F8 557 0 R /F30 764 0 R >> -/ProcSet [ /PDF /Text ] ->> -% 1703 0 obj -<< -/Type /Page -/Contents 1704 0 R -/Resources 1702 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1695 0 R ->> -% 1705 0 obj -<< -/D [1703 0 R /XYZ 98.895 753.953 null] ->> -% 513 0 obj -<< -/D [1703 0 R /XYZ 99.895 716.092 null] ->> -% 1702 0 obj -<< -/Font << /F16 554 0 R /F8 557 0 R /F14 767 0 R /F30 764 0 R >> -/ProcSet [ /PDF /Text ] ->> -% 1709 0 obj -<< -/Type /Page -/Contents 1710 0 R -/Resources 1708 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1695 0 R -/Annots [ 1706 0 R 1707 0 R ] +/Rect [321.343 574.94 388.401 586.065] +/A << /S /GoTo /D (precdata) >> >> -% 1706 0 obj +% 1777 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [372.153 511.179 439.211 522.304] -/A << /S /GoTo /D (precdata) >> +/Rect [347.301 519.15 423.355 530.274] +/A << /S /GoTo /D (vdata) >> >> -% 1707 0 obj +% 1778 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [219.641 421.792 226.103 433.832] -/A << /S /GoTo /D (Hfootnote.4) >> +/Rect [324.885 463.359 391.943 474.484] +/A << /S /GoTo /D (descdata) >> >> -% 1711 0 obj +% 1779 0 obj << -/D [1709 0 R /XYZ 149.705 753.953 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [347.301 274.069 423.355 285.194] +/A << /S /GoTo /D (vdata) >> >> -% 517 0 obj +% 1783 0 obj << -/D [1709 0 R /XYZ 150.705 720.077 null] +/D [1781 0 R /XYZ 98.895 753.953 null] >> -% 1712 0 obj +% 529 0 obj << -/D [1709 0 R /XYZ 165.948 129.79 null] +/D [1781 0 R /XYZ 99.895 720.077 null] >> -% 1708 0 obj +% 1780 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R /F11 750 0 R /F7 765 0 R /F32 768 0 R /F31 770 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 1718 0 obj +% 1786 0 obj << /Type /Page -/Contents 1719 0 R -/Resources 1717 0 R +/Contents 1787 0 R +/Resources 1785 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1695 0 R -/Annots [ 1713 0 R 1714 0 R 1715 0 R 1716 0 R ] ->> -% 1713 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [317.856 577.4 395.375 588.524] -/A << /S /GoTo /D (spdata) >> ->> -% 1714 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [396.921 506.7 463.979 517.825] -/A << /S /GoTo /D (precdata) >> ->> -% 1715 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [371.488 436.001 438.546 447.126] -/A << /S /GoTo /D (descdata) >> +/Parent 1755 0 R +/Annots [ 1784 0 R ] >> -% 1716 0 obj +% 1784 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [318.576 129.071 385.634 140.196] +/Rect [372.153 574.94 439.211 586.065] /A << /S /GoTo /D (precdata) >> >> -% 1720 0 obj +% 1788 0 obj << -/D [1718 0 R /XYZ 98.895 753.953 null] +/D [1786 0 R /XYZ 149.705 753.953 null] >> -% 521 0 obj +% 533 0 obj << -/D [1718 0 R /XYZ 99.895 720.077 null] +/D [1786 0 R /XYZ 150.705 720.077 null] >> -% 1717 0 obj +% 1785 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R /F11 755 0 R /F14 772 0 R >> /ProcSet [ /PDF /Text ] >> -% 1722 0 obj +% 1790 0 obj << /Type /Page -/Contents 1723 0 R -/Resources 1721 0 R +/Contents 1791 0 R +/Resources 1789 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1695 0 R +/Parent 1793 0 R >> -% 1724 0 obj +% 1792 0 obj << -/D [1722 0 R /XYZ 149.705 753.953 null] +/D [1790 0 R /XYZ 98.895 753.953 null] >> -% 1721 0 obj +% 537 0 obj +<< +/D [1790 0 R /XYZ 99.895 720.077 null] +>> +% 1789 0 obj << -/Font << /F27 556 0 R /F8 557 0 R /F30 764 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 1730 0 obj +% 1797 0 obj << /Type /Page -/Contents 1731 0 R -/Resources 1729 0 R +/Contents 1798 0 R +/Resources 1796 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1733 0 R -/Annots [ 1725 0 R 1726 0 R 1727 0 R 1728 0 R ] +/Parent 1793 0 R +/Annots [ 1794 0 R 1795 0 R ] >> -% 1725 0 obj +% 1794 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [321.343 574.94 388.401 586.065] +/Rect [372.153 574.94 439.211 586.065] /A << /S /GoTo /D (precdata) >> >> -% 1726 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [347.301 519.15 423.355 530.274] -/A << /S /GoTo /D (vdata) >> ->> -% 1727 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [324.885 463.359 391.943 474.484] -/A << /S /GoTo /D (descdata) >> ->> -% 1728 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [347.301 274.069 423.355 285.194] -/A << /S /GoTo /D (vdata) >> ->> -% 1732 0 obj -<< -/D [1730 0 R /XYZ 98.895 753.953 null] ->> -% 525 0 obj -<< -/D [1730 0 R /XYZ 99.895 720.077 null] ->> -% 1729 0 obj -<< -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R >> -/ProcSet [ /PDF /Text ] ->> -% 1736 0 obj -<< -/Type /Page -/Contents 1737 0 R -/Resources 1735 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1733 0 R -/Annots [ 1734 0 R ] ->> -% 1734 0 obj +% 1795 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [372.153 574.94 439.211 586.065] +/Rect [372.153 499.224 439.211 510.349] /A << /S /GoTo /D (precdata) >> >> -% 1738 0 obj +% 1799 0 obj << -/D [1736 0 R /XYZ 149.705 753.953 null] +/D [1797 0 R /XYZ 149.705 753.953 null] >> -% 529 0 obj +% 541 0 obj << -/D [1736 0 R /XYZ 150.705 720.077 null] +/D [1797 0 R /XYZ 150.705 720.077 null] >> -% 1735 0 obj +% 1796 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R /F11 750 0 R /F14 767 0 R >> +/Font << /F16 558 0 R /F30 769 0 R /F27 560 0 R /F8 561 0 R >> /ProcSet [ /PDF /Text ] >> -% 1740 0 obj +% 1801 0 obj << /Type /Page -/Contents 1741 0 R -/Resources 1739 0 R +/Contents 1802 0 R +/Resources 1800 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1733 0 R +/Parent 1793 0 R >> -% 1742 0 obj +% 1803 0 obj << -/D [1740 0 R /XYZ 98.895 753.953 null] +/D [1801 0 R /XYZ 98.895 753.953 null] >> -% 533 0 obj +% 545 0 obj << -/D [1740 0 R /XYZ 99.895 720.077 null] +/D [1801 0 R /XYZ 99.895 716.092 null] >> -% 1739 0 obj +% 1800 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F30 769 0 R >> /ProcSet [ /PDF /Text ] >> -% 1746 0 obj +% 1808 0 obj << /Type /Page -/Contents 1747 0 R -/Resources 1745 0 R +/Contents 1809 0 R +/Resources 1807 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1733 0 R -/Annots [ 1743 0 R 1744 0 R ] +/Parent 1793 0 R +/Annots [ 1804 0 R 1805 0 R ] >> -% 1743 0 obj +% 1804 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [372.153 574.94 439.211 586.065] -/A << /S /GoTo /D (precdata) >> +/Rect [384.578 276.229 391.04 288.268] +/A << /S /GoTo /D (Hfootnote.5) >> >> -% 1744 0 obj +% 1805 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [372.153 499.224 439.211 510.349] -/A << /S /GoTo /D (precdata) >> +/Rect [345.53 134.549 423.049 145.674] +/A << /S /GoTo /D (spdata) >> >> -% 1748 0 obj +% 1810 0 obj << -/D [1746 0 R /XYZ 149.705 753.953 null] +/D [1808 0 R /XYZ 149.705 753.953 null] >> -% 537 0 obj +% 549 0 obj << -/D [1746 0 R /XYZ 150.705 720.077 null] +/D [1808 0 R /XYZ 150.705 720.077 null] >> -% 1745 0 obj +% 1811 0 obj << -/Font << /F16 554 0 R /F30 764 0 R /F27 556 0 R /F8 557 0 R >> -/ProcSet [ /PDF /Text ] +/D [1808 0 R /XYZ 150.705 446.608 null] >> -% 1750 0 obj +% 1812 0 obj << -/Type /Page -/Contents 1751 0 R -/Resources 1749 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1733 0 R +/D [1808 0 R /XYZ 150.705 446.608 null] >> -% 1752 0 obj +% 1813 0 obj << -/D [1750 0 R /XYZ 98.895 753.953 null] +/D [1808 0 R /XYZ 150.705 434.653 null] >> -% 541 0 obj +% 1814 0 obj << -/D [1750 0 R /XYZ 99.895 716.092 null] +/D [1808 0 R /XYZ 165.948 129.79 null] >> -% 1749 0 obj +% 1807 0 obj << -/Font << /F16 554 0 R /F8 557 0 R /F30 764 0 R >> +/Font << /F16 558 0 R /F8 561 0 R /F27 560 0 R /F11 755 0 R /F14 772 0 R /F10 771 0 R /F7 770 0 R /F30 769 0 R /F32 773 0 R /F31 775 0 R /F33 1815 0 R >> /ProcSet [ /PDF /Text ] >> -% 1757 0 obj +% 1820 0 obj << /Type /Page -/Contents 1758 0 R -/Resources 1756 0 R +/Contents 1821 0 R +/Resources 1819 0 R /MediaBox [0 0 595.276 841.89] -/Parent 1733 0 R -/Annots [ 1753 0 R 1754 0 R ] +/Parent 1793 0 R +/Annots [ 1806 0 R 1816 0 R 1817 0 R 1818 0 R ] >> -% 1753 0 obj +% 1806 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [384.578 276.229 391.04 288.268] -/A << /S /GoTo /D (Hfootnote.5) >> +/Rect [294.721 655.098 361.779 666.223] +/A << /S /GoTo /D (precdata) >> >> -% 1754 0 obj +% 1816 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.53 134.549 423.049 145.674] -/A << /S /GoTo /D (spdata) >> +/Rect [347.301 587.85 423.355 598.975] +/A << /S /GoTo /D (vdata) >> >> -% 1759 0 obj +% 1817 0 obj << -/D [1757 0 R /XYZ 149.705 753.953 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [347.301 520.602 423.355 531.727] +/A << /S /GoTo /D (vdata) >> >> -% 545 0 obj +% 1818 0 obj << -/D [1757 0 R /XYZ 150.705 720.077 null] +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [294.721 386.107 361.779 397.232] +/A << /S /GoTo /D (descdata) >> >> -% 1760 0 obj +% 1822 0 obj << -/D [1757 0 R /XYZ 150.705 446.608 null] +/D [1820 0 R /XYZ 98.895 753.953 null] >> -% 1761 0 obj +% 1819 0 obj << -/D [1757 0 R /XYZ 150.705 446.608 null] +/Font << /F27 560 0 R /F8 561 0 R /F30 769 0 R /F11 755 0 R /F14 772 0 R >> +/ProcSet [ /PDF /Text ] >> -% 1762 0 obj +% 1825 0 obj << -/D [1757 0 R /XYZ 150.705 434.653 null] +/Type /Page +/Contents 1826 0 R +/Resources 1824 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1793 0 R +/Annots [ 1823 0 R ] >> - -endstream -endobj -1771 0 obj +% 1823 0 obj << -/Length 7084 +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [398.111 579.382 474.165 590.507] +/A << /S /GoTo /D (vdata) >> >> -stream -0 g 0 G -0 g 0 G -0 g 0 G -BT -/F27 9.9626 Tf 99.895 706.129 Td [(prec)]TJ -0 g 0 G -/F8 9.9626 Tf 26.408 0 Td [(The)-333(data)-334(structure)-333(con)28(taining)-333(the)-334(preconditioner.)]TJ -1.501 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ -ET -q -1 0 0 1 312.036 658.507 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 315.174 658.308 Td [(prec)]TJ -ET -q -1 0 0 1 336.723 658.507 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 339.861 658.308 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -260.887 -19.427 Td [(b)]TJ -0 g 0 G -/F8 9.9626 Tf 11.347 0 Td [(The)-333(RHS)-334(v)28(ector.)]TJ 13.56 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-333(arra)27(y)-333(or)-333(an)-334(ob)-55(ject)-333(of)-334(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 223.496 0 Td [(psb)]TJ -ET -q -1 0 0 1 364.616 591.26 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 367.754 591.06 Td [(T)]TJ -ET -q -1 0 0 1 373.612 591.26 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 376.751 591.06 Td [(vect)]TJ -ET -q -1 0 0 1 398.3 591.26 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 401.438 591.06 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -322.464 -19.427 Td [(x)]TJ -0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(The)-333(initial)-334(guess.)]TJ 13.879 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-333(arra)27(y)-333(or)-333(an)-334(ob)-55(ject)-333(of)-334(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 223.496 0 Td [(psb)]TJ -ET -q -1 0 0 1 364.616 524.012 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 367.754 523.813 Td [(T)]TJ -ET -q -1 0 0 1 373.612 524.012 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 376.751 523.813 Td [(vect)]TJ -ET -q -1 0 0 1 398.3 524.012 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 401.438 523.813 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -322.464 -19.428 Td [(eps)]TJ -0 g 0 G -/F8 9.9626 Tf 21.117 0 Td [(The)-333(stopping)-334(tolerance.)]TJ 3.79 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(real)-333(n)28(um)27(b)-27(er.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -19.427 Td [(desc)]TJ -ET -q -1 0 0 1 121.81 437.337 cm -[]0 d 0 J 0.398 w 0 0 m 3.437 0 l S -Q -BT -/F27 9.9626 Tf 125.247 437.138 Td [(a)]TJ -0 g 0 G -/F8 9.9626 Tf 10.551 0 Td [(con)28(tains)-334(d)1(ata)-334(structures)-333(for)-333(com)-1(m)28(unications.)]TJ -10.996 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(structured)-333(data)-333(of)-334(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 170.915 0 Td [(psb)]TJ -ET -q -1 0 0 1 312.036 389.516 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 315.174 389.317 Td [(desc)]TJ -ET -q -1 0 0 1 336.723 389.516 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 339.861 389.317 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.921 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -260.887 -19.427 Td [(itmax)]TJ -0 g 0 G -/F8 9.9626 Tf 33.783 0 Td [(The)-333(maxim)27(um)-333(n)28(um)28(b)-28(er)-333(of)-334(iterations)-333(to)-333(p)-28(erform.)]TJ -8.876 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(Default:)]TJ/F11 9.9626 Tf 39.436 0 Td [(itmax)]TJ/F8 9.9626 Tf 29.504 0 Td [(=)-278(1000.)]TJ -68.94 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(an)-333(in)28(teger)-333(v)55(ariable)]TJ/F11 9.9626 Tf 142.079 0 Td [(itmax)]TJ/F14 9.9626 Tf 29.504 0 Td [(\025)]TJ/F8 9.9626 Tf 10.516 0 Td [(1.)]TJ -0 g 0 G -/F27 9.9626 Tf -207.006 -19.427 Td [(itrace)]TJ -0 g 0 G -/F8 9.9626 Tf 33.251 0 Td [(If)]TJ/F11 9.9626 Tf 8.911 0 Td [(>)]TJ/F8 9.9626 Tf 10.517 0 Td [(0)-228(prin)28(t)-228(out)-228(an)-227(informational)-228(message)-228(ab)-28(out)-228(con)28(v)28(ergence)-228(ev)28(e)-1(r)1(y)]TJ/F11 9.9626 Tf 265.015 0 Td [(itr)-28(ace)]TJ/F8 9.9626 Tf -292.787 -11.955 Td [(iterations.)]TJ 0 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -67.94 -31.382 Td [(irst)]TJ -0 g 0 G -/F8 9.9626 Tf 21.857 0 Td [(An)-333(in)28(te)-1(ger)-333(sp)-28(ecifying)-333(the)-333(restart)-334(parameter.)]TJ 3.05 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.955 Td [(V)83(alues:)]TJ/F11 9.9626 Tf 37.506 0 Td [(ir)-28(st)-447(>)]TJ/F8 9.9626 Tf 33.135 0 Td [(0.)-750(This)-435(is)-435(emplo)28(y)28(e)-1(d)-435(for)-435(the)-435(BiCGST)84(AB)-1(L)-435(or)-435(R)28(GMRES)]TJ -70.641 -11.955 Td [(metho)-28(ds,)-333(otherwise)-334(it)-333(is)-333(ignored.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.907 -19.427 Td [(istop)]TJ -0 g 0 G -/F8 9.9626 Tf 29.232 0 Td [(An)-333(in)28(te)-1(ger)-333(sp)-28(ecifying)-333(the)-333(stopping)-334(crit)1(e)-1(ri)1(on.)]TJ -4.325 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ -0 g 0 G -/F8 9.9626 Tf 107.098 -29.888 Td [(139)]TJ -0 g 0 G -ET - -endstream -endobj -1777 0 obj +% 1827 0 obj +<< +/D [1825 0 R /XYZ 149.705 753.953 null] +>> +% 1824 0 obj +<< +/Font << /F8 561 0 R /F27 560 0 R /F30 769 0 R /F11 755 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1829 0 obj +<< +/Type /Page +/Contents 1830 0 R +/Resources 1828 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1836 0 R +>> +% 1831 0 obj +<< +/D [1829 0 R /XYZ 98.895 753.953 null] +>> +% 1832 0 obj +<< +/D [1829 0 R /XYZ 99.895 724.062 null] +>> +% 739 0 obj +<< +/D [1829 0 R /XYZ 99.895 699.619 null] +>> +% 1833 0 obj +<< +/D [1829 0 R /XYZ 99.895 643.15 null] +>> +% 790 0 obj +<< +/D [1829 0 R /XYZ 99.895 588.618 null] +>> +% 789 0 obj << -/Length 4414 +/D [1829 0 R /XYZ 99.895 534.087 null] >> -stream -0 g 0 G -0 g 0 G -BT -/F8 9.9626 Tf 175.611 706.129 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf 40.576 0 Td [(.)]TJ -70.188 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.548 0 Td [(.)]TJ -43.034 -11.955 Td [(V)83(alues:)-478(1:)-479(use)-351(the)-350(norm)28(wise)-351(bac)28(kw)28(ard)-351(error,)-354(2:)-479(use)-350(the)-351(scaled)-350(2-norm)-351(of)]TJ 0 -11.956 Td [(the)-333(residual,)-334(3:)-444(use)-333(the)-334(residual)-333(reduction)-333(in)-334(the)-333(2-norm.)-444(Default:)-445(2.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.906 -19.925 Td [(On)-383(Return)]TJ -0 g 0 G -0 g 0 G - 0 -19.925 Td [(x)]TJ -0 g 0 G -/F8 9.9626 Tf 11.028 0 Td [(The)-333(computed)-334(solution.)]TJ 13.878 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(inout)]TJ/F8 9.9626 Tf 26.096 0 Td [(.)]TJ -59.582 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(rank)-333(one)-334(ar)1(ra)27(y)-333(or)-333(an)-334(ob)-55(ject)-333(of)-334(t)28(yp)-28(e)]TJ -0 0 1 rg 0 0 1 RG -/F30 9.9626 Tf 223.496 0 Td [(psb)]TJ -ET -q -1 0 0 1 415.426 582.791 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 418.564 582.592 Td [(T)]TJ -ET -q -1 0 0 1 424.422 582.791 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 427.56 582.592 Td [(vect)]TJ -ET -q -1 0 0 1 449.109 582.791 cm -[]0 d 0 J 0.398 w 0 0 m 3.138 0 l S -Q -BT -/F30 9.9626 Tf 452.247 582.592 Td [(type)]TJ -0 g 0 G -/F8 9.9626 Tf 20.922 0 Td [(.)]TJ -0 g 0 G -/F27 9.9626 Tf -322.464 -19.925 Td [(iter)]TJ -0 g 0 G -/F8 9.9626 Tf 22.589 0 Td [(The)-333(n)27(u)1(m)27(b)-27(e)-1(r)-333(of)-333(iterations)-333(p)-28(erformed.)]TJ 2.317 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Returned)-333(as:)-445(an)-333(in)28(teger)-334(v)56(ariable.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.906 -19.925 Td [(err)]TJ -0 g 0 G -/F8 9.9626 Tf 19.669 0 Td [(The)-333(con)27(v)28(ergence)-333(estimate)-334(on)-333(exit.)]TJ 5.237 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.956 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Returned)-333(as:)-445(a)-333(real)-333(n)27(um)28(b)-28(er.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.906 -19.925 Td [(cond)]TJ -0 g 0 G -/F8 9.9626 Tf 28.532 0 Td [(An)-280(estimate)-280(of)-279(the)-280(condition)-280(n)28(um)28(b)-28(er)-280(of)-279(matrix)]TJ/F11 9.9626 Tf 204.226 0 Td [(A)]TJ/F8 9.9626 Tf 7.472 0 Td [(;)-298(only)-279(a)28(v)55(ailable)-280(with)-279(the)]TJ/F11 9.9626 Tf -215.324 -11.955 Td [(C)-72(G)]TJ/F8 9.9626 Tf 18.988 0 Td [(metho)-28(d)-333(on)-333(real)-334(data.)]TJ -18.988 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(optional)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Returned)-287(as:)-421(a)-287(real)-287(n)28(um)28(b)-28(er.)-429(A)-287(correct)-287(result)-286(will)-287(b)-28(e)-287(greater)-287(than)-287(or)-286(equal)]TJ 0 -11.955 Td [(to)-267(one;)-288(if)-267(sp)-28(eci\014ed)-266(for)-267(non-real)-266(data,)-280(or)-266(an)-267(error)-266(o)-28(ccurred,)-280(zero)-267(is)-266(returned.)]TJ -0 g 0 G -/F27 9.9626 Tf -24.906 -19.925 Td [(info)]TJ -0 g 0 G -/F8 9.9626 Tf 23.758 0 Td [(Error)-333(co)-28(de.)]TJ 1.148 -11.956 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(lo)-32(cal)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.612 0 Td [(required)]TJ/F8 9.9626 Tf -29.612 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(An)-333(in)28(te)-1(ger)-333(v)56(alue;)-334(0)-333(means)-333(no)-334(error)-333(has)-333(b)-28(een)-333(detec)-1(ted.)]TJ -0 g 0 G - 139.477 -197.26 Td [(140)]TJ -0 g 0 G -ET - -endstream -endobj -1781 0 obj +% 745 0 obj << -/Length 7014 +/D [1829 0 R /XYZ 99.895 479.555 null] >> -stream -0 g 0 G -0 g 0 G -BT -/F16 14.3462 Tf 99.895 706.129 Td [(References)]TJ -0 g 0 G -/F8 9.9626 Tf 4.982 -21.821 Td [([1])]TJ -0 g 0 G - [-500(D.)-441(Barbieri,)-468(V.)-441(Cardellini,)-467(S.)-441(Filipp)-28(one)-441(and)-441(D.)-441(Rouson)]TJ/F17 9.9626 Tf 267.833 0 Td [(Design)-457(Patterns)]TJ -252.336 -11.955 Td [(for)-441(S)-1(ci)1(ent)-1(i)1(\014)-1(c)-441(Computations)-442(on)-441(Sp)51(arse)-441(Matric)51(es)]TJ/F8 9.9626 Tf 210.802 0 Td [(,)-447(HPSS)-424(2011,)-447(Algorithms)]TJ -210.802 -11.955 Td [(and)-375(Programming)-374(T)83(o)-28(ols)-375(for)-374(Next-Generation)-375(High-P)28(erformance)-375(Scien)28(ti\014c)]TJ 0 -11.956 Td [(Soft)28(w)28(are,)-334(Bordeaux,)-333(Sep.)-333(2011)]TJ -0 g 0 G - -15.497 -18.666 Td [([2])]TJ -0 g 0 G - [-500(G.)-341(Bella,)-343(S.)-341(Filipp)-28(one,)-343(A.)-341(De)-341(Maio)-341(and)-341(M.)-341(T)84(esta,)]TJ/F17 9.9626 Tf 235.488 0 Td [(A)-365(Simulation)-365(Mo)51(del)-364(for)]TJ -219.991 -11.955 Td [(F)77(or)51(est)-365(Fir)51(es)]TJ/F8 9.9626 Tf 52.03 0 Td [(,)-343(in)-341(J.)-340(Dongarra,)-343(K.)-341(Madsen,)-343(J.)-341(W)84(asniewski,)-343(editors,)-343(Pro)-28(ceed-)]TJ -52.03 -11.955 Td [(ings)-394(of)-395(P)84(ARA)-395(04)-394(W)83(orkshop)-394(on)-395(State)-394(of)-395(the)-394(Art)-394(in)-395(Scien)28(ti\014c)-394(Com)-1(p)1(uting,)]TJ 0 -11.955 Td [(pp.)-333(546{553,)-334(Lecture)-333(Notes)-333(in)-334(Computer)-333(Science,)-333(Springer,)-334(2005.)]TJ -0 g 0 G - -15.497 -18.666 Td [([3])]TJ -0 g 0 G - [-500(A.)-316(Buttari,)-320(D.)-317(di)-316(Sera\014no,)-320(P)83(.)-316(D'Am)28(bra,)-320(S.)-317(Filipp)-27(one,)-100(2LEV-D2P4:)-436(a)-316(pac)28(k-)]TJ 15.497 -11.955 Td [(age)-388(of)-388(high-p)-28(erformance)-388(preconditioners,)-218(Applicable)-388(Alge)-1(b)1(ra)-389(in)-388(Engin)1(e)-1(er-)]TJ 0 -11.956 Td [(ing,)-393(Comm)27(un)1(ications)-382(and)-381(Computing,)-393(V)83(olume)-381(18,)-393(Num)27(b)-27(er)-382(3,)-393(Ma)28(y)83(,)-393(2007,)]TJ 0 -11.955 Td [(pp.)-333(223-239)]TJ -0 g 0 G - -15.497 -18.666 Td [([4])]TJ -0 g 0 G - [-500(P)83(.)-691(D'Am)28(bra,)-780(S.)-691(Filipp)-28(one,)-780(D.)-691(Di)-691(Sera\014no)-819(On)-691(the)-691(Dev)28(elopmen)28(t)-691(of)]TJ 15.497 -11.955 Td [(PSBLAS-based)-430(P)28(arallel)-430(Tw)28(o-lev)28(el)-430(Sc)27(h)28(w)28(arz)-430(Preconditioners)-731(Applied)-430(Nu-)]TJ 0 -11.955 Td [(merical)-245(Mathematics)-1(,)-262(Elsevier)-246(Science,)-263(V)83(ol)1(ume)-246(57,)-263(Issues)-245(11-12,)-263(No)27(v)28(em)28(b)-28(er-)]TJ 0 -11.955 Td [(Decem)28(b)-28(er)-333(2007)-1(,)-333(P)28(ages)-333(1181-1196.)]TJ -0 g 0 G - -15.497 -18.667 Td [([5])]TJ -0 g 0 G - [-500(Dongarra,)-529(J.)-490(J.,)-529(DuCroz,)-529(J.,)-529(Hammarling,)-529(S.)-490(and)-490(Hanson,)-529(R.,)-529(An)-490(Ex-)]TJ 15.497 -11.955 Td [(tended)-478(Set)-478(of)-478(F)83(ortran)-478(Basic)-478(Linear)-478(Algebra)-478(Subprograms,)-514(A)28(C)-1(M)-477(T)83(rans.)]TJ 0 -11.955 Td [(Math.)-333(Soft)28(w.)-334(v)28(ol.)-333(14,)-334(1{17,)-333(1988.)]TJ -0 g 0 G - -15.497 -18.666 Td [([6])]TJ -0 g 0 G - [-500(Dongarra,)-444(J.,)-444(DuCroz,)-444(J.,)-445(Hammarling,)-444(S.)-422(and)-422(Du\013,)-444(I.,)-444(A)-422(Set)-422(of)-422(lev)28(el)-422(3)]TJ 15.497 -11.955 Td [(Basic)-357(Linear)-357(Algebra)-357(Subpr)1(ogram)-1(s,)-362(A)27(CM)-356(T)83(rans.)-357(Math.)-357(Soft)28(w.)-357(v)28(ol.)-357(16,)-362(1{)]TJ 0 -11.955 Td [(17,)-333(1990.)]TJ -0 g 0 G - -15.497 -18.666 Td [([7])]TJ -0 g 0 G - [-500(J.)-265(J.)-266(Dongarra)-266(and)-265(R.)-266(C.)-265(Whaley)83(,)]TJ/F17 9.9626 Tf 162.063 0 Td [(A)-295(User's)-296(Guide)-295(to)-296(the)-295(BLA)25(CS)-295(v.)-295(1.1)]TJ/F8 9.9626 Tf 156.589 0 Td [(,)-279(La-)]TJ -303.155 -11.956 Td [(pac)28(k)-291(W)84(orking)-291(Note)-290(94,)-299(T)83(ec)28(h.)-290(Rep.)-291(UT-CS-95-281,)-299(Univ)28(ersit)28(y)-290(of)-291(T)84(ennesse)-1(e,)]TJ 0 -11.955 Td [(Marc)28(h)-334(1995)-333(\050up)-28(dated)-333(Ma)28(y)-333(1997\051.)]TJ -0 g 0 G - -15.497 -18.666 Td [([8])]TJ -0 g 0 G - [-500(I.)-488(Du\013,)-527(M.)-488(Marrone,)-526(G.)-488(Radicati)-488(and)-488(C.)-488(Vittoli,)]TJ/F17 9.9626 Tf 244.569 0 Td [(L)51(evel)-500(3)-500(Basic)-500(Line)51(ar)]TJ -229.072 -11.955 Td [(A)26(lgebr)51(a)-463(Subpr)52(o)51(gr)51(ams)-463(f)1(or)-463(Sp)51(arse)-462(Matric)51(es:)-669(a)-462(User)-462(L)51(evel)-463(Interfac)52(e)]TJ/F8 9.9626 Tf 292.206 0 Td [(,)-475(A)27(CM)]TJ -292.206 -11.955 Td [(T)83(ransactions)-333(on)-333(Mathematical)-334(Soft)28(w)28(are,)-333(23\0503\051,)-334(pp.)-333(379{401,)-333(1997.)]TJ -0 g 0 G - -15.497 -18.666 Td [([9])]TJ -0 g 0 G - [-500(I.)-358(Du\013,)-365(M.)-359(Heroux)-358(and)-359(R.)-358(P)27(ozo,)]TJ/F17 9.9626 Tf 162.007 0 Td [(A)26(n)-381(Overview)-381(of)-381(the)-381(Sp)51(arse)-381(Basic)-381(Line)51(ar)]TJ -146.51 -11.956 Td [(A)26(lgebr)51(a)-348(S)-1(u)1(bpr)51(o)51(gr)51(ams:)-455(the)-348(New)-349(Standar)51(d)-348(fr)51(om)-348(the)-348(BLAS)-348(T)76(e)51(chnic)52(al)-349(F)77(orum)]TJ/F8 9.9626 Tf 320.465 0 Td [(,)]TJ -320.465 -11.955 Td [(A)28(CM)-334(T)84(ransactions)-334(on)-333(Mathematical)-333(Soft)28(w)27(are,)-333(28\0502\051,)-333(pp.)-333(23)-1(9{267,)-333(2002.)]TJ -0 g 0 G - -20.479 -18.666 Td [([10])]TJ -0 g 0 G - [-500(S.)-451(Filipp)-28(one)-451(and)-451(M.)-451(Cola)-56(janni,)]TJ/F17 9.9626 Tf 165.708 0 Td [(PSBLAS:)-466(A)-466(Libr)51(ary)-466(for)-467(Par)51(al)-51(lel)-466(Line)51(ar)]TJ -145.229 -11.955 Td [(A)26(lgebr)51(a)-420(Computation)-420(on)-420(Sp)51(arse)-420(Matric)51(es)]TJ/F8 9.9626 Tf 181.375 0 Td [(,)-661(A)27(CM)-400(T)83(ransactions)-401(on)-401(Mathe-)]TJ -181.375 -11.955 Td [(matical)-333(Soft)27(w)28(are,)-333(26\0504\051,)-333(pp.)-334(527{550,)-333(2000.)]TJ -0 g 0 G - -20.479 -18.666 Td [([11])]TJ -0 g 0 G - [-500(S.)-425(Filipp)-27(one)-425(and)-425(A.)-425(Buttari,)]TJ/F17 9.9626 Tf 152.315 0 Td [(Obje)51(ct-Oriente)51(d)-442(T)77(e)51(chniques)-442(for)-441(Sp)51(arse)-442(Ma-)]TJ -131.836 -11.955 Td [(trix)-407(Computations)-406(in)-407(F)77(ortr)51(an)-407(2003)]TJ/F8 9.9626 Tf 153.485 0 Td [(,)-615(A)28(CM)-387(T)84(ransactions)-387(on)-386(Mathematical)]TJ -153.485 -11.956 Td [(Soft)28(w)28(are,)-334(38\0504\051,)-333(2012.)]TJ -0 g 0 G - -20.479 -18.666 Td [([12])]TJ -0 g 0 G - [-500(S.)-267(Filipp)-27(one,)-280(P)83(.)-267(D'Am)28(bra,)-280(M.)-267(Cola)-55(janni,)]TJ/F17 9.9626 Tf 197.776 0 Td [(Using)-297(a)-296(Par)51(al)-51(lel)-297(Libr)52(ary)-297(of)-296(Sp)51(arse)]TJ -177.297 -11.955 Td [(Line)51(ar)-352(A)26(lgebr)51(a)-352(in)-352(a)-352(Fluid)-352(Dynami)1(cs)-352(Applic)51(ations)-352(Co)51(de)-352(on)-352(Linux)-352(Clusters)]TJ/F8 9.9626 Tf 320.465 0 Td [(,)]TJ -320.465 -11.955 Td [(in)-398(G.)-399(Jou)1(b)-28(ert,)-415(A.)-398(Murli,)-414(F.)-399(P)28(eters,)-414(M.)-399(V)84(annesc)27(hi,)-414(editors,)-415(P)28(arallel)-398(Com-)]TJ 0 -11.955 Td [(puting)-354(-)-354(Adv)55(ances)-354(&)-354(Curren)28(t)-355(Issues,)-359(pp.)-354(441{448,)-360(Imp)-28(erial)-354(College)-354(Press,)]TJ 0 -11.955 Td [(2002.)]TJ -0 g 0 G - 143.905 -29.888 Td [(141)]TJ -0 g 0 G -ET - -endstream -endobj -1789 0 obj +% 746 0 obj << -/Length 3124 +/D [1829 0 R /XYZ 99.895 436.978 null] >> -stream -0 g 0 G -0 g 0 G -0 g 0 G -BT -/F8 9.9626 Tf 150.705 706.129 Td [([13])]TJ -0 g 0 G - [-500(Gamma,)-494(E.,)-987(Helm,)-493(R.,)-987(Johnson,)-494(R.,)-987(and)-923(Vlissides,)-494(J.)-461(1995.)]TJ/F17 9.9626 Tf 314.294 0 Td [(Design)]TJ -293.815 -11.955 Td [(Patterns:)-427(Elements)-293(of)-292(R)51(eusable)-293(Obje)51(ct-Oriente)51(d)-292(Softwar)51(e)]TJ/F8 9.9626 Tf 246.617 0 Td [(.)-262(Addison-W)83(esley)83(.)]TJ -0 g 0 G - -267.096 -19.926 Td [([14])]TJ -0 g 0 G - [-500(Karypis,)-561(G.)-515(and)-515(Kumar,)-561(V.,)]TJ/F17 9.9626 Tf 157.276 0 Td [(METIS:)-525(Unstructur)51(e)51(d)-525(Gr)51(aph)-525(Partitioning)]TJ -136.797 -11.955 Td [(and)-413(Sp)51(arse)-413(Matrix)-414(Or)51(deri)1(ng)-414(System)]TJ/F8 9.9626 Tf 158.597 0 Td [(.)-394(Minneap)-27(olis,)-409(MN)-394(55455:)-565(Univ)28(ersit)28(y)]TJ -158.597 -11.955 Td [(of)-420(Minnesota,)-441(Departmen)27(t)-420(of)-419(Computer)-420(Science,)-442(1995.)-420(In)28(ternet)-420(Address:)]TJ/F30 9.9626 Tf 0 -11.955 Td [(http://www.cs.umn.edu/~karypis)]TJ/F8 9.9626 Tf 156.91 0 Td [(.)]TJ -0 g 0 G - -177.389 -19.925 Td [([15])]TJ -0 g 0 G - [-500(La)28(wson,)-339(C.,)-339(Hanson,)-339(R.,)-339(Kincaid,)-339(D.)-338(and)-338(Krogh,)-339(F.,)-339(Basic)-338(Linear)-338(Algebra)]TJ 20.479 -11.956 Td [(Subprograms)-337(for)-336(Fortran)-337(usage,)-338(A)28(CM)-337(T)84(rans.)-337(Math.)-337(Soft)28(w.)-337(v)28(ol.)-337(5,)-337(38{329,)]TJ 0 -11.955 Td [(1979.)]TJ -0 g 0 G - -20.479 -19.925 Td [([16])]TJ -0 g 0 G - [-500(Mac)28(hiels,)-372(L.)-364(and)-364(Deville,)-372(M.)]TJ/F17 9.9626 Tf 148.97 0 Td [(F)77(ortr)51(an)-386(90:)-517(A)26(n)-387(entry)-386(to)-386(obje)51(ct-oriente)51(d)-386(pr)51(o-)]TJ -128.491 -11.955 Td [(gr)51(amming)-492(for)-492(the)-492(soluti)1(on)-492(of)-492(p)51(artial)-492(di\013er)51(ential)-492(e)51(quations.)]TJ/F8 9.9626 Tf 267.456 0 Td [(A)28(CM)-479(T)83(rans.)]TJ -267.456 -11.955 Td [(Math.)-333(Soft)28(w.)-334(v)28(ol.)-333(23,)-334(32{49.)]TJ -0 g 0 G - -20.479 -19.926 Td [([17])]TJ -0 g 0 G - [-500(Metcalf,)-434(M.,)-434(Reid,)-433(J.)-414(and)-414(Cohen,)-434(M.)]TJ/F17 9.9626 Tf 189.335 0 Td [(F)77(ortr)51(an)-432(95/2003)-432(explaine)51(d.)]TJ/F8 9.9626 Tf 123.907 0 Td [(Oxford)]TJ -292.763 -11.955 Td [(Univ)28(ersit)28(y)-334(Press,)-333(2004.)]TJ -0 g 0 G - -20.479 -19.925 Td [([18])]TJ -0 g 0 G - [-500(Rouson,)-374(D.W.I.,)-374(Xia,)-374(J.,)-374(Xu,)-373(X.:)-510(Scien)28(ti\014c)-366(Soft)28(w)28(are)-366(Design:)-510(Th)1(e)-366(Ob)-56(ject-)]TJ 20.479 -11.955 Td [(Orien)28(ted)-333(W)83(a)28(y.)-334(Cam)28(bridge)-333(Univ)28(ersit)27(y)-333(Press)-333(\0502011\051)]TJ -0 g 0 G - -20.479 -19.926 Td [([19])]TJ -0 g 0 G - [-500(M.)-443(Snir,)-471(S.)-443(Otto,)-471(S.)-443(Huss-Lederman,)-471(D.)-443(W)84(alk)27(er)-443(and)-443(J.)-443(Dongarra,)]TJ/F17 9.9626 Tf 321.124 0 Td [(MPI:)]TJ -300.645 -11.955 Td [(The)-365(Complete)-365(R)51(efer)51(enc)51(e.)-365(V)76(ol)1(ume)-366(1)-365(-)-365(The)-365(MPI)-365(Cor)51(e)]TJ/F8 9.9626 Tf 228.803 0 Td [(,)-343(sec)-1(on)1(d)-342(edition,)-343(MIT)]TJ -228.803 -11.955 Td [(Press,)-333(1998.)]TJ -0 g 0 G - 143.905 -352.677 Td [(142)]TJ -0 g 0 G -ET +% 762 0 obj +<< +/D [1829 0 R /XYZ 99.895 394.402 null] +>> +% 742 0 obj +<< +/D [1829 0 R /XYZ 99.895 351.272 null] +>> +% 743 0 obj +<< +/D [1829 0 R /XYZ 99.895 308.696 null] +>> +% 1834 0 obj +<< +/D [1829 0 R /XYZ 99.895 266.119 null] +>> +% 738 0 obj +<< +/D [1829 0 R /XYZ 99.895 223.543 null] +>> +% 1835 0 obj +<< +/D [1829 0 R /XYZ 99.895 180.966 null] +>> +% 1828 0 obj +<< +/Font << /F16 558 0 R /F8 561 0 R /F17 735 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1838 0 obj +<< +/Type /Page +/Contents 1839 0 R +/Resources 1837 0 R +/MediaBox [0 0 595.276 841.89] +/Parent 1836 0 R +>> +% 1840 0 obj +<< +/D [1838 0 R /XYZ 149.705 753.953 null] +>> +% 903 0 obj +<< +/D [1838 0 R /XYZ 150.705 716.092 null] +>> +% 777 0 obj +<< +/D [1838 0 R /XYZ 150.705 688.251 null] +>> +% 744 0 obj +<< +/D [1838 0 R /XYZ 150.705 632.184 null] +>> +% 741 0 obj +<< +/D [1838 0 R /XYZ 150.705 590.562 null] +>> +% 737 0 obj +<< +/D [1838 0 R /XYZ 150.705 544.789 null] +>> +% 740 0 obj +<< +/D [1838 0 R /XYZ 150.705 512.909 null] +>> +% 1841 0 obj +<< +/D [1838 0 R /XYZ 150.705 480.475 null] +>> +% 1837 0 obj +<< +/Font << /F8 561 0 R /F17 735 0 R /F30 769 0 R >> +/ProcSet [ /PDF /Text ] +>> +% 1842 0 obj +[757.3 871.7 778.7 672.4 827.9] +% 1843 0 obj +[575.2 657.4 525.9 657.4 543 361.6 591.7 657.4 328.7 361.6 624.5 328.7 986.1 657.4 591.7 657.4 624.5 488.1 466.8 460.2 657.4] +% 1844 0 obj +[1444.5 1277.8 555.6 1111.1 1111.1 1111.1 1111.1 1111.1 944.5 1277.8 555.6 1000 1444.5 555.6 1000 1444.5 472.2 472.2 527.8 527.8 527.8 527.8 666.7 666.7 1000 1000 1000 1000] +% 1845 0 obj +[285.5 399.7 399.7 513.9 799.4 285.5 342.6 285.5 513.9 513.9 513.9 513.9 513.9 513.9 513.9 513.9 513.9 513.9 513.9 285.5 285.5 285.5 799.4 485.3 485.3 799.4 770.7 727.9 742.3 785 699.4 670.8 806.5 770.7 371 528.1 799.2 642.3 942 770.7 799.4 699.4 799.4 756.5 571 742.3 770.7 770.7 1056.2 770.7 770.7 628.1 285.5 513.9 285.5 513.9 285.5 285.5 513.9 571 456.8 571 457.2 314 513.9 571 285.5 314 542.4 285.5 856.5 571 513.9 571 542.4 402 405.4 399.7 571 542.4 742.3 542.4 542.4 456.8] +% 1846 0 obj +[892.9 339.3 892.9 585.3 892.9 585.3 892.9 892.9 892.9 892.9 892.9 892.9 892.9 1138.9 585.3 585.3 892.9 892.9 892.9 892.9 892.9 892.9 892.9 892.9 892.9 892.9 892.9 892.9 1138.9 1138.9 892.9 892.9 1138.9 1138.9 585.3 585.3 1138.9 1138.9 1138.9 892.9 1138.9 1138.9 708.3 708.3 1138.9 1138.9 1138.9 892.9 329.4 1138.9] +% 1847 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] +% 1848 0 obj +[531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3] +% 1849 0 obj +[533.6] +% 1850 0 obj +[413.2 413.2 531.3 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 501.7 501.7 826.4 795.8 752.1 767.4 811.1 722.6 693.1 833.5 795.8 382.6 545.5 825.4 663.6 972.9 795.8 826.4 722.6 826.4 781.6 590.3 767.4 795.8 795.8 1091 795.8 795.8 649.3 295.1 531.3 295.1 531.3 295.1 295.1 531.3 590.3 472.2 590.3 472.2 324.7 531.3 590.3 295.1 324.7 560.8 295.1 885.4 590.3 531.3 590.3 560.8 414.1 419.1 413.2 590.3 560.8 767.4 560.8 560.8] +% 1851 0 obj +[611.1 611.1 611.1 611.1 611.1] +% 1852 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 750 833.3 416.7 666.7 666.7 777.8 777.8 444.4] +% 1853 0 obj +[339.3 892.9 585.3 892.9 585.3 610.1 859.1 863.2 819.4 934.1 838.7 724.5 889.4 935.6 506.3 632 959.9 783.7 1089.4 904.9 868.9 727.3 899.7 860.6 701.5 674.8 778.2 674.6 1074.4 936.9 671.5 778.4 462.3 462.3 462.3 1138.9 1138.9 478.2 619.7 502.4 510.5 594.7 542 557.1 557.3 668.8 404.2 472.7 607.3 361.3 1013.7 706.2] +% 1854 0 obj +[569.5 569.5 569.5 569.5 569.5 569.5 569.5 569.5 569.5 569.5 323.4] +% 1855 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] +% 1856 0 obj +[639.7 565.6 517.7 444.4 405.9 437.5 496.5 469.4 353.9 576.2 583.3 602.6 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.3 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.8 361.1 572.5 484.7 715.9 571.5 490.3 465.1] +% 1857 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] +% 1858 0 obj +[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] +% 1859 0 obj +[670.8 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.6 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 575 1150] endstream endobj -1811 0 obj +1863 0 obj << /Length1 2422 /Length2 20069 @@ -23136,7 +23956,7 @@ h } hjɣf/IV+\}3bGU 5"+IU(oVNo⮂b"ޢ:7cxst! @%e)\ /Cso^- qhKpڀ& /_ endstream endobj -1813 0 obj +1865 0 obj << /Length1 2366 /Length2 17268 @@ -23315,7 +24135,7 @@ u &gEu )?IqSb\Fb2pnzbZI]RA!,o5["/2!M98<]V<ʂe03L5R[ً>~K͚DHiDB.@0RyŏbcY2RDf42IECQj endstream endobj -1815 0 obj +1867 0 obj << /Length1 1599 /Length2 8420 @@ -23407,7 +24227,79 @@ I T,o|> +stream +%!PS-AdobeFont-1.0: CMEX10 003.002 +%%Title: CMEX10 +%Version: 003.002 +%%CreationDate: Mon Jul 13 16:17:00 2009 +%%Creator: David M. Jones +%Copyright: Copyright (c) 1997, 2009 American Mathematical Society +%Copyright: (), with Reserved Font Name CMEX10. +% This Font Software is licensed under the SIL Open Font License, Version 1.1. +% This license is in the accompanying file OFL.txt, and is also +% available with a FAQ at: http://scripts.sil.org/OFL. +%%EndComments +FontDirectory/CMEX10 known{/CMEX10 findfont dup/UniqueID known{dup +/UniqueID get 5092766 eq exch/FontType get 1 eq and}{pop false}ifelse +{save true}{false}ifelse}{false}ifelse +11 dict begin +/FontType 1 def +/FontMatrix [0.001 0 0 0.001 0 0 ]readonly def +/FontName /OUFNAH+CMEX10 def +/FontBBox {-24 -2960 1454 772 }readonly def +/PaintType 0 def +/FontInfo 9 dict dup begin +/version (003.002) readonly def +/Notice (Copyright \050c\051 1997, 2009 American Mathematical Society \050\051, with Reserved Font Name CMEX10.) readonly def +/FullName (CMEX10) readonly def +/FamilyName (Computer Modern) readonly def +/Weight (Medium) readonly def +/ItalicAngle 0 def +/isFixedPitch false def +/UnderlinePosition -100 def +/UnderlineThickness 50 def +end readonly def +/Encoding 256 array +0 1 255 {1 index exch /.notdef put} for +dup 115 /radicalBigg put +dup 88 /summationdisplay put +readonly def +currentdict end +currentfile eexec +oc;jAw-=%W)-{ru)rAE(@{빴Q|_R +ϤA -T@|q|VkJ%qu8PwGxŪ̆Q6K -U\%b"t-*xJ+ +}3{Z2zݬT2s$Z&{BJ{ޣ!fpG?[Ttku'5O P 1[.BBBo0 VoG;wCMdK&\YT{#v m E57G~ߡ +3[ť73ŝ:&uN]B Je v(7JIFO/kZ)Ckz*7Xuvw نg&֋U+DWAԳPx;%]r@G~fJ48{vFM"~wvԇ1I mJXk k51D[Wopl^(;w\FIzHy$$r ./xj83>z>9Nќv-v)TTD*IL}qbx>u}&:=l]o:Eiۧ[A^ [/ER;R;"6(ũK?C!>;gh) Ga 9nQ<@(<|+)}Pˇ2&dqmc#IhFeI-S n|{cfyv40]vO?݋ZωN#I'\9wÅPp`i(2NzfAʑ[?}7N)-t)^EI(^ܒM[ ҽTf[z{ rC2YcCŤŬfvnTgTBg^fOW 3Kgiuؓe>Nוq1S.֢+0ȉ<]vmZ =WVhY&R{!2ܼ'Nr6ɱbk_ک'@13{MKݐ__GaTAbʊ0ZB{䤡 d2J> 7RK7׏T;Ȱ+[4B*q4~;7D 5W?S&3[L^'{P)V̴~B,10Z]TC2e;=@7n6 +|,E+ʻ%_B κ7() xK6qQl: `qyi_O7MK!5(sfgHQ1N9!;8 @ߙ:Ϭ&-(D00fkC[x'=xWH i~ +swOVꮈiJL%{yݘF": +1[[ nse]-D.ct&_C$I]Dؘƫ'DGSQ$ҀpՄ6<~"Dg՞1o/+8>YX+갭҅:fXM(~t~xc+`Hcv"+!gl;%kι #v" %MA6ֆN{%]D`;>I뼳g!CSiØofglu:o3yUݢ\a;'f@ᛙv⬊Zj NB].yiW3 5{$";Y]`!i1{Zn|VS,v6.am$|%>)TCk"3o@*RU,6<#44`xDo:Et{M6#:]wޞCA'j]=K4EA=:MOa+VX[b,ma*69Z]ʤ|`?tvFwr2)/-Ov5@y9 ]#x~{! ˣz{TD]7d{WtMpiځ(+\, pZ]8âwcl_E΀G#ӱ¶ꭚ=]Y7*rQ !WQӄrgdM9n*P b3Bxe @1RhOj\Bycwzj eH? U~pE.kIc4g<BZ\B5hrEd^wŠim ;2 "? +]`_Z 8P\w)9%9dS6X?}+LYJ^y@1 (h{Uem,F/d"H7?j V}2 +l +Olb(FY8G߱4. eS]<b@{ɤA.S f>oLơ6/翔OHeAᤇ#:j +7 6Y^Rvr?NVIz1x^PA~KutS`ZGR`Tg3H4'eKR `܁k+j|7oHNPqJg4{"NJ.Go[yv.IS+9jULd+fu˥~mQfsGMb)RY2>y2d=Ue8@*<*?!.y]PhNЫ1qrYgMR/ +_X仾ru'Apue+`Y>q WXG6dZ e T_j^-'[nnyOZ:O?U3z;Fra}/_ -D'o!OQ'ʱL@ .!Ux~eRj=U=ΥDqKߒ&u9qD<: Lb.3c%x]׉; aRy Z:Սl^nz!/rUզ4)hOMMd 14/Xsa0"A묵erᶒlBNr8ݰY~ry9h?chٞ!c +Y猅Oc}q5\(y!^(L 153jvzh9鷔7ZCY即O:,!UC$*h[G%4O#+y6">RR-:#XL%YDd,[FTꠤgXcб:o9LJ\{h%v9'tUBQŕ&Fpԥ,8W뗶FF-QEWDEz5s#.TD1R0݊:$}+r*WޮUb\]Evs|?LkoOiFx(8z1d8w .b"%K^i59C|]J4ptjŊÑCȇ +ĭGe/" # @!aMbE0U?\ bYӽImʗ.`x+2qZ:j㱦tWMK;8ƦA s&q\oqVjQ %i3k$n'=E#* +WVV IPQ8>i 4bm miʾ.P`W0'20vwl.]elЂ!Yz"FkR͙,`k%Iuban\Rڇud :t?YS/WXlO]{j +f_p|=ZO(+`H +5 ~7dh֫]V1Ԅ2D(W[/tG +W ( zK֍3Z!>LWaF;w0cA܂LcEa; *DG5HX&sw*;s(#PBپ hoOt%J u.:ۃ &essE3a̕*Pv*k]5D6?x3{%ЯEiVjӨPNx[ ЩnP1#WvA8޿6dzLtGb5Pw,.#gF:4:uBV@aO2zn! `pgTwaG7= bzsФY@}0{9B6$ʗԧЋ>n4=#|h~ޕ4R_= !\SNм.bZ&zt~^ױ+[q'_`XƛS]LgLovc 4ˣkR.zSK.$ƪo5nPW EjISn$I~9VTm'`_JMWޮ8>`Q]K_CP(8!J٪S׊]lޯ_ɐBALQs&^ +1_%@quu=8LTUҧ{]訍-SHp׍/[Z +endstream +endobj +1871 0 obj << /Length1 2027 /Length2 14551 @@ -23557,7 +24449,7 @@ V tJF endstream endobj -1819 0 obj +1873 0 obj << /Length1 1385 /Length2 6193 @@ -23631,7 +24523,7 @@ U [,T>c.I%\F _I q!W&|F;wC;zBi*7au¨--X[1``X/c0@WՀ;y_Z~` endstream endobj -1821 0 obj +1875 0 obj << /Length1 1519 /Length2 8224 @@ -23717,7 +24609,7 @@ t f;&}tu"@HDu1j+?9>o>DqN6y Kn;p9cS&܅awX0i~ο;6v_ɵ|W$=;  >do\h6zx- &= A!:`bЂBJ:Y_ ͯj$>*XqBùCauF[̀ۊ%Z H2 (F]9Cf2!9}  㣽i ̌{b՛جDS`sZx^[.ZGPn!'FU-]1fj 6ORfWg$rdV+&K7IRͰd !HQ: YGdsz_| endstream endobj -1825 0 obj +1879 0 obj << /Length1 2668 /Length2 23272 @@ -24014,7 +24906,7 @@ A ie~x, 2!`z@r endstream endobj -1827 0 obj +1881 0 obj << /Length1 1425 /Length2 6648 @@ -24093,7 +24985,7 @@ B !N6@ |^(̮Pr@̀ endstream endobj -1839 0 obj +1893 0 obj << /Length1 2199 /Length2 18119 @@ -24834,7 +25726,7 @@ s Xj?izDRusuaSTk;֧_+_2(*O+5HM膽A1IYl9%d~Qc,Ae[޻wIݢf('BTnng endstream endobj -1841 0 obj +1895 0 obj << /Length1 1699 /Length2 10351 @@ -24941,7 +25833,7 @@ qO' X A StoCKr0E1O& \e;Hˁ lqάa]_i0y4 ^20 endstream endobj -1843 0 obj +1897 0 obj << /Length1 2477 /Length2 17492 @@ -25126,7 +26018,7 @@ C ѝhDcJ8 <݂grx!# tZ0Ы4ዜ)}=9) =(<_kMQGc<,%)-x eHr/?lk #ɻ9vЏ0_@~){%"z^)kåa]FH}pV8\Aɝ4{` Њf(n*_U:xJo%k'Z֦rSCkW)3 Ә^iFZ5#C;.4إ+j=Y:-fiaߪM"<]^,++GQn›3mT{=EXH` endstream endobj -1845 0 obj +1899 0 obj << /Length1 1494 /Length2 2555 @@ -25190,7 +26082,7 @@ currentfile eexec &̡Y5<1B dla;9^'lHn,W{Y[v endstream endobj -1847 0 obj +1901 0 obj << /Length1 1656 /Length2 8404 @@ -25215,347 +26107,114 @@ FontDirectory/CMTT9 known{/CMTT9 findfont dup/UniqueID known{dup 11 dict begin /FontType 1 def /FontMatrix [0.001 0 0 0.001 0 0 ]readonly def -/FontName /KMUHVJ+CMTT9 def -/FontBBox {-6 -233 542 698 }readonly def -/PaintType 0 def -/FontInfo 9 dict dup begin -/version (003.002) readonly def -/Notice (Copyright \050c\051 1997, 2009 American Mathematical Society \050\051, with Reserved Font Name CMTT9.) readonly def -/FullName (CMTT9) readonly def -/FamilyName (Computer Modern) readonly def -/Weight (Medium) readonly def -/ItalicAngle 0 def -/isFixedPitch true def -/UnderlinePosition -100 def -/UnderlineThickness 50 def -end readonly def -/Encoding 256 array -0 1 255 {1 index exch /.notdef put} for -dup 84 /T put -dup 97 /a put -dup 98 /b put -dup 99 /c put -dup 58 /colon put -dup 44 /comma put -dup 100 /d put -dup 101 /e put -dup 108 /l put -dup 110 /n put -dup 111 /o put -dup 112 /p put -dup 40 /parenleft put -dup 41 /parenright put -dup 114 /r put -dup 115 /s put -dup 116 /t put -dup 95 /underscore put -dup 121 /y put -readonly def -currentdict end -currentfile eexec -oc;jAw-=%W)-{ru)rAE(@{빴Q|_R -ϤA -T@|q|VkJ%qu8PwGxŪ̆Q6K -U\%b"t-*xJ+ -}3{Z2zݬT2s$Z&{BJ{=מ0).nBd^/!2-G+~b7 N&lds%o53NPc9U,Y뱂0L+OAdN;[9!"k_ӆ$Rb՘g uxVMhL$3Py5,o"7'*E<Zcb8r$`Fާ/r]:BI\$~=ԑψȜȿ!ꖲQS*_LyXg*!#B;Fdy9 vF.x&W܀cK[龭j - T-hj:ֲbcӢx~gk0^Z]Ψ&33g3wm2pBÌ:~qF邉u<^IE=*J.Zwc38Y.1jKAs;Ļ`R^yCQ4y &{uQgF -vlP︩ -e=Gylw -x]v&o9fiQpymQrijF\UBu :sy7R'T{cr/bzfuy-_Kh~ sӭ>a(zfz!#vZuZ"VUEɟw-@ i aI+ R̿P;XC 6e+je[7-^j[ -g93 ÅD c% ؙyJC=z[t vʩ>V3m9=Wp+l֏nׇ3g#7:Q@P~-u@ӱDV\sS;x; -J 'p -y?^CI $HGYt` \Lj%fxSڌrܾ0;=l;ÀMI>o C" - m޳I^:O|u.^Nuwb`95>dJJ 0Xp[tu^%ئ`' -0T I{ 6j=w ɽډ7Ș:{?lH)8OfmXn,ߗ Pii]X&Bx{5ǬfEޮDtz9nyB t+ 4,p$@x&|Ĩ4H~4J7B<«CP}uz|gr-:u[D\; }bUIS{27= FBk' - .~"tOz-3RٷZ[&hD|AQGCH :\'`aу2{=o>u&0߻;e01]V2c`CJ1/LW Yckɲ }c8LC|g%Y9.?e+PҁI4,}#yE؇]%T>},S !*. vt7[ORYSSԪ5՞l+>͎l6UY'_p%=]^:k2 b3Ҳvu\k!n2̋@Q*v}5z3mؚ/_~GfG쪑4,=5%ڹ]EHfnۀxRL/' 7.eϽaG}r -~) ]<$2uo6){QBX[#CI3je/NUX+`"P[\AXa|i Hnk, ? J_y3^c}|at <;1v@{EҬ /E7+?`+7TɈ/~2Fe匊I5)SXvNe BҮmy‰_14tl0w -3Kq -Tύ\Ӽzl]%bpg7G)t[VN~O^ v`v`чm -ňXh>r:9e1SNC$c% $¦,TM2COVe=S7u_{x $:#Zi1ʇl y ö^|QLψc&Hn) Ϩ|he }IMǕW*+-Z,dުyfmvԛ]t ;`o]WHY}'PN`SuBf$,ՕL=wm0mV l TOnt6M"X˃qDf0ms9?Ğ_mnH`AAmҚ -ܭajfnUۙCat/vPqE$NP^_مdv"TC[ |wҁ1|7B%fW"d6QIaҝE.Z;eF{N#{}?7yg -hS `tZ" *QC&KsulJ|6i$rEFXggξ&vH_I)LR*QgXuV,В"%_L΄"4vܹ٩vûZ! -Y@L{vߺ+N*Y+qi]/^L)my1=K ~{it{n?'2d,佛rt߳-F܅Fl L yfF?M_*a5պӽŒ!d 2Λiw/";qfW"^0$goaWvm.͢B/c@{:d"Av]P}C*&kx;k6܆xɃ% ^X2Lg]VmMhxP&({g^֣ ĤԒ|(dk/ܺHԔqJ'wBtgO`Oc \K*/g9Z<0vBWK=Q]a9'ro+&w@^l2?JVSVB]G G Oڡ=wf X`No{PIlYdfoY L?! b'UL%l tdNXF;Mv&DEc#GK∂ _-LݟG'r )~O* -ƨ01S7<Qಸ*L"+lk:z@N_qNyF@UZW0bBk/h:p!L^9<,_,&_x^1;t,_ -Qn1:.>4S, -K2~GLU3]q/GѭFLmι?q9Or-s*|V;ٝQ>WaPy -!?9%%: f2h~췲VFI#Ov݌E4r +]a見3pbSi\)NLeImzGH)(8+PdTMN&Ц&C|_] -oqhoL7|.29*!AʆRiVi1qc8#BU9MKEVP'O|е= ; -l2YL|Zs͍d|*.K4˜m Xc{GdpHJx F4VMw/TƕS$E0}XZj$"#NJFF> -RֿbO]k;eE2ei0g©X} aU j†U*ܤ泔'[Ï I86>SѩjO&@;_ꛪ 1,0gd3 r(L]iRlWԒX.働aAeゅ~#~> v>x4],^f{koO\AY<|/d!nt*HNy*sk@@"JQx-mYw_M TnlY>(aO,QeJ ;ϙb١A\ڶR,݄?NU~S-!z׶$O҃'S;?;ba.% ӳ@˞X{٭V?-.=xM֚JmPP{#'ށٽiDLTI_}g [V, -)OЎK _̤VBE igd#A\&鐣D#JZcfWU^*WBl_AI-a )5|%X(VpQF07"Wue dDة R# 52"T&DmIJ1{@i6KQΝ>D[>2@']}Uopż\mG^tUpnoq;#[u -ex -cECk y9ڷ҇VVן/" C͗4*78*`1ީS2 Q8I&ʺ3f73us>Xg*#zi'$ZYH2|?c^2sKʇXcERNpev5E>y\1`ki~~B, ͐ -ga!.Θ:ܨ+. -endstream -endobj -1765 0 obj -<< -/Type /ObjStm -/N 100 -/First 998 -/Length 20534 ->> -stream -1763 0 1756 58 1770 255 1755 421 1766 568 1767 711 1768 855 1772 1002 1769 1060 1776 1179 -1774 1318 1778 1462 1775 1521 1780 1627 1782 1745 1783 1803 734 1861 1784 1918 785 1975 784 2032 -740 2089 741 2146 757 2203 737 2260 738 2317 1785 2374 733 2432 1786 2489 1779 2547 1788 2640 -1790 2758 898 2817 772 2875 739 2933 736 2991 732 3049 735 3107 1791 3165 1787 3224 1792 3317 -1793 3362 1794 3501 1795 3995 1796 4324 1797 4667 1798 4796 1799 4817 1800 5323 1801 5368 1802 6058 -1803 6386 1804 6467 1805 6842 1806 7479 1807 8138 1808 8761 1809 9405 1810 9690 1812 10338 1814 10768 -1816 11191 1818 11440 1820 11768 1822 11985 1824 12224 1826 12446 1828 12983 1830 13220 1832 13468 1834 13850 -1836 14216 1838 14555 1840 14786 1842 15159 1844 15422 1846 15906 1848 16138 556 16422 554 16563 1607 16704 -750 16845 797 16986 766 17127 1764 17267 557 17407 768 17547 765 17685 770 17823 1170 17962 767 18102 -1082 18242 730 18381 555 18522 764 18663 825 18804 957 18944 558 19084 731 19197 826 19310 882 19423 -% 1763 0 obj -<< -/D [1757 0 R /XYZ 165.948 129.79 null] ->> -% 1756 0 obj -<< -/Font << /F16 554 0 R /F8 557 0 R /F27 556 0 R /F11 750 0 R /F14 767 0 R /F10 766 0 R /F7 765 0 R /F30 764 0 R /F32 768 0 R /F31 770 0 R /F33 1764 0 R >> -/ProcSet [ /PDF /Text ] ->> -% 1770 0 obj -<< -/Type /Page -/Contents 1771 0 R -/Resources 1769 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1773 0 R -/Annots [ 1755 0 R 1766 0 R 1767 0 R 1768 0 R ] ->> -% 1755 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 655.098 361.779 666.223] -/A << /S /GoTo /D (precdata) >> ->> -% 1766 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [347.301 587.85 423.355 598.975] -/A << /S /GoTo /D (vdata) >> ->> -% 1767 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [347.301 520.602 423.355 531.727] -/A << /S /GoTo /D (vdata) >> ->> -% 1768 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [294.721 386.107 361.779 397.232] -/A << /S /GoTo /D (descdata) >> ->> -% 1772 0 obj -<< -/D [1770 0 R /XYZ 98.895 753.953 null] ->> -% 1769 0 obj -<< -/Font << /F27 556 0 R /F8 557 0 R /F30 764 0 R /F11 750 0 R /F14 767 0 R >> -/ProcSet [ /PDF /Text ] ->> -% 1776 0 obj -<< -/Type /Page -/Contents 1777 0 R -/Resources 1775 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1773 0 R -/Annots [ 1774 0 R ] ->> -% 1774 0 obj -<< -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [398.111 579.382 474.165 590.507] -/A << /S /GoTo /D (vdata) >> ->> -% 1778 0 obj -<< -/D [1776 0 R /XYZ 149.705 753.953 null] ->> -% 1775 0 obj -<< -/Font << /F8 557 0 R /F27 556 0 R /F30 764 0 R /F11 750 0 R >> -/ProcSet [ /PDF /Text ] ->> -% 1780 0 obj -<< -/Type /Page -/Contents 1781 0 R -/Resources 1779 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1773 0 R ->> -% 1782 0 obj -<< -/D [1780 0 R /XYZ 98.895 753.953 null] ->> -% 1783 0 obj -<< -/D [1780 0 R /XYZ 99.895 724.062 null] ->> -% 734 0 obj -<< -/D [1780 0 R /XYZ 99.895 699.619 null] ->> -% 1784 0 obj -<< -/D [1780 0 R /XYZ 99.895 643.15 null] ->> -% 785 0 obj -<< -/D [1780 0 R /XYZ 99.895 588.618 null] ->> -% 784 0 obj -<< -/D [1780 0 R /XYZ 99.895 534.087 null] ->> -% 740 0 obj -<< -/D [1780 0 R /XYZ 99.895 479.555 null] ->> -% 741 0 obj -<< -/D [1780 0 R /XYZ 99.895 436.978 null] ->> -% 757 0 obj -<< -/D [1780 0 R /XYZ 99.895 394.402 null] ->> -% 737 0 obj -<< -/D [1780 0 R /XYZ 99.895 351.272 null] ->> -% 738 0 obj -<< -/D [1780 0 R /XYZ 99.895 308.696 null] ->> -% 1785 0 obj -<< -/D [1780 0 R /XYZ 99.895 266.119 null] ->> -% 733 0 obj -<< -/D [1780 0 R /XYZ 99.895 223.543 null] ->> -% 1786 0 obj -<< -/D [1780 0 R /XYZ 99.895 180.966 null] ->> -% 1779 0 obj -<< -/Font << /F16 554 0 R /F8 557 0 R /F17 730 0 R >> -/ProcSet [ /PDF /Text ] ->> -% 1788 0 obj -<< -/Type /Page -/Contents 1789 0 R -/Resources 1787 0 R -/MediaBox [0 0 595.276 841.89] -/Parent 1773 0 R ->> -% 1790 0 obj -<< -/D [1788 0 R /XYZ 149.705 753.953 null] ->> -% 898 0 obj -<< -/D [1788 0 R /XYZ 150.705 716.092 null] ->> -% 772 0 obj -<< -/D [1788 0 R /XYZ 150.705 688.251 null] ->> -% 739 0 obj -<< -/D [1788 0 R /XYZ 150.705 632.184 null] ->> -% 736 0 obj -<< -/D [1788 0 R /XYZ 150.705 590.562 null] ->> -% 732 0 obj -<< -/D [1788 0 R /XYZ 150.705 544.789 null] ->> -% 735 0 obj -<< -/D [1788 0 R /XYZ 150.705 512.909 null] ->> -% 1791 0 obj -<< -/D [1788 0 R /XYZ 150.705 480.475 null] ->> -% 1787 0 obj +/FontName /KMUHVJ+CMTT9 def +/FontBBox {-6 -233 542 698 }readonly def +/PaintType 0 def +/FontInfo 9 dict dup begin +/version (003.002) readonly def +/Notice (Copyright \050c\051 1997, 2009 American Mathematical Society \050\051, with Reserved Font Name CMTT9.) readonly def +/FullName (CMTT9) readonly def +/FamilyName (Computer Modern) readonly def +/Weight (Medium) readonly def +/ItalicAngle 0 def +/isFixedPitch true def +/UnderlinePosition -100 def +/UnderlineThickness 50 def +end readonly def +/Encoding 256 array +0 1 255 {1 index exch /.notdef put} for +dup 84 /T put +dup 97 /a put +dup 98 /b put +dup 99 /c put +dup 58 /colon put +dup 44 /comma put +dup 100 /d put +dup 101 /e put +dup 108 /l put +dup 110 /n put +dup 111 /o put +dup 112 /p put +dup 40 /parenleft put +dup 41 /parenright put +dup 114 /r put +dup 115 /s put +dup 116 /t put +dup 95 /underscore put +dup 121 /y put +readonly def +currentdict end +currentfile eexec +oc;jAw-=%W)-{ru)rAE(@{빴Q|_R +ϤA -T@|q|VkJ%qu8PwGxŪ̆Q6K -U\%b"t-*xJ+ +}3{Z2zݬT2s$Z&{BJ{=מ0).nBd^/!2-G+~b7 N&lds%o53NPc9U,Y뱂0L+OAdN;[9!"k_ӆ$Rb՘g uxVMhL$3Py5,o"7'*E<Zcb8r$`Fާ/r]:BI\$~=ԑψȜȿ!ꖲQS*_LyXg*!#B;Fdy9 vF.x&W܀cK[龭j + T-hj:ֲbcӢx~gk0^Z]Ψ&33g3wm2pBÌ:~qF邉u<^IE=*J.Zwc38Y.1jKAs;Ļ`R^yCQ4y &{uQgF +vlP︩ +e=Gylw +x]v&o9fiQpymQrijF\UBu :sy7R'T{cr/bzfuy-_Kh~ sӭ>a(zfz!#vZuZ"VUEɟw-@ i aI+ R̿P;XC 6e+je[7-^j[ +g93 ÅD c% ؙyJC=z[t vʩ>V3m9=Wp+l֏nׇ3g#7:Q@P~-u@ӱDV\sS;x; +J 'p +y?^CI $HGYt` \Lj%fxSڌrܾ0;=l;ÀMI>o C" + m޳I^:O|u.^Nuwb`95>dJJ 0Xp[tu^%ئ`' +0T I{ 6j=w ɽډ7Ș:{?lH)8OfmXn,ߗ Pii]X&Bx{5ǬfEޮDtz9nyB t+ 4,p$@x&|Ĩ4H~4J7B<«CP}uz|gr-:u[D\; }bUIS{27= FBk' + .~"tOz-3RٷZ[&hD|AQGCH :\'`aу2{=o>u&0߻;e01]V2c`CJ1/LW Yckɲ }c8LC|g%Y9.?e+PҁI4,}#yE؇]%T>},S !*. vt7[ORYSSԪ5՞l+>͎l6UY'_p%=]^:k2 b3Ҳvu\k!n2̋@Q*v}5z3mؚ/_~GfG쪑4,=5%ڹ]EHfnۀxRL/' 7.eϽaG}r +~) ]<$2uo6){QBX[#CI3je/NUX+`"P[\AXa|i Hnk, ? J_y3^c}|at <;1v@{EҬ /E7+?`+7TɈ/~2Fe匊I5)SXvNe BҮmy‰_14tl0w +3Kq +Tύ\Ӽzl]%bpg7G)t[VN~O^ v`v`чm +ňXh>r:9e1SNC$c% $¦,TM2COVe=S7u_{x $:#Zi1ʇl y ö^|QLψc&Hn) Ϩ|he }IMǕW*+-Z,dުyfmvԛ]t ;`o]WHY}'PN`SuBf$,ՕL=wm0mV l TOnt6M"X˃qDf0ms9?Ğ_mnH`AAmҚ +ܭajfnUۙCat/vPqE$NP^_مdv"TC[ |wҁ1|7B%fW"d6QIaҝE.Z;eF{N#{}?7yg +hS `tZ" *QC&KsulJ|6i$rEFXggξ&vH_I)LR*QgXuV,В"%_L΄"4vܹ٩vûZ! +Y@L{vߺ+N*Y+qi]/^L)my1=K ~{it{n?'2d,佛rt߳-F܅Fl L yfF?M_*a5պӽŒ!d 2Λiw/";qfW"^0$goaWvm.͢B/c@{:d"Av]P}C*&kx;k6܆xɃ% ^X2Lg]VmMhxP&({g^֣ ĤԒ|(dk/ܺHԔqJ'wBtgO`Oc \K*/g9Z<0vBWK=Q]a9'ro+&w@^l2?JVSVB]G G Oڡ=wf X`No{PIlYdfoY L?! b'UL%l tdNXF;Mv&DEc#GK∂ _-LݟG'r )~O* +ƨ01S7<Qಸ*L"+lk:z@N_qNyF@UZW0bBk/h:p!L^9<,_,&_x^1;t,_ +Qn1:.>4S, +K2~GLU3]q/GѭFLmι?q9Or-s*|V;ٝQ>WaPy +!?9%%: f2h~췲VFI#Ov݌E4r +]a見3pbSi\)NLeImzGH)(8+PdTMN&Ц&C|_] +oqhoL7|.29*!AʆRiVi1qc8#BU9MKEVP'O|е= ; +l2YL|Zs͍d|*.K4˜m Xc{GdpHJx F4VMw/TƕS$E0}XZj$"#NJFF> +RֿbO]k;eE2ei0g©X} aU j†U*ܤ泔'[Ï I86>SѩjO&@;_ꛪ 1,0gd3 r(L]iRlWԒX.働aAeゅ~#~> v>x4],^f{koO\AY<|/d!nt*HNy*sk@@"JQx-mYw_M TnlY>(aO,QeJ ;ϙb١A\ڶR,݄?NU~S-!z׶$O҃'S;?;ba.% ӳ@˞X{٭V?-.=xM֚JmPP{#'ށٽiDLTI_}g [V, +)OЎK _̤VBE igd#A\&鐣D#JZcfWU^*WBl_AI-a )5|%X(VpQF07"Wue dDة R# 52"T&DmIJ1{@i6KQΝ>D[>2@']}Uopż\mG^tUpnoq;#[u +ex +cECk y9ڷ҇VVן/" C͗4*78*`1ީS2 Q8I&ʺ3f73us>Xg*#zi'$ZYH2|?c^2sKʇXcERNpev5E>y\1`ki~~B, ͐ +ga!.Θ:ܨ+. +endstream +endobj +1861 0 obj << -/Font << /F8 557 0 R /F17 730 0 R /F30 764 0 R >> -/ProcSet [ /PDF /Text ] +/Type /ObjStm +/N 100 +/First 1006 +/Length 17043 >> -% 1792 0 obj -[757.3 871.7 778.7 672.4 827.9] -% 1793 0 obj -[575.2 657.4 525.9 657.4 543 361.6 591.7 657.4 328.7 361.6 624.5 328.7 986.1 657.4 591.7 657.4 624.5 488.1 466.8 460.2 657.4] -% 1794 0 obj -[285.5 399.7 399.7 513.9 799.4 285.5 342.6 285.5 513.9 513.9 513.9 513.9 513.9 513.9 513.9 513.9 513.9 513.9 513.9 285.5 285.5 285.5 799.4 485.3 485.3 799.4 770.7 727.9 742.3 785 699.4 670.8 806.5 770.7 371 528.1 799.2 642.3 942 770.7 799.4 699.4 799.4 756.5 571 742.3 770.7 770.7 1056.2 770.7 770.7 628.1 285.5 513.9 285.5 513.9 285.5 285.5 513.9 571 456.8 571 457.2 314 513.9 571 285.5 314 542.4 285.5 856.5 571 513.9 571 542.4 402 405.4 399.7 571 542.4 742.3 542.4 542.4 456.8] -% 1795 0 obj -[892.9 339.3 892.9 585.3 892.9 585.3 892.9 892.9 892.9 892.9 892.9 892.9 892.9 1138.9 585.3 585.3 892.9 892.9 892.9 892.9 892.9 892.9 892.9 892.9 892.9 892.9 892.9 892.9 1138.9 1138.9 892.9 892.9 1138.9 1138.9 585.3 585.3 1138.9 1138.9 1138.9 892.9 1138.9 1138.9 708.3 708.3 1138.9 1138.9 1138.9 892.9 329.4 1138.9] -% 1796 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] -% 1797 0 obj -[531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3] -% 1798 0 obj -[533.6] -% 1799 0 obj -[413.2 413.2 531.3 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 501.7 501.7 826.4 795.8 752.1 767.4 811.1 722.6 693.1 833.5 795.8 382.6 545.5 825.4 663.6 972.9 795.8 826.4 722.6 826.4 781.6 590.3 767.4 795.8 795.8 1091 795.8 795.8 649.3 295.1 531.3 295.1 531.3 295.1 295.1 531.3 590.3 472.2 590.3 472.2 324.7 531.3 590.3 295.1 324.7 560.8 295.1 885.4 590.3 531.3 590.3 560.8 414.1 419.1 413.2 590.3 560.8 767.4 560.8 560.8] -% 1800 0 obj -[611.1 611.1 611.1 611.1 611.1] -% 1801 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 750 833.3 416.7 666.7 666.7 777.8 777.8 444.4] -% 1802 0 obj -[339.3 892.9 585.3 892.9 585.3 610.1 859.1 863.2 819.4 934.1 838.7 724.5 889.4 935.6 506.3 632 959.9 783.7 1089.4 904.9 868.9 727.3 899.7 860.6 701.5 674.8 778.2 674.6 1074.4 936.9 671.5 778.4 462.3 462.3 462.3 1138.9 1138.9 478.2 619.7 502.4 510.5 594.7 542 557.1 557.3 668.8 404.2 472.7 607.3 361.3 1013.7 706.2] -% 1803 0 obj -[569.5 569.5 569.5 569.5 569.5 569.5 569.5 569.5 569.5 569.5 323.4] -% 1804 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] -% 1805 0 obj -[639.7 565.6 517.7 444.4 405.9 437.5 496.5 469.4 353.9 576.2 583.3 602.6 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.3 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.8 361.1 572.5 484.7 715.9 571.5 490.3 465.1] -% 1806 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] -% 1807 0 obj -[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] -% 1808 0 obj -[670.8 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.6 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 575 1150] -% 1809 0 obj +stream +1860 0 1862 285 1864 933 1866 1363 1868 1786 1870 2035 1872 2277 1874 2605 1876 2822 1878 3061 +1880 3283 1882 3820 1884 4057 1886 4305 1888 4687 1890 5053 1892 5392 1894 5623 1896 5996 1898 6259 +1900 6743 1902 6975 560 7259 558 7400 1656 7541 1630 7682 755 7824 802 7965 771 8106 1815 8246 +561 8386 773 8526 770 8664 775 8802 1211 8941 772 9081 1125 9221 735 9360 559 9501 769 9642 +830 9783 962 9923 562 10063 736 10176 831 10289 887 10402 922 10515 953 10628 999 10741 1053 10859 +1102 10979 1158 11099 1212 11219 1268 11339 1309 11459 1348 11579 1400 11699 1439 11819 1473 11939 1511 12059 +1553 12179 1584 12299 1617 12419 1680 12539 1717 12659 1755 12779 1793 12899 1836 13019 1903 13103 1904 13218 +1905 13338 1906 13459 1907 13580 1908 13664 1909 13760 550 13829 546 13889 542 14000 538 14074 534 14162 +530 14250 526 14338 522 14426 518 14500 514 14625 510 14699 506 14787 502 14875 498 14963 494 15051 +490 15125 486 15250 482 15324 478 15412 474 15500 470 15574 466 15699 462 15773 458 15861 454 15949 +% 1860 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] -% 1810 0 obj +% 1862 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 500 562.5 1125] -% 1812 0 obj +% 1864 0 obj << /Type /FontDescriptor /FontName /RAJOBS+CMBX10 @@ -25568,9 +26227,9 @@ stream /StemV 114 /XHeight 444 /CharSet (/A/B/C/D/E/F/G/H/I/J/L/M/N/O/P/R/S/T/U/V/Z/a/b/c/colon/comma/d/e/eight/emdash/endash/equal/f/ff/ffi/fi/five/fl/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/z/zero) -/FontFile 1811 0 R +/FontFile 1863 0 R >> -% 1814 0 obj +% 1866 0 obj << /Type /FontDescriptor /FontName /GBHFLB+CMBX12 @@ -25583,9 +26242,9 @@ stream /StemV 109 /XHeight 444 /CharSet (/A/B/C/D/E/F/G/H/I/K/L/M/N/O/P/Q/R/S/T/U/V/W/a/b/c/d/e/eight/emdash/endash/f/fi/five/four/g/h/hyphen/i/k/l/m/n/nine/o/one/p/parenleft/parenright/period/q/quoteright/r/s/seven/six/t/three/two/u/v/w/x/y/z/zero) -/FontFile 1813 0 R +/FontFile 1865 0 R >> -% 1816 0 obj +% 1868 0 obj << /Type /FontDescriptor /FontName /VUBHOM+CMBX9 @@ -25598,9 +26257,24 @@ stream /StemV 117 /XHeight 444 /CharSet (/a/b/c/d/e/f/g/h/i/l/n/o/q/r/s/t/u) -/FontFile 1815 0 R +/FontFile 1867 0 R >> -% 1818 0 obj +% 1870 0 obj +<< +/Type /FontDescriptor +/FontName /OUFNAH+CMEX10 +/Flags 4 +/FontBBox [-24 -2960 1454 772] +/Ascent 40 +/CapHeight 0 +/Descent -600 +/ItalicAngle 0 +/StemV 47 +/XHeight 431 +/CharSet (/radicalBigg/summationdisplay) +/FontFile 1869 0 R +>> +% 1872 0 obj << /Type /FontDescriptor /FontName /PUWBWT+CMMI10 @@ -25613,9 +26287,9 @@ stream /StemV 72 /XHeight 431 /CharSet (/A/C/D/G/I/L/N/O/P/Q/T/U/X/a/alpha/b/beta/c/comma/d/e/f/g/greater/i/j/k/l/less/m/n/o/p/period/r/s/t/u/v/w/x/y/z) -/FontFile 1817 0 R +/FontFile 1871 0 R >> -% 1820 0 obj +% 1874 0 obj << /Type /FontDescriptor /FontName /RVPZIX+CMMI5 @@ -25628,9 +26302,9 @@ stream /StemV 90 /XHeight 431 /CharSet (/i) -/FontFile 1819 0 R +/FontFile 1873 0 R >> -% 1822 0 obj +% 1876 0 obj << /Type /FontDescriptor /FontName /ZUYGVH+CMMI7 @@ -25643,9 +26317,9 @@ stream /StemV 81 /XHeight 431 /CharSet (/H/I/T/a/comma/i/j/k/m/n) -/FontFile 1821 0 R +/FontFile 1875 0 R >> -% 1824 0 obj +% 1878 0 obj << /Type /FontDescriptor /FontName /ZOAUSA+CMMI8 @@ -25658,9 +26332,9 @@ stream /StemV 78 /XHeight 431 /CharSet (/C/F/G) -/FontFile 1823 0 R +/FontFile 1877 0 R >> -% 1826 0 obj +% 1880 0 obj << /Type /FontDescriptor /FontName /SEWPRR+CMR10 @@ -25673,9 +26347,9 @@ stream /StemV 69 /XHeight 431 /CharSet (/A/B/C/D/E/F/G/H/I/J/K/L/M/N/O/P/R/S/T/U/V/W/X/a/ampersand/b/bracketleft/bracketright/c/colon/comma/d/e/eight/endash/equal/f/ff/ffi/fi/five/fl/four/g/h/hyphen/i/j/k/l/m/n/nine/o/one/p/parenleft/parenright/percent/period/plus/q/quotedblleft/quotedblright/quoteright/r/s/semicolon/seven/six/slash/t/three/two/u/v/w/x/y/z/zero) -/FontFile 1825 0 R +/FontFile 1879 0 R >> -% 1828 0 obj +% 1882 0 obj << /Type /FontDescriptor /FontName /UJRPBG+CMR6 @@ -25688,9 +26362,9 @@ stream /StemV 83 /XHeight 431 /CharSet (/five/four/one/three/two) -/FontFile 1827 0 R +/FontFile 1881 0 R >> -% 1830 0 obj +% 1884 0 obj << /Type /FontDescriptor /FontName /GIODUE+CMR7 @@ -25703,9 +26377,9 @@ stream /StemV 79 /XHeight 431 /CharSet (/colon/five/four/one/three/two/zero) -/FontFile 1829 0 R +/FontFile 1883 0 R >> -% 1832 0 obj +% 1886 0 obj << /Type /FontDescriptor /FontName /HFTEUS+CMR8 @@ -25718,9 +26392,9 @@ stream /StemV 76 /XHeight 431 /CharSet (/B/G/I/L/N/O/P/T/X/a/b/c/colon/comma/d/e/eight/f/five/four/g/h/hyphen/i/k/l/m/n/nine/o/one/p/parenleft/parenright/period/q/r/s/seven/six/slash/t/three/two/u/v/w/x/y/zero) -/FontFile 1831 0 R +/FontFile 1885 0 R >> -% 1834 0 obj +% 1888 0 obj << /Type /FontDescriptor /FontName /KKURMF+CMR9 @@ -25733,9 +26407,9 @@ stream /StemV 74 /XHeight 431 /CharSet (/B/G/I/L/O/P/X/a/b/c/comma/d/e/eight/equal/f/five/four/g/h/i/m/n/nine/o/one/p/parenleft/parenright/period/quoteright/r/s/seven/six/t/three/two/u/x/z/zero) -/FontFile 1833 0 R +/FontFile 1887 0 R >> -% 1836 0 obj +% 1890 0 obj << /Type /FontDescriptor /FontName /IMOIOS+CMSY10 @@ -25748,9 +26422,9 @@ stream /StemV 40 /XHeight 431 /CharSet (/B/H/I/arrowleft/bar/bardbl/braceleft/braceright/bullet/element/greaterequal/lessequal/minus/negationslash/radical/section) -/FontFile 1835 0 R +/FontFile 1889 0 R >> -% 1838 0 obj +% 1892 0 obj << /Type /FontDescriptor /FontName /XNLILI+CMSY7 @@ -25763,9 +26437,9 @@ stream /StemV 49 /XHeight 431 /CharSet (/infinity/minus) -/FontFile 1837 0 R +/FontFile 1891 0 R >> -% 1840 0 obj +% 1894 0 obj << /Type /FontDescriptor /FontName /HBJLDT+CMTI10 @@ -25778,9 +26452,9 @@ stream /StemV 68 /XHeight 431 /CharSet (/A/B/C/D/E/F/G/I/L/M/N/O/P/R/S/T/U/V/a/b/c/colon/d/e/f/ff/fi/five/g/h/hyphen/i/j/l/m/n/nine/o/one/p/period/q/quoteright/r/s/slash/t/three/two/u/v/w/x/y/zero) -/FontFile 1839 0 R +/FontFile 1893 0 R >> -% 1842 0 obj +% 1896 0 obj << /Type /FontDescriptor /FontName /OZJPZO+CMTI12 @@ -25793,9 +26467,9 @@ stream /StemV 63 /XHeight 431 /CharSet (/A/B/L/P/S/a/b/c/d/e/f/g/h/i/l/n/o/p/r/s/t/u/y) -/FontFile 1841 0 R +/FontFile 1895 0 R >> -% 1844 0 obj +% 1898 0 obj << /Type /FontDescriptor /FontName /BGSLBR+CMTT10 @@ -25808,9 +26482,9 @@ stream /StemV 69 /XHeight 431 /CharSet (/A/B/C/D/E/F/I/K/L/M/N/O/P/R/S/T/U/W/Y/a/ampersand/asciitilde/asterisk/b/backslash/bracketleft/bracketright/c/colon/comma/d/e/equal/f/four/g/h/hyphen/i/j/k/l/m/n/nine/o/one/p/parenleft/parenright/percent/period/plus/q/r/s/six/slash/t/three/two/u/underscore/v/w/x/y/z/zero) -/FontFile 1843 0 R +/FontFile 1897 0 R >> -% 1846 0 obj +% 1900 0 obj << /Type /FontDescriptor /FontName /HZGQIC+CMTT8 @@ -25823,9 +26497,9 @@ stream /StemV 76 /XHeight 431 /CharSet (/b/c/e/i/l/n/p/r/s/t) -/FontFile 1845 0 R +/FontFile 1899 0 R >> -% 1848 0 obj +% 1902 0 obj << /Type /FontDescriptor /FontName /KMUHVJ+CMTT9 @@ -25838,470 +26512,474 @@ stream /StemV 74 /XHeight 431 /CharSet (/T/a/b/c/colon/comma/d/e/l/n/o/p/parenleft/parenright/r/s/t/underscore/y) -/FontFile 1847 0 R +/FontFile 1901 0 R >> -% 556 0 obj +% 560 0 obj << /Type /Font /Subtype /Type1 /BaseFont /RAJOBS+CMBX10 -/FontDescriptor 1812 0 R +/FontDescriptor 1864 0 R /FirstChar 11 /LastChar 124 -/Widths 1808 0 R +/Widths 1859 0 R >> -% 554 0 obj +% 558 0 obj << /Type /Font /Subtype /Type1 /BaseFont /GBHFLB+CMBX12 -/FontDescriptor 1814 0 R +/FontDescriptor 1866 0 R /FirstChar 12 /LastChar 124 -/Widths 1810 0 R +/Widths 1862 0 R >> -% 1607 0 obj +% 1656 0 obj << /Type /Font /Subtype /Type1 /BaseFont /VUBHOM+CMBX9 -/FontDescriptor 1816 0 R +/FontDescriptor 1868 0 R /FirstChar 97 /LastChar 117 -/Widths 1793 0 R +/Widths 1843 0 R +>> +% 1630 0 obj +<< +/Type /Font +/Subtype /Type1 +/BaseFont /OUFNAH+CMEX10 +/FontDescriptor 1870 0 R +/FirstChar 88 +/LastChar 115 +/Widths 1844 0 R >> -% 750 0 obj +% 755 0 obj << /Type /Font /Subtype /Type1 /BaseFont /PUWBWT+CMMI10 -/FontDescriptor 1818 0 R +/FontDescriptor 1872 0 R /FirstChar 11 /LastChar 122 -/Widths 1805 0 R +/Widths 1856 0 R >> -% 797 0 obj +% 802 0 obj << /Type /Font /Subtype /Type1 /BaseFont /RVPZIX+CMMI5 -/FontDescriptor 1820 0 R +/FontDescriptor 1874 0 R /FirstChar 105 /LastChar 105 -/Widths 1798 0 R +/Widths 1849 0 R >> -% 766 0 obj +% 771 0 obj << /Type /Font /Subtype /Type1 /BaseFont /ZUYGVH+CMMI7 -/FontDescriptor 1822 0 R +/FontDescriptor 1876 0 R /FirstChar 59 /LastChar 110 -/Widths 1802 0 R +/Widths 1853 0 R >> -% 1764 0 obj +% 1815 0 obj << /Type /Font /Subtype /Type1 /BaseFont /ZOAUSA+CMMI8 -/FontDescriptor 1824 0 R +/FontDescriptor 1878 0 R /FirstChar 67 /LastChar 71 -/Widths 1792 0 R +/Widths 1842 0 R >> -% 557 0 obj +% 561 0 obj << /Type /Font /Subtype /Type1 /BaseFont /SEWPRR+CMR10 -/FontDescriptor 1826 0 R +/FontDescriptor 1880 0 R /FirstChar 11 /LastChar 123 -/Widths 1807 0 R +/Widths 1858 0 R >> -% 768 0 obj +% 773 0 obj << /Type /Font /Subtype /Type1 /BaseFont /UJRPBG+CMR6 -/FontDescriptor 1828 0 R +/FontDescriptor 1882 0 R /FirstChar 49 /LastChar 53 -/Widths 1800 0 R +/Widths 1851 0 R >> -% 765 0 obj +% 770 0 obj << /Type /Font /Subtype /Type1 /BaseFont /GIODUE+CMR7 -/FontDescriptor 1830 0 R +/FontDescriptor 1884 0 R /FirstChar 48 /LastChar 58 -/Widths 1803 0 R +/Widths 1854 0 R >> -% 770 0 obj +% 775 0 obj << /Type /Font /Subtype /Type1 /BaseFont /HFTEUS+CMR8 -/FontDescriptor 1832 0 R +/FontDescriptor 1886 0 R /FirstChar 40 /LastChar 121 -/Widths 1799 0 R +/Widths 1850 0 R >> -% 1170 0 obj +% 1211 0 obj << /Type /Font /Subtype /Type1 /BaseFont /KKURMF+CMR9 -/FontDescriptor 1834 0 R +/FontDescriptor 1888 0 R /FirstChar 39 /LastChar 122 -/Widths 1794 0 R +/Widths 1845 0 R >> -% 767 0 obj +% 772 0 obj << /Type /Font /Subtype /Type1 /BaseFont /IMOIOS+CMSY10 -/FontDescriptor 1836 0 R +/FontDescriptor 1890 0 R /FirstChar 0 /LastChar 120 -/Widths 1801 0 R +/Widths 1852 0 R >> -% 1082 0 obj +% 1125 0 obj << /Type /Font /Subtype /Type1 /BaseFont /XNLILI+CMSY7 -/FontDescriptor 1838 0 R +/FontDescriptor 1892 0 R /FirstChar 0 /LastChar 49 -/Widths 1795 0 R +/Widths 1846 0 R >> -% 730 0 obj +% 735 0 obj << /Type /Font /Subtype /Type1 /BaseFont /HBJLDT+CMTI10 -/FontDescriptor 1840 0 R +/FontDescriptor 1894 0 R /FirstChar 11 /LastChar 121 -/Widths 1806 0 R +/Widths 1857 0 R >> -% 555 0 obj +% 559 0 obj << /Type /Font /Subtype /Type1 /BaseFont /OZJPZO+CMTI12 -/FontDescriptor 1842 0 R +/FontDescriptor 1896 0 R /FirstChar 65 /LastChar 121 -/Widths 1809 0 R +/Widths 1860 0 R >> -% 764 0 obj +% 769 0 obj << /Type /Font /Subtype /Type1 /BaseFont /BGSLBR+CMTT10 -/FontDescriptor 1844 0 R +/FontDescriptor 1898 0 R /FirstChar 37 /LastChar 126 -/Widths 1804 0 R +/Widths 1855 0 R >> -% 825 0 obj +% 830 0 obj << /Type /Font /Subtype /Type1 /BaseFont /HZGQIC+CMTT8 -/FontDescriptor 1846 0 R +/FontDescriptor 1900 0 R /FirstChar 98 /LastChar 116 -/Widths 1797 0 R +/Widths 1848 0 R >> -% 957 0 obj +% 962 0 obj << /Type /Font /Subtype /Type1 /BaseFont /KMUHVJ+CMTT9 -/FontDescriptor 1848 0 R +/FontDescriptor 1902 0 R /FirstChar 40 /LastChar 121 -/Widths 1796 0 R +/Widths 1847 0 R >> -% 558 0 obj +% 562 0 obj << /Type /Pages /Count 6 -/Parent 1849 0 R -/Kids [549 0 R 560 0 R 611 0 R 664 0 R 709 0 R 714 0 R] +/Parent 1903 0 R +/Kids [553 0 R 564 0 R 615 0 R 668 0 R 714 0 R 719 0 R] >> -% 731 0 obj +% 736 0 obj << /Type /Pages /Count 6 -/Parent 1849 0 R -/Kids [728 0 R 748 0 R 761 0 R 777 0 R 789 0 R 794 0 R] +/Parent 1903 0 R +/Kids [733 0 R 753 0 R 766 0 R 782 0 R 794 0 R 799 0 R] >> -% 826 0 obj +% 831 0 obj << /Type /Pages /Count 6 -/Parent 1849 0 R -/Kids [808 0 R 830 0 R 841 0 R 851 0 R 864 0 R 875 0 R] +/Parent 1903 0 R +/Kids [813 0 R 835 0 R 846 0 R 856 0 R 869 0 R 880 0 R] >> -% 882 0 obj +% 887 0 obj << /Type /Pages /Count 6 -/Parent 1849 0 R -/Kids [879 0 R 884 0 R 892 0 R 900 0 R 904 0 R 909 0 R] +/Parent 1903 0 R +/Kids [884 0 R 889 0 R 897 0 R 905 0 R 909 0 R 915 0 R] >> - -endstream -endobj -1850 0 obj +% 922 0 obj << -/Type /ObjStm -/N 100 -/First 914 -/Length 10489 +/Type /Pages +/Count 6 +/Parent 1903 0 R +/Kids [919 0 R 924 0 R 928 0 R 932 0 R 938 0 R 944 0 R] >> -stream -917 0 948 113 995 226 1040 343 1084 463 1138 583 1198 703 1246 823 1288 943 1328 1063 -1378 1183 1413 1303 1449 1423 1488 1543 1529 1663 1556 1783 1592 1903 1655 2023 1695 2143 1733 2263 -1773 2383 1849 2485 1851 2600 1852 2720 1853 2841 1854 2962 1855 3037 1856 3133 546 3202 542 3262 -538 3373 534 3447 530 3535 526 3623 522 3711 518 3799 514 3873 510 3998 506 4072 502 4160 -498 4248 494 4336 490 4424 486 4498 482 4623 478 4697 474 4785 470 4873 466 4947 462 5072 -458 5146 454 5234 450 5322 446 5410 442 5498 438 5586 434 5674 430 5762 426 5850 422 5938 -418 6026 414 6114 410 6202 406 6290 401 6378 397 6452 393 6578 389 6652 385 6740 381 6828 -377 6916 373 7004 369 7092 365 7180 361 7268 357 7356 353 7444 349 7532 345 7620 341 7708 -337 7796 333 7884 329 7972 325 8060 321 8148 317 8236 313 8324 309 8412 305 8500 301 8588 -297 8676 293 8764 289 8852 285 8926 281 9052 277 9126 273 9214 269 9302 265 9376 261 9501 -% 917 0 obj +% 953 0 obj << /Type /Pages /Count 6 -/Parent 1849 0 R -/Kids [914 0 R 919 0 R 923 0 R 927 0 R 933 0 R 939 0 R] +/Parent 1903 0 R +/Kids [950 0 R 958 0 R 965 0 R 969 0 R 980 0 R 986 0 R] >> -% 948 0 obj +% 999 0 obj << /Type /Pages /Count 6 -/Parent 1849 0 R -/Kids [945 0 R 953 0 R 960 0 R 964 0 R 975 0 R 981 0 R] +/Parent 1904 0 R +/Kids [995 0 R 1002 0 R 1019 0 R 1024 0 R 1031 0 R 1036 0 R] >> -% 995 0 obj +% 1053 0 obj << /Type /Pages /Count 6 -/Parent 1851 0 R -/Kids [991 0 R 997 0 R 1007 0 R 1013 0 R 1020 0 R 1028 0 R] +/Parent 1904 0 R +/Kids [1049 0 R 1058 0 R 1063 0 R 1076 0 R 1081 0 R 1088 0 R] >> -% 1040 0 obj +% 1102 0 obj << /Type /Pages /Count 6 -/Parent 1851 0 R -/Kids [1036 0 R 1045 0 R 1050 0 R 1057 0 R 1065 0 R 1072 0 R] +/Parent 1904 0 R +/Kids [1093 0 R 1107 0 R 1114 0 R 1122 0 R 1133 0 R 1148 0 R] >> -% 1084 0 obj +% 1158 0 obj << /Type /Pages /Count 6 -/Parent 1851 0 R -/Kids [1079 0 R 1091 0 R 1106 0 R 1112 0 R 1124 0 R 1130 0 R] +/Parent 1904 0 R +/Kids [1154 0 R 1166 0 R 1172 0 R 1177 0 R 1185 0 R 1195 0 R] >> -% 1138 0 obj +% 1212 0 obj << /Type /Pages /Count 6 -/Parent 1851 0 R -/Kids [1135 0 R 1144 0 R 1154 0 R 1167 0 R 1175 0 R 1187 0 R] +/Parent 1904 0 R +/Kids [1208 0 R 1217 0 R 1229 0 R 1238 0 R 1242 0 R 1257 0 R] >> -% 1198 0 obj +% 1268 0 obj << /Type /Pages /Count 6 -/Parent 1851 0 R -/Kids [1195 0 R 1200 0 R 1215 0 R 1223 0 R 1229 0 R 1239 0 R] +/Parent 1904 0 R +/Kids [1265 0 R 1272 0 R 1281 0 R 1285 0 R 1290 0 R 1296 0 R] >> -% 1246 0 obj +% 1309 0 obj << /Type /Pages /Count 6 -/Parent 1851 0 R -/Kids [1243 0 R 1249 0 R 1255 0 R 1260 0 R 1270 0 R 1275 0 R] +/Parent 1905 0 R +/Kids [1301 0 R 1312 0 R 1317 0 R 1326 0 R 1333 0 R 1338 0 R] >> -% 1288 0 obj +% 1348 0 obj << /Type /Pages /Count 6 -/Parent 1852 0 R -/Kids [1284 0 R 1292 0 R 1297 0 R 1303 0 R 1307 0 R 1315 0 R] +/Parent 1905 0 R +/Kids [1344 0 R 1350 0 R 1358 0 R 1368 0 R 1372 0 R 1387 0 R] >> -% 1328 0 obj +% 1400 0 obj << /Type /Pages /Count 6 -/Parent 1852 0 R -/Kids [1325 0 R 1330 0 R 1346 0 R 1350 0 R 1362 0 R 1368 0 R] +/Parent 1905 0 R +/Kids [1391 0 R 1404 0 R 1410 0 R 1417 0 R 1423 0 R 1427 0 R] >> -% 1378 0 obj +% 1439 0 obj << /Type /Pages /Count 6 -/Parent 1852 0 R -/Kids [1375 0 R 1382 0 R 1386 0 R 1395 0 R 1401 0 R 1405 0 R] +/Parent 1905 0 R +/Kids [1436 0 R 1443 0 R 1447 0 R 1453 0 R 1457 0 R 1464 0 R] >> -% 1413 0 obj +% 1473 0 obj << /Type /Pages /Count 6 -/Parent 1852 0 R -/Kids [1410 0 R 1415 0 R 1422 0 R 1427 0 R 1433 0 R 1439 0 R] +/Parent 1905 0 R +/Kids [1469 0 R 1476 0 R 1482 0 R 1488 0 R 1494 0 R 1501 0 R] >> -% 1449 0 obj +% 1511 0 obj << /Type /Pages /Count 6 -/Parent 1852 0 R -/Kids [1445 0 R 1453 0 R 1460 0 R 1467 0 R 1471 0 R 1481 0 R] +/Parent 1905 0 R +/Kids [1508 0 R 1513 0 R 1523 0 R 1527 0 R 1531 0 R 1544 0 R] >> -% 1488 0 obj +% 1553 0 obj << /Type /Pages /Count 6 -/Parent 1852 0 R -/Kids [1485 0 R 1490 0 R 1503 0 R 1507 0 R 1513 0 R 1519 0 R] +/Parent 1906 0 R +/Kids [1548 0 R 1555 0 R 1562 0 R 1569 0 R 1573 0 R 1577 0 R] >> -% 1529 0 obj +% 1584 0 obj << /Type /Pages /Count 6 -/Parent 1853 0 R -/Kids [1526 0 R 1531 0 R 1535 0 R 1539 0 R 1543 0 R 1547 0 R] +/Parent 1906 0 R +/Kids [1581 0 R 1586 0 R 1590 0 R 1594 0 R 1600 0 R 1606 0 R] >> -% 1556 0 obj +% 1617 0 obj << /Type /Pages /Count 6 -/Parent 1853 0 R -/Kids [1551 0 R 1559 0 R 1565 0 R 1571 0 R 1577 0 R 1583 0 R] +/Parent 1906 0 R +/Kids [1612 0 R 1619 0 R 1625 0 R 1633 0 R 1638 0 R 1645 0 R] >> -% 1592 0 obj +% 1680 0 obj << /Type /Pages /Count 6 -/Parent 1853 0 R -/Kids [1588 0 R 1596 0 R 1602 0 R 1632 0 R 1638 0 R 1644 0 R] +/Parent 1906 0 R +/Kids [1651 0 R 1683 0 R 1689 0 R 1695 0 R 1701 0 R 1707 0 R] >> -% 1655 0 obj +% 1717 0 obj << /Type /Pages /Count 6 -/Parent 1853 0 R -/Kids [1650 0 R 1657 0 R 1663 0 R 1670 0 R 1677 0 R 1683 0 R] +/Parent 1906 0 R +/Kids [1712 0 R 1720 0 R 1727 0 R 1733 0 R 1740 0 R 1746 0 R] >> -% 1695 0 obj +% 1755 0 obj << /Type /Pages /Count 6 -/Parent 1853 0 R -/Kids [1690 0 R 1697 0 R 1703 0 R 1709 0 R 1718 0 R 1722 0 R] +/Parent 1906 0 R +/Kids [1752 0 R 1759 0 R 1768 0 R 1773 0 R 1781 0 R 1786 0 R] >> -% 1733 0 obj +% 1793 0 obj << /Type /Pages /Count 6 -/Parent 1853 0 R -/Kids [1730 0 R 1736 0 R 1740 0 R 1746 0 R 1750 0 R 1757 0 R] +/Parent 1907 0 R +/Kids [1790 0 R 1797 0 R 1801 0 R 1808 0 R 1820 0 R 1825 0 R] >> -% 1773 0 obj +% 1836 0 obj << /Type /Pages -/Count 4 -/Parent 1854 0 R -/Kids [1770 0 R 1776 0 R 1780 0 R 1788 0 R] +/Count 2 +/Parent 1907 0 R +/Kids [1829 0 R 1838 0 R] >> -% 1849 0 obj +% 1903 0 obj << /Type /Pages /Count 36 -/Parent 1855 0 R -/Kids [558 0 R 731 0 R 826 0 R 882 0 R 917 0 R 948 0 R] +/Parent 1908 0 R +/Kids [562 0 R 736 0 R 831 0 R 887 0 R 922 0 R 953 0 R] >> -% 1851 0 obj +% 1904 0 obj << /Type /Pages /Count 36 -/Parent 1855 0 R -/Kids [995 0 R 1040 0 R 1084 0 R 1138 0 R 1198 0 R 1246 0 R] +/Parent 1908 0 R +/Kids [999 0 R 1053 0 R 1102 0 R 1158 0 R 1212 0 R 1268 0 R] >> -% 1852 0 obj +% 1905 0 obj << /Type /Pages /Count 36 -/Parent 1855 0 R -/Kids [1288 0 R 1328 0 R 1378 0 R 1413 0 R 1449 0 R 1488 0 R] +/Parent 1908 0 R +/Kids [1309 0 R 1348 0 R 1400 0 R 1439 0 R 1473 0 R 1511 0 R] >> -% 1853 0 obj +% 1906 0 obj << /Type /Pages /Count 36 -/Parent 1855 0 R -/Kids [1529 0 R 1556 0 R 1592 0 R 1655 0 R 1695 0 R 1733 0 R] +/Parent 1908 0 R +/Kids [1553 0 R 1584 0 R 1617 0 R 1680 0 R 1717 0 R 1755 0 R] >> -% 1854 0 obj +% 1907 0 obj << /Type /Pages -/Count 4 -/Parent 1855 0 R -/Kids [1773 0 R] +/Count 8 +/Parent 1908 0 R +/Kids [1793 0 R 1836 0 R] >> -% 1855 0 obj +% 1908 0 obj << /Type /Pages -/Count 148 -/Kids [1849 0 R 1851 0 R 1852 0 R 1853 0 R 1854 0 R] +/Count 152 +/Kids [1903 0 R 1904 0 R 1905 0 R 1906 0 R 1907 0 R] >> -% 1856 0 obj +% 1909 0 obj << /Type /Outlines /First 4 0 R /Last 4 0 R /Count 1 >> +% 550 0 obj +<< +/Title 551 0 R +/A 548 0 R +/Parent 546 0 R +>> % 546 0 obj << /Title 547 0 R /A 544 0 R -/Parent 542 0 R +/Parent 4 0 R +/Prev 518 0 R +/First 550 0 R +/Last 550 0 R +/Count -1 >> % 542 0 obj << /Title 543 0 R /A 540 0 R -/Parent 4 0 R -/Prev 514 0 R -/First 546 0 R -/Last 546 0 R -/Count -1 +/Parent 518 0 R +/Prev 538 0 R >> % 538 0 obj << /Title 539 0 R /A 536 0 R -/Parent 514 0 R +/Parent 518 0 R /Prev 534 0 R +/Next 542 0 R >> % 534 0 obj << /Title 535 0 R /A 532 0 R -/Parent 514 0 R +/Parent 518 0 R /Prev 530 0 R /Next 538 0 R >> @@ -26309,7 +26987,7 @@ stream << /Title 531 0 R /A 528 0 R -/Parent 514 0 R +/Parent 518 0 R /Prev 526 0 R /Next 534 0 R >> @@ -26317,7 +26995,7 @@ stream << /Title 527 0 R /A 524 0 R -/Parent 514 0 R +/Parent 518 0 R /Prev 522 0 R /Next 530 0 R >> @@ -26325,40 +27003,40 @@ stream << /Title 523 0 R /A 520 0 R -/Parent 514 0 R -/Prev 518 0 R +/Parent 518 0 R /Next 526 0 R >> % 518 0 obj << /Title 519 0 R /A 516 0 R -/Parent 514 0 R -/Next 522 0 R +/Parent 4 0 R +/Prev 490 0 R +/Next 546 0 R +/First 522 0 R +/Last 542 0 R +/Count -6 >> % 514 0 obj << /Title 515 0 R /A 512 0 R -/Parent 4 0 R -/Prev 486 0 R -/Next 542 0 R -/First 518 0 R -/Last 538 0 R -/Count -6 +/Parent 490 0 R +/Prev 510 0 R >> % 510 0 obj << /Title 511 0 R /A 508 0 R -/Parent 486 0 R +/Parent 490 0 R /Prev 506 0 R +/Next 514 0 R >> % 506 0 obj << /Title 507 0 R /A 504 0 R -/Parent 486 0 R +/Parent 490 0 R /Prev 502 0 R /Next 510 0 R >> @@ -26366,7 +27044,7 @@ stream << /Title 503 0 R /A 500 0 R -/Parent 486 0 R +/Parent 490 0 R /Prev 498 0 R /Next 506 0 R >> @@ -26374,7 +27052,7 @@ stream << /Title 499 0 R /A 496 0 R -/Parent 486 0 R +/Parent 490 0 R /Prev 494 0 R /Next 502 0 R >> @@ -26382,40 +27060,40 @@ stream << /Title 495 0 R /A 492 0 R -/Parent 486 0 R -/Prev 490 0 R +/Parent 490 0 R /Next 498 0 R >> % 490 0 obj << /Title 491 0 R /A 488 0 R -/Parent 486 0 R -/Next 494 0 R +/Parent 4 0 R +/Prev 470 0 R +/Next 518 0 R +/First 494 0 R +/Last 514 0 R +/Count -6 >> % 486 0 obj << /Title 487 0 R /A 484 0 R -/Parent 4 0 R -/Prev 466 0 R -/Next 514 0 R -/First 490 0 R -/Last 510 0 R -/Count -6 +/Parent 470 0 R +/Prev 482 0 R >> % 482 0 obj << /Title 483 0 R /A 480 0 R -/Parent 466 0 R +/Parent 470 0 R /Prev 478 0 R +/Next 486 0 R >> % 478 0 obj << /Title 479 0 R /A 476 0 R -/Parent 466 0 R +/Parent 470 0 R /Prev 474 0 R /Next 482 0 R >> @@ -26423,27 +27101,26 @@ stream << /Title 475 0 R /A 472 0 R -/Parent 466 0 R -/Prev 470 0 R +/Parent 470 0 R /Next 478 0 R >> % 470 0 obj << /Title 471 0 R /A 468 0 R -/Parent 466 0 R -/Next 474 0 R +/Parent 4 0 R +/Prev 397 0 R +/Next 490 0 R +/First 474 0 R +/Last 486 0 R +/Count -4 >> % 466 0 obj << /Title 467 0 R /A 464 0 R -/Parent 4 0 R -/Prev 397 0 R -/Next 486 0 R -/First 470 0 R -/Last 482 0 R -/Count -4 +/Parent 397 0 R +/Prev 462 0 R >> % 462 0 obj << @@ -26451,6 +27128,7 @@ stream /A 460 0 R /Parent 397 0 R /Prev 458 0 R +/Next 466 0 R >> % 458 0 obj << @@ -26468,6 +27146,27 @@ stream /Prev 450 0 R /Next 458 0 R >> + +endstream +endobj +1910 0 obj +<< +/Type /ObjStm +/N 100 +/First 873 +/Length 9636 +>> +stream +450 0 446 88 442 176 438 264 434 352 430 440 426 528 422 616 418 704 414 792 +410 880 406 968 401 1056 397 1130 393 1256 389 1330 385 1418 381 1506 377 1594 373 1682 +369 1770 365 1858 361 1946 357 2034 353 2122 349 2210 345 2298 341 2386 337 2474 333 2562 +329 2650 325 2738 321 2826 317 2914 313 3002 309 3090 305 3178 301 3266 297 3354 293 3442 +289 3530 285 3604 281 3730 277 3804 273 3892 269 3980 265 4054 261 4179 257 4253 253 4341 +249 4429 245 4517 241 4605 237 4693 233 4781 229 4869 225 4957 221 5045 217 5133 213 5221 +209 5295 205 5420 200 5493 196 5580 192 5654 188 5742 184 5830 180 5918 176 5992 172 6091 +168 6216 164 6288 160 6361 156 6448 152 6535 148 6622 144 6709 140 6796 136 6883 132 6970 +128 7057 124 7144 120 7231 116 7318 112 7405 108 7492 104 7579 100 7666 96 7738 92 7848 +88 7969 84 8038 80 8107 76 8189 72 8271 68 8353 64 8435 60 8517 56 8599 52 8681 % 450 0 obj << /Title 451 0 R @@ -26577,10 +27276,10 @@ stream /A 395 0 R /Parent 4 0 R /Prev 285 0 R -/Next 466 0 R +/Next 470 0 R /First 401 0 R -/Last 462 0 R -/Count -16 +/Last 466 0 R +/Count -17 >> % 393 0 obj << @@ -26855,27 +27554,6 @@ stream /Parent 209 0 R /Prev 257 0 R >> - -endstream -endobj -1857 0 obj -<< -/Type /ObjStm -/N 100 -/First 906 -/Length 13388 ->> -stream -257 0 253 88 249 176 245 264 241 352 237 440 233 528 229 616 225 704 221 792 -217 880 213 968 209 1042 205 1167 200 1240 196 1327 192 1401 188 1489 184 1577 180 1665 -176 1739 172 1838 168 1963 164 2035 160 2108 156 2195 152 2282 148 2369 144 2456 140 2543 -136 2630 132 2717 128 2804 124 2891 120 2978 116 3065 112 3152 108 3239 104 3326 100 3413 -96 3485 92 3595 88 3716 84 3785 80 3854 76 3936 72 4018 68 4100 64 4182 60 4264 -56 4346 52 4428 48 4510 44 4579 40 4686 36 4792 32 4912 28 4981 24 5037 20 5156 -16 5238 12 5307 8 5424 4 5489 1858 5582 1859 5778 1860 5951 1861 6131 1862 6308 1863 6485 -1864 6651 1865 6816 1866 6982 1867 7146 1868 7310 1869 7480 1870 7650 1871 7822 1872 7992 1873 8164 -1874 8334 1875 8506 1876 8676 1877 8848 1878 9017 1879 9194 1880 9392 1881 9618 1882 9834 1883 10026 -1884 10201 1885 10410 1886 10635 1887 10855 1888 11088 1889 11321 1890 11552 1891 11788 1892 12023 1893 12254 % 257 0 obj << /Title 258 0 R @@ -27295,6 +27973,27 @@ stream /Prev 48 0 R /Next 56 0 R >> + +endstream +endobj +1911 0 obj +<< +/Type /ObjStm +/N 100 +/First 1000 +/Length 18704 +>> +stream +48 0 44 69 40 176 36 282 32 402 28 471 24 527 20 646 16 728 12 797 +8 914 4 979 1912 1072 1913 1268 1914 1441 1915 1621 1916 1798 1917 1975 1918 2155 1919 2324 +1920 2489 1921 2655 1922 2820 1923 2986 1924 3153 1925 3322 1926 3494 1927 3664 1928 3836 1929 4006 +1930 4178 1931 4348 1932 4520 1933 4690 1934 4862 1935 5052 1936 5281 1937 5492 1938 5689 1939 5866 +1940 6069 1941 6297 1942 6521 1943 6743 1944 6975 1945 7211 1946 7443 1947 7673 1948 7901 1949 8131 +1950 8367 1951 8602 1952 8834 1953 9038 1954 9218 1955 9396 1956 9576 1957 9754 1958 9934 1959 10112 +1960 10292 1961 10470 1962 10643 1963 10808 1964 10974 1965 11141 1966 11313 1967 11482 1968 11651 1969 11823 +1970 11993 1971 12165 1972 12335 1973 12507 1974 12677 1975 12849 1976 13019 1977 13191 1978 13363 1979 13566 +1980 13769 1981 13971 1982 14166 1983 14364 1984 14560 1985 14758 1986 14954 1987 15152 1988 15348 1989 15546 +1990 15742 1991 15940 1992 16135 1993 16330 1994 16528 1995 16724 1996 16922 1997 17113 1998 17293 1999 17486 % 48 0 obj << /Title 49 0 R @@ -27394,641 +28093,665 @@ stream << /Title 5 0 R /A 1 0 R -/Parent 1856 0 R +/Parent 1909 0 R /First 8 0 R -/Last 542 0 R +/Last 546 0 R /Count -11 >> -% 1858 0 obj +% 1912 0 obj << -/Names [(Doc-Start) 553 0 R (Hfootnote.1) 769 0 R (Hfootnote.2) 771 0 R (Hfootnote.3) 824 0 R (Hfootnote.4) 1712 0 R (Hfootnote.5) 1763 0 R] +/Names [(Doc-Start) 557 0 R (Hfootnote.1) 774 0 R (Hfootnote.2) 776 0 R (Hfootnote.3) 829 0 R (Hfootnote.4) 1762 0 R (Hfootnote.5) 1814 0 R] /Limits [(Doc-Start) (Hfootnote.5)] >> -% 1859 0 obj +% 1913 0 obj << -/Names [(Item.1) 798 0 R (Item.10) 812 0 R (Item.100) 1501 0 R (Item.101) 1510 0 R (Item.102) 1511 0 R (Item.103) 1516 0 R] +/Names [(Item.1) 803 0 R (Item.10) 817 0 R (Item.100) 1538 0 R (Item.101) 1539 0 R (Item.102) 1540 0 R (Item.103) 1541 0 R] /Limits [(Item.1) (Item.103)] >> -% 1860 0 obj +% 1914 0 obj << -/Names [(Item.104) 1517 0 R (Item.105) 1522 0 R (Item.106) 1523 0 R (Item.107) 1524 0 R (Item.108) 1554 0 R (Item.109) 1555 0 R] +/Names [(Item.104) 1542 0 R (Item.105) 1551 0 R (Item.106) 1552 0 R (Item.107) 1558 0 R (Item.108) 1559 0 R (Item.109) 1565 0 R] /Limits [(Item.104) (Item.109)] >> -% 1861 0 obj +% 1915 0 obj << -/Names [(Item.11) 813 0 R (Item.110) 1562 0 R (Item.111) 1563 0 R (Item.112) 1568 0 R (Item.113) 1569 0 R (Item.114) 1574 0 R] +/Names [(Item.11) 818 0 R (Item.110) 1566 0 R (Item.111) 1567 0 R (Item.112) 1597 0 R (Item.113) 1598 0 R (Item.114) 1603 0 R] /Limits [(Item.11) (Item.114)] >> -% 1862 0 obj +% 1916 0 obj << -/Names [(Item.115) 1575 0 R (Item.116) 1580 0 R (Item.117) 1581 0 R (Item.118) 1586 0 R (Item.119) 1591 0 R (Item.12) 814 0 R] +/Names [(Item.115) 1604 0 R (Item.116) 1609 0 R (Item.117) 1610 0 R (Item.118) 1615 0 R (Item.119) 1616 0 R (Item.12) 819 0 R] /Limits [(Item.115) (Item.12)] >> -% 1863 0 obj +% 1917 0 obj << -/Names [(Item.13) 815 0 R (Item.14) 816 0 R (Item.15) 817 0 R (Item.16) 818 0 R (Item.17) 819 0 R (Item.18) 820 0 R] -/Limits [(Item.13) (Item.18)] +/Names [(Item.120) 1622 0 R (Item.121) 1623 0 R (Item.122) 1628 0 R (Item.123) 1629 0 R (Item.124) 1631 0 R (Item.125) 1636 0 R] +/Limits [(Item.120) (Item.125)] >> -% 1864 0 obj +% 1918 0 obj << -/Names [(Item.19) 821 0 R (Item.2) 799 0 R (Item.20) 822 0 R (Item.21) 823 0 R (Item.22) 833 0 R (Item.23) 834 0 R] -/Limits [(Item.19) (Item.23)] +/Names [(Item.126) 1641 0 R (Item.13) 820 0 R (Item.14) 821 0 R (Item.15) 822 0 R (Item.16) 823 0 R (Item.17) 824 0 R] +/Limits [(Item.126) (Item.17)] >> -% 1865 0 obj +% 1919 0 obj << -/Names [(Item.24) 835 0 R (Item.25) 836 0 R (Item.26) 837 0 R (Item.27) 838 0 R (Item.28) 854 0 R (Item.29) 855 0 R] -/Limits [(Item.24) (Item.29)] +/Names [(Item.18) 825 0 R (Item.19) 826 0 R (Item.2) 804 0 R (Item.20) 827 0 R (Item.21) 828 0 R (Item.22) 838 0 R] +/Limits [(Item.18) (Item.22)] >> -% 1866 0 obj +% 1920 0 obj << -/Names [(Item.3) 800 0 R (Item.30) 856 0 R (Item.31) 857 0 R (Item.32) 858 0 R (Item.33) 859 0 R (Item.34) 860 0 R] -/Limits [(Item.3) (Item.34)] +/Names [(Item.23) 839 0 R (Item.24) 840 0 R (Item.25) 841 0 R (Item.26) 842 0 R (Item.27) 843 0 R (Item.28) 859 0 R] +/Limits [(Item.23) (Item.28)] >> -% 1867 0 obj +% 1921 0 obj << -/Names [(Item.35) 861 0 R (Item.36) 862 0 R (Item.37) 867 0 R (Item.38) 868 0 R (Item.39) 869 0 R (Item.4) 801 0 R] -/Limits [(Item.35) (Item.4)] +/Names [(Item.29) 860 0 R (Item.3) 805 0 R (Item.30) 861 0 R (Item.31) 862 0 R (Item.32) 863 0 R (Item.33) 864 0 R] +/Limits [(Item.29) (Item.33)] >> -% 1868 0 obj +% 1922 0 obj << -/Names [(Item.40) 870 0 R (Item.41) 907 0 R (Item.42) 1190 0 R (Item.43) 1191 0 R (Item.44) 1192 0 R (Item.45) 1252 0 R] -/Limits [(Item.40) (Item.45)] +/Names [(Item.34) 865 0 R (Item.35) 866 0 R (Item.36) 867 0 R (Item.37) 872 0 R (Item.38) 873 0 R (Item.39) 874 0 R] +/Limits [(Item.34) (Item.39)] >> -% 1869 0 obj +% 1923 0 obj << -/Names [(Item.46) 1258 0 R (Item.47) 1263 0 R (Item.48) 1264 0 R (Item.49) 1265 0 R (Item.5) 802 0 R (Item.50) 1266 0 R] -/Limits [(Item.46) (Item.50)] +/Names [(Item.4) 806 0 R (Item.40) 875 0 R (Item.41) 912 0 R (Item.42) 1005 0 R (Item.43) 1039 0 R (Item.44) 1066 0 R] +/Limits [(Item.4) (Item.44)] >> -% 1870 0 obj +% 1924 0 obj << -/Names [(Item.51) 1267 0 R (Item.52) 1278 0 R (Item.53) 1279 0 R (Item.54) 1280 0 R (Item.55) 1287 0 R (Item.56) 1310 0 R] -/Limits [(Item.51) (Item.56)] +/Names [(Item.45) 1096 0 R (Item.46) 1232 0 R (Item.47) 1233 0 R (Item.48) 1234 0 R (Item.49) 1293 0 R (Item.5) 807 0 R] +/Limits [(Item.45) (Item.5)] >> -% 1871 0 obj +% 1925 0 obj << -/Names [(Item.57) 1311 0 R (Item.58) 1318 0 R (Item.59) 1319 0 R (Item.6) 803 0 R (Item.60) 1320 0 R (Item.61) 1333 0 R] -/Limits [(Item.57) (Item.61)] +/Names [(Item.50) 1299 0 R (Item.51) 1304 0 R (Item.52) 1305 0 R (Item.53) 1306 0 R (Item.54) 1307 0 R (Item.55) 1308 0 R] +/Limits [(Item.50) (Item.55)] >> -% 1872 0 obj +% 1926 0 obj << -/Names [(Item.62) 1334 0 R (Item.63) 1335 0 R (Item.64) 1336 0 R (Item.65) 1337 0 R (Item.66) 1338 0 R (Item.67) 1339 0 R] -/Limits [(Item.62) (Item.67)] +/Names [(Item.56) 1320 0 R (Item.57) 1321 0 R (Item.58) 1322 0 R (Item.59) 1329 0 R (Item.6) 808 0 R (Item.60) 1353 0 R] +/Limits [(Item.56) (Item.60)] >> -% 1873 0 obj +% 1927 0 obj << -/Names [(Item.68) 1340 0 R (Item.69) 1341 0 R (Item.7) 804 0 R (Item.70) 1353 0 R (Item.71) 1354 0 R (Item.72) 1355 0 R] -/Limits [(Item.68) (Item.72)] +/Names [(Item.61) 1354 0 R (Item.62) 1361 0 R (Item.63) 1362 0 R (Item.64) 1363 0 R (Item.65) 1375 0 R (Item.66) 1376 0 R] +/Limits [(Item.61) (Item.66)] >> -% 1874 0 obj +% 1928 0 obj << -/Names [(Item.73) 1356 0 R (Item.74) 1357 0 R (Item.75) 1358 0 R (Item.76) 1371 0 R (Item.77) 1389 0 R (Item.78) 1390 0 R] -/Limits [(Item.73) (Item.78)] +/Names [(Item.67) 1377 0 R (Item.68) 1378 0 R (Item.69) 1379 0 R (Item.7) 809 0 R (Item.70) 1380 0 R (Item.71) 1381 0 R] +/Limits [(Item.67) (Item.71)] >> -% 1875 0 obj +% 1929 0 obj << -/Names [(Item.79) 1418 0 R (Item.8) 805 0 R (Item.80) 1419 0 R (Item.81) 1430 0 R (Item.82) 1436 0 R (Item.83) 1442 0 R] -/Limits [(Item.79) (Item.83)] +/Names [(Item.72) 1382 0 R (Item.73) 1383 0 R (Item.74) 1394 0 R (Item.75) 1395 0 R (Item.76) 1396 0 R (Item.77) 1397 0 R] +/Limits [(Item.72) (Item.77)] >> -% 1876 0 obj +% 1930 0 obj << -/Names [(Item.84) 1448 0 R (Item.85) 1456 0 R (Item.86) 1457 0 R (Item.87) 1463 0 R (Item.88) 1464 0 R (Item.89) 1474 0 R] -/Limits [(Item.84) (Item.89)] +/Names [(Item.78) 1398 0 R (Item.79) 1399 0 R (Item.8) 810 0 R (Item.80) 1413 0 R (Item.81) 1430 0 R (Item.82) 1431 0 R] +/Limits [(Item.78) (Item.82)] >> -% 1877 0 obj +% 1931 0 obj << -/Names [(Item.9) 811 0 R (Item.90) 1475 0 R (Item.91) 1476 0 R (Item.92) 1493 0 R (Item.93) 1494 0 R (Item.94) 1495 0 R] -/Limits [(Item.9) (Item.94)] +/Names [(Item.83) 1460 0 R (Item.84) 1461 0 R (Item.85) 1472 0 R (Item.86) 1479 0 R (Item.87) 1485 0 R (Item.88) 1491 0 R] +/Limits [(Item.83) (Item.88)] >> -% 1878 0 obj +% 1932 0 obj << -/Names [(Item.95) 1496 0 R (Item.96) 1497 0 R (Item.97) 1498 0 R (Item.98) 1499 0 R (Item.99) 1500 0 R (cite.2007c) 784 0 R] -/Limits [(Item.95) (cite.2007c)] +/Names [(Item.89) 1497 0 R (Item.9) 816 0 R (Item.90) 1498 0 R (Item.91) 1504 0 R (Item.92) 1505 0 R (Item.93) 1516 0 R] +/Limits [(Item.89) (Item.93)] >> -% 1879 0 obj +% 1933 0 obj << -/Names [(cite.2007d) 785 0 R (cite.BLACS) 757 0 R (cite.BLAS1) 739 0 R (cite.BLAS2) 740 0 R (cite.BLAS3) 741 0 R (cite.DesPat:11) 734 0 R] -/Limits [(cite.2007d) (cite.DesPat:11)] +/Names [(Item.94) 1517 0 R (Item.95) 1518 0 R (Item.96) 1534 0 R (Item.97) 1535 0 R (Item.98) 1536 0 R (Item.99) 1537 0 R] +/Limits [(Item.94) (Item.99)] >> -% 1880 0 obj +% 1934 0 obj << -/Names [(cite.DesignPatterns) 898 0 R (cite.KIVA3PSBLAS) 1786 0 R (cite.METIS) 772 0 R (cite.MPI1) 1791 0 R (cite.PARA04FOREST) 1784 0 R (cite.PSBLAS) 1785 0 R] -/Limits [(cite.DesignPatterns) (cite.PSBLAS)] +/Names [(cite.2007c) 789 0 R (cite.2007d) 790 0 R (cite.BLACS) 762 0 R (cite.BLAS1) 744 0 R (cite.BLAS2) 745 0 R (cite.BLAS3) 746 0 R] +/Limits [(cite.2007c) (cite.BLAS3)] >> -% 1881 0 obj +% 1935 0 obj << -/Names [(cite.RouXiaXu:11) 735 0 R (cite.Sparse03) 733 0 R (cite.machiels) 736 0 R (cite.metcalf) 732 0 R (cite.sblas02) 738 0 R (cite.sblas97) 737 0 R] -/Limits [(cite.RouXiaXu:11) (cite.sblas97)] +/Names [(cite.DesPat:11) 739 0 R (cite.DesignPatterns) 903 0 R (cite.KIVA3PSBLAS) 1835 0 R (cite.METIS) 777 0 R (cite.MPI1) 1841 0 R (cite.PARA04FOREST) 1833 0 R] +/Limits [(cite.DesPat:11) (cite.PARA04FOREST)] >> -% 1882 0 obj +% 1936 0 obj << -/Names [(descdata) 844 0 R (equation.4.1) 1094 0 R (equation.4.2) 1095 0 R (equation.4.3) 1096 0 R (figure.1) 751 0 R (figure.10) 1600 0 R] -/Limits [(descdata) (figure.10)] +/Names [(cite.PSBLAS) 1834 0 R (cite.RouXiaXu:11) 740 0 R (cite.Sparse03) 738 0 R (cite.machiels) 741 0 R (cite.metcalf) 737 0 R (cite.sblas02) 743 0 R] +/Limits [(cite.PSBLAS) (cite.sblas02)] >> -% 1883 0 obj +% 1937 0 obj << -/Names [(figure.2) 780 0 R (figure.3) 871 0 R (figure.4) 897 0 R (figure.5) 937 0 R (figure.6) 958 0 R (figure.7) 1157 0 R] -/Limits [(figure.2) (figure.7)] +/Names [(cite.sblas97) 742 0 R (descdata) 849 0 R (equation.4.1) 1136 0 R (equation.4.2) 1137 0 R (equation.4.3) 1138 0 R (figure.1) 756 0 R] +/Limits [(cite.sblas97) (figure.1)] >> -% 1884 0 obj +% 1938 0 obj << -/Names [(figure.8) 1193 0 R (figure.9) 1599 0 R (lstlisting.-1) 1148 0 R (lstlisting.-10) 1666 0 R (lstlisting.-11) 1673 0 R (lstlisting.-12) 1680 0 R] -/Limits [(figure.8) (lstlisting.-12)] +/Names [(figure.10) 1649 0 R (figure.2) 785 0 R (figure.3) 876 0 R (figure.4) 902 0 R (figure.5) 942 0 R (figure.6) 963 0 R] +/Limits [(figure.10) (figure.6)] >> -% 1885 0 obj +% 1939 0 obj << -/Names [(lstlisting.-13) 1686 0 R (lstlisting.-14) 1693 0 R (lstlisting.-15) 1700 0 R (lstlisting.-16) 1760 0 R (lstlisting.-2) 1179 0 R (lstlisting.-3) 1219 0 R] -/Limits [(lstlisting.-13) (lstlisting.-3)] +/Names [(figure.7) 1198 0 R (figure.8) 1235 0 R (figure.9) 1648 0 R (lstlisting.-1) 1006 0 R (lstlisting.-10) 1686 0 R (lstlisting.-11) 1692 0 R] +/Limits [(figure.7) (lstlisting.-11)] >> -% 1886 0 obj +% 1940 0 obj << -/Names [(lstlisting.-4) 1233 0 R (lstlisting.-5) 1605 0 R (lstlisting.-6) 1635 0 R (lstlisting.-7) 1641 0 R (lstlisting.-8) 1647 0 R (lstlisting.-9) 1653 0 R] -/Limits [(lstlisting.-4) (lstlisting.-9)] +/Names [(lstlisting.-12) 1698 0 R (lstlisting.-13) 1704 0 R (lstlisting.-14) 1715 0 R (lstlisting.-15) 1723 0 R (lstlisting.-16) 1730 0 R (lstlisting.-17) 1736 0 R] +/Limits [(lstlisting.-12) (lstlisting.-17)] >> -% 1887 0 obj +% 1941 0 obj << -/Names [(lstnumber.-1.1) 1149 0 R (lstnumber.-1.2) 1150 0 R (lstnumber.-10.1) 1667 0 R (lstnumber.-11.1) 1674 0 R (lstnumber.-12.1) 1681 0 R (lstnumber.-13.1) 1687 0 R] -/Limits [(lstnumber.-1.1) (lstnumber.-13.1)] +/Names [(lstlisting.-18) 1743 0 R (lstlisting.-19) 1749 0 R (lstlisting.-2) 1040 0 R (lstlisting.-20) 1811 0 R (lstlisting.-3) 1067 0 R (lstlisting.-4) 1097 0 R] +/Limits [(lstlisting.-18) (lstlisting.-4)] >> -% 1888 0 obj +% 1942 0 obj << -/Names [(lstnumber.-14.1) 1694 0 R (lstnumber.-15.1) 1701 0 R (lstnumber.-16.1) 1761 0 R (lstnumber.-16.2) 1762 0 R (lstnumber.-2.1) 1180 0 R (lstnumber.-2.2) 1181 0 R] -/Limits [(lstnumber.-14.1) (lstnumber.-2.2)] +/Names [(lstlisting.-5) 1189 0 R (lstlisting.-6) 1221 0 R (lstlisting.-7) 1261 0 R (lstlisting.-8) 1276 0 R (lstlisting.-9) 1654 0 R (lstnumber.-1.1) 1007 0 R] +/Limits [(lstlisting.-5) (lstnumber.-1.1)] >> -% 1889 0 obj +% 1943 0 obj << -/Names [(lstnumber.-3.1) 1220 0 R (lstnumber.-3.2) 1221 0 R (lstnumber.-4.1) 1234 0 R (lstnumber.-5.1) 1606 0 R (lstnumber.-5.10) 1616 0 R (lstnumber.-5.11) 1617 0 R] -/Limits [(lstnumber.-3.1) (lstnumber.-5.11)] +/Names [(lstnumber.-1.2) 1008 0 R (lstnumber.-1.3) 1009 0 R (lstnumber.-1.4) 1010 0 R (lstnumber.-10.1) 1687 0 R (lstnumber.-11.1) 1693 0 R (lstnumber.-12.1) 1699 0 R] +/Limits [(lstnumber.-1.2) (lstnumber.-12.1)] >> -% 1890 0 obj +% 1944 0 obj << -/Names [(lstnumber.-5.12) 1618 0 R (lstnumber.-5.13) 1619 0 R (lstnumber.-5.14) 1620 0 R (lstnumber.-5.15) 1621 0 R (lstnumber.-5.16) 1622 0 R (lstnumber.-5.17) 1623 0 R] -/Limits [(lstnumber.-5.12) (lstnumber.-5.17)] +/Names [(lstnumber.-13.1) 1705 0 R (lstnumber.-14.1) 1716 0 R (lstnumber.-15.1) 1724 0 R (lstnumber.-16.1) 1731 0 R (lstnumber.-17.1) 1737 0 R (lstnumber.-18.1) 1744 0 R] +/Limits [(lstnumber.-13.1) (lstnumber.-18.1)] >> -% 1891 0 obj +% 1945 0 obj << -/Names [(lstnumber.-5.18) 1624 0 R (lstnumber.-5.19) 1625 0 R (lstnumber.-5.2) 1608 0 R (lstnumber.-5.20) 1626 0 R (lstnumber.-5.21) 1627 0 R (lstnumber.-5.22) 1628 0 R] -/Limits [(lstnumber.-5.18) (lstnumber.-5.22)] +/Names [(lstnumber.-19.1) 1750 0 R (lstnumber.-2.1) 1041 0 R (lstnumber.-2.2) 1042 0 R (lstnumber.-2.3) 1043 0 R (lstnumber.-2.4) 1044 0 R (lstnumber.-20.1) 1812 0 R] +/Limits [(lstnumber.-19.1) (lstnumber.-20.1)] >> -% 1892 0 obj +% 1946 0 obj << -/Names [(lstnumber.-5.23) 1629 0 R (lstnumber.-5.24) 1630 0 R (lstnumber.-5.3) 1609 0 R (lstnumber.-5.4) 1610 0 R (lstnumber.-5.5) 1611 0 R (lstnumber.-5.6) 1612 0 R] -/Limits [(lstnumber.-5.23) (lstnumber.-5.6)] +/Names [(lstnumber.-20.2) 1813 0 R (lstnumber.-3.1) 1068 0 R (lstnumber.-3.2) 1069 0 R (lstnumber.-3.3) 1070 0 R (lstnumber.-3.4) 1071 0 R (lstnumber.-4.1) 1098 0 R] +/Limits [(lstnumber.-20.2) (lstnumber.-4.1)] >> -% 1893 0 obj +% 1947 0 obj << -/Names [(lstnumber.-5.7) 1613 0 R (lstnumber.-5.8) 1614 0 R (lstnumber.-5.9) 1615 0 R (lstnumber.-6.1) 1636 0 R (lstnumber.-7.1) 1642 0 R (lstnumber.-8.1) 1648 0 R] -/Limits [(lstnumber.-5.7) (lstnumber.-8.1)] +/Names [(lstnumber.-4.2) 1099 0 R (lstnumber.-4.3) 1100 0 R (lstnumber.-4.4) 1101 0 R (lstnumber.-5.1) 1190 0 R (lstnumber.-5.2) 1191 0 R (lstnumber.-6.1) 1222 0 R] +/Limits [(lstnumber.-4.2) (lstnumber.-6.1)] >> - -endstream -endobj -1968 0 obj +% 1948 0 obj << - /Title (Parallel Sparse BLAS V. 3.5.0) /Subject (Parallel Sparse Basic Linear Algebra Subroutines) /Keywords (Computer Science Linear Algebra Fluid Dynamics Parallel Linux MPI PSBLAS Iterative Solvers Preconditioners) /Creator (pdfLaTeX) /Producer ($Id$) /Author()/Title()/Subject()/Creator(LaTeX with hyperref package)/Producer(pdfTeX-1.40.17)/Keywords() -/CreationDate (D:20180323100717Z) -/ModDate (D:20180323100717Z) -/Trapped /False -/PTEX.Fullbanner (This is pdfTeX, Version 3.14159265-2.6-1.40.17 (TeX Live 2016) kpathsea version 6.2.2) +/Names [(lstnumber.-6.2) 1223 0 R (lstnumber.-7.1) 1262 0 R (lstnumber.-7.2) 1263 0 R (lstnumber.-8.1) 1277 0 R (lstnumber.-9.1) 1655 0 R (lstnumber.-9.10) 1665 0 R] +/Limits [(lstnumber.-6.2) (lstnumber.-9.10)] >> -endobj -1895 0 obj +% 1949 0 obj << -/Type /ObjStm -/N 73 -/First 738 -/Length 12624 +/Names [(lstnumber.-9.11) 1666 0 R (lstnumber.-9.12) 1667 0 R (lstnumber.-9.13) 1668 0 R (lstnumber.-9.14) 1669 0 R (lstnumber.-9.15) 1670 0 R (lstnumber.-9.16) 1671 0 R] +/Limits [(lstnumber.-9.11) (lstnumber.-9.16)] >> -stream -1894 0 1896 187 1897 367 1898 545 1899 725 1900 902 1901 1079 1902 1259 1903 1437 1904 1608 -1905 1773 1906 1939 1907 2105 1908 2274 1909 2446 1910 2616 1911 2788 1912 2958 1913 3130 1914 3300 -1915 3472 1916 3642 1917 3814 1918 3983 1919 4152 1920 4330 1921 4536 1922 4740 1923 4940 1924 5136 -1925 5334 1926 5530 1927 5728 1928 5924 1929 6122 1930 6317 1931 6512 1932 6710 1933 6906 1934 7104 -1935 7300 1936 7498 1937 7694 1938 7892 1939 8076 1940 8258 1941 8460 1942 8689 1943 8924 1944 9104 -1945 9278 1946 9450 1947 9520 1948 9633 1949 9744 1950 9855 1951 9971 1952 10091 1953 10217 1954 10335 -1955 10447 1956 10558 1957 10668 1958 10783 1959 10901 1960 11020 1961 11135 1962 11227 1963 11347 1964 11468 -1965 11554 1966 11638 1967 11673 -% 1894 0 obj +% 1950 0 obj << -/Names [(lstnumber.-9.1) 1654 0 R (page.1) 552 0 R (page.10) 853 0 R (page.100) 1509 0 R (page.101) 1515 0 R (page.102) 1521 0 R] -/Limits [(lstnumber.-9.1) (page.102)] +/Names [(lstnumber.-9.17) 1672 0 R (lstnumber.-9.18) 1673 0 R (lstnumber.-9.19) 1674 0 R (lstnumber.-9.2) 1657 0 R (lstnumber.-9.20) 1675 0 R (lstnumber.-9.21) 1676 0 R] +/Limits [(lstnumber.-9.17) (lstnumber.-9.21)] >> -% 1896 0 obj +% 1951 0 obj << -/Names [(page.103) 1528 0 R (page.104) 1533 0 R (page.105) 1537 0 R (page.106) 1541 0 R (page.107) 1545 0 R (page.108) 1549 0 R] -/Limits [(page.103) (page.108)] +/Names [(lstnumber.-9.22) 1677 0 R (lstnumber.-9.23) 1678 0 R (lstnumber.-9.24) 1679 0 R (lstnumber.-9.3) 1658 0 R (lstnumber.-9.4) 1659 0 R (lstnumber.-9.5) 1660 0 R] +/Limits [(lstnumber.-9.22) (lstnumber.-9.5)] >> -% 1897 0 obj +% 1952 0 obj << -/Names [(page.109) 1553 0 R (page.11) 866 0 R (page.110) 1561 0 R (page.111) 1567 0 R (page.112) 1573 0 R (page.113) 1579 0 R] -/Limits [(page.109) (page.113)] +/Names [(lstnumber.-9.6) 1661 0 R (lstnumber.-9.7) 1662 0 R (lstnumber.-9.8) 1663 0 R (lstnumber.-9.9) 1664 0 R (page.1) 556 0 R (page.10) 858 0 R] +/Limits [(lstnumber.-9.6) (page.10)] >> -% 1898 0 obj +% 1953 0 obj << -/Names [(page.114) 1585 0 R (page.115) 1590 0 R (page.116) 1598 0 R (page.117) 1604 0 R (page.118) 1634 0 R (page.119) 1640 0 R] -/Limits [(page.114) (page.119)] +/Names [(page.100) 1529 0 R (page.101) 1533 0 R (page.102) 1546 0 R (page.103) 1550 0 R (page.104) 1557 0 R (page.105) 1564 0 R] +/Limits [(page.100) (page.105)] >> -% 1899 0 obj +% 1954 0 obj << -/Names [(page.12) 877 0 R (page.120) 1646 0 R (page.121) 1652 0 R (page.122) 1659 0 R (page.123) 1665 0 R (page.124) 1672 0 R] -/Limits [(page.12) (page.124)] +/Names [(page.106) 1571 0 R (page.107) 1575 0 R (page.108) 1579 0 R (page.109) 1583 0 R (page.11) 871 0 R (page.110) 1588 0 R] +/Limits [(page.106) (page.110)] >> -% 1900 0 obj +% 1955 0 obj << -/Names [(page.125) 1679 0 R (page.126) 1685 0 R (page.127) 1692 0 R (page.128) 1699 0 R (page.129) 1705 0 R (page.13) 881 0 R] -/Limits [(page.125) (page.13)] +/Names [(page.111) 1592 0 R (page.112) 1596 0 R (page.113) 1602 0 R (page.114) 1608 0 R (page.115) 1614 0 R (page.116) 1621 0 R] +/Limits [(page.111) (page.116)] >> -% 1901 0 obj +% 1956 0 obj << -/Names [(page.130) 1711 0 R (page.131) 1720 0 R (page.132) 1724 0 R (page.133) 1732 0 R (page.134) 1738 0 R (page.135) 1742 0 R] -/Limits [(page.130) (page.135)] +/Names [(page.117) 1627 0 R (page.118) 1635 0 R (page.119) 1640 0 R (page.12) 882 0 R (page.120) 1647 0 R (page.121) 1653 0 R] +/Limits [(page.117) (page.121)] >> -% 1902 0 obj +% 1957 0 obj << -/Names [(page.136) 1748 0 R (page.137) 1752 0 R (page.138) 1759 0 R (page.139) 1772 0 R (page.14) 886 0 R (page.140) 1778 0 R] -/Limits [(page.136) (page.140)] +/Names [(page.122) 1685 0 R (page.123) 1691 0 R (page.124) 1697 0 R (page.125) 1703 0 R (page.126) 1709 0 R (page.127) 1714 0 R] +/Limits [(page.122) (page.127)] >> -% 1903 0 obj +% 1958 0 obj << -/Names [(page.141) 1782 0 R (page.142) 1790 0 R (page.15) 894 0 R (page.16) 902 0 R (page.17) 906 0 R (page.18) 911 0 R] -/Limits [(page.141) (page.18)] +/Names [(page.128) 1722 0 R (page.129) 1729 0 R (page.13) 886 0 R (page.130) 1735 0 R (page.131) 1742 0 R (page.132) 1748 0 R] +/Limits [(page.128) (page.132)] >> -% 1904 0 obj +% 1959 0 obj << -/Names [(page.19) 916 0 R (page.2) 562 0 R (page.20) 921 0 R (page.21) 925 0 R (page.22) 929 0 R (page.23) 935 0 R] -/Limits [(page.19) (page.23)] +/Names [(page.133) 1754 0 R (page.134) 1761 0 R (page.135) 1770 0 R (page.136) 1775 0 R (page.137) 1783 0 R (page.138) 1788 0 R] +/Limits [(page.133) (page.138)] >> -% 1905 0 obj +% 1960 0 obj << -/Names [(page.24) 941 0 R (page.25) 947 0 R (page.26) 955 0 R (page.27) 962 0 R (page.28) 966 0 R (page.29) 977 0 R] -/Limits [(page.24) (page.29)] +/Names [(page.139) 1792 0 R (page.14) 891 0 R (page.140) 1799 0 R (page.141) 1803 0 R (page.142) 1810 0 R (page.143) 1822 0 R] +/Limits [(page.139) (page.143)] >> -% 1906 0 obj +% 1961 0 obj << -/Names [(page.3) 763 0 R (page.30) 983 0 R (page.31) 993 0 R (page.32) 999 0 R (page.33) 1009 0 R (page.34) 1015 0 R] -/Limits [(page.3) (page.34)] +/Names [(page.144) 1827 0 R (page.145) 1831 0 R (page.146) 1840 0 R (page.15) 899 0 R (page.16) 907 0 R (page.17) 911 0 R] +/Limits [(page.144) (page.17)] >> -% 1907 0 obj +% 1962 0 obj << -/Names [(page.35) 1022 0 R (page.36) 1030 0 R (page.37) 1038 0 R (page.38) 1047 0 R (page.39) 1052 0 R (page.4) 779 0 R] -/Limits [(page.35) (page.4)] +/Names [(page.18) 917 0 R (page.19) 921 0 R (page.2) 566 0 R (page.20) 926 0 R (page.21) 930 0 R (page.22) 934 0 R] +/Limits [(page.18) (page.22)] >> -% 1908 0 obj +% 1963 0 obj << -/Names [(page.40) 1059 0 R (page.41) 1067 0 R (page.42) 1074 0 R (page.43) 1081 0 R (page.44) 1093 0 R (page.45) 1108 0 R] -/Limits [(page.40) (page.45)] +/Names [(page.23) 940 0 R (page.24) 946 0 R (page.25) 952 0 R (page.26) 960 0 R (page.27) 967 0 R (page.28) 971 0 R] +/Limits [(page.23) (page.28)] >> -% 1909 0 obj +% 1964 0 obj << -/Names [(page.46) 1114 0 R (page.47) 1126 0 R (page.48) 1132 0 R (page.49) 1137 0 R (page.5) 791 0 R (page.50) 1146 0 R] -/Limits [(page.46) (page.50)] +/Names [(page.29) 982 0 R (page.3) 768 0 R (page.30) 988 0 R (page.31) 997 0 R (page.32) 1004 0 R (page.33) 1021 0 R] +/Limits [(page.29) (page.33)] >> -% 1910 0 obj +% 1965 0 obj << -/Names [(page.51) 1156 0 R (page.52) 1169 0 R (page.53) 1177 0 R (page.54) 1189 0 R (page.55) 1197 0 R (page.56) 1202 0 R] -/Limits [(page.51) (page.56)] +/Names [(page.34) 1026 0 R (page.35) 1033 0 R (page.36) 1038 0 R (page.37) 1051 0 R (page.38) 1060 0 R (page.39) 1065 0 R] +/Limits [(page.34) (page.39)] >> -% 1911 0 obj +% 1966 0 obj << -/Names [(page.57) 1217 0 R (page.58) 1225 0 R (page.59) 1231 0 R (page.6) 796 0 R (page.60) 1241 0 R (page.61) 1245 0 R] -/Limits [(page.57) (page.61)] +/Names [(page.4) 784 0 R (page.40) 1078 0 R (page.41) 1083 0 R (page.42) 1090 0 R (page.43) 1095 0 R (page.44) 1109 0 R] +/Limits [(page.4) (page.44)] >> -% 1912 0 obj +% 1967 0 obj << -/Names [(page.62) 1251 0 R (page.63) 1257 0 R (page.64) 1262 0 R (page.65) 1272 0 R (page.66) 1277 0 R (page.67) 1286 0 R] -/Limits [(page.62) (page.67)] +/Names [(page.45) 1116 0 R (page.46) 1124 0 R (page.47) 1135 0 R (page.48) 1150 0 R (page.49) 1156 0 R (page.5) 796 0 R] +/Limits [(page.45) (page.5)] >> -% 1913 0 obj +% 1968 0 obj << -/Names [(page.68) 1294 0 R (page.69) 1299 0 R (page.7) 810 0 R (page.70) 1305 0 R (page.71) 1309 0 R (page.72) 1317 0 R] -/Limits [(page.68) (page.72)] +/Names [(page.50) 1168 0 R (page.51) 1174 0 R (page.52) 1179 0 R (page.53) 1187 0 R (page.54) 1197 0 R (page.55) 1210 0 R] +/Limits [(page.50) (page.55)] >> -% 1914 0 obj +% 1969 0 obj << -/Names [(page.73) 1327 0 R (page.74) 1332 0 R (page.75) 1348 0 R (page.76) 1352 0 R (page.77) 1364 0 R (page.78) 1370 0 R] -/Limits [(page.73) (page.78)] +/Names [(page.56) 1219 0 R (page.57) 1231 0 R (page.58) 1240 0 R (page.59) 1244 0 R (page.6) 801 0 R (page.60) 1259 0 R] +/Limits [(page.56) (page.60)] >> -% 1915 0 obj +% 1970 0 obj << -/Names [(page.79) 1377 0 R (page.8) 832 0 R (page.80) 1384 0 R (page.81) 1388 0 R (page.82) 1397 0 R (page.83) 1403 0 R] -/Limits [(page.79) (page.83)] +/Names [(page.61) 1267 0 R (page.62) 1274 0 R (page.63) 1283 0 R (page.64) 1287 0 R (page.65) 1292 0 R (page.66) 1298 0 R] +/Limits [(page.61) (page.66)] >> -% 1916 0 obj +% 1971 0 obj << -/Names [(page.84) 1407 0 R (page.85) 1412 0 R (page.86) 1417 0 R (page.87) 1424 0 R (page.88) 1429 0 R (page.89) 1435 0 R] -/Limits [(page.84) (page.89)] +/Names [(page.67) 1303 0 R (page.68) 1314 0 R (page.69) 1319 0 R (page.7) 815 0 R (page.70) 1328 0 R (page.71) 1335 0 R] +/Limits [(page.67) (page.71)] >> -% 1917 0 obj +% 1972 0 obj << -/Names [(page.9) 843 0 R (page.90) 1441 0 R (page.91) 1447 0 R (page.92) 1455 0 R (page.93) 1462 0 R (page.94) 1469 0 R] -/Limits [(page.9) (page.94)] +/Names [(page.72) 1340 0 R (page.73) 1346 0 R (page.74) 1352 0 R (page.75) 1360 0 R (page.76) 1370 0 R (page.77) 1374 0 R] +/Limits [(page.72) (page.77)] >> -% 1918 0 obj +% 1973 0 obj << -/Names [(page.95) 1473 0 R (page.96) 1483 0 R (page.97) 1487 0 R (page.98) 1492 0 R (page.99) 1505 0 R (page.i) 613 0 R] -/Limits [(page.95) (page.i)] +/Names [(page.78) 1389 0 R (page.79) 1393 0 R (page.8) 837 0 R (page.80) 1406 0 R (page.81) 1412 0 R (page.82) 1419 0 R] +/Limits [(page.78) (page.82)] >> -% 1919 0 obj +% 1974 0 obj << -/Names [(page.ii) 666 0 R (page.iii) 711 0 R (page.iv) 716 0 R (precdata) 956 0 R (section*.1) 614 0 R (section*.10) 79 0 R] -/Limits [(page.ii) (section*.10)] +/Names [(page.83) 1425 0 R (page.84) 1429 0 R (page.85) 1438 0 R (page.86) 1445 0 R (page.87) 1449 0 R (page.88) 1455 0 R] +/Limits [(page.83) (page.88)] >> -% 1920 0 obj +% 1975 0 obj << -/Names [(section*.100) 497 0 R (section*.101) 501 0 R (section*.102) 505 0 R (section*.103) 509 0 R (section*.104) 517 0 R (section*.105) 521 0 R] -/Limits [(section*.100) (section*.105)] +/Names [(page.89) 1459 0 R (page.9) 848 0 R (page.90) 1466 0 R (page.91) 1471 0 R (page.92) 1478 0 R (page.93) 1484 0 R] +/Limits [(page.89) (page.93)] >> -% 1921 0 obj +% 1976 0 obj << -/Names [(section*.106) 525 0 R (section*.107) 529 0 R (section*.108) 533 0 R (section*.109) 537 0 R (section*.11) 83 0 R (section*.110) 545 0 R] -/Limits [(section*.106) (section*.110)] +/Names [(page.94) 1490 0 R (page.95) 1496 0 R (page.96) 1503 0 R (page.97) 1510 0 R (page.98) 1515 0 R (page.99) 1525 0 R] +/Limits [(page.94) (page.99)] >> -% 1922 0 obj +% 1977 0 obj << -/Names [(section*.111) 1783 0 R (section*.12) 99 0 R (section*.13) 103 0 R (section*.14) 107 0 R (section*.15) 111 0 R (section*.16) 115 0 R] -/Limits [(section*.111) (section*.16)] +/Names [(page.i) 617 0 R (page.ii) 670 0 R (page.iii) 716 0 R (page.iv) 721 0 R (precdata) 961 0 R (section*.1) 618 0 R] +/Limits [(page.i) (section*.1)] >> -% 1923 0 obj +% 1978 0 obj << -/Names [(section*.17) 119 0 R (section*.18) 123 0 R (section*.19) 127 0 R (section*.2) 47 0 R (section*.20) 131 0 R (section*.21) 135 0 R] -/Limits [(section*.17) (section*.21)] +/Names [(section*.10) 79 0 R (section*.100) 497 0 R (section*.101) 501 0 R (section*.102) 505 0 R (section*.103) 509 0 R (section*.104) 513 0 R] +/Limits [(section*.10) (section*.104)] >> -% 1924 0 obj +% 1979 0 obj << -/Names [(section*.22) 139 0 R (section*.23) 143 0 R (section*.24) 147 0 R (section*.25) 151 0 R (section*.26) 155 0 R (section*.27) 159 0 R] -/Limits [(section*.22) (section*.27)] +/Names [(section*.105) 521 0 R (section*.106) 525 0 R (section*.107) 529 0 R (section*.108) 533 0 R (section*.109) 537 0 R (section*.11) 83 0 R] +/Limits [(section*.105) (section*.11)] >> -% 1925 0 obj +% 1980 0 obj << -/Names [(section*.28) 163 0 R (section*.29) 179 0 R (section*.3) 51 0 R (section*.30) 183 0 R (section*.31) 187 0 R (section*.32) 191 0 R] -/Limits [(section*.28) (section*.32)] +/Names [(section*.110) 541 0 R (section*.111) 549 0 R (section*.112) 1832 0 R (section*.12) 99 0 R (section*.13) 103 0 R (section*.14) 107 0 R] +/Limits [(section*.110) (section*.14)] >> -% 1926 0 obj +% 1981 0 obj << -/Names [(section*.33) 195 0 R (section*.34) 212 0 R (section*.35) 216 0 R (section*.36) 220 0 R (section*.37) 224 0 R (section*.38) 228 0 R] -/Limits [(section*.33) (section*.38)] +/Names [(section*.15) 111 0 R (section*.16) 115 0 R (section*.17) 119 0 R (section*.18) 123 0 R (section*.19) 127 0 R (section*.2) 47 0 R] +/Limits [(section*.15) (section*.2)] >> -% 1927 0 obj +% 1982 0 obj << -/Names [(section*.39) 232 0 R (section*.4) 55 0 R (section*.40) 236 0 R (section*.41) 240 0 R (section*.42) 244 0 R (section*.43) 248 0 R] -/Limits [(section*.39) (section*.43)] +/Names [(section*.20) 131 0 R (section*.21) 135 0 R (section*.22) 139 0 R (section*.23) 143 0 R (section*.24) 147 0 R (section*.25) 151 0 R] +/Limits [(section*.20) (section*.25)] >> -% 1928 0 obj +% 1983 0 obj << -/Names [(section*.44) 252 0 R (section*.45) 256 0 R (section*.46) 260 0 R (section*.47) 268 0 R (section*.48) 272 0 R (section*.49) 276 0 R] -/Limits [(section*.44) (section*.49)] +/Names [(section*.26) 155 0 R (section*.27) 159 0 R (section*.28) 163 0 R (section*.29) 179 0 R (section*.3) 51 0 R (section*.30) 183 0 R] +/Limits [(section*.26) (section*.30)] >> -% 1929 0 obj +% 1984 0 obj << -/Names [(section*.5) 59 0 R (section*.50) 280 0 R (section*.51) 288 0 R (section*.52) 292 0 R (section*.53) 296 0 R (section*.54) 300 0 R] -/Limits [(section*.5) (section*.54)] +/Names [(section*.31) 187 0 R (section*.32) 191 0 R (section*.33) 195 0 R (section*.34) 212 0 R (section*.35) 216 0 R (section*.36) 220 0 R] +/Limits [(section*.31) (section*.36)] >> -% 1930 0 obj +% 1985 0 obj << -/Names [(section*.55) 304 0 R (section*.56) 308 0 R (section*.57) 312 0 R (section*.58) 316 0 R (section*.59) 320 0 R (section*.6) 63 0 R] -/Limits [(section*.55) (section*.6)] +/Names [(section*.37) 224 0 R (section*.38) 228 0 R (section*.39) 232 0 R (section*.4) 55 0 R (section*.40) 236 0 R (section*.41) 240 0 R] +/Limits [(section*.37) (section*.41)] >> -% 1931 0 obj +% 1986 0 obj << -/Names [(section*.60) 324 0 R (section*.61) 328 0 R (section*.62) 332 0 R (section*.63) 336 0 R (section*.64) 340 0 R (section*.65) 344 0 R] -/Limits [(section*.60) (section*.65)] +/Names [(section*.42) 244 0 R (section*.43) 248 0 R (section*.44) 252 0 R (section*.45) 256 0 R (section*.46) 260 0 R (section*.47) 268 0 R] +/Limits [(section*.42) (section*.47)] >> -% 1932 0 obj +% 1987 0 obj << -/Names [(section*.66) 348 0 R (section*.67) 352 0 R (section*.68) 356 0 R (section*.69) 360 0 R (section*.7) 67 0 R (section*.70) 364 0 R] -/Limits [(section*.66) (section*.70)] +/Names [(section*.48) 272 0 R (section*.49) 276 0 R (section*.5) 59 0 R (section*.50) 280 0 R (section*.51) 288 0 R (section*.52) 292 0 R] +/Limits [(section*.48) (section*.52)] >> -% 1933 0 obj +% 1988 0 obj << -/Names [(section*.71) 368 0 R (section*.72) 372 0 R (section*.73) 376 0 R (section*.74) 380 0 R (section*.75) 384 0 R (section*.76) 388 0 R] -/Limits [(section*.71) (section*.76)] +/Names [(section*.53) 296 0 R (section*.54) 300 0 R (section*.55) 304 0 R (section*.56) 308 0 R (section*.57) 312 0 R (section*.58) 316 0 R] +/Limits [(section*.53) (section*.58)] >> -% 1934 0 obj +% 1989 0 obj << -/Names [(section*.77) 392 0 R (section*.78) 400 0 R (section*.79) 405 0 R (section*.8) 71 0 R (section*.80) 409 0 R (section*.81) 413 0 R] -/Limits [(section*.77) (section*.81)] +/Names [(section*.59) 320 0 R (section*.6) 63 0 R (section*.60) 324 0 R (section*.61) 328 0 R (section*.62) 332 0 R (section*.63) 336 0 R] +/Limits [(section*.59) (section*.63)] >> -% 1935 0 obj +% 1990 0 obj << -/Names [(section*.82) 417 0 R (section*.83) 421 0 R (section*.84) 425 0 R (section*.85) 429 0 R (section*.86) 433 0 R (section*.87) 437 0 R] -/Limits [(section*.82) (section*.87)] +/Names [(section*.64) 340 0 R (section*.65) 344 0 R (section*.66) 348 0 R (section*.67) 352 0 R (section*.68) 356 0 R (section*.69) 360 0 R] +/Limits [(section*.64) (section*.69)] >> -% 1936 0 obj +% 1991 0 obj << -/Names [(section*.88) 441 0 R (section*.89) 445 0 R (section*.9) 75 0 R (section*.90) 449 0 R (section*.91) 453 0 R (section*.92) 457 0 R] -/Limits [(section*.88) (section*.92)] +/Names [(section*.7) 67 0 R (section*.70) 364 0 R (section*.71) 368 0 R (section*.72) 372 0 R (section*.73) 376 0 R (section*.74) 380 0 R] +/Limits [(section*.7) (section*.74)] >> -% 1937 0 obj +% 1992 0 obj << -/Names [(section*.93) 461 0 R (section*.94) 469 0 R (section*.95) 473 0 R (section*.96) 477 0 R (section*.97) 481 0 R (section*.98) 489 0 R] -/Limits [(section*.93) (section*.98)] +/Names [(section*.75) 384 0 R (section*.76) 388 0 R (section*.77) 392 0 R (section*.78) 400 0 R (section*.79) 405 0 R (section*.8) 71 0 R] +/Limits [(section*.75) (section*.8)] >> -% 1938 0 obj +% 1993 0 obj << -/Names [(section*.99) 493 0 R (section.1) 7 0 R (section.10) 513 0 R (section.11) 541 0 R (section.2) 11 0 R (section.3) 35 0 R] -/Limits [(section*.99) (section.3)] +/Names [(section*.80) 409 0 R (section*.81) 413 0 R (section*.82) 417 0 R (section*.83) 421 0 R (section*.84) 425 0 R (section*.85) 429 0 R] +/Limits [(section*.80) (section*.85)] >> -% 1939 0 obj +% 1994 0 obj << -/Names [(section.4) 208 0 R (section.5) 264 0 R (section.6) 284 0 R (section.7) 396 0 R (section.8) 465 0 R (section.9) 485 0 R] -/Limits [(section.4) (section.9)] +/Names [(section*.86) 433 0 R (section*.87) 437 0 R (section*.88) 441 0 R (section*.89) 445 0 R (section*.9) 75 0 R (section*.90) 449 0 R] +/Limits [(section*.86) (section*.90)] >> -% 1940 0 obj +% 1995 0 obj << -/Names [(spbasedata) 896 0 R (spdata) 895 0 R (subsection.2.1) 15 0 R (subsection.2.2) 19 0 R (subsection.2.3) 23 0 R (subsection.2.4) 31 0 R] -/Limits [(spbasedata) (subsection.2.4)] +/Names [(section*.91) 453 0 R (section*.92) 457 0 R (section*.93) 461 0 R (section*.94) 465 0 R (section*.95) 473 0 R (section*.96) 477 0 R] +/Limits [(section*.91) (section*.96)] >> -% 1941 0 obj +% 1996 0 obj << -/Names [(subsection.3.1) 39 0 R (subsection.3.2) 91 0 R (subsection.3.3) 171 0 R (subsection.3.4) 199 0 R (subsection.3.5) 204 0 R (subsubsection.2.3.1) 27 0 R] -/Limits [(subsection.3.1) (subsubsection.2.3.1)] +/Names [(section*.97) 481 0 R (section*.98) 485 0 R (section*.99) 493 0 R (section.1) 7 0 R (section.10) 517 0 R (section.11) 545 0 R] +/Limits [(section*.97) (section.11)] >> -% 1942 0 obj +% 1997 0 obj << -/Names [(subsubsection.3.1.1) 43 0 R (subsubsection.3.1.2) 87 0 R (subsubsection.3.2.1) 95 0 R (subsubsection.3.2.2) 167 0 R (subsubsection.3.3.1) 175 0 R (table.1) 949 0 R] -/Limits [(subsubsection.3.1.1) (table.1)] +/Names [(section.2) 11 0 R (section.3) 35 0 R (section.4) 208 0 R (section.5) 264 0 R (section.6) 284 0 R (section.7) 396 0 R] +/Limits [(section.2) (section.7)] >> -% 1943 0 obj +% 1998 0 obj << -/Names [(table.10) 1075 0 R (table.11) 1083 0 R (table.12) 1097 0 R (table.13) 1115 0 R (table.14) 1147 0 R (table.15) 1178 0 R] -/Limits [(table.10) (table.15)] +/Names [(section.8) 469 0 R (section.9) 489 0 R (spbasedata) 901 0 R (spdata) 900 0 R (subsection.2.1) 15 0 R (subsection.2.2) 19 0 R] +/Limits [(section.8) (subsection.2.2)] >> -% 1944 0 obj +% 1999 0 obj << -/Names [(table.16) 1218 0 R (table.17) 1232 0 R (table.2) 994 0 R (table.3) 1010 0 R (table.4) 1023 0 R (table.5) 1031 0 R] -/Limits [(table.16) (table.5)] +/Names [(subsection.2.3) 23 0 R (subsection.2.4) 31 0 R (subsection.3.1) 39 0 R (subsection.3.2) 91 0 R (subsection.3.3) 171 0 R (subsection.3.4) 199 0 R] +/Limits [(subsection.2.3) (subsection.3.4)] >> -% 1945 0 obj + +endstream +endobj +2028 0 obj << -/Names [(table.6) 1039 0 R (table.7) 1048 0 R (table.8) 1060 0 R (table.9) 1068 0 R (title.0) 3 0 R (vbasedata) 887 0 R] -/Limits [(table.6) (vbasedata)] + /Title (Parallel Sparse BLAS V. 3.5.0) /Subject (Parallel Sparse Basic Linear Algebra Subroutines) /Keywords (Computer Science Linear Algebra Fluid Dynamics Parallel Linux MPI PSBLAS Iterative Solvers Preconditioners) /Creator (pdfLaTeX) /Producer ($Id$) /Author()/Title()/Subject()/Creator(LaTeX with hyperref package)/Producer(pdfTeX-1.40.17)/Keywords() +/CreationDate (D:20180420155528+01'00') +/ModDate (D:20180420155528+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) >> -% 1946 0 obj +endobj +2001 0 obj << -/Names [(vdata) 936 0 R] -/Limits [(vdata) (vdata)] +/Type /ObjStm +/N 27 +/First 262 +/Length 3661 >> -% 1947 0 obj +stream +2000 0 2002 248 2003 447 2004 623 2005 795 2006 903 2007 1017 2008 1129 2009 1240 2010 1361 +2011 1482 2012 1606 2013 1725 2014 1838 2015 1950 2016 2060 2017 2174 2018 2293 2019 2412 2020 2531 +2021 2647 2022 2730 2023 2850 2024 2972 2025 3067 2026 3151 2027 3186 +% 2000 0 obj << -/Kids [1858 0 R 1859 0 R 1860 0 R 1861 0 R 1862 0 R 1863 0 R] -/Limits [(Doc-Start) (Item.18)] +/Names [(subsection.3.5) 204 0 R (subsubsection.2.3.1) 27 0 R (subsubsection.3.1.1) 43 0 R (subsubsection.3.1.2) 87 0 R (subsubsection.3.2.1) 95 0 R (subsubsection.3.2.2) 167 0 R] +/Limits [(subsection.3.5) (subsubsection.3.2.2)] >> -% 1948 0 obj +% 2002 0 obj << -/Kids [1864 0 R 1865 0 R 1866 0 R 1867 0 R 1868 0 R 1869 0 R] -/Limits [(Item.19) (Item.50)] +/Names [(subsubsection.3.3.1) 175 0 R (table.1) 954 0 R (table.10) 1117 0 R (table.11) 1126 0 R (table.12) 1139 0 R (table.13) 1157 0 R] +/Limits [(subsubsection.3.3.1) (table.13)] >> -% 1949 0 obj +% 2003 0 obj << -/Kids [1870 0 R 1871 0 R 1872 0 R 1873 0 R 1874 0 R 1875 0 R] -/Limits [(Item.51) (Item.83)] +/Names [(table.14) 1188 0 R (table.15) 1220 0 R (table.16) 1260 0 R (table.17) 1275 0 R (table.2) 998 0 R (table.3) 1022 0 R] +/Limits [(table.14) (table.3)] >> -% 1950 0 obj +% 2004 0 obj << -/Kids [1876 0 R 1877 0 R 1878 0 R 1879 0 R 1880 0 R 1881 0 R] -/Limits [(Item.84) (cite.sblas97)] +/Names [(table.4) 1034 0 R (table.5) 1052 0 R (table.6) 1061 0 R (table.7) 1079 0 R (table.8) 1091 0 R (table.9) 1110 0 R] +/Limits [(table.4) (table.9)] >> -% 1951 0 obj +% 2005 0 obj << -/Kids [1882 0 R 1883 0 R 1884 0 R 1885 0 R 1886 0 R 1887 0 R] -/Limits [(descdata) (lstnumber.-13.1)] +/Names [(title.0) 3 0 R (vbasedata) 892 0 R (vdata) 941 0 R] +/Limits [(title.0) (vdata)] >> -% 1952 0 obj +% 2006 0 obj << -/Kids [1888 0 R 1889 0 R 1890 0 R 1891 0 R 1892 0 R 1893 0 R] -/Limits [(lstnumber.-14.1) (lstnumber.-8.1)] +/Kids [1912 0 R 1913 0 R 1914 0 R 1915 0 R 1916 0 R 1917 0 R] +/Limits [(Doc-Start) (Item.125)] >> -% 1953 0 obj +% 2007 0 obj << -/Kids [1894 0 R 1896 0 R 1897 0 R 1898 0 R 1899 0 R 1900 0 R] -/Limits [(lstnumber.-9.1) (page.13)] +/Kids [1918 0 R 1919 0 R 1920 0 R 1921 0 R 1922 0 R 1923 0 R] +/Limits [(Item.126) (Item.44)] >> -% 1954 0 obj +% 2008 0 obj << -/Kids [1901 0 R 1902 0 R 1903 0 R 1904 0 R 1905 0 R 1906 0 R] -/Limits [(page.130) (page.34)] +/Kids [1924 0 R 1925 0 R 1926 0 R 1927 0 R 1928 0 R 1929 0 R] +/Limits [(Item.45) (Item.77)] >> -% 1955 0 obj +% 2009 0 obj << -/Kids [1907 0 R 1908 0 R 1909 0 R 1910 0 R 1911 0 R 1912 0 R] -/Limits [(page.35) (page.67)] +/Kids [1930 0 R 1931 0 R 1932 0 R 1933 0 R 1934 0 R 1935 0 R] +/Limits [(Item.78) (cite.PARA04FOREST)] >> -% 1956 0 obj +% 2010 0 obj << -/Kids [1913 0 R 1914 0 R 1915 0 R 1916 0 R 1917 0 R 1918 0 R] -/Limits [(page.68) (page.i)] +/Kids [1936 0 R 1937 0 R 1938 0 R 1939 0 R 1940 0 R 1941 0 R] +/Limits [(cite.PSBLAS) (lstlisting.-4)] >> -% 1957 0 obj +% 2011 0 obj << -/Kids [1919 0 R 1920 0 R 1921 0 R 1922 0 R 1923 0 R 1924 0 R] -/Limits [(page.ii) (section*.27)] +/Kids [1942 0 R 1943 0 R 1944 0 R 1945 0 R 1946 0 R 1947 0 R] +/Limits [(lstlisting.-5) (lstnumber.-6.1)] >> -% 1958 0 obj +% 2012 0 obj << -/Kids [1925 0 R 1926 0 R 1927 0 R 1928 0 R 1929 0 R 1930 0 R] -/Limits [(section*.28) (section*.6)] +/Kids [1948 0 R 1949 0 R 1950 0 R 1951 0 R 1952 0 R 1953 0 R] +/Limits [(lstnumber.-6.2) (page.105)] >> -% 1959 0 obj +% 2013 0 obj << -/Kids [1931 0 R 1932 0 R 1933 0 R 1934 0 R 1935 0 R 1936 0 R] -/Limits [(section*.60) (section*.92)] +/Kids [1954 0 R 1955 0 R 1956 0 R 1957 0 R 1958 0 R 1959 0 R] +/Limits [(page.106) (page.138)] >> -% 1960 0 obj +% 2014 0 obj << -/Kids [1937 0 R 1938 0 R 1939 0 R 1940 0 R 1941 0 R 1942 0 R] -/Limits [(section*.93) (table.1)] +/Kids [1960 0 R 1961 0 R 1962 0 R 1963 0 R 1964 0 R 1965 0 R] +/Limits [(page.139) (page.39)] >> -% 1961 0 obj +% 2015 0 obj << -/Kids [1943 0 R 1944 0 R 1945 0 R 1946 0 R] -/Limits [(table.10) (vdata)] +/Kids [1966 0 R 1967 0 R 1968 0 R 1969 0 R 1970 0 R 1971 0 R] +/Limits [(page.4) (page.71)] >> -% 1962 0 obj +% 2016 0 obj << -/Kids [1947 0 R 1948 0 R 1949 0 R 1950 0 R 1951 0 R 1952 0 R] -/Limits [(Doc-Start) (lstnumber.-8.1)] +/Kids [1972 0 R 1973 0 R 1974 0 R 1975 0 R 1976 0 R 1977 0 R] +/Limits [(page.72) (section*.1)] >> -% 1963 0 obj +% 2017 0 obj << -/Kids [1953 0 R 1954 0 R 1955 0 R 1956 0 R 1957 0 R 1958 0 R] -/Limits [(lstnumber.-9.1) (section*.6)] +/Kids [1978 0 R 1979 0 R 1980 0 R 1981 0 R 1982 0 R 1983 0 R] +/Limits [(section*.10) (section*.30)] >> -% 1964 0 obj +% 2018 0 obj << -/Kids [1959 0 R 1960 0 R 1961 0 R] -/Limits [(section*.60) (vdata)] +/Kids [1984 0 R 1985 0 R 1986 0 R 1987 0 R 1988 0 R 1989 0 R] +/Limits [(section*.31) (section*.63)] >> -% 1965 0 obj +% 2019 0 obj +<< +/Kids [1990 0 R 1991 0 R 1992 0 R 1993 0 R 1994 0 R 1995 0 R] +/Limits [(section*.64) (section*.96)] +>> +% 2020 0 obj +<< +/Kids [1996 0 R 1997 0 R 1998 0 R 1999 0 R 2000 0 R 2002 0 R] +/Limits [(section*.97) (table.13)] +>> +% 2021 0 obj +<< +/Kids [2003 0 R 2004 0 R 2005 0 R] +/Limits [(table.14) (vdata)] +>> +% 2022 0 obj +<< +/Kids [2006 0 R 2007 0 R 2008 0 R 2009 0 R 2010 0 R 2011 0 R] +/Limits [(Doc-Start) (lstnumber.-6.1)] +>> +% 2023 0 obj +<< +/Kids [2012 0 R 2013 0 R 2014 0 R 2015 0 R 2016 0 R 2017 0 R] +/Limits [(lstnumber.-6.2) (section*.30)] +>> +% 2024 0 obj +<< +/Kids [2018 0 R 2019 0 R 2020 0 R 2021 0 R] +/Limits [(section*.31) (vdata)] +>> +% 2025 0 obj << -/Kids [1962 0 R 1963 0 R 1964 0 R] +/Kids [2022 0 R 2023 0 R 2024 0 R] /Limits [(Doc-Start) (vdata)] >> -% 1966 0 obj +% 2026 0 obj << -/Dests 1965 0 R +/Dests 2025 0 R >> -% 1967 0 obj +% 2027 0 obj << /Type /Catalog -/Pages 1855 0 R -/Outlines 1856 0 R -/Names 1966 0 R +/Pages 1908 0 R +/Outlines 1909 0 R +/Names 2026 0 R /URI (http://ce.uniroma2.it/psblas) /PageMode/UseOutlines/PageLabels<>2<>6<>]>> -/OpenAction 548 0 R +/OpenAction 552 0 R >> endstream endobj -1969 0 obj +2029 0 obj << /Type /XRef -/Index [0 1970] -/Size 1970 +/Index [0 2030] +/Size 2030 /W [1 3 1] -/Root 1967 0 R -/Info 1968 0 R -/ID [ ] -/Length 9850 +/Root 2027 0 R +/Info 2028 0 R +/ID [<6EBF9D8966F3D97AEE3732EC7B41E698> <6EBF9D8966F3D97AEE3732EC7B41E698>] +/Length 10150 >> stream -LA?(A>2A=:A<FA;  -OA:  ; A9 ;A8;A7;A6;3A5;4A4;:A3;;A2;<A1;@A0 ;AA/!";BA.#$;FA-%&;HA,'(;IA+)*;PA*+,;QA)-.;XA(/0;YA'12;ZA&34;^A%56;`A$78;aA#9:A";<A!=>A ?@AABACD AEF AGHAIJAKLAMNAOPAQRASTAUV%AWX&AYZ'A[\(A]^.A_`4Aab5Ac8A ?A IA ZA -A   -A  A A'A2A:AAAHAQA\:c\:b \:a!"\7:`#$\X:_%&:^'( :])*:\+,%:[-.2:Z/09:Y12>:X34D:W56O:V78X:U9:>:T;<>:S=>>:R?@>#:QAB>):PCD>5:OEF>;:NGH>?:MIJ>D:LKL>N:KMN>S:JOP>Y:IQR>_:HST:GUV:FWX:EYZ:D[\":C]^&:B_`6:Aab::@cj@:?F:>M:=Q:<U:;  -Y::  ]:9 a:8:7:6 :5:4:3:2$:1+:0 M:/!"S:.#$Y:-%&_:,'(|:+)*|:*+,| :)-.|:(/0|:'12|!:&34|':%56|-:$78|3:#9:|<:";<|G:!=>|L: ?@|P:AB|V:CD|Z:EF|`:GHIM$JKN\MT`PN'ORSTUVWXYZ[\]^_`abcgggggggggg g -g g g ggggggggggggggg gQ( -ggg!g"g#g$g%g&g'g(g)g*g+g,g-g.g/g0g1g2g3g4g5g6g7g8g9g:g;g<g=g>g?g@gAgBgCgDgEgFgGgHgIgJgKgLgMgNgRgPggOgSgTgUgVgWgXgYgZg[g\g]g^g_g`gagbgc  -   gQض9\ !"#$%&')]M[a#$"!/0164*~P3+,-.78=5/9]VRYU;W< BCG>DE?@AIJLHKZXM[NQPQRSTUVW;;Yj[\]^_`abc;;;;;;^bo; ;;k; -; ; ;;;;;;; ;;;;;;+;,;);=;; ;!;";#;$;%;&;';(;5;*$;-;.;/;0;1;2;7;8;=;6ڍ;9;C;>;?c;J;D;E;G;L;M;N;U;K;O;R;S;T;[;V=;W;b;\M;];_;c\! : - !ٯ $)"#+,/*-:J1290#36_7<:)d;@=,>BCDEFGMKA-pHNOQLJmPSTUVWX\RUY[:_]t#^abc`v ]    - ! :#$%)"l&(,*0`+./04-3 13678<5M9;>?C=e@BEFJD{GZI:LMNOXVKPRSTUYZ[\]^_aWE`c\\b\\p\\\\ \ -\ \ \4\ \\\\3\\\\Fb\:\\\\*\"\I\\\\ \!rK\+\.\#e\,\-\$\%\&\'\(\)\1\/\0X\3\4\5\<\2\6\8\9\:\;\>6!\?\@\E\=\\A\B\C\D\Q\H\F&\G:\R\I4\P\J\K\L\M\N\ODx.\T\U\V\]\S\W\Y\Z\[\\\`\^ʯ\_\b\aП\c K -   1) :Je! #&"X$(-')*+,/04.113:67:58<?;=ABE@CJF VGHILMSK NPQRUV[YT !W: >Z 3\]^_`abc>> -o>>>> u>>>  >> -> > > >>>>>>> J>>>>> >>> >!>$> Z>": ->&>'>*>% Ȋ>(>/>+ >,>->.>1>2>3>6>0 >4>8>9><>7 >:>@>= - ->>>B>E>A ->C: >J>F -1>G>H>I>L>O>K -4>M>Q>U>P -K'>R>T>W>[>V -X3>X>Z>]>a>\ -k>^>`>c>b -x:   - -L    -e  - - # -u!'$ -%: 3( !)*+,-./01274 =5=8 > 9;<C> T?ABJD frEGHINK wL:RO `PVS nTZW HX^[ G\b_ `c : $ -    5   &t! ;1 &" Pg#%:(),' e*HIJ- ~./0O123456789:;<=>?@ABCDEFGPK ALNOVQ RTU\W XZ[b] Y^`a:|c | Ԉ|| | |||| || - | ||||| -|||||  |||||$| '| |"|#:|*|% 8F|&|(|)|.|+ E|,|0|1|5|/ J|2|4|7|8|9|:|=|6 \y|;|@|> z|?|B|C|D|E|H|A |F:|J|M|I |K|Q|N L|O|S|T|W|R f|U|[|X M|Y|]|^|\ |_|a|b|cS8 : -    +O&F%'()*+,-./0123456789Sc:;< A=ah>f?@>A*BJClDhE.FG3zH=IJKOL:::::::A@AAABACADAEAFAGAHAIAJAKALAMANAOAPAQARASATAUAVAWAXAYAZA[A\A]A^A_A`AaAbAcgggggggggg g -g g g ggggggggggggggggggg g!g"g#g$g%g&g'g(g)g*g+g,g-g.g/g0g1g2g3g4g5g6g7g8g9g:g;g<g=g>g?g@gAgBgCgDgEgFgGgHr +Nw +w +5w =wIw  +Rw  @w @w@w@w@6w@7w@=vc@>vb@?va@Cv` @Dv_!"@Ev^#$@Iv]%&@Kv\'(@Lv[)*@SvZ+,@TvY-.@[vX/0@\vW12@]vV34@avU56@cvT78vS9:vR;<vQ=>vP?@ +vOAB vNCDvMEFvLGHvKIJvJKLvIMNvHOPvGQR!vFST"vEUV(vDWX)vCYZ*vB[\+vA]^1v@_`7v?ab8v>c;v=Bv<Lv;\v: v9  +v8  )v7 1v6Bv5Mv4^v3^v2^v1^v0^%v/^:v. ^Av-!"^[v,#$v+%&$v*'(1v))*2v(+,Iv'-.Vv&/0]v%12bv$34Cv#56Cv"78Cv!9:C+v ;<C:v=>C@v?@CGvABCMvCDCYvEFC_vGHCcvIJvKLvMNvOPvQRvST%vUV+vWX2vYZ9v[\Fv]^Jv_`Zv ab^v cjv v + v vv  +v  v !v%v+v1v7v=EcCEbJEaOE` VE_!"E^#$E]%& E\'(&E[)*,EZ+,1EY-.8EX/0?EW12EEV34LEU56RET78XES9:^ER;<EQ=>EP?@EOABENCDEMEF!ELGH'EKIJKO$LMEE&EEE*RP'QTUVWXYZ[\]^_`abckkkkkkkkkk k +k k k kkkkkkkkkkkkkkkkk"k S( +kksk#k$k%k&k'k(k)k*k+k,k-k.k/k0k1k2k3k4k5k6k7k8k9k:k;k<k=k>k?k@kAkBkCkDkEkFkGkHkIkJkKkLkMkNkOkPkTkRk!kQkUkVkWkXkYkZk[k\k]k^k_k`kakbkc  +   kS:]!"#$%&'()*, ^3E%E+NE;OMBCL?@23497-E6./01rA:;@8<E'E EE#E>E!?KEFJAGHBCD>=LMOKN][PAQESTUVWXYZ@ @ \P^_`abc@@@@@@@@@E(E,^@ @@ +m@ @@@@@@@@@@@@@ @!@.@/@,@8@"@#@$@%@&@'@(@)@*@+@8@-@0@1@2@3@4@5@:@;@@@9܈@<@F@A@BE-@M@G@H@J@O@P@Q@X@N@R@U@V@WJ@^@Y?@Z@_O@`@b: # E. zȍ$K #',%y&./2-$0E/M45<369E):?=+>C@.2AEFGHIJPND/ KQRTOL SVWXYZ^UV[]E0`_tabcm  + M ҞL#S !"%&'+$e(*E1-./3,X02<4756789:;>?@D=FACGEcFIJKOHfLNXPQRSTUVWE2Z[\`YU]_bc^a^^f<^^^ +^ ^E$^ ^ ^ ^^^^^ ^^^^^^^^^^^^^!^^ ^#^)^'^":6^$^&E3^*^+^,^-^.^/^1^(T^0^3^4^6^2s^5^8^;^7^9^=^>^?^N^F^<^@^B^C^D^E-^O^R^Gt^P^Q^H^I^J^K^L^M^U^S!^TE"E4^W^X^Y^`^V-^Z^\^]^^^_^b)^c^aO )G  +   6 <E5"*(!B#%&'+,.)aE-3/q058467:=9;<E>G?@ABCDE6GJFHLQK(MNOPSTXR UWZ[^Y \`c_ aCCCC UwC +ZE7C +C lCCC C C CC  sKCCCCCCCCC CC&C CCCCC C!C"C#C$C%C(C)C,C' C*C5C- JC.C/C0C1C2C3C4E8C7C8C;C6 OC9C=C>CBC< C?CACDCECHCC lCFCJCKCNCI + CLCSCO +&~CPCQCRCUCVCWCZCT ++CXE9C\C]C`C[ +?C^Ca +M"Cb  + + +    +s  +E: +! + #'" +$&).( +r*,-05/ 1347:6 8E;@; -<=>?BCDGA <EKH MIWL cMNOPQRSTUV[X bYa\ Z]_`E<b Vc 0 + J     8 A 0E= 9"  (# $&'.) -T*,-4/ A023:5 V,689E>@; j<>?GA BDEEFLH IKQM VNPSTWR {UX ۿYZ[E\]^_`abc  +   E? ] V +# 0!")$ 7n%'(-* ?+/4. B9023E@6;5 U.79:=B< i>@AHC xlDFGJOI KMNUP QSTYV WEA[\`Z ]_bca    +   %EB)"4 $%.,#7b&()*+E/013-X +2574s6G8n9:<DFECQHIPRSTUVWXYZ[\]^_`abcEuE"E@bEyEEҷEE1EXOE wE +mE ZE 5E `EEOEE5Ee*EEEEDEEEFEGEHEIEJ.fTgw w wwwwwwwwwwwwwwwwwww w!w"w#w$w%w&w'w(w)w*w+w,w-w.w/w0w1w2w3w4w5w6w7w8w9w:w;w<w=w>w?w@wAwBwCwDwEwFwGwHwIwJwKwLwMwNwOwPwQwRwSwTwUwVwWwXwYwZw[w\w]w^w_w`wawbwc  +    endstream endobj startxref -1252210 +1289919 %%EOF diff --git a/docs/src/penv.tex b/docs/src/penv.tex index 0962e580..91f010ef 100644 --- a/docs/src/penv.tex +++ b/docs/src/penv.tex @@ -595,6 +595,66 @@ Type, kind, rank and size must agree on all processes. \item The \verb|dat| argument may also be a long integer scalar. \end{enumerate} +\clearpage\subsection*{psb\_nrm2 --- Global 2-norm reduction} +\addcontentsline{toc}{subsection}{psb\_nrm2} + +\begin{verbatim} +call psb_nrm2(icontxt, dat, root) +\end{verbatim} + +This subroutine implements a 2-norm value reduction +operation based on the underlying communication library. +\begin{description} +\item[Type:] Synchronous. +\item[\bf On Entry ] +\item[icontxt] the communication context identifying the virtual + parallel machine.\\ +Scope: {\bf global}.\\ +Type: {\bf required}.\\ +Intent: {\bf in}.\\ +Specified as: an integer variable. +\item[dat] The local contribution to the global minimum.\\ +Scope: {\bf local}.\\ +Type: {\bf required}.\\ +Intent: {\bf inout}.\\ +Specified as: a real variable, which may be a +scalar, or a rank 1 array. \ +Kind, rank and size must agree on all processes. +\item[root] Process to hold the final value, or $-1$ to make it available + on all processes.\\ +Scope: {\bf global}.\\ +Type: {\bf optional}.\\ +Intent: {\bf in}.\\ +Specified as: an integer value $-1<= root <= np-1$, default -1. \\ +\end{description} + + +\begin{description} +\item[\bf On Return] +\item[dat] On destination process(es), the result of the 2-norm reduction.\\ +Scope: {\bf global}.\\ +Type: {\bf required}.\\ +Intent: {\bf inout}.\\ +Specified as: a real variable, which may be a +scalar, or a rank 1 array. \\ +Kind, rank and size must agree on all processes. +\end{description} + + +{\par\noindent\large\bfseries Notes} +\begin{enumerate} +\item This reduction is appropriate to compute the results of multiple + (local) NRM2 operations at the same time. +\item Denoting by $dat_i$ the value of the variable $dat$ on process + $i$, the output $res$ is equivalent to the computation of + \[ res = \sqrt{\sum_i dat_i^2},\] + with care taken to avoid unnecessary overflow. +\item The \verb|dat| argument is both input and output, and its + value may be changed even on processes different from the final + result destination. +\end{enumerate} + + \clearpage\subsection*{psb\_snd --- Send data} \addcontentsline{toc}{subsection}{psb\_snd} diff --git a/docs/src/psbrout.tex b/docs/src/psbrout.tex index 3efca302..d4767c8a 100644 --- a/docs/src/psbrout.tex +++ b/docs/src/psbrout.tex @@ -105,7 +105,6 @@ Intent: {\bf out}.\\ An integer value; 0 means no error has been detected. \end{description} - %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % % F90DOT PRODUCT @@ -129,7 +128,7 @@ Else if $x$ and $y$ are complex vectors then it computes dot-product as: %% \end{description} \begin{verbatim} -psb_gedot(x, y, desc_a, info) +psb_gedot(x, y, desc_a, info [,global]) \end{verbatim} %% \syntax*{psb\_gedot}{x, y, desc\_a, info, jx, jy} \begin{table}[h] @@ -176,6 +175,13 @@ Scope: {\bf local} \\ Type: {\bf required}\\ Intent: {\bf in}.\\ Specified as: an object of type \descdata. +\item[global] Specifies whether the computation should include the + global reduction across all processes.\\ +Scope: {\bf global} \\ +Type: {\bf optional}.\\ +Intent: {\bf in}.\\ +Specified as: a logical scalar. +Default: \verb|global=.true.|\\ %% \item[jx] the column index of global dense matrix $x$, %% identifying the column of subvector $x$.\\ %% Scope: {\bf global} \\ @@ -190,7 +196,8 @@ Specified as: an object of type \descdata. %% Specified as: an integer variable $jy\ge 1$. \item[\bf On Return] \item[Function value] is the dot product of subvectors $x$ and $y$.\\ -Scope: {\bf global} \\ +Scope: {\bf global} unless the optional variable +\verb|global=.false.| as been specified\\ Specified as: a number of the data type indicated in Table~\ref{tab:f90dot}. \item[info] Error code.\\ Scope: {\bf local} \\ @@ -198,7 +205,25 @@ Type: {\bf required} \\ Intent: {\bf out}.\\ An integer value; 0 means no error has been detected. \end{description} -%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +{\par\noindent\large\bfseries Notes} +\begin{enumerate} +\item The computation of a global result requires a global + communication, which entails a significant overhead. It may be + necessary and/or advisable to compute multiple dot products at the same + time; in this case, it is possible to improve the runtime efficiency + by using the following scheme: + \begin{lstlisting} + vres(1) = psb_gedot(x1,y1,desc_a,info,global=.false.) + vres(2) = psb_gedot(x2,y2,desc_a,info,global=.false.) + vres(3) = psb_gedot(x3,y3,desc_a,info,global=.false.) + call psb_sum(ictxt,vres(1:3)) + \end{lstlisting} + In this way the global communication, which for small sizes is a + latency-bound operation, is invoked only once. +\end{enumerate} + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % % F90DOT PRODUCT % @@ -294,8 +319,8 @@ else if $x$ is a complex vector then it computes the infinity-norm as: %% \end{description} \begin{verbatim} -psb_geamax(x, desc_a, info) -psb_normi(x, desc_a, info) +psb_geamax(x, desc_a, info [,global]) +psb_normi(x, desc_a, info [,global]) \end{verbatim} %% \syntax*{psb\_geamax}{x, desc\_a, info, jx} @@ -334,7 +359,13 @@ Scope: {\bf local} \\ Type: {\bf required}\\ Intent: {\bf in}.\\ Specified as: an object of type \descdata. -%% \item[jx] the column index of global dense matrix $x$, +\item[global] Specifies whether the computation should include the + global reduction across all processes.\\ +Scope: {\bf global} \\ +Type: {\bf optional}.\\ +Intent: {\bf in}.\\ +Specified as: a logical scalar. +Default: \verb|global=.true.|\\%% \item[jx] the column index of global dense matrix $x$, %% identifying the column of subvector $x$.\\ %% Scope: {\bf global} \\ %% Type: {\bf optional}; can only be present if $x$ is of rank 2.\\ @@ -343,7 +374,8 @@ Specified as: an object of type \descdata. \item[\bf On Return] \item[Function value] is the infinity norm of subvector $x$.\\ -Scope: {\bf global} \\ +Scope: {\bf global} unless the optional variable +\verb|global=.false.| as been specified\\ Specified as: a long precision real number. \item[info] Error code.\\ Scope: {\bf local} \\ @@ -351,7 +383,25 @@ Type: {\bf required} \\ Intent: {\bf out}.\\ An integer value; 0 means no error has been detected. \end{description} -%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +{\par\noindent\large\bfseries Notes} +\begin{enumerate} +\item The computation of a global result requires a global + communication, which entails a significant overhead. It may be + necessary and/or advisable to compute multiple norms at the same + time; in this case, it is possible to improve the runtime efficiency + by using the following scheme: + \begin{lstlisting} + vres(1) = psb_geamax(x1,desc_a,info,global=.false.) + vres(2) = psb_geamax(x2,desc_a,info,global=.false.) + vres(3) = psb_geamax(x3,desc_a,info,global=.false.) + call psb_amx(ictxt,vres(1:3)) + \end{lstlisting} + In this way the global communication, which for small sizes is a + latency-bound operation, is invoked only once. +\end{enumerate} + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % % Infinity norm % @@ -431,8 +481,8 @@ else if $x$ is a complex vector then it computes 1-norm as: \begin{verbatim} -psb_geasum(x, desc_a, info) -psb_norm1(x, desc_a, info) +psb_geasum(x, desc_a, info [,global]) +psb_norm1(x, desc_a, info [,global]) \end{verbatim} \begin{table}[h] @@ -469,10 +519,18 @@ Scope: {\bf local} \\ Type: {\bf required}\\ Intent: {\bf in}.\\ Specified as: an object of type \descdata. +\item[global] Specifies whether the computation should include the + global reduction across all processes.\\ +Scope: {\bf global} \\ +Type: {\bf optional}.\\ +Intent: {\bf in}.\\ +Specified as: a logical scalar. +Default: \verb|global=.true.|\\ \item[\bf On Return] \item[Function value] is the 1-norm of vector $x$.\\ -Scope: {\bf global} \\ +Scope: {\bf global} unless the optional variable +\verb|global=.false.| as been specified\\ Specified as: a long precision real number. \item[info] Error code.\\ Scope: {\bf local} \\ @@ -481,6 +539,23 @@ Intent: {\bf out}.\\ An integer value; 0 means no error has been detected. \end{description} +{\par\noindent\large\bfseries Notes} +\begin{enumerate} +\item The computation of a global result requires a global + communication, which entails a significant overhead. It may be + necessary and/or advisable to compute multiple norms at the same + time; in this case, it is possible to improve the runtime efficiency + by using the following scheme: + \begin{lstlisting} + vres(1) = psb_geasum(x1,desc_a,info,global=.false.) + vres(2) = psb_geasum(x2,desc_a,info,global=.false.) + vres(3) = psb_geasum(x3,desc_a,info,global=.false.) + call psb_sum(ictxt,vres(1:3)) + \end{lstlisting} + In this way the global communication, which for small sizes is a + latency-bound operation, is invoked only once. +\end{enumerate} + \clearpage\subsection*{psb\_geasums --- Generalized 1-Norm of Vector} \addcontentsline{toc}{subsection}{psb\_geasums} @@ -587,8 +662,8 @@ Long Precision Real&Long Precision Complex & psb\_genrm2 \\ \end{table} \begin{verbatim} -psb_genrm2(x, desc_a, info) -psb_norm2(x, desc_a, info) +psb_genrm2(x, desc_a, info [,global]) +psb_norm2(x, desc_a, info [,global]) \end{verbatim} %% \syntax*{psb\_genrm2}{x, desc\_a, info, jx} @@ -610,7 +685,13 @@ Scope: {\bf local} \\ Type: {\bf required}\\ Intent: {\bf in}.\\ Specified as: an object of type \descdata. -%% \item[jx] the column index of global dense matrix $x$, +\item[global] Specifies whether the computation should include the + global reduction across all processes.\\ +Scope: {\bf global} \\ +Type: {\bf optional}.\\ +Intent: {\bf in}.\\ +Specified as: a logical scalar. +Default: \verb|global=.true.|\\%% \item[jx] the column index of global dense matrix $x$, %% identifying the column of subvector $x$.\\ %% Scope: {\bf global} \\ %% Type: {\bf optional}; can only be present if $x$ is of rank 2.\\ @@ -619,7 +700,8 @@ Specified as: an object of type \descdata. \item[\bf On Return] \item[Function Value] is the 2-norm of subvector $x$.\\ -Scope: {\bf global} \\ +Scope: {\bf global} unless the optional variable +\verb|global=.false.| as been specified\\ Type: {\bf required} \\ Specified as: a long precision real number. \item[info] Error code.\\ @@ -629,6 +711,23 @@ Intent: {\bf out}.\\ An integer value; 0 means no error has been detected. \end{description} +{\par\noindent\large\bfseries Notes} +\begin{enumerate} +\item The computation of a global result requires a global + communication, which entails a significant overhead. It may be + necessary and/or advisable to compute multiple norms at the same + time; in this case, it is possible to improve the runtime efficiency + by using the following scheme: + \begin{lstlisting} + vres(1) = psb_genrm2(x1,desc_a,info,global=.false.) + vres(2) = psb_genrm2(x2,desc_a,info,global=.false.) + vres(3) = psb_genrm2(x3,desc_a,info,global=.false.) + call psb_nrm2(ictxt,vres(1:3)) + \end{lstlisting} + In this way the global communication, which for small sizes is a + latency-bound operation, is invoked only once. +\end{enumerate} + \clearpage\subsection*{psb\_genrm2s --- Generalized 2-Norm of Vector} From 22b97ccfc86f4f0394c098119299656249c4dc54 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Fri, 20 Apr 2018 16:15:47 +0100 Subject: [PATCH 4/7] Fixed spelling in docs. --- docs/html/node54.html | 4 +-- docs/html/node55.html | 2 +- docs/html/node56.html | 4 +-- docs/html/node58.html | 2 +- docs/html/node60.html | 4 +-- docs/psblas-3.5.pdf | 80 +++++++++++++++++++++---------------------- docs/src/psbrout.tex | 36 +++++++++---------- 7 files changed, 66 insertions(+), 66 deletions(-) diff --git a/docs/html/node54.html b/docs/html/node54.html index d08b64d4..ae5d6b92 100644 --- a/docs/html/node54.html +++ b/docs/html/node54.html @@ -235,7 +235,7 @@ Default: global=.true.
            Function value
            -
            is the dot product of subvectors is the dot product of vectors $x$ and global=.true. ALT="$y$">.
            Scope: global unless the optional variable -global=.false. as been specified +global=.false. has been specified
            Specified as: a number of the data type indicated in Table 2.
            diff --git a/docs/html/node55.html b/docs/html/node55.html index 55e32c88..95cc3e36 100644 --- a/docs/html/node55.html +++ b/docs/html/node55.html @@ -205,7 +205,7 @@ Specified as: an object of type descdatapsb_desc_type.
            res
            -
            is the dot product of subvectors is the dot product of vectors $x$ and global=.true.
            Function value
            -
            is the infinity norm of subvector is the infinity norm of vector $x$.
            Scope: global unless the optional variable -global=.false. as been specified +global=.false. has been specified
            Specified as: a long precision real number.
            diff --git a/docs/html/node58.html b/docs/html/node58.html index 5cb839b1..e31738c2 100644 --- a/docs/html/node58.html +++ b/docs/html/node58.html @@ -208,7 +208,7 @@ Default: global=.true. ALT="$x$">.
            Scope: global unless the optional variable -global=.false. as been specified +global=.false. has been specified
            Specified as: a long precision real number.
    4. diff --git a/docs/html/node60.html b/docs/html/node60.html index 77a6ca43..ecce45be 100644 --- a/docs/html/node60.html +++ b/docs/html/node60.html @@ -203,13 +203,13 @@ Default: global=.true.
      Function Value
      -
      is the 2-norm of subvector is the 2-norm of vector $x$.
      Scope: global unless the optional variable -global=.false. as been specified +global=.false. has been specified
      Type: required
      diff --git a/docs/psblas-3.5.pdf b/docs/psblas-3.5.pdf index 296c255d..8aa24754 100644 --- a/docs/psblas-3.5.pdf +++ b/docs/psblas-3.5.pdf @@ -8223,7 +8223,7 @@ endstream endobj 1003 0 obj << -/Length 5129 +/Length 5114 >> stream 0 g 0 G @@ -8236,7 +8236,7 @@ BT 0 g 0 G 0 -19.925 Td [(F)96(unction)-384(v)64(alue)]TJ 0 g 0 G -/F8 9.9626 Tf 78.386 0 Td [(is)-333(the)-334(dot)-333(pro)-28(duct)-333(of)-333(sub)28(v)27(ectors)]TJ/F11 9.9626 Tf 142.189 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(and)]TJ/F11 9.9626 Tf 19.372 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -229.298 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.167 0 Td [(global)]TJ/F8 9.9626 Tf 32.653 0 Td [(unless)-291(the)-291(option)1(a)-1(l)-290(v)55(ariable)]TJ/F30 9.9626 Tf 121.039 0 Td [(global=.false.)]TJ/F8 9.9626 Tf 76.121 0 Td [(as)-291(b)-28(een)-290(sp)-28(ec-)]TJ -261.98 -11.955 Td [(i\014ed)]TJ 0 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(n)28(um)28(b)-28(er)-333(of)-334(the)-333(data)-333(t)27(yp)-27(e)-334(indicated)-333(in)-333(T)83(able)]TJ +/F8 9.9626 Tf 78.386 0 Td [(is)-333(the)-334(dot)-333(pro)-28(duct)-333(of)-333(v)28(e)-1(ctors)]TJ/F11 9.9626 Tf 127.467 0 Td [(x)]TJ/F8 9.9626 Tf 9.014 0 Td [(and)]TJ/F11 9.9626 Tf 19.372 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -214.575 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 31.841 0 Td [(global)]TJ/F8 9.9626 Tf 32.002 0 Td [(unless)-225(the)-226(optional)-225(v)55(ariable)]TJ/F30 9.9626 Tf 118.434 0 Td [(global=.false.)]TJ/F8 9.9626 Tf 75.471 0 Td [(has)-225(b)-28(een)-226(sp)-27(ec-)]TJ -257.748 -11.955 Td [(i\014ed)]TJ 0 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(n)28(um)28(b)-28(er)-333(of)-334(the)-333(data)-333(t)27(yp)-27(e)-334(indicated)-333(in)-333(T)83(able)]TJ 0 0 1 rg 0 0 1 RG [-333(2)]TJ 0 g 0 G @@ -8248,7 +8248,7 @@ BT 0 g 0 G /F8 9.9626 Tf 12.176 -19.926 Td [(1.)]TJ 0 g 0 G - [-500(The)-241(computation)-240(of)-241(a)-241(gl)1(obal)-241(result)-241(requires)-240(a)-241(global)-241(comm)28(unication,)-259(whic)28(h)]TJ 12.73 -11.955 Td [(en)28(tails)-421(a)-420(s)-1(i)1(gni\014can)27(t)-420(o)28(v)27(erhead.)-706(It)-420(ma)27(y)-420(b)-28(e)-421(necessary)-420(and/or)-421(advisable)-420(to)]TJ 0 -11.955 Td [(compute)-265(m)27(ultiple)-265(dot)-265(pro)-28(ducts)-265(at)-266(the)-265(same)-266(time;)-288(in)-265(this)-265(case,)-279(it)-266(is)-265(p)-28(ossible)]TJ 0 -11.955 Td [(to)-333(impro)27(v)28(e)-333(the)-333(run)27(time)-333(e\016ciency)-333(b)27(y)-333(using)-333(the)-334(f)1(o)-1(l)1(lo)27(wing)-333(sc)28(heme:)]TJ 25.19 -17.933 Td [(v)-128(r)-129(e)-128(s)-259(\050)-130(1)-131(\051)-642(=)-625(p)-115(s)-114(b)]TJ + [-500(The)-241(computation)-240(of)-241(a)-241(gl)1(obal)-241(result)-241(requires)-240(a)-241(global)-241(comm)28(unication,)-259(whic)28(h)]TJ 12.73 -11.955 Td [(en)28(tails)-421(a)-420(s)-1(i)1(gni\014can)27(t)-420(o)28(v)27(erhead.)-706(It)-420(ma)27(y)-420(b)-28(e)-421(necessary)-420(and/or)-421(advisable)-420(to)]TJ 0 -11.955 Td [(compute)-265(m)27(ultiple)-265(dot)-265(pro)-28(ducts)-265(at)-266(the)-265(same)-266(time;)-288(in)-265(this)-265(case,)-279(it)-266(is)-265(p)-28(ossible)]TJ 0 -11.955 Td [(to)-333(impro)27(v)28(e)-333(the)-333(run)27(time)-333(e\016ciency)-333(b)27(y)-333(using)-333(the)-334(f)1(ollo)27(wing)-333(sc)28(heme:)]TJ 25.19 -17.933 Td [(v)-128(r)-129(e)-128(s)-259(\050)-130(1)-131(\051)-642(=)-625(p)-115(s)-114(b)]TJ ET q 1 0 0 1 279.461 443.314 cm @@ -8897,7 +8897,7 @@ endstream endobj 1020 0 obj << -/Length 8468 +/Length 8462 >> stream 0 g 0 G @@ -9077,7 +9077,7 @@ BT 0 g 0 G 0 -18.428 Td [(res)]TJ 0 g 0 G -/F8 9.9626 Tf 19.47 0 Td [(is)-333(the)-334(dot)-333(pro)-28(duct)-333(of)-333(sub)28(v)27(ectors)]TJ/F11 9.9626 Tf 142.19 0 Td [(x)]TJ/F8 9.9626 Tf 9.014 0 Td [(and)]TJ/F11 9.9626 Tf 19.372 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -170.381 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-357(as)-1(:)-493(a)-357(n)27(um)28(b)-28(er)-357(or)-358(a)-358(rank-one)-358(ar)1(ra)27(y)-357(of)-358(the)-358(data)-358(t)28(yp)-27(e)-358(indicated)-358(in)]TJ 0 -11.955 Td [(T)83(able)]TJ +/F8 9.9626 Tf 19.47 0 Td [(is)-333(the)-334(dot)-333(pro)-28(duct)-333(of)-333(v)27(ectors)]TJ/F11 9.9626 Tf 127.467 0 Td [(x)]TJ/F8 9.9626 Tf 9.015 0 Td [(and)]TJ/F11 9.9626 Tf 19.372 0 Td [(y)]TJ/F8 9.9626 Tf 5.242 0 Td [(.)]TJ -155.659 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.379 0 Td [(global)]TJ/F8 9.9626 Tf -32.379 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(out)]TJ/F8 9.9626 Tf 16.549 0 Td [(.)]TJ -50.035 -11.955 Td [(Sp)-28(eci\014ed)-357(as)-1(:)-493(a)-357(n)27(um)28(b)-28(er)-357(or)-358(a)-358(rank-one)-358(ar)1(ra)27(y)-357(of)-358(the)-358(data)-358(t)28(yp)-27(e)-358(indicated)-358(in)]TJ 0 -11.955 Td [(T)83(able)]TJ 0 0 1 rg 0 0 1 RG [-333(2)]TJ 0 g 0 G @@ -9267,7 +9267,7 @@ endstream endobj 1037 0 obj << -/Length 4565 +/Length 4563 >> stream 0 g 0 G @@ -9276,7 +9276,7 @@ stream BT /F27 9.9626 Tf 150.705 706.129 Td [(F)96(unction)-384(v)64(alue)]TJ 0 g 0 G -/F8 9.9626 Tf 78.386 0 Td [(is)-333(the)-334(in\014nit)28(y)-333(norm)-333(of)-334(sub)28(v)28(ector)]TJ/F11 9.9626 Tf 143.518 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -202.692 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.167 0 Td [(global)]TJ/F8 9.9626 Tf 32.653 0 Td [(unless)-291(the)-291(optional)-290(v)55(ariable)]TJ/F30 9.9626 Tf 121.039 0 Td [(global=.false.)]TJ/F8 9.9626 Tf 76.121 0 Td [(as)-291(b)-28(een)-290(sp)-28(ec-)]TJ -261.98 -11.955 Td [(i\014ed)]TJ 0 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(long)-333(precision)-334(r)1(e)-1(al)-333(n)28(um)28(b)-28(er.)]TJ +/F8 9.9626 Tf 78.386 0 Td [(is)-333(the)-334(in\014nit)28(y)-333(norm)-333(of)-334(v)28(ector)]TJ/F11 9.9626 Tf 128.795 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -187.969 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 31.842 0 Td [(global)]TJ/F8 9.9626 Tf 32.002 0 Td [(unless)-225(the)-226(optional)-225(v)55(ari)1(able)]TJ/F30 9.9626 Tf 118.433 0 Td [(global=.false.)]TJ/F8 9.9626 Tf 75.471 0 Td [(has)-225(b)-28(een)-226(sp)-27(ec-)]TJ -257.748 -11.955 Td [(i\014ed)]TJ 0 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(long)-333(precision)-334(r)1(e)-1(al)-333(n)28(um)28(b)-28(er.)]TJ 0 g 0 G /F27 9.9626 Tf -24.906 -19.925 Td [(info)]TJ 0 g 0 G @@ -9507,7 +9507,7 @@ endstream endobj 1059 0 obj << -/Length 7149 +/Length 7148 >> stream 0 g 0 G @@ -9658,7 +9658,7 @@ BT 0 g 0 G 0 -18.819 Td [(F)96(unction)-384(v)64(alue)]TJ 0 g 0 G -/F8 9.9626 Tf 78.386 0 Td [(is)-333(the)-334(1-norm)-333(of)-333(v)27(ector)]TJ/F11 9.9626 Tf 102.781 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -161.955 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.167 0 Td [(global)]TJ/F8 9.9626 Tf 32.653 0 Td [(unless)-291(the)-291(option)1(al)-291(v)55(ariable)]TJ/F30 9.9626 Tf 121.039 0 Td [(global=.false.)]TJ/F8 9.9626 Tf 76.121 0 Td [(as)-291(b)-28(een)-290(sp)-28(ec-)]TJ -261.98 -11.955 Td [(i\014ed)]TJ 0 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(long)-333(precision)-334(r)1(e)-1(al)-333(n)28(um)28(b)-28(er.)]TJ +/F8 9.9626 Tf 78.386 0 Td [(is)-333(the)-334(1-norm)-333(of)-333(v)27(ector)]TJ/F11 9.9626 Tf 102.781 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -161.955 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 31.841 0 Td [(global)]TJ/F8 9.9626 Tf 32.002 0 Td [(unless)-225(the)-226(optional)-225(v)55(ariable)]TJ/F30 9.9626 Tf 118.434 0 Td [(global=.false.)]TJ/F8 9.9626 Tf 75.471 0 Td [(has)-225(b)-28(een)-226(sp)-27(ec-)]TJ -257.748 -11.955 Td [(i\014ed)]TJ 0 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(long)-333(precision)-334(r)1(e)-1(al)-333(n)28(um)28(b)-28(er.)]TJ 0 g 0 G 141.968 -29.888 Td [(38)]TJ 0 g 0 G @@ -10090,7 +10090,7 @@ endstream endobj 1094 0 obj << -/Length 4631 +/Length 4633 >> stream 0 g 0 G @@ -10099,7 +10099,7 @@ stream BT /F27 9.9626 Tf 99.895 706.129 Td [(F)96(unction)-384(V)96(alue)]TJ 0 g 0 G -/F8 9.9626 Tf 80.684 0 Td [(is)-333(the)-334(2-norm)-333(of)-333(sub)28(v)27(ector)]TJ/F11 9.9626 Tf 117.503 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -178.974 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 32.167 0 Td [(global)]TJ/F8 9.9626 Tf 32.653 0 Td [(unless)-291(the)-291(opti)1(onal)-291(v)55(ariable)]TJ/F30 9.9626 Tf 121.038 0 Td [(global=.false.)]TJ/F8 9.9626 Tf 76.122 0 Td [(as)-291(b)-28(een)-290(sp)-28(ec-)]TJ -261.98 -11.955 Td [(i\014ed)]TJ 0 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(long)-333(precision)-333(real)-334(n)28(um)28(b)-28(er.)]TJ +/F8 9.9626 Tf 80.684 0 Td [(is)-333(the)-334(2-norm)-333(of)-333(v)28(e)-1(ctor)]TJ/F11 9.9626 Tf 102.781 0 Td [(x)]TJ/F8 9.9626 Tf 5.694 0 Td [(.)]TJ -164.252 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 31.841 0 Td [(global)]TJ/F8 9.9626 Tf 32.002 0 Td [(unless)-225(the)-226(optional)-225(v)55(ariabl)1(e)]TJ/F30 9.9626 Tf 118.434 0 Td [(global=.false.)]TJ/F8 9.9626 Tf 75.47 0 Td [(has)-225(b)-28(een)-226(sp)-27(ec)-1(-)]TJ -257.747 -11.955 Td [(i\014ed)]TJ 0 -11.956 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 29.611 0 Td [(required)]TJ/F8 9.9626 Tf -29.611 -11.955 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(long)-333(precision)-333(real)-334(n)28(um)28(b)-28(er.)]TJ 0 g 0 G /F27 9.9626 Tf -24.907 -19.925 Td [(info)]TJ 0 g 0 G @@ -28544,8 +28544,8 @@ endobj 2028 0 obj << /Title (Parallel Sparse BLAS V. 3.5.0) /Subject (Parallel Sparse Basic Linear Algebra Subroutines) /Keywords (Computer Science Linear Algebra Fluid Dynamics Parallel Linux MPI PSBLAS Iterative Solvers Preconditioners) /Creator (pdfLaTeX) /Producer ($Id$) /Author()/Title()/Subject()/Creator(LaTeX with hyperref package)/Producer(pdfTeX-1.40.17)/Keywords() -/CreationDate (D:20180420155528+01'00') -/ModDate (D:20180420155528+01'00') +/CreationDate (D:20180420161526+01'00') +/ModDate (D:20180420161526+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) >> @@ -28710,7 +28710,7 @@ endobj /W [1 3 1] /Root 2027 0 R /Info 2028 0 R -/ID [<6EBF9D8966F3D97AEE3732EC7B41E698> <6EBF9D8966F3D97AEE3732EC7B41E698>] +/ID [<8D4B0BAB35DAEB67AE8FE745DCD8C80F> <8D4B0BAB35DAEB67AE8FE745DCD8C80F>] /Length 10150 >> stream @@ -28724,34 +28724,34 @@ stream k k k kkkkkkkkkkkkkkkkk"k S( kksk#k$k%k&k'k(k)k*k+k,k-k.k/k0k1k2k3k4k5k6k7k8k9k:k;k<k=k>k?k@kAkBkCkDkEkFkGkHkIkJkKkLkMkNkOkPkTkRk!kQkUkVkWkXkYkZk[k\k]k^k_k`kakbkc     kS:]!"#$%&'()*, ^3E%E+NE;OMBCL?@23497-E6./01rA:;@8<E'E EE#E>E!?KEFJAGHBCD>=LMOKN][PAQESTUVWXYZ@ @ \P^_`abc@@@@@@@@@E(E,^@ @@ -m@ @@@@@@@@@@@@@ @!@.@/@,@8@"@#@$@%@&@'@(@)@*@+@8@-@0@1@2@3@4@5@:@;@@@9܈@<@F@A@BE-@M@G@H@J@O@P@Q@X@N@R@U@V@WJ@^@Y?@Z@_O@`@b: # E. zȍ$K #',%y&./2-$0E/M45<369E):?=+>C@.2AEFGHIJPND/ KQRTOL SVWXYZ^UV[]E0`_tabcm  - M ҞL#S !"%&'+$e(*E1-./3,X02<4756789:;>?@D=FACGEcFIJKOHfLNXPQRSTUVWE2Z[\`YU]_bc^a^^f<^^^ -^ ^E$^ ^ ^ ^^^^^ ^^^^^^^^^^^^^!^^ ^#^)^'^":6^$^&E3^*^+^,^-^.^/^1^(T^0^3^4^6^2s^5^8^;^7^9^=^>^?^N^F^<^@^B^C^D^E-^O^R^Gt^P^Q^H^I^J^K^L^M^U^S!^TE"E4^W^X^Y^`^V-^Z^\^]^^^_^b)^c^aO )G  -   6 <E5"*(!B#%&'+,.)aE-3/q058467:=9;<E>G?@ABCDE6GJFHLQK(MNOPSTXR UWZ[^Y \`c_ aCCCC UwC -ZE7C -C lCCC C C CC  sKCCCCCCCCC CC&C CCCCC C!C"C#C$C%C(C)C,C' C*C5C- JC.C/C0C1C2C3C4E8C7C8C;C6 OC9C=C>CBC< C?CACDCECHCC lCFCJCKCNCI - CLCSCO -&~CPCQCRCUCVCWCZCT -+CXE9C\C]C`C[ -?C^Ca -M"Cb  - +m@ @@@@@@@@@@@@@ @!@.@/@,@8@"@#@$@%@&@'@(@)@*@+@8@-@0@1@2@3@4@5@:@;@@@9܈@<@F@A@BE-@M@G@H@J@O@P@Q@X@N@R@U@V@WJ@^@Y?@Z@_O@`@b+ # E. zȍ$K #',%y&./2-$0E/M45<369E):?=+>C@.2AEFGHIJPND/ KQRTOL SVWXYZ^UV[]E0`_tabcW  + > ҉7#> !"%&'+$N(*E1-./3,A02<47j56789:;>?@D=FACGEcFIJKOHfnLNXPQRSTUVWE2Z[\`Y?]_bc^a^^f&^^^ +^^E$^ ^ ^ ^^^^^ ^^^^^^^^^^^^^!^^ ^#^)^'^": ^$^&E3^*^+^,^-^.^/^1^(T^0^3^4^6^2s^5^8^;^7^9^=^>^?^N^F^<^@^B^C^D^E^O^R^G^^P^Q^H^I^J^K^L^Mr^U^S!y^TE"E4^W^X^Y^`^V-^Z^\^]^^^_^b^c^aN )u1  +     <E5"*(!Bw#%&'+,.)a/-3/q058467:=9;<E>1?@ABCDE6GJFHLQKMNOPSTXR UWZ[^Y k\`c_ uaCCCC UaC +ZE7C +C lCCC C C CC  s5CCCCCCCCC CC&C CCCCC C!C"C#C$C%C(C)C,C' C*C5C- 4C.C/C0C1C2C3C4E8C7C8C;C6 9C9C=C>CBC< C?CACDCECHCC VCFCJCKCNCI + CLCSCO +&hCPCQCRCUCVCWCZCT ++CXE9C\C]C`C[ +?C^Ca +M Cb  +  -    -s  -E: -! - #'" -$&).( -r*,-05/ 1347:6 8E;@; -<=>?BCDGA <EKH MIWL cMNOPQRSTUV[X bYa\ Z]_`E<b Vc 0 - J     8 A 0E= 9"  (# $&'.) -T*,-4/ A023:5 V,689E>@; j<>?GA BDEEFLH IKQM VNPSTWR {UX ۿYZ[E\]^_`abc  -   E? ] V +# 0!")$ 7n%'(-* ?+/4. B9023E@6;5 U.79:=B< i>@AHC xlDFGJOI KMNUP QSTYV WEA[\`Z ]_bca    -   %EB)"4 $%.,#7b&()*+E/013-X -2574s6G8n9:<DFECQHIPRSTUVWXYZ[\]^_`abcEuE"E@bEyEEҷEE1EXOE wE -mE ZE 5E `EEOEE5Ee*EEEEDEEEFEGEHEIEJ.fTgw w wwwwwwwwwwwwwwwwwww w!w"w#w$w%w&w'w(w)w*w+w,w-w.w/w0w1w2w3w4w5w6w7w8w9w:w;w<w=w>w?w@wAwBwCwDwEwFwGwHwIwJwKwLwMwNwOwPwQwRwSwTwUwVwWwXwYwZw[w\w]w^w_w`wawbwc  -    +l    +]  +E: +! +غ #'" +$&).( +\*,-05/ 1347:6  8E;@; -<=>?BCDGA <EKH LIWL cMNOPQRSTUV[X LYa\ D]_`E<b @c  + 4   u  " + E= #"  (# $&'.) ->*,-4/ A023:5 V689E>@; j<>?GA BDEEFLH +IKQM @NPSTWR eUX ۩YZ[E\]^_`abc  +   E? G @ +# 0!")$ 7X%'(-* ?+/4. B#023E@6;5 U79:=B< i>@AHC xVDFGJOI KMNUP QSTYV WEA[\`Z ]_bca l i  +   %EB)"4 $%.,#7L&()*+E/013-W2574s6G8X9:<DFECQHIPRSTUVWXYZ[\]^_`abcE_E E@LEcEEҡEE1EX9E wE +WE DE E `EE9EE5EeEzEïEEDEEEFEGEHEIEJ.PTQw w wwwwwwwwwwwwwwwwwww w!w"w#w$w%w&w'w(w)w*w+w,w-w.w/w0w1w2w3w4w5w6w7w8w9w:w;w<w=w>w?w@wAwBwCwDwEwFwGwHwIwJwKwLwMwNwOwPwQwRwSwTwUwVwWwXwYwZw[w\w]w^w_w`wawbwc  +    endstream endobj startxref -1289919 +1289897 %%EOF diff --git a/docs/src/psbrout.tex b/docs/src/psbrout.tex index d4767c8a..d8288093 100644 --- a/docs/src/psbrout.tex +++ b/docs/src/psbrout.tex @@ -123,8 +123,8 @@ Else if $x$ and $y$ are complex vectors then it computes dot-product as: \[dot \leftarrow x^H y\] %% where: %% \begin{description} -%% \item[$x$] represents the global subvector $x_{:,jx}$ -%% \item[$y$] represents the global subvector $y_{:,jy}$ +%% \item[$x$] represents the global vector $x_{:,jx}$ +%% \item[$y$] represents the global vector $y_{:,jy}$ %% \end{description} \begin{verbatim} @@ -183,21 +183,21 @@ Intent: {\bf in}.\\ Specified as: a logical scalar. Default: \verb|global=.true.|\\ %% \item[jx] the column index of global dense matrix $x$, -%% identifying the column of subvector $x$.\\ +%% identifying the column of vector $x$.\\ %% Scope: {\bf global} \\ %% Type: {\bf optional}; can only be present if $x$ and $y$ are of rank 2.\\ %% Default: $jx = 1$.\\ %% \item[jy] the column index of global dense matrix $y$, -%% identifying the column of subvector $y$.\\ +%% identifying the column of vector $y$.\\ %% Scope: {\bf global} \\ %% Type: {\bf optional}; can only be present if $x$ and $y$ are of rank 2.\\ %% Default: $jy = 1$.\\ %% Specified as: an integer variable $jy\ge 1$. \item[\bf On Return] -\item[Function value] is the dot product of subvectors $x$ and $y$.\\ +\item[Function value] is the dot product of vectors $x$ and $y$.\\ Scope: {\bf global} unless the optional variable -\verb|global=.false.| as been specified\\ +\verb|global=.false.| has been specified\\ Specified as: a number of the data type indicated in Table~\ref{tab:f90dot}. \item[info] Error code.\\ Scope: {\bf local} \\ @@ -284,7 +284,7 @@ Type: {\bf required}\\ Intent: {\bf in}.\\ Specified as: an object of type \descdata. \item[\bf On Return] -\item[res] is the dot product of subvectors $x$ and $y$.\\ +\item[res] is the dot product of vectors $x$ and $y$.\\ Scope: {\bf global} \\ Intent: {\bf out}.\\ Specified as: a number or a rank-one array of the data type indicated @@ -315,7 +315,7 @@ else if $x$ is a complex vector then it computes the infinity-norm as: \[ amax \leftarrow \max_i {(|re(x_i)| + |im(x_i)|)}\] %% where: %% \begin{description} -%% \item[$x$] represents the global subvector $x_{:,jx}$ +%% \item[$x$] represents the global vector $x_{:,jx}$ %% \end{description} \begin{verbatim} @@ -366,16 +366,16 @@ Type: {\bf optional}.\\ Intent: {\bf in}.\\ Specified as: a logical scalar. Default: \verb|global=.true.|\\%% \item[jx] the column index of global dense matrix $x$, -%% identifying the column of subvector $x$.\\ +%% identifying the column of vector $x$.\\ %% Scope: {\bf global} \\ %% Type: {\bf optional}; can only be present if $x$ is of rank 2.\\ %% Default: $jx = 1$\\ %% Specified as: an integer variable $jx\ge 1$. \item[\bf On Return] -\item[Function value] is the infinity norm of subvector $x$.\\ +\item[Function value] is the infinity norm of vector $x$.\\ Scope: {\bf global} unless the optional variable -\verb|global=.false.| as been specified\\ +\verb|global=.false.| has been specified\\ Specified as: a long precision real number. \item[info] Error code.\\ Scope: {\bf local} \\ @@ -530,7 +530,7 @@ Default: \verb|global=.true.|\\ \item[\bf On Return] \item[Function value] is the 1-norm of vector $x$.\\ Scope: {\bf global} unless the optional variable -\verb|global=.false.| as been specified\\ +\verb|global=.false.| has been specified\\ Specified as: a long precision real number. \item[info] Error code.\\ Scope: {\bf local} \\ @@ -642,7 +642,7 @@ else if $x$ is a complex vector then it computes 2-norm as: \[ nrm2 \leftarrow \sqrt{x^H x}\] %% where: %% \begin{description} -%% \item[$x$] represents the global subvector $x_{:,jx}$ +%% \item[$x$] represents the global vector $x_{:,jx}$ %% \end{description} \begin{table}[h] @@ -692,16 +692,16 @@ Type: {\bf optional}.\\ Intent: {\bf in}.\\ Specified as: a logical scalar. Default: \verb|global=.true.|\\%% \item[jx] the column index of global dense matrix $x$, -%% identifying the column of subvector $x$.\\ +%% identifying the column of vector $x$.\\ %% Scope: {\bf global} \\ %% Type: {\bf optional}; can only be present if $x$ is of rank 2.\\ %% Default: $jx = 1$\\ %% Specified as: an integer variable $jx\ge 1$. \item[\bf On Return] -\item[Function Value] is the 2-norm of subvector $x$.\\ +\item[Function Value] is the 2-norm of vector $x$.\\ Scope: {\bf global} unless the optional variable -\verb|global=.false.| as been specified\\ +\verb|global=.false.| has been specified\\ Type: {\bf required} \\ Specified as: a long precision real number. \item[info] Error code.\\ @@ -1040,13 +1040,13 @@ Specified as: a character variable. %% Default: \verb|min(size(x,2)-jx+1,size(y,2)-jy+1)|\\ %% Specified as: an integer variable $ k \ge 1$. %% \item[jx] the column index of global dense matrix $x$, -%% identifying the column of subvector $x$.\\ +%% identifying the column of vector $x$.\\ %% Scope: {\bf global} \\ %% Type: {\bf optional}; can only be present if $x$ is of rank 2.\\ %% Default: $iy = 1$\\ %% Specified as: an integer variable $jx\ge 1$. %% \item[jy] the column index of global dense matrix $y$, -%% identifying the column of subvector $y$.\\ +%% identifying the column of vector $y$.\\ %% Scope: {\bf global} \\ %% Type: {\bf optional}; can only be present if $y$ is of rank 2.\\ %% Default: $jy = 1$\\ From 9e90a04e311d4eac69b7ce61e896e52984336406 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Sun, 22 Apr 2018 15:36:01 +0100 Subject: [PATCH 5/7] Change default in CDALL with VL: no global checks. Split psb_cd_choose_large_state with psb_cd_is_large. --- base/modules/desc/psb_desc_mod.F90 | 20 +++++++++++++++----- base/tools/psb_cd_inloc.f90 | 18 +++++++----------- 2 files changed, 22 insertions(+), 16 deletions(-) diff --git a/base/modules/desc/psb_desc_mod.F90 b/base/modules/desc/psb_desc_mod.F90 index 724b9114..41893ff2 100644 --- a/base/modules/desc/psb_desc_mod.F90 +++ b/base/modules/desc/psb_desc_mod.F90 @@ -334,11 +334,23 @@ contains val = cd_large_threshold end function psb_cd_get_large_threshold - logical function psb_cd_choose_large_state(ictxt,m) + function psb_cd_is_large_size(m) result(val) use psb_penv_mod implicit none - integer(psb_ipk_), intent(in) :: ictxt,m + integer(psb_ipk_), intent(in) :: m + logical :: val + !locals + val = (m > psb_cd_get_large_threshold()) + end function psb_cd_is_large_size + + function psb_cd_choose_large_state(ictxt,m) result(val) + use psb_penv_mod + + implicit none + integer(psb_ipk_), intent(in) :: ictxt + integer(psb_ipk_), intent(in) :: m + logical :: val !locals integer(psb_ipk_) :: np,me @@ -348,9 +360,7 @@ contains ! it makes no sense to use them if you don't have at least ! 3 processes, no matter what the size of the process. ! - psb_cd_choose_large_state = & - & (m > psb_cd_get_large_threshold()) .and. & - & (np > 2) + val = psb_cd_is_large_size(m) .and. (np > 2) end function psb_cd_choose_large_state subroutine psb_nullify_desc(desc) diff --git a/base/tools/psb_cd_inloc.f90 b/base/tools/psb_cd_inloc.f90 index 1b31fe2e..6ea184d1 100644 --- a/base/tools/psb_cd_inloc.f90 +++ b/base/tools/psb_cd_inloc.f90 @@ -82,19 +82,15 @@ subroutine psb_cd_inloc(v, ictxt, desc, info, globalcheck,idx) iictxt = ictxt loc_row = size(v) - if (.false.) then - m = loc_row - call psb_sum(ictxt,m) - else - m = maxval(v) - nrt = loc_row - call psb_sum(ictxt,nrt) - call psb_max(ictxt,m) - end if + m = maxval(v) + nrt = loc_row + call psb_sum(ictxt,nrt) + call psb_max(ictxt,m) + if (present(globalcheck)) then check_ = globalcheck else - check_ = .true. + check_ = .false. end if n = m @@ -138,7 +134,7 @@ subroutine psb_cd_inloc(v, ictxt, desc, info, globalcheck,idx) if (debug_level >= psb_debug_ext_) & & write(debug_unit,*) me,' ',trim(name),': doing global checks' - islarge = psb_cd_choose_large_state(ictxt,m) + islarge = psb_cd_is_large_size(m) allocate(vl(loc_row),ix(loc_row),stat=info) if (info /= psb_success_) then From a06985ea7308ee7136e63c61b65f0d7fdc1312ba Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Sun, 22 Apr 2018 15:36:58 +0100 Subject: [PATCH 6/7] Document default in CDALL with VL: no global checks. --- docs/html/node72.html | 4 +-- docs/psblas-3.5.pdf | 62 +++++++++++++++++++++--------------------- docs/src/toolsrout.tex | 4 +-- 3 files changed, 35 insertions(+), 35 deletions(-) diff --git a/docs/html/node72.html b/docs/html/node72.html index fd420f32..58b79db9 100644 --- a/docs/html/node72.html +++ b/docs/html/node72.html @@ -56,7 +56,7 @@ psb_cdall -- Allocates a communication descriptor
       call psb_cdall(icontxt, desc_a, info,mg=mg,parts=parts)
       call psb_cdall(icontxt, desc_a, info,vg=vg,[mg=mg,flag=flag])
      -call psb_cdall(icontxt, desc_a, info,vl=vl,[nl=nl,globalcheck=.true.,lidx=lidx])
      +call psb_cdall(icontxt, desc_a, info,vl=vl,[nl=nl,globalcheck=.false.,lidx=lidx])
       call psb_cdall(icontxt, desc_a, info,nl=nl)
       call psb_cdall(icontxt, desc_a, info,mg=mg,repl=.true.)
       
      @@ -199,7 +199,7 @@ Type:optional.
      Intent: in.
      -Specified as: a logical value, default: .true. +Specified as: a logical value, default: .false.
      lidx
      Data allocation: the set of local indices diff --git a/docs/psblas-3.5.pdf b/docs/psblas-3.5.pdf index 8aa24754..96e8c452 100644 --- a/docs/psblas-3.5.pdf +++ b/docs/psblas-3.5.pdf @@ -14180,7 +14180,7 @@ endstream endobj 1286 0 obj << -/Length 6539 +/Length 6540 >> stream 0 g 0 G @@ -14196,7 +14196,7 @@ BT /F16 11.9552 Tf 175.796 682.315 Td [(cdall)-375(|)-375(Allo)-31(cates)-375(a)-375(comm)31(unication)-375(descriptor)]TJ 0 g 0 G 0 g 0 G -/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,mg=mg,parts=parts\051)]TJ 0 -11.955 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,vg=vg,[mg=mg,flag=flag]\051)]TJ 0 -11.955 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,vl=vl,[nl=nl,globalcheck=.true.,lidx=lidx]\051)]TJ 0 -11.955 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,nl=nl\051)]TJ 0 -11.956 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,mg=mg,repl=.true.\051)]TJ/F8 9.9626 Tf 14.944 -20.107 Td [(This)-314(subroutine)-314(initializes)-315(th)1(e)-315(comm)28(unication)-314(descriptor)-314(ass)-1(o)-27(ciated)-315(with)-314(an)]TJ -14.944 -11.955 Td [(index)-326(space.)-442(One)-326(of)-326(the)-327(op)1(tional)-327(argu)1(m)-1(en)28(ts)]TJ/F30 9.9626 Tf 193.679 0 Td [(parts)]TJ/F8 9.9626 Tf 26.152 0 Td [(,)]TJ/F30 9.9626 Tf 6.031 0 Td [(vg)]TJ/F8 9.9626 Tf 10.461 0 Td [(,)]TJ/F30 9.9626 Tf 6.031 0 Td [(vl)]TJ/F8 9.9626 Tf 10.46 0 Td [(,)]TJ/F30 9.9626 Tf 6.031 0 Td [(nl)]TJ/F8 9.9626 Tf 13.71 0 Td [(or)]TJ/F30 9.9626 Tf 12.133 0 Td [(repl)]TJ/F8 9.9626 Tf 24.17 0 Td [(m)28(ust)-326(b)-28(e)]TJ -308.858 -11.955 Td [(sp)-28(eci\014ed,)-333(thereb)28(y)-334(c)28(ho)-28(osing)-333(the)-333(sp)-28(eci\014c)-333(initialization)-334(strategy)84(.)]TJ +/F30 9.9626 Tf -25.091 -18.389 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,mg=mg,parts=parts\051)]TJ 0 -11.955 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,vg=vg,[mg=mg,flag=flag]\051)]TJ 0 -11.955 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,vl=vl,[nl=nl,globalcheck=.false.,lidx=lidx]\051)]TJ 0 -11.955 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,nl=nl\051)]TJ 0 -11.956 Td [(call)-525(psb_cdall\050icontxt,)-525(desc_a,)-525(info,mg=mg,repl=.true.\051)]TJ/F8 9.9626 Tf 14.944 -20.107 Td [(This)-314(subroutine)-314(initializes)-315(th)1(e)-315(comm)28(unication)-314(descriptor)-314(ass)-1(o)-27(ciated)-315(with)-314(an)]TJ -14.944 -11.955 Td [(index)-326(space.)-442(One)-326(of)-326(the)-327(op)1(tional)-327(argu)1(m)-1(en)28(ts)]TJ/F30 9.9626 Tf 193.679 0 Td [(parts)]TJ/F8 9.9626 Tf 26.152 0 Td [(,)]TJ/F30 9.9626 Tf 6.031 0 Td [(vg)]TJ/F8 9.9626 Tf 10.461 0 Td [(,)]TJ/F30 9.9626 Tf 6.031 0 Td [(vl)]TJ/F8 9.9626 Tf 10.46 0 Td [(,)]TJ/F30 9.9626 Tf 6.031 0 Td [(nl)]TJ/F8 9.9626 Tf 13.71 0 Td [(or)]TJ/F30 9.9626 Tf 12.133 0 Td [(repl)]TJ/F8 9.9626 Tf 24.17 0 Td [(m)28(ust)-326(b)-28(e)]TJ -308.858 -11.955 Td [(sp)-28(eci\014ed,)-333(thereb)28(y)-334(c)28(ho)-28(osing)-333(the)-333(sp)-28(eci\014c)-333(initialization)-334(strategy)84(.)]TJ 0 g 0 G /F27 9.9626 Tf 0 -18.477 Td [(On)-383(En)32(try)]TJ 0 g 0 G @@ -14237,7 +14237,7 @@ endstream endobj 1291 0 obj << -/Length 6637 +/Length 6638 >> stream 0 g 0 G @@ -14254,7 +14254,7 @@ BT 0 g 0 G /F27 9.9626 Tf -156.691 -20.135 Td [(globalc)32(hec)32(k)]TJ 0 g 0 G -/F8 9.9626 Tf 61.948 0 Td [(Data)-333(allo)-28(cation:)-445(d)1(o)-334(global)-333(c)28(hec)27(ks)-333(on)-333(the)-334(lo)-27(cal)-334(index)-333(lists)]TJ/F30 9.9626 Tf 250.201 0 Td [(vl)]TJ/F8 9.9626 Tf -287.242 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -57.707 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(logical)-333(v)55(alue,)-333(default:)]TJ/F30 9.9626 Tf 163.056 0 Td [(.true.)]TJ +/F8 9.9626 Tf 61.948 0 Td [(Data)-333(allo)-28(cation:)-445(d)1(o)-334(global)-333(c)28(hec)27(ks)-333(on)-333(the)-334(lo)-27(cal)-334(index)-333(lists)]TJ/F30 9.9626 Tf 250.201 0 Td [(vl)]TJ/F8 9.9626 Tf -287.242 -11.955 Td [(Scop)-28(e:)]TJ/F27 9.9626 Tf 27.951 0 Td [(global)]TJ/F8 9.9626 Tf 29.756 0 Td [(.)]TJ -57.707 -11.955 Td [(T)28(yp)-28(e:)]TJ/F27 9.9626 Tf 25.183 0 Td [(optional)]TJ/F8 9.9626 Tf 40.577 0 Td [(.)]TJ -65.76 -11.955 Td [(In)28(ten)28(t:)]TJ/F27 9.9626 Tf 33.486 0 Td [(in)]TJ/F8 9.9626 Tf 9.547 0 Td [(.)]TJ -43.033 -11.956 Td [(Sp)-28(eci\014ed)-333(as:)-445(a)-333(logical)-333(v)55(alue,)-333(default:)]TJ/F30 9.9626 Tf 163.056 0 Td [(.false.)]TJ 0 g 0 G /F27 9.9626 Tf -187.963 -20.135 Td [(lidx)]TJ 0 g 0 G @@ -28544,8 +28544,8 @@ endobj 2028 0 obj << /Title (Parallel Sparse BLAS V. 3.5.0) /Subject (Parallel Sparse Basic Linear Algebra Subroutines) /Keywords (Computer Science Linear Algebra Fluid Dynamics Parallel Linux MPI PSBLAS Iterative Solvers Preconditioners) /Creator (pdfLaTeX) /Producer ($Id$) /Author()/Title()/Subject()/Creator(LaTeX with hyperref package)/Producer(pdfTeX-1.40.17)/Keywords() -/CreationDate (D:20180420161526+01'00') -/ModDate (D:20180420161526+01'00') +/CreationDate (D:20180422153634+01'00') +/ModDate (D:20180422153634+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) >> @@ -28710,7 +28710,7 @@ endobj /W [1 3 1] /Root 2027 0 R /Info 2028 0 R -/ID [<8D4B0BAB35DAEB67AE8FE745DCD8C80F> <8D4B0BAB35DAEB67AE8FE745DCD8C80F>] +/ID [<8F88B2428FC2AB5F6A7533BB5EB65F64> <8F88B2428FC2AB5F6A7533BB5EB65F64>] /Length 10150 >> stream @@ -28726,32 +28726,32 @@ stream    kS:]!"#$%&'()*, ^3E%E+NE;OMBCL?@23497-E6./01rA:;@8<E'E EE#E>E!?KEFJAGHBCD>=LMOKN][PAQESTUVWXYZ@ @ \P^_`abc@@@@@@@@@E(E,^@ @@ m@ @@@@@@@@@@@@@ @!@.@/@,@8@"@#@$@%@&@'@(@)@*@+@8@-@0@1@2@3@4@5@:@;@@@9܈@<@F@A@BE-@M@G@H@J@O@P@Q@X@N@R@U@V@WJ@^@Y?@Z@_O@`@b+ # E. zȍ$K #',%y&./2-$0E/M45<369E):?=+>C@.2AEFGHIJPND/ KQRTOL SVWXYZ^UV[]E0`_tabcW   > ҉7#> !"%&'+$N(*E1-./3,A02<47j56789:;>?@D=FACGEcFIJKOHfnLNXPQRSTUVWE2Z[\`Y?]_bc^a^^f&^^^ -^^E$^ ^ ^ ^^^^^ ^^^^^^^^^^^^^!^^ ^#^)^'^": ^$^&E3^*^+^,^-^.^/^1^(T^0^3^4^6^2s^5^8^;^7^9^=^>^?^N^F^<^@^B^C^D^E^O^R^G^^P^Q^H^I^J^K^L^Mr^U^S!y^TE"E4^W^X^Y^`^V-^Z^\^]^^^_^b^c^aN )u1  -     <E5"*(!Bw#%&'+,.)a/-3/q058467:=9;<E>1?@ABCDE6GJFHLQKMNOPSTXR UWZ[^Y k\`c_ uaCCCC UaC -ZE7C -C lCCC C C CC  s5CCCCCCCCC CC&C CCCCC C!C"C#C$C%C(C)C,C' C*C5C- 4C.C/C0C1C2C3C4E8C7C8C;C6 9C9C=C>CBC< C?CACDCECHCC VCFCJCKCNCI - CLCSCO -&hCPCQCRCUCVCWCZCT -+CXE9C\C]C`C[ -?C^Ca -M Cb  - +^^E$^ ^ ^ ^^^^^ ^^^^^^^^^^^^^!^^ ^#^)^'^": ^$^&E3^*^+^,^-^.^/^1^(T^0^3^4^6^2s^5^8^;^7^9^=^>^?^N^F^<^@^B^C^D^E^O^R^G^^P^Q^H^I^J^K^L^Mr^U^S!y^TE"E4^W^X^Y^`^V-^Z^\^]^^^_^b^c^aN )w1  +     <E5"*(!Bw#%&'+,.)a/-3/q058467:=9;<E>3?@ABCDE6GJFHLQKMNOPSTXR UWZ[^Y m\`c_ waCCCC UcC +ZE7C +C lCCC C C CC  s7CCCCCCCCC CC&C CCCCC C!C"C#C$C%C(C)C,C' C*C5C- 6C.C/C0C1C2C3C4E8C7C8C;C6 ;C9C=C>CBC< C?CACDCECHCC XCFCJCKCNCI + CLCSCO +&jCPCQCRCUCVCWCZCT ++CXE9C\C]C`C[ +?C^Ca +MCb  +  -l    -]  -E: -! -غ #'" -$&).( -\*,-05/ 1347:6  8E;@; -<=>?BCDGA <EKH LIWL cMNOPQRSTUV[X LYa\ D]_`E<b @c  - 4   u  " + E= #"  (# $&'.) ->*,-4/ A023:5 V689E>@; j<>?GA BDEEFLH -IKQM @NPSTWR eUX ۩YZ[E\]^_`abc  -   E? G @ +# 0!")$ 7X%'(-* ?+/4. B#023E@6;5 U79:=B< i>@AHC xVDFGJOI KMNUP QSTYV WEA[\`Z ]_bca l i  -   %EB)"4 $%.,#7L&()*+E/013-W2574s6G8X9:<DFECQHIPRSTUVWXYZ[\]^_`abcE_E E@LEcEEҡEE1EX9E wE -WE DE E `EE9EE5EeEzEïEEDEEEFEGEHEIEJ.PTQw w wwwwwwwwwwwwwwwwwww w!w"w#w$w%w&w'w(w)w*w+w,w-w.w/w0w1w2w3w4w5w6w7w8w9w:w;w<w=w>w?w@wAwBwCwDwEwFwGwHwIwJwKwLwMwNwOwPwQwRwSwTwUwVwWwXwYwZw[w\w]w^w_w`wawbwc  -    +n    +_  +E: +! +ؼ #'" +$&).( +^*,-05/ 1347:6  8E;@; -<=>?BCDGA <EKH LIWL cMNOPQRSTUV[X NYa\ F]_`E<b Bc  + 6   w  $ - E= %"  (# $&'.) -@*,-4/ A023:5 V689E>@; j<>?GA BDEEFLH IKQM BNPSTWR gUX ۫YZ[E\]^_`abc  +   E? I B + +# 0!")$ 7Z%'(-* ?+/4. B%023E@6;5 U79:=B< i>@AHC xXDFGJOI KMNUP QSTYV WEA[\`Z ]_bca n k  +   %EB)"4 $%.,#7N&()*+E/013-W2574s6G8Z9:<DFECQHIPRSTUVWXYZ[\]^_`abcEaEE@NEeEEңEE1EX;E wE +YE FE !E `EE;EE5EeE|EñEEDEEEFEGEHEIEJ.RTSw w wwwwwwwwwwwwwwwwwww w!w"w#w$w%w&w'w(w)w*w+w,w-w.w/w0w1w2w3w4w5w6w7w8w9w:w;w<w=w>w?w@wAwBwCwDwEwFwGwHwIwJwKwLwMwNwOwPwQwRwSwTwUwVwWwXwYwZw[w\w]w^w_w`wawbwc  +    endstream endobj startxref -1289897 +1289899 %%EOF diff --git a/docs/src/toolsrout.tex b/docs/src/toolsrout.tex index a072baed..e39c18b6 100644 --- a/docs/src/toolsrout.tex +++ b/docs/src/toolsrout.tex @@ -11,7 +11,7 @@ \begin{verbatim} call psb_cdall(icontxt, desc_a, info,mg=mg,parts=parts) call psb_cdall(icontxt, desc_a, info,vg=vg,[mg=mg,flag=flag]) -call psb_cdall(icontxt, desc_a, info,vl=vl,[nl=nl,globalcheck=.true.,lidx=lidx]) +call psb_cdall(icontxt, desc_a, info,vl=vl,[nl=nl,globalcheck=.false.,lidx=lidx]) call psb_cdall(icontxt, desc_a, info,nl=nl) call psb_cdall(icontxt, desc_a, info,mg=mg,repl=.true.) \end{verbatim} @@ -75,7 +75,7 @@ Specified as: the logical value \verb|.true.| Scope:{\bf global}.\\ Type:{\bf optional}.\\ Intent: {\bf in}.\\ -Specified as: a logical value, default: \verb|.true.| +Specified as: a logical value, default: \verb|.false.| \item[lidx] Data allocation: the set of local indices $lidx(1:nl)$ to be assigned to the global indices $vl$. \\ Scope:{\bf local}.\\ From 96d224c91283694475de8bbf0078777b2e1c40d5 Mon Sep 17 00:00:00 2001 From: Salvatore Filippone Date: Mon, 23 Apr 2018 07:51:42 +0100 Subject: [PATCH 7/7] Updated changelog --- Changelog | 2 ++ 1 file changed, 2 insertions(+) diff --git a/Changelog b/Changelog index 14021522..4790da3d 100644 --- a/Changelog +++ b/Changelog @@ -1,5 +1,7 @@ Changelog. A lot less detailed than usual, at least for past history. +2018/04/23: Change default for CDALL with VL. New GLOBAL argument for + reductions. 2018/04/15: Fixed pargen benchmark programs. Made MOLD mandatory. 2018/01/10: Updated docs. 2017/12/15: Fixed preconditioner build.
    $x_i, y$ Subroutine