diff --git a/base/modules/psb_tools_mod.f90 b/base/modules/psb_tools_mod.f90 index cb6d7d3c..746e1ceb 100644 --- a/base/modules/psb_tools_mod.f90 +++ b/base/modules/psb_tools_mod.f90 @@ -586,9 +586,116 @@ Module psb_tools_mod module procedure psb_dlinmap_asb, psb_zlinmap_asb end interface + interface psb_is_owned + module procedure psb_is_owned + end interface + + interface psb_is_local + module procedure psb_is_local + end interface + + interface psb_owned_index + module procedure psb_owned_index, psb_owned_index_v + end interface + + interface psb_local_index + module procedure psb_local_index, psb_local_index_v + end interface contains + function psb_is_owned(idx,desc) + use psb_descriptor_type + implicit none + integer, intent(in) :: idx + type(psb_desc_type), intent(in) :: desc + logical :: psb_is_owned + logical :: res + integer :: info + + call psb_owned_index(res,idx,desc,info) + if (info /= 0) res=.false. + psb_is_owned = res + end function psb_is_owned + + function psb_is_local(idx,desc) + use psb_descriptor_type + implicit none + integer, intent(in) :: idx + type(psb_desc_type), intent(in) :: desc + logical :: psb_is_local + logical :: res + integer :: info + + call psb_local_index(res,idx,desc,info) + if (info /= 0) res=.false. + psb_is_local = res + end function psb_is_local + + subroutine psb_owned_index(res,idx,desc,info) + use psb_descriptor_type + implicit none + integer, intent(in) :: idx + type(psb_desc_type), intent(in) :: desc + logical, intent(out) :: res + integer, intent(out) :: info + + integer :: lx + + call psb_glob_to_loc(idx,lx,desc,info,iact='I',owned=.true.) + + res = (lx>0) + end subroutine psb_owned_index + + subroutine psb_owned_index_v(res,idx,desc,info) + use psb_descriptor_type + implicit none + integer, intent(in) :: idx(:) + type(psb_desc_type), intent(in) :: desc + logical, intent(out) :: res(:) + integer, intent(out) :: info + integer, allocatable :: lx(:) + + allocate(lx(size(idx)),stat=info) + res=.false. + if (info /= 0) return + call psb_glob_to_loc(idx,lx,desc,info,iact='I',owned=.true.) + + res = (lx>0) + end subroutine psb_owned_index_v + + subroutine psb_local_index(res,idx,desc,info) + use psb_descriptor_type + implicit none + integer, intent(in) :: idx + type(psb_desc_type), intent(in) :: desc + logical, intent(out) :: res + integer, intent(out) :: info + + integer :: lx + + call psb_glob_to_loc(idx,lx,desc,info,iact='I',owned=.false.) + + res = (lx>0) + end subroutine psb_local_index + + subroutine psb_local_index_v(res,idx,desc,info) + use psb_descriptor_type + implicit none + integer, intent(in) :: idx(:) + type(psb_desc_type), intent(in) :: desc + logical, intent(out) :: res(:) + integer, intent(out) :: info + integer, allocatable :: lx(:) + + allocate(lx(size(idx)),stat=info) + res=.false. + if (info /= 0) return + call psb_glob_to_loc(idx,lx,desc,info,iact='I',owned=.false.) + + res = (lx>0) + end subroutine psb_local_index_v + subroutine psb_get_boundary(bndel,desc,info) use psb_descriptor_type use psi_mod diff --git a/base/serial/psb_dcoins.f90 b/base/serial/psb_dcoins.f90 index c7434963..66853d53 100644 --- a/base/serial/psb_dcoins.f90 +++ b/base/serial/psb_dcoins.f90 @@ -494,6 +494,10 @@ contains integer, intent(out) :: info integer, intent(in), optional :: ng,gtl(:) integer :: i,ir,ic + character(len=20) :: name, ch_err + + + name='psb_inner_upd' if (present(gtl)) then if (.not.present(ng)) then @@ -504,6 +508,7 @@ contains do i=1, nz nza = nza + 1 if (nza>maxsz) then + call psb_errpush(50,name,i_err=(/7,maxsz,5,0,nza /)) info = -71 return endif diff --git a/base/serial/psb_update_mod.f90 b/base/serial/psb_update_mod.f90 index db74f090..dc7e987c 100644 --- a/base/serial/psb_update_mod.f90 +++ b/base/serial/psb_update_mod.f90 @@ -62,11 +62,11 @@ contains type(psb_dspmat_type), intent(inout) :: a integer, intent(in) :: nz, imin,imax,jmin,jmax,nzl - integer, intent(in) :: ia(*),ja(*) + integer, intent(in) :: ia(:),ja(:) integer, intent(inout) :: nza - real(psb_dpk_), intent(in) :: val(*) + real(psb_dpk_), intent(in) :: val(:) integer, intent(out) :: info - integer, intent(in), optional :: ng,gtl(*) + integer, intent(in), optional :: ng,gtl(:) info = 0 @@ -107,11 +107,11 @@ contains type(psb_zspmat_type), intent(inout) :: a integer, intent(in) :: nz, imin,imax,jmin,jmax,nzl - integer, intent(in) :: ia(*),ja(*) + integer, intent(in) :: ia(:),ja(:) integer, intent(inout) :: nza - complex(psb_dpk_), intent(in) :: val(*) + complex(psb_dpk_), intent(in) :: val(:) integer, intent(out) :: info - integer, intent(in), optional :: ng,gtl(*) + integer, intent(in), optional :: ng,gtl(:) info = 0 @@ -170,11 +170,11 @@ contains type(psb_dspmat_type), intent(inout) :: a integer, intent(in) :: nz, imin,imax,jmin,jmax,nzl - integer, intent(in) :: ia(*),ja(*) + integer, intent(in) :: ia(:),ja(:) integer, intent(inout) :: nza - real(psb_dpk_), intent(in) :: val(*) + real(psb_dpk_), intent(in) :: val(:) integer, intent(out) :: info - integer, intent(in), optional :: ng,gtl(*) + integer, intent(in), optional :: ng,gtl(:) integer :: debug_level, debug_unit character(len=20) :: name='d_csr_srch_upd' @@ -211,51 +211,20 @@ contains i2 = a%ia2(ir+1) nc=i2-i1 - - if (.true.) then - call issrch(ip,ic,nc,a%ia1(i1:i2-1)) - if (ip>0) then - a%aspk(i1+ip-1) = val(i) - else - if (debug_level >= psb_debug_serial_) & - & write(debug_unit,*) trim(name),& - & ': Was searching ',ic,' in: ',i1,i2,& - & ' : ',a%ia1(i1:i2-1) - info = i - return - end if - + call ibsrch(ip,ic,nc,a%ia1(i1:i2-1)) + if (ip>0) then + a%aspk(i1+ip-1) = val(i) else -!!$ - ip = -1 - lb = i1 - ub = i2-1 - do - if (lb > ub) exit - m = (lb+ub)/2 - if (ic == a%ia1(m)) then - ip = m - lb = ub + 1 - else if (ic < a%ia1(m)) then - ub = m-1 - else - lb = m + 1 - end if - enddo - - if (ip>0) then - a%aspk(ip) = val(i) - else - if (debug_level >= psb_debug_serial_) & - & write(debug_unit,*) trim(name),& - & ': Was searching ',ic,' in: ',i1,i2,& - & ' : ',a%ia1(i1:i2-1) - info = i - return - end if - + if (debug_level >= psb_debug_serial_) & + & write(debug_unit,*) trim(name),& + & ': Was searching ',ic,' in: ',i1,i2,& + & ' : ',a%ia1(i1:i2-1) + info = i + return end if + else + if (debug_level >= psb_debug_serial_) & & write(debug_unit,*) trim(name),& & ': Discarding row that does not belong to us.' @@ -277,7 +246,7 @@ contains i1 = a%ia2(ir) i2 = a%ia2(ir+1) nc = i2-i1 - call issrch(ip,ic,nc,a%ia1(i1:i2-1)) + call ibsrch(ip,ic,nc,a%ia1(i1:i2-1)) if (ip>0) then a%aspk(i1+ip-1) = a%aspk(i1+ip-1) + val(i) else @@ -322,48 +291,18 @@ contains i2 = a%ia2(ir+1) nc=i2-i1 - - if (.true.) then - call issrch(ip,ic,nc,a%ia1(i1:i2-1)) - if (ip>0) then - a%aspk(i1+ip-1) = val(i) - else - if (debug_level >= psb_debug_serial_) & - & write(debug_unit,*) trim(name),& - & ': Was searching ',ic,' in: ',i1,i2,& - & ' : ',a%ia1(i1:i2-1) - info = i - return - end if - + call ibsrch(ip,ic,nc,a%ia1(i1:i2-1)) + if (ip>0) then + a%aspk(i1+ip-1) = val(i) else - ip = -1 - lb = i1 - ub = i2-1 - do - if (lb > ub) exit - m = (lb+ub)/2 - if (ic == a%ia1(m)) then - ip = m - lb = ub + 1 - else if (ic < a%ia1(m)) then - ub = m-1 - else - lb = m + 1 - end if - enddo - - if (ip>0) then - a%aspk(ip) = val(i) - else - if (debug_level >= psb_debug_serial_) & - & write(debug_unit,*) trim(name),& - & ': Was searching ',ic,' in: ',i1,i2,& - & ' : ',a%ia1(i1:i2-1) - info = i - return - end if + if (debug_level >= psb_debug_serial_) & + & write(debug_unit,*) trim(name),& + & ': Was searching ',ic,' in: ',i1,i2,& + & ' : ',a%ia1(i1:i2-1) + info = i + return end if + else if (debug_level >= psb_debug_serial_) & & write(debug_unit,*) trim(name),& @@ -383,7 +322,7 @@ contains i1 = a%ia2(ir) i2 = a%ia2(ir+1) nc = i2-i1 - call issrch(ip,ic,nc,a%ia1(i1:i2-1)) + call ibsrch(ip,ic,nc,a%ia1(i1:i2-1)) if (ip>0) then a%aspk(i1+ip-1) = a%aspk(i1+ip-1) + val(i) else @@ -419,11 +358,11 @@ contains type(psb_dspmat_type), intent(inout) :: a integer, intent(in) :: nz, imin,imax,jmin,jmax,nzl - integer, intent(in) :: ia(*),ja(*) + integer, intent(in) :: ia(:),ja(:) integer, intent(inout) :: nza - real(psb_dpk_), intent(in) :: val(*) + real(psb_dpk_), intent(in) :: val(:) integer, intent(out) :: info - integer, intent(in), optional :: ng,gtl(*) + integer, intent(in), optional :: ng,gtl(:) integer :: i,ir,ic, ilr, ilc, ip, & & i1,i2,nc,nnz,dupl integer :: debug_level, debug_unit @@ -644,11 +583,11 @@ contains type(psb_dspmat_type), intent(inout), target :: a integer, intent(in) :: nz, imin,imax,jmin,jmax,nzl - integer, intent(in) :: ia(*),ja(*) + integer, intent(in) :: ia(:),ja(:) integer, intent(inout) :: nza - real(psb_dpk_), intent(in) :: val(*) + real(psb_dpk_), intent(in) :: val(:) integer, intent(out) :: info - integer, intent(in), optional :: ng,gtl(*) + integer, intent(in), optional :: ng,gtl(:) integer, pointer :: ia1(:), ia2(:), ia3(:),& & ja_(:), ka_(:) @@ -882,11 +821,11 @@ contains type(psb_zspmat_type), intent(inout) :: a integer, intent(in) :: nz, imin,imax,jmin,jmax,nzl - integer, intent(in) :: ia(*),ja(*) + integer, intent(in) :: ia(:),ja(:) integer, intent(inout) :: nza - complex(psb_dpk_), intent(in) :: val(*) + complex(psb_dpk_), intent(in) :: val(:) integer, intent(out) :: info - integer, intent(in), optional :: ng,gtl(*) + integer, intent(in), optional :: ng,gtl(:) integer :: i,ir,ic, ilr, ilc, ip, & & i1,i2,nc,lb,ub,m,dupl @@ -924,50 +863,18 @@ contains i2 = a%ia2(ir+1) nc=i2-i1 - - if (.true.) then - call issrch(ip,ic,nc,a%ia1(i1:i2-1)) - if (ip>0) then - a%aspk(i1+ip-1) = val(i) - else - if (debug_level >= psb_debug_serial_) & - & write(debug_unit,*) trim(name),& - & ': Was searching ',ic,' in: ',i1,i2,& - & ' : ',a%ia1(i1:i2-1) - info = i - return - end if - + call ibsrch(ip,ic,nc,a%ia1(i1:i2-1)) + if (ip>0) then + a%aspk(i1+ip-1) = val(i) else -!!$ - ip = -1 - lb = i1 - ub = i2-1 - do - if (lb > ub) exit - m = (lb+ub)/2 - if (ic == a%ia1(m)) then - ip = m - lb = ub + 1 - else if (ic < a%ia1(m)) then - ub = m-1 - else - lb = m + 1 - end if - enddo - - if (ip>0) then - a%aspk(ip) = val(i) - else - if (debug_level >= psb_debug_serial_) & - & write(debug_unit,*) trim(name),& - & ': Was searching ',ic,' in: ',i1,i2,& - & ' : ',a%ia1(i1:i2-1) - info = i - return - end if - + if (debug_level >= psb_debug_serial_) & + & write(debug_unit,*) trim(name),& + & ': Was searching ',ic,' in: ',i1,i2,& + & ' : ',a%ia1(i1:i2-1) + info = i + return end if + else if (debug_level >= psb_debug_serial_) & & write(debug_unit,*) trim(name),& @@ -1035,48 +942,18 @@ contains i2 = a%ia2(ir+1) nc=i2-i1 - - if (.true.) then - call issrch(ip,ic,nc,a%ia1(i1:i2-1)) - if (ip>0) then - a%aspk(i1+ip-1) = val(i) - else - if (debug_level >= psb_debug_serial_) & - & write(debug_unit,*) trim(name),& - & ': Was searching ',ic,' in: ',i1,i2,& - & ' : ',a%ia1(i1:i2-1) - info = i - return - end if - + call ibsrch(ip,ic,nc,a%ia1(i1:i2-1)) + if (ip>0) then + a%aspk(i1+ip-1) = val(i) else - ip = -1 - lb = i1 - ub = i2-1 - do - if (lb > ub) exit - m = (lb+ub)/2 - if (ic == a%ia1(m)) then - ip = m - lb = ub + 1 - else if (ic < a%ia1(m)) then - ub = m-1 - else - lb = m + 1 - end if - enddo - - if (ip>0) then - a%aspk(ip) = val(i) - else - if (debug_level >= psb_debug_serial_) & - & write(debug_unit,*) trim(name),& - & ': Was searching ',ic,' in: ',i1,i2,& - & ' : ',a%ia1(i1:i2-1) - info = i - return - end if + if (debug_level >= psb_debug_serial_) & + & write(debug_unit,*) trim(name),& + & ': Was searching ',ic,' in: ',i1,i2,& + & ' : ',a%ia1(i1:i2-1) + info = i + return end if + else if (debug_level >= psb_debug_serial_) & & write(debug_unit,*) trim(name),& @@ -1096,7 +973,7 @@ contains i1 = a%ia2(ir) i2 = a%ia2(ir+1) nc = i2-i1 - call issrch(ip,ic,nc,a%ia1(i1:i2-1)) + call ibsrch(ip,ic,nc,a%ia1(i1:i2-1)) if (ip>0) then a%aspk(i1+ip-1) = a%aspk(i1+ip-1) + val(i) else @@ -1132,11 +1009,11 @@ contains type(psb_zspmat_type), intent(inout) :: a integer, intent(in) :: nz, imin,imax,jmin,jmax,nzl - integer, intent(in) :: ia(*),ja(*) + integer, intent(in) :: ia(:),ja(:) integer, intent(inout) :: nza - complex(psb_dpk_), intent(in) :: val(*) + complex(psb_dpk_), intent(in) :: val(:) integer, intent(out) :: info - integer, intent(in), optional :: ng,gtl(*) + integer, intent(in), optional :: ng,gtl(:) integer :: i,ir,ic, ilr, ilc, ip, & & i1,i2,nc,nnz,dupl integer :: debug_level, debug_unit @@ -1360,11 +1237,11 @@ contains type(psb_zspmat_type), intent(inout), target :: a integer, intent(in) :: nz, imin,imax,jmin,jmax,nzl - integer, intent(in) :: ia(*),ja(*) + integer, intent(in) :: ia(:),ja(:) integer, intent(inout) :: nza - complex(psb_dpk_), intent(in) :: val(*) + complex(psb_dpk_), intent(in) :: val(:) integer, intent(out) :: info - integer, intent(in), optional :: ng,gtl(*) + integer, intent(in), optional :: ng,gtl(:) integer, pointer :: ia1(:), ia2(:), ia3(:),& & ja_(:), ka_(:) diff --git a/base/serial/psb_zcoins.f90 b/base/serial/psb_zcoins.f90 index bfa37a60..5a2828c7 100644 --- a/base/serial/psb_zcoins.f90 +++ b/base/serial/psb_zcoins.f90 @@ -29,9 +29,30 @@ !!$ POSSIBILITY OF SUCH DAMAGE. !!$ !!$ -! File: psbzcoins.f90 - ! Subroutine: - ! Parameters: +! File: psb_zcoins.f90 +! Subroutine: psb_zcoins +! Takes a cloud of coefficients and inserts them into a sparse matrix. +! This subroutine is the serial, inner counterpart to the outer, user-level +! psb_spins. +! +! Arguments: +! +! nz - integer, input The number of points to insert. +! ia(:) - integer, input The row indices of the coefficients. +! ja(:) - integer, input The column indices of the coefficients. +! val(:) - complex, input The values of the coefficients to be inserted. +! a - type(psb_zspmat_type), inout The sparse destination matrix. +! imin - integer, input The minimum valid row index +! imax - integer, input The maximum valid row index +! jmin - integer, input The minimum valid col index +! jmax - integer, input The maximum valid col index +! info - integer, output Return code. +! gtl(:) - integer, input,optional An index mapping to be applied +! default: identity +! rebuild - logical, input, optional Rebuild in case of update +! finding a new index. Default: false. +! Not fully tested. +! subroutine psb_zcoins(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl,rebuild) use psb_spmat_type @@ -54,7 +75,7 @@ subroutine psb_zcoins(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl,rebuild) character(len=5) :: ufida integer :: ng, nza, isza,spstate, & & ip1, nzl, err_act, int_err(5), iupd, irst - logical, parameter :: debug=.false. + integer :: debug_level, debug_unit logical :: rebuild_ character(len=20) :: name, ch_err type(psb_zspmat_type) :: tmp @@ -62,6 +83,8 @@ subroutine psb_zcoins(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl,rebuild) name='psb_zcoins' info = 0 call psb_erractionsave(err_act) + debug_unit = psb_get_debug_unit() + debug_level = psb_get_debug_level() info = 0 if (nz <= 0) then @@ -140,9 +163,9 @@ subroutine psb_zcoins(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl,rebuild) call psb_errpush(4013,name,a_err=ch_err,i_err=(/info,0,0,0,0/)) goto 9999 endif - if (debug) then + if (debug_level >= psb_debug_serial_) then if ((nza - a%infoa(psb_nnz_)) /= nz) then - write(0,*) 'PSB_COINS: insert discarded items ' + write(debug_unit,*) trim(name),': insert discarded items ' end if end if if ((nza - psb_sp_getifld(psb_nnz_,a,info)) /= nz) then @@ -172,9 +195,9 @@ subroutine psb_zcoins(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl,rebuild) call psb_errpush(4013,name,a_err=ch_err,i_err=(/info,0,0,0,0/)) goto 9999 endif - if (debug) then + if (debug_level >= psb_debug_serial_) then if ((nza - a%ia2(ip1+psb_nnz_)) /= nz) then - write(0,*) 'PSB_COINS: update discarded items ' + write(debug_unit,*) trim(name),': update discarded items ' end if end if @@ -185,7 +208,8 @@ subroutine psb_zcoins(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl,rebuild) a%ia2(ip1+psb_nnz_) = nza end select - if (debug) write(0,*) 'From COINS(UPD) : NZA:',nza + if (debug_level >= psb_debug_serial_) & + & write(debug_unit,*) trim(name),': (UPD) : NZA:',nza case (psb_upd_srch_) @@ -194,8 +218,10 @@ subroutine psb_zcoins(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl,rebuild) if (info > 0) then if (rebuild_) then - if (debug) write(0,*)& - & 'COINS: Going through rebuild_ fingers crossed!' + if (debug_level >= psb_debug_serial_) & + & write(debug_unit,*)& + & trim(name),& + & ': Going through rebuild_ fingers crossed!' irst = info call psb_nullify_sp(tmp) call psb_spcnv(a,tmp,info,afmt='coo') @@ -206,9 +232,9 @@ subroutine psb_zcoins(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl,rebuild) goto 9999 endif call psb_sp_setifld(psb_spmat_bld_,psb_state_,tmp,info) - if (debug) then - write(0,*) 'COINS Rebuild: size',tmp%infoa(psb_nnz_) ,irst - endif + if (debug_level >= psb_debug_serial_) & + & write(debug_unit,*) trim(name),& + & ': Rebuild size',tmp%infoa(psb_nnz_) ,irst call psb_sp_transfer(tmp,a,info) if(info /= izero) then info=4010 @@ -225,8 +251,9 @@ subroutine psb_zcoins(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl,rebuild) goto 9999 endif - if (debug) write(0,*)& - & 'COINS: Reinserting',a%fida,nza,isza,irst,nz + if (debug_level >= psb_debug_serial_) write(debug_unit,*)& + & trim(name),': Reinserting',a%fida,nza,isza,irst,nz + if ((nza+nz)>isza) then call psb_sp_reall(a,max(nza+nz,int(1.5*isza)),info) if(info /= izero) then @@ -245,7 +272,7 @@ subroutine psb_zcoins(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl,rebuild) ch_err='psb_inner_ins' call psb_errpush(4013,name,a_err=ch_err,i_err=(/info,0,0,0,0/)) endif - + call psb_sp_setifld(nza,psb_del_bnd_,a,info) call psb_sp_setifld(nza,psb_nnz_,a,info) end if @@ -321,14 +348,13 @@ subroutine psb_zcoins(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl,rebuild) goto 9999 endif - if (debug) then + if (debug_level >= psb_debug_serial_) then if ((nza - a%infoa(psb_nnz_)) /= nz) then - write(0,*) 'PSB_COINS: insert discarded items ' + write(debug_unit,*) trim(name),': insert discarded items ' end if end if if ((nza - psb_sp_getifld(psb_nnz_,a,info)) /= nz) then call psb_sp_setifld(nza,psb_del_bnd_,a,info) -!!$ write(0,*) 'Settind del_bnd_ 2: ',nza endif call psb_sp_setifld(nza,psb_nnz_,a,info) @@ -350,14 +376,15 @@ subroutine psb_zcoins(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl,rebuild) goto 9999 endif - if (debug) then + if (debug_level >= psb_debug_serial_) then if ((nza - a%ia2(ip1+psb_nnz_)) /= nz) then - write(0,*) 'PSB_COINS: update discarded items ' + write(debug_unit,*) trim(name),': update discarded items ' end if end if a%ia2(ip1+psb_nnz_) = nza - if (debug) write(0,*) 'From COINS(UPD) : NZA:',nza + if (debug_level >= psb_debug_serial_)& + & write(debug_unit,*) trim(name),':(UPD) : NZA:',nza case (psb_upd_srch_) @@ -366,15 +393,17 @@ subroutine psb_zcoins(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl,rebuild) if (info > 0) then if (rebuild_) then - if (debug) write(0,*)& - & 'COINS: Going through rebuild_ fingers crossed!' + if (debug_level >= psb_debug_serial_) & + & write(debug_unit,*)& + & trim(name),& + & ': Going through rebuild_ fingers crossed!' irst = info call psb_nullify_sp(tmp) call psb_spcnv(a,tmp,info,afmt='coo') call psb_sp_setifld(psb_spmat_bld_,psb_state_,tmp,info) - if (debug) then - write(0,*) 'COINS Rebuild: size',tmp%infoa(psb_nnz_) ,irst - endif + if (debug_level >= psb_debug_serial_) & + & write(debug_unit,*) trim(name),& + & ': Rebuild size',tmp%infoa(psb_nnz_) ,irst call psb_sp_transfer(tmp,a,info) call psb_sp_info(psb_nztotreq_,a,nza,info) call psb_sp_info(psb_nzsizereq_,a,isza,info) @@ -385,8 +414,9 @@ subroutine psb_zcoins(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl,rebuild) goto 9999 endif - if (debug) write(0,*)& - & 'COINS: Reinserting',a%fida,nza,isza + if (debug_level >= psb_debug_serial_) write(debug_unit,*)& + & trim(name),': Reinserting',a%fida,nza,isza + if ((nza+nz)>isza) then call psb_sp_reall(a,max(nza+nz,int(1.5*isza)),info) if(info /= izero) then @@ -405,7 +435,7 @@ subroutine psb_zcoins(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl,rebuild) ch_err='psb_inner_ins' call psb_errpush(4013,name,a_err=ch_err,i_err=(/info,0,0,0,0/)) endif - + call psb_sp_setifld(nza,psb_del_bnd_,a,info) call psb_sp_setifld(nza,psb_nnz_,a,info) end if @@ -438,6 +468,7 @@ subroutine psb_zcoins(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl,rebuild) endif + call psb_erractionrestore(err_act) return @@ -463,6 +494,10 @@ contains integer, intent(out) :: info integer, intent(in), optional :: ng,gtl(:) integer :: i,ir,ic + character(len=20) :: name, ch_err + + + name='psb_inner_upd' if (present(gtl)) then if (.not.present(ng)) then @@ -473,7 +508,7 @@ contains do i=1, nz nza = nza + 1 if (nza>maxsz) then - write(0,*) 'Out of bounds in INNER_UPD ',nza,maxsz + call psb_errpush(50,name,i_err=(/7,maxsz,5,0,nza /)) info = -71 return endif diff --git a/docs/pdf/toolsrout.tex b/docs/pdf/toolsrout.tex index 81cf607f..886dee87 100644 --- a/docs/pdf/toolsrout.tex +++ b/docs/pdf/toolsrout.tex @@ -1058,11 +1058,6 @@ An integer value; 0 means no error has been detected. \item The default \verb|I|gnore means that the negative output is the only action taken on an out-of-range input. \end{enumerate} - - -% -%% psb_loc_to_glob %% -% \subroutine{psb\_loc\_to\_glob}{Local to global indices conversion} \syntax{call psb\_loc\_to\_glob}{x, y, desc\_a, info, iact} @@ -1113,6 +1108,180 @@ An integer value; 0 means no error has been detected. +% +%% psb_loc_to_glob %% +% +\subroutine{psb\_is\_owned}{} + +\syntax{call psb\_is\_owned}{x, desc\_a} + +\begin{description} +\item[Type:] Asynchronous. +\item[\bf On Entry] +\item[x] Integer index.\\ +Scope: {\bf local} \\ +Type: {\bf required}\\ +Intent: {\bf in}.\\ +Specified as: a scalar integer.\\ +\item[desc\_a] the communication descriptor.\\ +Scope:{\bf local}.\\ +Type:{\bf required}.\\ +Intent: {\bf in}.\\ +Specified as: a structured data of type \descdata. +\end{description} + +\begin{description} +\item[\bf On Return] +\item[Function value] A logical mask which is true if + $x$ is owned by the current process +Scope: {\bf local} \\ +Type: {\bf required}\\ +Intent: {\bf out}.\\ +\end{description} + + +\section*{Notes} +\begin{enumerate} +\item This routine returns a \verb|.true.| value for an index + that is strictly owned by the current process, excluding the halo + indices +\end{enumerate} + + +\subroutine{psb\_owned\_index}{} + +\syntax{call psb\_owned\_index}{y, x, desc\_a, info} + +\begin{description} +\item[Type:] Asynchronous. +\item[\bf On Entry] +\item[x] Integer indices.\\ +Scope: {\bf local} \\ +Type: {\bf required}\\ +Intent: {\bf in, inout}.\\ +Specified as: a scalar or a rank one integer array.\\ +\item[desc\_a] the communication descriptor.\\ +Scope:{\bf local}.\\ +Type:{\bf required}.\\ +Intent: {\bf in}.\\ +Specified as: a structured data of type \descdata. +\item[iact] specifies action to be taken in case of range errors. +Scope: {\bf global} \\ +Type: {\bf optional}\\ +Intent: {\bf in}.\\ +Specified as: a character variable \verb|I|gnore, \verb|W|arning or +\verb|A|bort, default \verb|I|gnore. +\end{description} + +\begin{description} +\item[\bf On Return] +\item[y] A logical mask which is true for all corresponding entries of + $x$ that are owned by the current process +Scope: {\bf local} \\ +Type: {\bf required}\\ +Intent: {\bf out}.\\ +Specified as: a scalar or rank one logical array. +\item[info] Error code.\\ +Scope: {\bf local} \\ +Type: {\bf required} \\ +Intent: {\bf out}.\\ +An integer value; 0 means no error has been detected. +\end{description} + + +\section*{Notes} +\begin{enumerate} +\item This routine returns a \verb|.true.| value for those indices + that are strictly owned by the current process, excluding the halo + indices +\end{enumerate} + + +\subroutine{psb\_is\_local}{} + +\syntax{call psb\_is\_local}{x, desc\_a} + +\begin{description} +\item[Type:] Asynchronous. +\item[\bf On Entry] +\item[x] Integer index.\\ +Scope: {\bf local} \\ +Type: {\bf required}\\ +Intent: {\bf in}.\\ +Specified as: a scalar integer.\\ +\item[desc\_a] the communication descriptor.\\ +Scope:{\bf local}.\\ +Type:{\bf required}.\\ +Intent: {\bf in}.\\ +Specified as: a structured data of type \descdata. +\end{description} + +\begin{description} +\item[\bf On Return] +\item[Function value] A logical mask which is true if + $x$ is local to the current process +Scope: {\bf local} \\ +Type: {\bf required}\\ +Intent: {\bf out}.\\ +\end{description} + + +\section*{Notes} +\begin{enumerate} +\item This routine returns a \verb|.true.| value for an index + that is local to the current process, including the halo + indices +\end{enumerate} + +\subroutine{psb\_local\_index}{} + +\syntax{call psb\_local\_index}{y, x, desc\_a, info} + +\begin{description} +\item[Type:] Asynchronous. +\item[\bf On Entry] +\item[x] Integer indices.\\ +Scope: {\bf local} \\ +Type: {\bf required}\\ +Intent: {\bf in, inout}.\\ +Specified as: a scalar or a rank one integer array.\\ +\item[desc\_a] the communication descriptor.\\ +Scope:{\bf local}.\\ +Type:{\bf required}.\\ +Intent: {\bf in}.\\ +Specified as: a structured data of type \descdata. +\item[iact] specifies action to be taken in case of range errors. +Scope: {\bf global} \\ +Type: {\bf optional}\\ +Intent: {\bf in}.\\ +Specified as: a character variable \verb|I|gnore, \verb|W|arning or +\verb|A|bort, default \verb|I|gnore. +\end{description} + +\begin{description} +\item[\bf On Return] +\item[y] A logical mask which is true for all corresponding entries of + $x$ that are local to the current process +Scope: {\bf local} \\ +Type: {\bf required}\\ +Intent: {\bf out}.\\ +Specified as: a scalar or rank one logical array. +\item[info] Error code.\\ +Scope: {\bf local} \\ +Type: {\bf required} \\ +Intent: {\bf out}.\\ +An integer value; 0 means no error has been detected. +\end{description} + + +\section*{Notes} +\begin{enumerate} +\item This routine returns a \verb|.true.| value for those indices + that are local to the current process, including the halo + indices. +\end{enumerate} + + % %% psb_ins %% diff --git a/docs/userguide.pdf b/docs/userguide.pdf index 51f53f7b..f76eef93 100644 --- a/docs/userguide.pdf +++ b/docs/userguide.pdf @@ -369,259 +369,283 @@ endobj << /S /GoTo /D (section*.106) >> endobj 252 0 obj -(psb\137get\137boundary) +(psb\137is\137owned) endobj 253 0 obj << /S /GoTo /D (section*.109) >> endobj 256 0 obj -(psb\137get\137overlap) +(psb\137owned\137index) endobj 257 0 obj << /S /GoTo /D (section*.112) >> endobj 260 0 obj -(psb\137sp\137getrow) +(psb\137is\137local) endobj 261 0 obj << /S /GoTo /D (section*.115) >> endobj 264 0 obj -(psb\137sizeof) +(psb\137local\137index) endobj 265 0 obj -<< /S /GoTo /D (section*.117) >> +<< /S /GoTo /D (section*.118) >> endobj 268 0 obj -(Sorting utilities) +(psb\137get\137boundary) endobj 269 0 obj -<< /S /GoTo /D (section*.118) >> +<< /S /GoTo /D (section*.121) >> endobj 272 0 obj -(psb\137msort) +(psb\137get\137overlap) endobj 273 0 obj -<< /S /GoTo /D (section*.119) >> +<< /S /GoTo /D (section*.124) >> endobj 276 0 obj -(psb\137qsort) +(psb\137sp\137getrow) endobj 277 0 obj -<< /S /GoTo /D (section*.120) >> +<< /S /GoTo /D (section*.127) >> endobj 280 0 obj -(psb\137hsort) +(psb\137sizeof) endobj 281 0 obj -<< /S /GoTo /D (section.7) >> +<< /S /GoTo /D (section*.129) >> endobj 284 0 obj -(7 Parallel environment routines) +(Sorting utilities) endobj 285 0 obj -<< /S /GoTo /D (section*.123) >> +<< /S /GoTo /D (section*.130) >> endobj 288 0 obj -(psb\137init) +(psb\137msort) endobj 289 0 obj -<< /S /GoTo /D (section*.126) >> +<< /S /GoTo /D (section*.131) >> endobj 292 0 obj -(psb\137info) +(psb\137qsort) endobj 293 0 obj -<< /S /GoTo /D (section*.129) >> +<< /S /GoTo /D (section*.132) >> endobj 296 0 obj -(psb\137exit) +(psb\137hsort) endobj 297 0 obj -<< /S /GoTo /D (section*.132) >> +<< /S /GoTo /D (section.7) >> endobj 300 0 obj -(psb\137get\137mpicomm) +(7 Parallel environment routines) endobj 301 0 obj -<< /S /GoTo /D (section*.134) >> +<< /S /GoTo /D (section*.135) >> endobj 304 0 obj -(psb\137get\137rank) +(psb\137init) endobj 305 0 obj -<< /S /GoTo /D (section*.136) >> +<< /S /GoTo /D (section*.138) >> endobj 308 0 obj -(psb\137wtime) +(psb\137info) endobj 309 0 obj -<< /S /GoTo /D (section*.138) >> +<< /S /GoTo /D (section*.141) >> endobj 312 0 obj -(psb\137barrier) +(psb\137exit) endobj 313 0 obj -<< /S /GoTo /D (section*.140) >> +<< /S /GoTo /D (section*.144) >> endobj 316 0 obj -(psb\137abort) +(psb\137get\137mpicomm) endobj 317 0 obj -<< /S /GoTo /D (section*.142) >> +<< /S /GoTo /D (section*.146) >> endobj 320 0 obj -(psb\137bcast) +(psb\137get\137rank) endobj 321 0 obj -<< /S /GoTo /D (section*.144) >> +<< /S /GoTo /D (section*.148) >> endobj 324 0 obj -(psb\137sum) +(psb\137wtime) endobj 325 0 obj -<< /S /GoTo /D (section*.147) >> +<< /S /GoTo /D (section*.150) >> endobj 328 0 obj -(psb\137max) +(psb\137barrier) endobj 329 0 obj -<< /S /GoTo /D (section*.150) >> +<< /S /GoTo /D (section*.152) >> endobj 332 0 obj -(psb\137min) +(psb\137abort) endobj 333 0 obj -<< /S /GoTo /D (section*.153) >> +<< /S /GoTo /D (section*.154) >> endobj 336 0 obj -(psb\137amx) +(psb\137bcast) endobj 337 0 obj << /S /GoTo /D (section*.156) >> endobj 340 0 obj -(psb\137amn) +(psb\137sum) endobj 341 0 obj << /S /GoTo /D (section*.159) >> endobj 344 0 obj -(psb\137snd) +(psb\137max) endobj 345 0 obj << /S /GoTo /D (section*.162) >> endobj 348 0 obj -(psb\137rcv) +(psb\137min) endobj 349 0 obj -<< /S /GoTo /D (section.8) >> +<< /S /GoTo /D (section*.165) >> endobj 352 0 obj -(8 Error handling) +(psb\137amx) endobj 353 0 obj -<< /S /GoTo /D (section*.165) >> +<< /S /GoTo /D (section*.168) >> endobj 356 0 obj -(psb\137errpush) +(psb\137amn) endobj 357 0 obj -<< /S /GoTo /D (section*.167) >> +<< /S /GoTo /D (section*.171) >> endobj 360 0 obj -(psb\137error) +(psb\137snd) endobj 361 0 obj -<< /S /GoTo /D (section*.169) >> +<< /S /GoTo /D (section*.174) >> endobj 364 0 obj -(psb\137set\137errverbosity) +(psb\137rcv) endobj 365 0 obj -<< /S /GoTo /D (section*.171) >> +<< /S /GoTo /D (section.8) >> endobj 368 0 obj -(psb\137set\137erraction) +(8 Error handling) endobj 369 0 obj -<< /S /GoTo /D (section.9) >> +<< /S /GoTo /D (section*.177) >> endobj 372 0 obj -(9 Utilities) +(psb\137errpush) endobj 373 0 obj -<< /S /GoTo /D (section*.173) >> +<< /S /GoTo /D (section*.179) >> endobj 376 0 obj -(hb\137read) +(psb\137error) endobj 377 0 obj -<< /S /GoTo /D (section*.175) >> +<< /S /GoTo /D (section*.181) >> endobj 380 0 obj -(hb\137write) +(psb\137set\137errverbosity) endobj 381 0 obj -<< /S /GoTo /D (section*.177) >> +<< /S /GoTo /D (section*.183) >> endobj 384 0 obj -(mm\137mat\137read) +(psb\137set\137erraction) endobj 385 0 obj -<< /S /GoTo /D (section*.179) >> +<< /S /GoTo /D (section.9) >> endobj 388 0 obj -(mm\137mat\137write) +(9 Utilities) endobj 389 0 obj -<< /S /GoTo /D (section.10) >> +<< /S /GoTo /D (section*.185) >> endobj 392 0 obj -(10 Preconditioner routines) +(hb\137read) endobj 393 0 obj -<< /S /GoTo /D (section*.181) >> +<< /S /GoTo /D (section*.187) >> endobj 396 0 obj -(psb\137precinit) +(hb\137write) endobj 397 0 obj -<< /S /GoTo /D (section*.184) >> +<< /S /GoTo /D (section*.189) >> endobj 400 0 obj -(psb\137precbld) +(mm\137mat\137read) endobj 401 0 obj -<< /S /GoTo /D (section*.186) >> +<< /S /GoTo /D (section*.191) >> endobj 404 0 obj -(psb\137precaply) +(mm\137mat\137write) endobj 405 0 obj -<< /S /GoTo /D (section*.188) >> +<< /S /GoTo /D (section.10) >> endobj 408 0 obj -(psb\137prec\137descr) +(10 Preconditioner routines) endobj 409 0 obj -<< /S /GoTo /D (section.11) >> +<< /S /GoTo /D (section*.193) >> endobj 412 0 obj -(11 Iterative Methods) +(psb\137precinit) endobj 413 0 obj -<< /S /GoTo /D (section*.190) >> +<< /S /GoTo /D (section*.196) >> endobj 416 0 obj -(psb\137krylov ) +(psb\137precbld) endobj 417 0 obj -<< /S /GoTo /D [418 0 R /Fit ] >> +<< /S /GoTo /D (section*.198) >> +endobj +420 0 obj +(psb\137precaply) endobj -420 0 obj << -/Length 1190 +421 0 obj +<< /S /GoTo /D (section*.200) >> +endobj +424 0 obj +(psb\137prec\137descr) +endobj +425 0 obj +<< /S /GoTo /D (section.11) >> +endobj +428 0 obj +(11 Iterative Methods) +endobj +429 0 obj +<< /S /GoTo /D (section*.202) >> +endobj +432 0 obj +(psb\137krylov ) +endobj +433 0 obj +<< /S /GoTo /D [434 0 R /Fit ] >> +endobj +436 0 obj << +/Length 1187 >> stream 1 0 0 1 99.8954 740.9981 cm @@ -666,7 +690,7 @@ ET 0 g 0 G 1 0 0 1 -350.8992 -405.1423 cm BT -/F29 9.9626 Tf 355.8805 405.1423 Td[(b)32(y)-383(Sal)-1(v)64(ator)1(e)-384(Fili)-1(pp)-32(on)1(e)]TJ 12.8891 -11.9552 Td[(and)-383(A)-1(lfredo)-383(Butt)-1(ar)1(i)]TJ/F8 9.9626 Tf -52.5191 -11.9551 Td[(Uni)1(v)28(e)-1(r)1(s)-1(it)28(y)-333(of)-333(Rome)-334(\134T)83(or)-333(V)83(ergata".)]TJ 90.7431 -24.8236 Td[(Mar)1(c)27(h)-333(5,)-333(2008)]TJ +/F29 9.9626 Tf 355.8805 405.1423 Td[(b)32(y)-383(Sal)-1(v)64(ator)1(e)-384(Fili)-1(pp)-32(on)1(e)]TJ 12.8891 -11.9552 Td[(and)-383(A)-1(lfredo)-383(Butt)-1(ar)1(i)]TJ/F8 9.9626 Tf -52.5191 -11.9551 Td[(Uni)1(v)28(e)-1(r)1(s)-1(it)28(y)-333(of)-333(Rome)-334(\134T)83(or)-333(V)83(ergata".)]TJ 91.0199 -24.8236 Td[(Apr)1(il)-333(15,)-333(2008)]TJ ET 1 0 0 1 99.8954 90.4377 cm 0 g 0 G @@ -674,27 +698,27 @@ ET 0 g 0 G endstream endobj -418 0 obj << +434 0 obj << /Type /Page -/Contents 420 0 R -/Resources 419 0 R +/Contents 436 0 R +/Resources 435 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 435 0 R +/Parent 451 0 R >> endobj -421 0 obj << -/D [418 0 R /XYZ 99.8954 740.9981 null] +437 0 obj << +/D [434 0 R /XYZ 99.8954 740.9981 null] >> endobj -422 0 obj << -/D [418 0 R /XYZ 99.8954 716.0915 null] +438 0 obj << +/D [434 0 R /XYZ 99.8954 716.0915 null] >> endobj 6 0 obj << -/D [418 0 R /XYZ 99.8954 716.0915 null] +/D [434 0 R /XYZ 99.8954 716.0915 null] >> endobj -419 0 obj << -/Font << /F18 425 0 R /F20 428 0 R /F29 431 0 R /F8 434 0 R >> +435 0 obj << +/Font << /F18 441 0 R /F20 444 0 R /F29 447 0 R /F8 450 0 R >> /ProcSet [ /PDF /Text ] >> endobj -438 0 obj << +454 0 obj << /Length 218 >> stream @@ -712,21 +736,21 @@ ET 0 g 0 G endstream endobj -437 0 obj << +453 0 obj << /Type /Page -/Contents 438 0 R -/Resources 436 0 R +/Contents 454 0 R +/Resources 452 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 435 0 R +/Parent 451 0 R >> endobj -439 0 obj << -/D [437 0 R /XYZ 150.7049 740.9981 null] +455 0 obj << +/D [453 0 R /XYZ 150.7049 740.9981 null] >> endobj -436 0 obj << -/Font << /F8 434 0 R >> +452 0 obj << +/Font << /F8 450 0 R >> /ProcSet [ /PDF /Text ] >> endobj -442 0 obj << +458 0 obj << /Length 32016 >> stream @@ -2204,313 +2228,313 @@ ET 0 g 0 G endstream endobj -441 0 obj << +457 0 obj << /Type /Page -/Contents 442 0 R -/Resources 440 0 R +/Contents 458 0 R +/Resources 456 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 435 0 R -/Annots [ 445 0 R 446 0 R 447 0 R 448 0 R 449 0 R 450 0 R 451 0 R 452 0 R 453 0 R 454 0 R 455 0 R 456 0 R 457 0 R 458 0 R 459 0 R 460 0 R 461 0 R 462 0 R 463 0 R 464 0 R 465 0 R 466 0 R 467 0 R 468 0 R 469 0 R 470 0 R 471 0 R 472 0 R 473 0 R 474 0 R 475 0 R 476 0 R 477 0 R 478 0 R 479 0 R 480 0 R 481 0 R 482 0 R 483 0 R 484 0 R 485 0 R ] +/Parent 451 0 R +/Annots [ 461 0 R 462 0 R 463 0 R 464 0 R 465 0 R 466 0 R 467 0 R 468 0 R 469 0 R 470 0 R 471 0 R 472 0 R 473 0 R 474 0 R 475 0 R 476 0 R 477 0 R 478 0 R 479 0 R 480 0 R 481 0 R 482 0 R 483 0 R 484 0 R 485 0 R 486 0 R 487 0 R 488 0 R 489 0 R 490 0 R 491 0 R 492 0 R 493 0 R 494 0 R 495 0 R 496 0 R 497 0 R 498 0 R 499 0 R 500 0 R 501 0 R ] >> endobj -445 0 obj << +461 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [98.8991 681.4919 179.0012 690.4029] /Subtype /Link /A << /S /GoTo /D (section.1) >> >> endobj -446 0 obj << +462 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [98.8991 657.8512 202.863 666.7622] /Subtype /Link /A << /S /GoTo /D (section.2) >> >> endobj -447 0 obj << +463 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 644.8623 225.8677 653.7734] /Subtype /Link /A << /S /GoTo /D (subsection.2.1) >> >> endobj -448 0 obj << +464 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 629.9363 210.6746 640.7845] /Subtype /Link /A << /S /GoTo /D (subsection.2.2) >> >> endobj -449 0 obj << +465 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 616.9474 232.122 627.7956] /Subtype /Link /A << /S /GoTo /D (subsection.2.3) >> >> endobj -450 0 obj << +466 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 603.9585 227.7773 614.8067] /Subtype /Link /A << /S /GoTo /D (subsection.2.4) >> >> endobj -451 0 obj << +467 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [98.8991 582.255 196.3402 591.083] /Subtype /Link /A << /S /GoTo /D (section.3) >> >> endobj -452 0 obj << +468 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 567.3289 249.529 578.1771] /Subtype /Link /A << /S /GoTo /D (subsection.3.1) >> >> endobj -453 0 obj << +469 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [136.7572 556.2772 248.2283 565.1883] /Subtype /Link /A << /S /GoTo /D (subsubsection.3.1.1) >> >> endobj -454 0 obj << +470 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 541.3512 265.7183 552.1994] /Subtype /Link /A << /S /GoTo /D (subsection.3.2) >> >> endobj -455 0 obj << +471 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [136.7572 530.2995 248.2283 539.2105] /Subtype /Link /A << /S /GoTo /D (subsubsection.3.2.1) >> >> endobj -456 0 obj << +472 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 517.3106 268.0153 526.2216] /Subtype /Link /A << /S /GoTo /D (subsection.3.3) >> >> endobj -457 0 obj << +473 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 502.3845 268.9008 513.122] /Subtype /Link /A << /S /GoTo /D (subsection.3.4) >> >> endobj -458 0 obj << +474 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [136.7572 489.3956 231.2752 500.2438] /Subtype /Link /A << /S /GoTo /D (section*.2) >> >> endobj -459 0 obj << +475 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [136.7572 476.4068 227.6499 487.255] /Subtype /Link /A << /S /GoTo /D (section*.4) >> >> endobj -460 0 obj << +476 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [136.7572 463.4179 237.0868 474.2661] /Subtype /Link /A << /S /GoTo /D (section*.6) >> >> endobj -461 0 obj << +477 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [136.7572 450.429 233.4615 461.2772] /Subtype /Link /A << /S /GoTo /D (section*.8) >> >> endobj -462 0 obj << +478 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [136.7572 437.4401 219.8569 448.2883] /Subtype /Link /A << /S /GoTo /D (section*.10) >> >> endobj -463 0 obj << +479 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [136.7572 424.4512 252.8886 435.2994] /Subtype /Link /A << /S /GoTo /D (section*.12) >> >> endobj -464 0 obj << +480 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [136.7572 411.4623 251.837 422.3105] /Subtype /Link /A << /S /GoTo /D (section*.14) >> >> endobj -465 0 obj << +481 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [136.7572 398.4735 212.5232 409.3217] /Subtype /Link /A << /S /GoTo /D (section*.16) >> >> endobj -466 0 obj << +482 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [136.7572 385.4846 208.898 396.3328] /Subtype /Link /A << /S /GoTo /D (section*.18) >> >> endobj -467 0 obj << +483 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [136.7572 372.4957 219.9952 383.3439] /Subtype /Link /A << /S /GoTo /D (section*.20) >> >> endobj -468 0 obj << +484 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [98.8991 348.855 235.0283 359.7032] /Subtype /Link /A << /S /GoTo /D (section.4) >> >> endobj -469 0 obj << +485 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 335.8661 170.1211 346.7143] /Subtype /Link /A << /S /GoTo /D (section*.23) >> >> endobj -470 0 obj << +486 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 322.8772 158.2212 333.7254] /Subtype /Link /A << /S /GoTo /D (section*.25) >> >> endobj -471 0 obj << +487 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 309.8883 162.1509 320.7366] /Subtype /Link /A << /S /GoTo /D (section*.27) >> >> endobj -472 0 obj << +488 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 296.8995 167.3537 307.7477] /Subtype /Link /A << /S /GoTo /D (section*.29) >> >> endobj -473 0 obj << +489 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 283.9106 171.2834 294.7588] /Subtype /Link /A << /S /GoTo /D (section*.31) >> >> endobj -474 0 obj << +490 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 270.9217 166.5788 281.7699] /Subtype /Link /A << /S /GoTo /D (section*.33) >> >> endobj -475 0 obj << +491 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 257.9328 170.5085 268.781] /Subtype /Link /A << /S /GoTo /D (section*.35) >> >> endobj -476 0 obj << +492 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 244.9439 166.5511 255.7921] /Subtype /Link /A << /S /GoTo /D (section*.37) >> >> endobj -477 0 obj << +493 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 231.955 170.4808 242.8032] /Subtype /Link /A << /S /GoTo /D (section*.39) >> >> endobj -478 0 obj << +494 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 218.9662 164.3925 229.8144] /Subtype /Link /A << /S /GoTo /D (section*.41) >> >> endobj -479 0 obj << +495 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 205.9773 160.4905 216.8255] /Subtype /Link /A << /S /GoTo /D (section*.43) >> >> endobj -480 0 obj << +496 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 192.9884 156.118 203.8366] /Subtype /Link /A << /S /GoTo /D (section*.45) >> >> endobj -481 0 obj << +497 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [98.8991 171.2849 239.3247 180.1959] /Subtype /Link /A << /S /GoTo /D (section.5) >> >> endobj -482 0 obj << +498 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 156.3588 152.6864 167.207] /Subtype /Link /A << /S /GoTo /D (section*.47) >> >> endobj -483 0 obj << +499 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 143.3699 151.0537 154.2181] /Subtype /Link /A << /S /GoTo /D (section*.50) >> >> endobj -484 0 obj << +500 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 130.3811 162.1233 141.2293] /Subtype /Link /A << /S /GoTo /D (section*.54) >> >> endobj -485 0 obj << +501 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 117.3922 163.839 128.2404] /Subtype /Link /A << /S /GoTo /D (section*.57) >> >> endobj -443 0 obj << -/D [441 0 R /XYZ 99.8954 740.9981 null] +459 0 obj << +/D [457 0 R /XYZ 99.8954 740.9981 null] >> endobj -444 0 obj << -/D [441 0 R /XYZ 99.8954 695.5213 null] +460 0 obj << +/D [457 0 R /XYZ 99.8954 695.5213 null] >> endobj -440 0 obj << -/Font << /F18 425 0 R /F29 431 0 R /F8 434 0 R >> +456 0 obj << +/Font << /F18 441 0 R /F29 447 0 R /F8 450 0 R >> /ProcSet [ /PDF /Text ] >> endobj -488 0 obj << -/Length 35470 +504 0 obj << +/Length 39207 >> stream 1 0 0 1 150.7049 740.9981 cm @@ -2529,13 +2553,13 @@ ET BT /F29 9.9626 Tf 482.959 706.1289 Td[(55)]TJ ET -1 0 0 1 165.6488 692.7591 cm +1 0 0 1 165.6488 693.8811 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -692.7591 cm +1 0 0 1 -165.6488 -693.8811 cm BT -/F8 9.9626 Tf 165.6488 692.7591 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 693.8811 Td[(psb)]TJ ET -1 0 0 1 181.2459 692.7591 cm +1 0 0 1 181.2459 693.8811 cm q []0 d 0 J @@ -2544,31 +2568,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -692.7591 cm +1 0 0 1 -181.2459 -693.8811 cm BT -/F8 9.9626 Tf 184.2347 692.7591 Td[(cdall)]TJ +/F8 9.9626 Tf 184.2347 693.8811 Td[(cdall)]TJ ET -1 0 0 1 204.7135 692.7591 cm +1 0 0 1 204.7135 693.8811 cm 0 g 0 G -1 0 0 1 -204.7135 -692.7591 cm +1 0 0 1 -204.7135 -693.8811 cm BT -/F8 9.9626 Tf 207.4357 692.7591 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +/F8 9.9626 Tf 207.4357 693.8811 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ ET -1 0 0 1 484.4533 692.7591 cm +1 0 0 1 484.4533 693.8811 cm 0 g 0 G -1 0 0 1 -484.4533 -692.7591 cm +1 0 0 1 -484.4533 -693.8811 cm BT -/F8 9.9626 Tf 484.4533 692.7591 Td[(56)]TJ +/F8 9.9626 Tf 484.4533 693.8811 Td[(56)]TJ ET -1 0 0 1 494.4159 692.7591 cm +1 0 0 1 494.4159 693.8811 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -679.3894 cm +1 0 0 1 -165.6488 -681.6333 cm BT -/F8 9.9626 Tf 165.6488 679.3894 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 681.6333 Td[(psb)]TJ ET -1 0 0 1 181.2459 679.3894 cm +1 0 0 1 181.2459 681.6333 cm q []0 d 0 J @@ -2577,31 +2601,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -679.3894 cm +1 0 0 1 -181.2459 -681.6333 cm BT -/F8 9.9626 Tf 184.2347 679.3894 Td[(cdin)1(s)]TJ +/F8 9.9626 Tf 184.2347 681.6333 Td[(cdin)1(s)]TJ ET -1 0 0 1 206.4293 679.3894 cm +1 0 0 1 206.4293 681.6333 cm 0 g 0 G -1 0 0 1 -206.4293 -679.3894 cm +1 0 0 1 -206.4293 -681.6333 cm BT -/F8 9.9626 Tf 215.1843 679.3894 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ +/F8 9.9626 Tf 215.1843 681.6333 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ ET -1 0 0 1 484.4533 679.3894 cm +1 0 0 1 484.4533 681.6333 cm 0 g 0 G -1 0 0 1 -484.4533 -679.3894 cm +1 0 0 1 -484.4533 -681.6333 cm BT -/F8 9.9626 Tf 484.4533 679.3894 Td[(59)]TJ +/F8 9.9626 Tf 484.4533 681.6333 Td[(59)]TJ ET -1 0 0 1 494.4159 679.3894 cm +1 0 0 1 494.4159 681.6333 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -666.0197 cm +1 0 0 1 -165.6488 -669.3855 cm BT -/F8 9.9626 Tf 165.6488 666.0197 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 669.3855 Td[(psb)]TJ ET -1 0 0 1 181.2459 666.0197 cm +1 0 0 1 181.2459 669.3855 cm q []0 d 0 J @@ -2610,31 +2634,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -666.0197 cm +1 0 0 1 -181.2459 -669.3855 cm BT -/F8 9.9626 Tf 184.2347 666.0197 Td[(cdasb)]TJ +/F8 9.9626 Tf 184.2347 669.3855 Td[(cdasb)]TJ ET -1 0 0 1 208.6432 666.0197 cm +1 0 0 1 208.6432 669.3855 cm 0 g 0 G -1 0 0 1 -208.6432 -666.0197 cm +1 0 0 1 -208.6432 -669.3855 cm BT -/F8 9.9626 Tf 215.1843 666.0197 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ +/F8 9.9626 Tf 215.1843 669.3855 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ ET -1 0 0 1 484.4533 666.0197 cm +1 0 0 1 484.4533 669.3855 cm 0 g 0 G -1 0 0 1 -484.4533 -666.0197 cm +1 0 0 1 -484.4533 -669.3855 cm BT -/F8 9.9626 Tf 484.4533 666.0197 Td[(61)]TJ +/F8 9.9626 Tf 484.4533 669.3855 Td[(61)]TJ ET -1 0 0 1 494.4159 666.0197 cm +1 0 0 1 494.4159 669.3855 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -652.65 cm +1 0 0 1 -165.6488 -657.1377 cm BT -/F8 9.9626 Tf 165.6488 652.65 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 657.1377 Td[(psb)]TJ ET -1 0 0 1 181.2459 652.65 cm +1 0 0 1 181.2459 657.1377 cm q []0 d 0 J @@ -2643,31 +2667,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -652.65 cm +1 0 0 1 -181.2459 -657.1377 cm BT -/F8 9.9626 Tf 184.2347 652.65 Td[(cdcp)28(y)]TJ +/F8 9.9626 Tf 184.2347 657.1377 Td[(cdcp)28(y)]TJ ET -1 0 0 1 209.1414 652.65 cm +1 0 0 1 209.1414 657.1377 cm 0 g 0 G -1 0 0 1 -209.1414 -652.65 cm +1 0 0 1 -209.1414 -657.1377 cm BT -/F8 9.9626 Tf 215.1843 652.65 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ +/F8 9.9626 Tf 215.1843 657.1377 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ ET -1 0 0 1 484.4533 652.65 cm +1 0 0 1 484.4533 657.1377 cm 0 g 0 G -1 0 0 1 -484.4533 -652.65 cm +1 0 0 1 -484.4533 -657.1377 cm BT -/F8 9.9626 Tf 484.4533 652.65 Td[(62)]TJ +/F8 9.9626 Tf 484.4533 657.1377 Td[(62)]TJ ET -1 0 0 1 494.4159 652.65 cm +1 0 0 1 494.4159 657.1377 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -639.2803 cm +1 0 0 1 -165.6488 -644.8899 cm BT -/F8 9.9626 Tf 165.6488 639.2803 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 644.8899 Td[(psb)]TJ ET -1 0 0 1 181.2459 639.2803 cm +1 0 0 1 181.2459 644.8899 cm q []0 d 0 J @@ -2676,31 +2700,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -639.2803 cm +1 0 0 1 -181.2459 -644.8899 cm BT -/F8 9.9626 Tf 184.2347 639.2803 Td[(cdfr)1(e)-1(e)]TJ +/F8 9.9626 Tf 184.2347 644.8899 Td[(cdfr)1(e)-1(e)]TJ ET -1 0 0 1 209.9993 639.2803 cm +1 0 0 1 209.9993 644.8899 cm 0 g 0 G -1 0 0 1 -209.9993 -639.2803 cm +1 0 0 1 -209.9993 -644.8899 cm BT -/F8 9.9626 Tf 215.1843 639.2803 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ +/F8 9.9626 Tf 215.1843 644.8899 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ ET -1 0 0 1 484.4533 639.2803 cm +1 0 0 1 484.4533 644.8899 cm 0 g 0 G -1 0 0 1 -484.4533 -639.2803 cm +1 0 0 1 -484.4533 -644.8899 cm BT -/F8 9.9626 Tf 484.4533 639.2803 Td[(63)]TJ +/F8 9.9626 Tf 484.4533 644.8899 Td[(63)]TJ ET -1 0 0 1 494.4159 639.2803 cm +1 0 0 1 494.4159 644.8899 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2477 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -625.9106 cm +1 0 0 1 -165.6488 -632.6422 cm BT -/F8 9.9626 Tf 165.6488 625.9106 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 632.6422 Td[(psb)]TJ ET -1 0 0 1 181.2459 625.9106 cm +1 0 0 1 181.2459 632.6422 cm q []0 d 0 J @@ -2709,31 +2733,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -625.9106 cm +1 0 0 1 -181.2459 -632.6422 cm BT -/F8 9.9626 Tf 184.2347 625.9106 Td[(cdbl)1(dext)]TJ +/F8 9.9626 Tf 184.2347 632.6422 Td[(cdbl)1(dext)]TJ ET -1 0 0 1 221.5947 625.9106 cm +1 0 0 1 221.5947 632.6422 cm 0 g 0 G -1 0 0 1 -221.5947 -625.9106 cm +1 0 0 1 -221.5947 -632.6422 cm BT -/F8 9.9626 Tf 230.6815 625.9106 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)]TJ +/F8 9.9626 Tf 230.6815 632.6422 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)]TJ ET -1 0 0 1 484.4533 625.9106 cm +1 0 0 1 484.4533 632.6422 cm 0 g 0 G -1 0 0 1 -484.4533 -625.9106 cm +1 0 0 1 -484.4533 -632.6422 cm BT -/F8 9.9626 Tf 484.4533 625.9106 Td[(64)]TJ +/F8 9.9626 Tf 484.4533 632.6422 Td[(64)]TJ ET -1 0 0 1 494.4159 625.9106 cm +1 0 0 1 494.4159 632.6422 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -612.5409 cm +1 0 0 1 -165.6488 -620.3944 cm BT -/F8 9.9626 Tf 165.6488 612.5409 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 620.3944 Td[(psb)]TJ ET -1 0 0 1 181.2459 612.5409 cm +1 0 0 1 181.2459 620.3944 cm q []0 d 0 J @@ -2742,31 +2766,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -612.5409 cm +1 0 0 1 -181.2459 -620.3944 cm BT -/F8 9.9626 Tf 184.2347 612.5409 Td[(spall)]TJ +/F8 9.9626 Tf 184.2347 620.3944 Td[(spall)]TJ ET -1 0 0 1 204.2154 612.5409 cm +1 0 0 1 204.2154 620.3944 cm 0 g 0 G -1 0 0 1 -204.2154 -612.5409 cm +1 0 0 1 -204.2154 -620.3944 cm BT -/F8 9.9626 Tf 207.4357 612.5409 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +/F8 9.9626 Tf 207.4357 620.3944 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ ET -1 0 0 1 484.4533 612.5409 cm +1 0 0 1 484.4533 620.3944 cm 0 g 0 G -1 0 0 1 -484.4533 -612.5409 cm +1 0 0 1 -484.4533 -620.3944 cm BT -/F8 9.9626 Tf 484.4533 612.5409 Td[(66)]TJ +/F8 9.9626 Tf 484.4533 620.3944 Td[(66)]TJ ET -1 0 0 1 494.4159 612.5409 cm +1 0 0 1 494.4159 620.3944 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -599.1712 cm +1 0 0 1 -165.6488 -608.1466 cm BT -/F8 9.9626 Tf 165.6488 599.1712 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 608.1466 Td[(psb)]TJ ET -1 0 0 1 181.2459 599.1712 cm +1 0 0 1 181.2459 608.1466 cm q []0 d 0 J @@ -2775,31 +2799,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -599.1712 cm +1 0 0 1 -181.2459 -608.1466 cm BT -/F8 9.9626 Tf 184.2347 599.1712 Td[(spin)1(s)]TJ +/F8 9.9626 Tf 184.2347 608.1466 Td[(spin)1(s)]TJ ET -1 0 0 1 205.9312 599.1712 cm +1 0 0 1 205.9312 608.1466 cm 0 g 0 G -1 0 0 1 -205.9312 -599.1712 cm +1 0 0 1 -205.9312 -608.1466 cm BT -/F8 9.9626 Tf 215.1843 599.1712 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ +/F8 9.9626 Tf 215.1843 608.1466 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ ET -1 0 0 1 484.4533 599.1712 cm +1 0 0 1 484.4533 608.1466 cm 0 g 0 G -1 0 0 1 -484.4533 -599.1712 cm +1 0 0 1 -484.4533 -608.1466 cm BT -/F8 9.9626 Tf 484.4533 599.1712 Td[(67)]TJ +/F8 9.9626 Tf 484.4533 608.1466 Td[(67)]TJ ET -1 0 0 1 494.4159 599.1712 cm +1 0 0 1 494.4159 608.1466 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -585.8015 cm +1 0 0 1 -165.6488 -595.8988 cm BT -/F8 9.9626 Tf 165.6488 585.8015 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 595.8988 Td[(psb)]TJ ET -1 0 0 1 181.2459 585.8015 cm +1 0 0 1 181.2459 595.8988 cm q []0 d 0 J @@ -2808,31 +2832,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -585.8015 cm +1 0 0 1 -181.2459 -595.8988 cm BT -/F8 9.9626 Tf 184.2347 585.8015 Td[(spasb)]TJ +/F8 9.9626 Tf 184.2347 595.8988 Td[(spasb)]TJ ET -1 0 0 1 208.1451 585.8015 cm +1 0 0 1 208.1451 595.8988 cm 0 g 0 G -1 0 0 1 -208.1451 -585.8015 cm +1 0 0 1 -208.1451 -595.8988 cm BT -/F8 9.9626 Tf 215.1843 585.8015 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ +/F8 9.9626 Tf 215.1843 595.8988 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ ET -1 0 0 1 484.4533 585.8015 cm +1 0 0 1 484.4533 595.8988 cm 0 g 0 G -1 0 0 1 -484.4533 -585.8015 cm +1 0 0 1 -484.4533 -595.8988 cm BT -/F8 9.9626 Tf 484.4533 585.8015 Td[(69)]TJ +/F8 9.9626 Tf 484.4533 595.8988 Td[(69)]TJ ET -1 0 0 1 494.4159 585.8015 cm +1 0 0 1 494.4159 595.8988 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2477 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -572.4318 cm +1 0 0 1 -165.6488 -583.6511 cm BT -/F8 9.9626 Tf 165.6488 572.4318 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 583.6511 Td[(psb)]TJ ET -1 0 0 1 181.2459 572.4318 cm +1 0 0 1 181.2459 583.6511 cm q []0 d 0 J @@ -2841,31 +2865,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -572.4318 cm +1 0 0 1 -181.2459 -583.6511 cm BT -/F8 9.9626 Tf 184.2347 572.4318 Td[(spfr)1(e)-1(e)]TJ +/F8 9.9626 Tf 184.2347 583.6511 Td[(spfr)1(e)-1(e)]TJ ET -1 0 0 1 209.5011 572.4318 cm +1 0 0 1 209.5011 583.6511 cm 0 g 0 G -1 0 0 1 -209.5011 -572.4318 cm +1 0 0 1 -209.5011 -583.6511 cm BT -/F8 9.9626 Tf 215.1843 572.4318 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ +/F8 9.9626 Tf 215.1843 583.6511 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ ET -1 0 0 1 484.4533 572.4318 cm +1 0 0 1 484.4533 583.6511 cm 0 g 0 G -1 0 0 1 -484.4533 -572.4318 cm +1 0 0 1 -484.4533 -583.6511 cm BT -/F8 9.9626 Tf 484.4533 572.4318 Td[(71)]TJ +/F8 9.9626 Tf 484.4533 583.6511 Td[(71)]TJ ET -1 0 0 1 494.4159 572.4318 cm +1 0 0 1 494.4159 583.6511 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -559.0621 cm +1 0 0 1 -165.6488 -571.4033 cm BT -/F8 9.9626 Tf 165.6488 559.0621 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 571.4033 Td[(psb)]TJ ET -1 0 0 1 181.2459 559.0621 cm +1 0 0 1 181.2459 571.4033 cm q []0 d 0 J @@ -2874,31 +2898,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -559.0621 cm +1 0 0 1 -181.2459 -571.4033 cm BT -/F8 9.9626 Tf 184.2347 559.0621 Td[(sprn)]TJ +/F8 9.9626 Tf 184.2347 571.4033 Td[(sprn)]TJ ET -1 0 0 1 203.1361 559.0621 cm +1 0 0 1 203.1361 571.4033 cm 0 g 0 G -1 0 0 1 -203.1361 -559.0621 cm +1 0 0 1 -203.1361 -571.4033 cm BT -/F8 9.9626 Tf 207.4357 559.0621 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +/F8 9.9626 Tf 207.4357 571.4033 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ ET -1 0 0 1 484.4533 559.0621 cm +1 0 0 1 484.4533 571.4033 cm 0 g 0 G -1 0 0 1 -484.4533 -559.0621 cm +1 0 0 1 -484.4533 -571.4033 cm BT -/F8 9.9626 Tf 484.4533 559.0621 Td[(72)]TJ +/F8 9.9626 Tf 484.4533 571.4033 Td[(72)]TJ ET -1 0 0 1 494.4159 559.0621 cm +1 0 0 1 494.4159 571.4033 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -545.6923 cm +1 0 0 1 -165.6488 -559.1555 cm BT -/F8 9.9626 Tf 165.6488 545.6923 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 559.1555 Td[(psb)]TJ ET -1 0 0 1 181.2459 545.6923 cm +1 0 0 1 181.2459 559.1555 cm q []0 d 0 J @@ -2907,31 +2931,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -545.6923 cm +1 0 0 1 -181.2459 -559.1555 cm BT -/F8 9.9626 Tf 184.2347 545.6923 Td[(geall)]TJ +/F8 9.9626 Tf 184.2347 559.1555 Td[(geall)]TJ ET -1 0 0 1 204.1601 545.6923 cm +1 0 0 1 204.1601 559.1555 cm 0 g 0 G -1 0 0 1 -204.1601 -545.6923 cm +1 0 0 1 -204.1601 -559.1555 cm BT -/F8 9.9626 Tf 207.4357 545.6923 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +/F8 9.9626 Tf 207.4357 559.1555 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ ET -1 0 0 1 484.4533 545.6923 cm +1 0 0 1 484.4533 559.1555 cm 0 g 0 G -1 0 0 1 -484.4533 -545.6923 cm +1 0 0 1 -484.4533 -559.1555 cm BT -/F8 9.9626 Tf 484.4533 545.6923 Td[(73)]TJ +/F8 9.9626 Tf 484.4533 559.1555 Td[(73)]TJ ET -1 0 0 1 494.4159 545.6923 cm +1 0 0 1 494.4159 559.1555 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -532.3226 cm +1 0 0 1 -165.6488 -546.9077 cm BT -/F8 9.9626 Tf 165.6488 532.3226 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 546.9077 Td[(psb)]TJ ET -1 0 0 1 181.2459 532.3226 cm +1 0 0 1 181.2459 546.9077 cm q []0 d 0 J @@ -2940,31 +2964,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -532.3226 cm +1 0 0 1 -181.2459 -546.9077 cm BT -/F8 9.9626 Tf 184.2347 532.3226 Td[(geins)]TJ +/F8 9.9626 Tf 184.2347 546.9077 Td[(geins)]TJ ET -1 0 0 1 205.8758 532.3226 cm +1 0 0 1 205.8758 546.9077 cm 0 g 0 G -1 0 0 1 -205.8758 -532.3226 cm +1 0 0 1 -205.8758 -546.9077 cm BT -/F8 9.9626 Tf 215.1843 532.3226 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ +/F8 9.9626 Tf 215.1843 546.9077 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ ET -1 0 0 1 484.4533 532.3226 cm +1 0 0 1 484.4533 546.9077 cm 0 g 0 G -1 0 0 1 -484.4533 -532.3226 cm +1 0 0 1 -484.4533 -546.9077 cm BT -/F8 9.9626 Tf 484.4533 532.3226 Td[(74)]TJ +/F8 9.9626 Tf 484.4533 546.9077 Td[(74)]TJ ET -1 0 0 1 494.4159 532.3226 cm +1 0 0 1 494.4159 546.9077 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2477 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -518.9529 cm +1 0 0 1 -165.6488 -534.66 cm BT -/F8 9.9626 Tf 165.6488 518.9529 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 534.66 Td[(psb)]TJ ET -1 0 0 1 181.2459 518.9529 cm +1 0 0 1 181.2459 534.66 cm q []0 d 0 J @@ -2973,31 +2997,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -518.9529 cm +1 0 0 1 -181.2459 -534.66 cm BT -/F8 9.9626 Tf 184.2347 518.9529 Td[(geas)-1(b)]TJ +/F8 9.9626 Tf 184.2347 534.66 Td[(geas)-1(b)]TJ ET -1 0 0 1 208.0898 518.9529 cm +1 0 0 1 208.0898 534.66 cm 0 g 0 G -1 0 0 1 -208.0898 -518.9529 cm +1 0 0 1 -208.0898 -534.66 cm BT -/F8 9.9626 Tf 215.1843 518.9529 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ +/F8 9.9626 Tf 215.1843 534.66 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ ET -1 0 0 1 484.4533 518.9529 cm +1 0 0 1 484.4533 534.66 cm 0 g 0 G -1 0 0 1 -484.4533 -518.9529 cm +1 0 0 1 -484.4533 -534.66 cm BT -/F8 9.9626 Tf 484.4533 518.9529 Td[(76)]TJ +/F8 9.9626 Tf 484.4533 534.66 Td[(76)]TJ ET -1 0 0 1 494.4159 518.9529 cm +1 0 0 1 494.4159 534.66 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -505.5832 cm +1 0 0 1 -165.6488 -522.4122 cm BT -/F8 9.9626 Tf 165.6488 505.5832 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 522.4122 Td[(psb)]TJ ET -1 0 0 1 181.2459 505.5832 cm +1 0 0 1 181.2459 522.4122 cm q []0 d 0 J @@ -3006,31 +3030,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -505.5832 cm +1 0 0 1 -181.2459 -522.4122 cm BT -/F8 9.9626 Tf 184.2347 505.5832 Td[(gefree)]TJ +/F8 9.9626 Tf 184.2347 522.4122 Td[(gefree)]TJ ET -1 0 0 1 209.4458 505.5832 cm +1 0 0 1 209.4458 522.4122 cm 0 g 0 G -1 0 0 1 -209.4458 -505.5832 cm +1 0 0 1 -209.4458 -522.4122 cm BT -/F8 9.9626 Tf 215.1843 505.5832 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ +/F8 9.9626 Tf 215.1843 522.4122 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ ET -1 0 0 1 484.4533 505.5832 cm +1 0 0 1 484.4533 522.4122 cm 0 g 0 G -1 0 0 1 -484.4533 -505.5832 cm +1 0 0 1 -484.4533 -522.4122 cm BT -/F8 9.9626 Tf 484.4533 505.5832 Td[(77)]TJ +/F8 9.9626 Tf 484.4533 522.4122 Td[(77)]TJ ET -1 0 0 1 494.4159 505.5832 cm +1 0 0 1 494.4159 522.4122 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -492.2135 cm +1 0 0 1 -165.6488 -510.1644 cm BT -/F8 9.9626 Tf 165.6488 492.2135 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 510.1644 Td[(psb)]TJ ET -1 0 0 1 181.2459 492.2135 cm +1 0 0 1 181.2459 510.1644 cm q []0 d 0 J @@ -3039,31 +3063,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -492.2135 cm +1 0 0 1 -181.2459 -510.1644 cm BT -/F8 9.9626 Tf 184.2347 492.2135 Td[(gelp)]TJ +/F8 9.9626 Tf 184.2347 510.1644 Td[(gelp)]TJ ET -1 0 0 1 201.9461 492.2135 cm +1 0 0 1 201.9461 510.1644 cm 0 g 0 G -1 0 0 1 -201.9461 -492.2135 cm +1 0 0 1 -201.9461 -510.1644 cm BT -/F8 9.9626 Tf 207.4357 492.2135 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +/F8 9.9626 Tf 207.4357 510.1644 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ ET -1 0 0 1 484.4533 492.2135 cm +1 0 0 1 484.4533 510.1644 cm 0 g 0 G -1 0 0 1 -484.4533 -492.2135 cm +1 0 0 1 -484.4533 -510.1644 cm BT -/F8 9.9626 Tf 484.4533 492.2135 Td[(78)]TJ +/F8 9.9626 Tf 484.4533 510.1644 Td[(78)]TJ ET -1 0 0 1 494.4159 492.2135 cm +1 0 0 1 494.4159 510.1644 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -478.8438 cm +1 0 0 1 -165.6488 -497.9166 cm BT -/F8 9.9626 Tf 165.6488 478.8438 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 497.9166 Td[(psb)]TJ ET -1 0 0 1 181.2459 478.8438 cm +1 0 0 1 181.2459 497.9166 cm q []0 d 0 J @@ -3072,11 +3096,11 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -478.8438 cm +1 0 0 1 -181.2459 -497.9166 cm BT -/F8 9.9626 Tf 184.2347 478.8438 Td[(glob)]TJ +/F8 9.9626 Tf 184.2347 497.9166 Td[(glob)]TJ ET -1 0 0 1 203.0974 478.8438 cm +1 0 0 1 203.0974 497.9166 cm q []0 d 0 J @@ -3085,11 +3109,11 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -203.0974 -478.8438 cm +1 0 0 1 -203.0974 -497.9166 cm BT -/F8 9.9626 Tf 206.0862 478.8438 Td[(to)]TJ +/F8 9.9626 Tf 206.0862 497.9166 Td[(to)]TJ ET -1 0 0 1 215.5396 478.8438 cm +1 0 0 1 215.5396 497.9166 cm q []0 d 0 J @@ -3098,31 +3122,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -215.5396 -478.8438 cm +1 0 0 1 -215.5396 -497.9166 cm BT -/F8 9.9626 Tf 218.5284 478.8438 Td[(lo)-28(c)]TJ +/F8 9.9626 Tf 218.5284 497.9166 Td[(lo)-28(c)]TJ ET -1 0 0 1 230.9818 478.8438 cm +1 0 0 1 230.9818 497.9166 cm 0 g 0 G -1 0 0 1 -230.9818 -478.8438 cm +1 0 0 1 -230.9818 -497.9166 cm BT -/F8 9.9626 Tf 238.4301 478.8438 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +/F8 9.9626 Tf 238.4301 497.9166 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ ET -1 0 0 1 484.4533 478.8438 cm +1 0 0 1 484.4533 497.9166 cm 0 g 0 G -1 0 0 1 -484.4533 -478.8438 cm +1 0 0 1 -484.4533 -497.9166 cm BT -/F8 9.9626 Tf 484.4533 478.8438 Td[(79)]TJ +/F8 9.9626 Tf 484.4533 497.9166 Td[(79)]TJ ET -1 0 0 1 494.4159 478.8438 cm +1 0 0 1 494.4159 497.9166 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -465.4741 cm +1 0 0 1 -165.6488 -485.6688 cm BT -/F8 9.9626 Tf 165.6488 465.4741 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 485.6688 Td[(psb)]TJ ET -1 0 0 1 181.2459 465.4741 cm +1 0 0 1 181.2459 485.6688 cm q []0 d 0 J @@ -3131,11 +3155,11 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -465.4741 cm +1 0 0 1 -181.2459 -485.6688 cm BT -/F8 9.9626 Tf 184.2347 465.4741 Td[(lo)-28(c)]TJ +/F8 9.9626 Tf 184.2347 485.6688 Td[(lo)-28(c)]TJ ET -1 0 0 1 197.2858 465.4741 cm +1 0 0 1 197.2858 485.6688 cm q []0 d 0 J @@ -3144,11 +3168,11 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -197.2858 -465.4741 cm +1 0 0 1 -197.2858 -485.6688 cm BT -/F8 9.9626 Tf 200.2746 465.4741 Td[(to)]TJ +/F8 9.9626 Tf 200.2746 485.6688 Td[(to)]TJ ET -1 0 0 1 209.7281 465.4741 cm +1 0 0 1 209.7281 485.6688 cm q []0 d 0 J @@ -3157,31 +3181,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -209.7281 -465.4741 cm +1 0 0 1 -209.7281 -485.6688 cm BT -/F8 9.9626 Tf 212.7169 465.4741 Td[(glob)]TJ +/F8 9.9626 Tf 212.7169 485.6688 Td[(glob)]TJ ET -1 0 0 1 230.9818 465.4741 cm +1 0 0 1 230.9818 485.6688 cm 0 g 0 G -1 0 0 1 -230.9818 -465.4741 cm +1 0 0 1 -230.9818 -485.6688 cm BT -/F8 9.9626 Tf 238.4301 465.4741 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +/F8 9.9626 Tf 238.4301 485.6688 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ ET -1 0 0 1 484.4533 465.4741 cm +1 0 0 1 484.4533 485.6688 cm 0 g 0 G -1 0 0 1 -484.4533 -465.4741 cm +1 0 0 1 -484.4533 -485.6688 cm BT -/F8 9.9626 Tf 484.4533 465.4741 Td[(81)]TJ +/F8 9.9626 Tf 484.4533 485.6688 Td[(81)]TJ ET -1 0 0 1 494.4159 465.4741 cm +1 0 0 1 494.4159 485.6688 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2477 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -452.1044 cm +1 0 0 1 -165.6488 -473.4211 cm BT -/F8 9.9626 Tf 165.6488 452.1044 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 473.4211 Td[(psb)]TJ ET -1 0 0 1 181.2459 452.1044 cm +1 0 0 1 181.2459 473.4211 cm q []0 d 0 J @@ -3190,11 +3214,11 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -452.1044 cm +1 0 0 1 -181.2459 -473.4211 cm BT -/F8 9.9626 Tf 184.2347 452.1044 Td[(get)]TJ +/F8 9.9626 Tf 184.2347 473.4211 Td[(is)]TJ ET -1 0 0 1 198.116 452.1044 cm +1 0 0 1 191.5296 473.4211 cm q []0 d 0 J @@ -3203,31 +3227,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -198.116 -452.1044 cm +1 0 0 1 -191.5296 -473.4211 cm BT -/F8 9.9626 Tf 201.1048 452.1044 Td[(b)-27(oun)1(dary)]TJ +/F8 9.9626 Tf 194.5184 473.4211 Td[(o)28(wned)]TJ ET -1 0 0 1 242.6436 452.1044 cm +1 0 0 1 221.9157 473.4211 cm 0 g 0 G -1 0 0 1 -242.6436 -452.1044 cm +1 0 0 1 -221.9157 -473.4211 cm BT -/F8 9.9626 Tf 246.1787 452.1044 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)]TJ +/F8 9.9626 Tf 230.6815 473.4211 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)]TJ ET -1 0 0 1 484.4533 452.1044 cm +1 0 0 1 484.4533 473.4211 cm 0 g 0 G -1 0 0 1 -484.4533 -452.1044 cm +1 0 0 1 -484.4533 -473.4211 cm BT -/F8 9.9626 Tf 484.4533 452.1044 Td[(82)]TJ +/F8 9.9626 Tf 484.4533 473.4211 Td[(82)]TJ ET -1 0 0 1 494.4159 452.1044 cm +1 0 0 1 494.4159 473.4211 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -438.7347 cm +1 0 0 1 -165.6488 -461.1733 cm BT -/F8 9.9626 Tf 165.6488 438.7347 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 461.1733 Td[(psb)]TJ ET -1 0 0 1 181.2459 438.7347 cm +1 0 0 1 181.2459 461.1733 cm q []0 d 0 J @@ -3236,11 +3260,11 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -438.7347 cm +1 0 0 1 -181.2459 -461.1733 cm BT -/F8 9.9626 Tf 184.2347 438.7347 Td[(get)]TJ +/F8 9.9626 Tf 184.2347 461.1733 Td[(o)28(wned)]TJ ET -1 0 0 1 198.116 438.7347 cm +1 0 0 1 212.2298 461.1733 cm q []0 d 0 J @@ -3249,31 +3273,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -198.116 -438.7347 cm +1 0 0 1 -212.2298 -461.1733 cm BT -/F8 9.9626 Tf 201.1048 438.7347 Td[(o)28(v)28(e)-1(r)1(lap)]TJ +/F8 9.9626 Tf 215.2186 461.1733 Td[(in)1(dex)]TJ ET -1 0 0 1 232.4042 438.7347 cm +1 0 0 1 238.7416 461.1733 cm 0 g 0 G -1 0 0 1 -232.4042 -438.7347 cm +1 0 0 1 -238.7416 -461.1733 cm BT -/F8 9.9626 Tf 238.4301 438.7347 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +/F8 9.9626 Tf 246.1787 461.1733 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)]TJ ET -1 0 0 1 484.4533 438.7347 cm +1 0 0 1 484.4533 461.1733 cm 0 g 0 G -1 0 0 1 -484.4533 -438.7347 cm +1 0 0 1 -484.4533 -461.1733 cm BT -/F8 9.9626 Tf 484.4533 438.7347 Td[(83)]TJ +/F8 9.9626 Tf 484.4533 461.1733 Td[(83)]TJ ET -1 0 0 1 494.4159 438.7347 cm +1 0 0 1 494.4159 461.1733 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -425.3649 cm +1 0 0 1 -165.6488 -448.9255 cm BT -/F8 9.9626 Tf 165.6488 425.3649 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 448.9255 Td[(psb)]TJ ET -1 0 0 1 181.2459 425.3649 cm +1 0 0 1 181.2459 448.9255 cm q []0 d 0 J @@ -3282,11 +3306,11 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -425.3649 cm +1 0 0 1 -181.2459 -448.9255 cm BT -/F8 9.9626 Tf 184.2347 425.3649 Td[(sp)]TJ +/F8 9.9626 Tf 184.2347 448.9255 Td[(is)]TJ ET -1 0 0 1 194.297 425.3649 cm +1 0 0 1 191.5296 448.9255 cm q []0 d 0 J @@ -3295,31 +3319,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -194.297 -425.3649 cm +1 0 0 1 -191.5296 -448.9255 cm BT -/F8 9.9626 Tf 197.2858 425.3649 Td[(getro)28(w)]TJ +/F8 9.9626 Tf 194.5184 448.9255 Td[(lo)-28(cal)]TJ ET -1 0 0 1 226.3712 425.3649 cm +1 0 0 1 214.7205 448.9255 cm 0 g 0 G -1 0 0 1 -226.3712 -425.3649 cm +1 0 0 1 -214.7205 -448.9255 cm BT -/F8 9.9626 Tf 230.6815 425.3649 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)]TJ +/F8 9.9626 Tf 222.9329 448.9255 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)]TJ ET -1 0 0 1 484.4533 425.3649 cm +1 0 0 1 484.4533 448.9255 cm 0 g 0 G -1 0 0 1 -484.4533 -425.3649 cm +1 0 0 1 -484.4533 -448.9255 cm BT -/F8 9.9626 Tf 484.4533 425.3649 Td[(84)]TJ +/F8 9.9626 Tf 484.4533 448.9255 Td[(84)]TJ ET -1 0 0 1 494.4159 425.3649 cm +1 0 0 1 494.4159 448.9255 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -411.9952 cm +1 0 0 1 -165.6488 -436.6777 cm BT -/F8 9.9626 Tf 165.6488 411.9952 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 436.6777 Td[(psb)]TJ ET -1 0 0 1 181.2459 411.9952 cm +1 0 0 1 181.2459 436.6777 cm q []0 d 0 J @@ -3328,51 +3352,57 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -411.9952 cm +1 0 0 1 -181.2459 -436.6777 cm BT -/F8 9.9626 Tf 184.2347 411.9952 Td[(siz)-1(eof)]TJ +/F8 9.9626 Tf 184.2347 436.6777 Td[(lo)-28(cal)]TJ ET -1 0 0 1 207.813 411.9952 cm -0 g 0 G -1 0 0 1 -207.813 -411.9952 cm -BT -/F8 9.9626 Tf 215.1843 411.9952 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ -ET -1 0 0 1 484.4533 411.9952 cm -0 g 0 G -1 0 0 1 -484.4533 -411.9952 cm +1 0 0 1 205.0345 436.6777 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +2.9888 0.1992 l +S +Q +1 0 0 1 -205.0345 -436.6777 cm BT -/F8 9.9626 Tf 484.4533 411.9952 Td[(86)]TJ +/F8 9.9626 Tf 208.0234 436.6777 Td[(in)1(dex)]TJ ET -1 0 0 1 494.4159 411.9952 cm +1 0 0 1 231.5463 436.6777 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm -0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -398.6255 cm +1 0 0 1 -231.5463 -436.6777 cm BT -/F8 9.9626 Tf 165.6488 398.6255 Td[(Sor)1(tin)1(g)-334(u)1(tilit)1(ie)-1(s)]TJ +/F8 9.9626 Tf 238.4301 436.6777 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ ET -1 0 0 1 233.2566 398.6255 cm +1 0 0 1 484.4533 436.6777 cm 0 g 0 G -1 0 0 1 -233.2566 -398.6255 cm +1 0 0 1 -484.4533 -436.6777 cm BT -/F8 9.9626 Tf 238.4301 398.6255 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +/F8 9.9626 Tf 484.4533 436.6777 Td[(85)]TJ ET -1 0 0 1 484.4533 398.6255 cm +1 0 0 1 494.4159 436.6777 cm 0 g 0 G -1 0 0 1 -484.4533 -398.6255 cm +1 0 0 1 -328.7671 -12.2477 cm +0 0 1 rg 0 0 1 RG +1 0 0 1 -165.6488 -424.43 cm BT -/F8 9.9626 Tf 484.4533 398.6255 Td[(87)]TJ +/F8 9.9626 Tf 165.6488 424.43 Td[(psb)]TJ ET -1 0 0 1 494.4159 398.6255 cm -0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm -0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -385.2558 cm +1 0 0 1 181.2459 424.43 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +2.9888 0.1992 l +S +Q +1 0 0 1 -181.2459 -424.43 cm BT -/F8 9.9626 Tf 165.6488 385.2558 Td[(psb)]TJ +/F8 9.9626 Tf 184.2347 424.43 Td[(get)]TJ ET -1 0 0 1 181.2459 385.2558 cm +1 0 0 1 198.116 424.43 cm q []0 d 0 J @@ -3381,31 +3411,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -385.2558 cm +1 0 0 1 -198.116 -424.43 cm BT -/F8 9.9626 Tf 184.2347 385.2558 Td[(ms)-1(or)1(t)]TJ +/F8 9.9626 Tf 201.1048 424.43 Td[(b)-27(oun)1(dary)]TJ ET -1 0 0 1 209.2244 385.2558 cm +1 0 0 1 242.6436 424.43 cm 0 g 0 G -1 0 0 1 -209.2244 -385.2558 cm +1 0 0 1 -242.6436 -424.43 cm BT -/F8 9.9626 Tf 215.1843 385.2558 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ +/F8 9.9626 Tf 246.1787 424.43 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)]TJ ET -1 0 0 1 484.4533 385.2558 cm +1 0 0 1 484.4533 424.43 cm 0 g 0 G -1 0 0 1 -484.4533 -385.2558 cm +1 0 0 1 -484.4533 -424.43 cm BT -/F8 9.9626 Tf 484.4533 385.2558 Td[(87)]TJ +/F8 9.9626 Tf 484.4533 424.43 Td[(86)]TJ ET -1 0 0 1 494.4159 385.2558 cm +1 0 0 1 494.4159 424.43 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -371.8861 cm +1 0 0 1 -165.6488 -412.1822 cm BT -/F8 9.9626 Tf 165.6488 371.8861 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 412.1822 Td[(psb)]TJ ET -1 0 0 1 181.2459 371.8861 cm +1 0 0 1 181.2459 412.1822 cm q []0 d 0 J @@ -3414,31 +3444,90 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -371.8861 cm +1 0 0 1 -181.2459 -412.1822 cm BT -/F8 9.9626 Tf 184.2347 371.8861 Td[(qsort)]TJ +/F8 9.9626 Tf 184.2347 412.1822 Td[(get)]TJ ET -1 0 0 1 206.1803 371.8861 cm +1 0 0 1 198.116 412.1822 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +2.9888 0.1992 l +S +Q +1 0 0 1 -198.116 -412.1822 cm +BT +/F8 9.9626 Tf 201.1048 412.1822 Td[(o)28(v)28(e)-1(r)1(lap)]TJ +ET +1 0 0 1 232.4042 412.1822 cm +0 g 0 G +1 0 0 1 -232.4042 -412.1822 cm +BT +/F8 9.9626 Tf 238.4301 412.1822 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +ET +1 0 0 1 484.4533 412.1822 cm +0 g 0 G +1 0 0 1 -484.4533 -412.1822 cm +BT +/F8 9.9626 Tf 484.4533 412.1822 Td[(87)]TJ +ET +1 0 0 1 494.4159 412.1822 cm +0 g 0 G +1 0 0 1 -328.7671 -12.2478 cm +0 0 1 rg 0 0 1 RG +1 0 0 1 -165.6488 -399.9344 cm +BT +/F8 9.9626 Tf 165.6488 399.9344 Td[(psb)]TJ +ET +1 0 0 1 181.2459 399.9344 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +2.9888 0.1992 l +S +Q +1 0 0 1 -181.2459 -399.9344 cm +BT +/F8 9.9626 Tf 184.2347 399.9344 Td[(sp)]TJ +ET +1 0 0 1 194.297 399.9344 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +2.9888 0.1992 l +S +Q +1 0 0 1 -194.297 -399.9344 cm +BT +/F8 9.9626 Tf 197.2858 399.9344 Td[(getro)28(w)]TJ +ET +1 0 0 1 226.3712 399.9344 cm 0 g 0 G -1 0 0 1 -206.1803 -371.8861 cm +1 0 0 1 -226.3712 -399.9344 cm BT -/F8 9.9626 Tf 215.1843 371.8861 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ +/F8 9.9626 Tf 230.6815 399.9344 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)]TJ ET -1 0 0 1 484.4533 371.8861 cm +1 0 0 1 484.4533 399.9344 cm 0 g 0 G -1 0 0 1 -484.4533 -371.8861 cm +1 0 0 1 -484.4533 -399.9344 cm BT -/F8 9.9626 Tf 484.4533 371.8861 Td[(87)]TJ +/F8 9.9626 Tf 484.4533 399.9344 Td[(88)]TJ ET -1 0 0 1 494.4159 371.8861 cm +1 0 0 1 494.4159 399.9344 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -358.5164 cm +1 0 0 1 -165.6488 -387.6866 cm BT -/F8 9.9626 Tf 165.6488 358.5164 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 387.6866 Td[(psb)]TJ ET -1 0 0 1 181.2459 358.5164 cm +1 0 0 1 181.2459 387.6866 cm q []0 d 0 J @@ -3447,43 +3536,51 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -358.5164 cm +1 0 0 1 -181.2459 -387.6866 cm BT -/F8 9.9626 Tf 184.2347 358.5164 Td[(hsort)]TJ +/F8 9.9626 Tf 184.2347 387.6866 Td[(siz)-1(eof)]TJ ET -1 0 0 1 206.457 358.5164 cm +1 0 0 1 207.813 387.6866 cm 0 g 0 G -1 0 0 1 -206.457 -358.5164 cm +1 0 0 1 -207.813 -387.6866 cm BT -/F8 9.9626 Tf 215.1843 358.5164 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ +/F8 9.9626 Tf 215.1843 387.6866 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ ET -1 0 0 1 484.4533 358.5164 cm +1 0 0 1 484.4533 387.6866 cm 0 g 0 G -1 0 0 1 -484.4533 -358.5164 cm +1 0 0 1 -484.4533 -387.6866 cm BT -/F8 9.9626 Tf 484.4533 358.5164 Td[(87)]TJ +/F8 9.9626 Tf 484.4533 387.6866 Td[(90)]TJ ET -1 0 0 1 494.4159 358.5164 cm +1 0 0 1 494.4159 387.6866 cm 0 g 0 G -1 0 0 1 -343.7111 -24.2754 cm +1 0 0 1 -328.7671 -12.2477 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -150.7048 -334.241 cm +1 0 0 1 -165.6488 -375.4389 cm +BT +/F8 9.9626 Tf 165.6488 375.4389 Td[(Sor)1(tin)1(g)-334(u)1(tilit)1(ie)-1(s)]TJ +ET +1 0 0 1 233.2566 375.4389 cm +0 g 0 G +1 0 0 1 -233.2566 -375.4389 cm BT -/F29 9.9626 Tf 150.7048 334.241 Td[(7)-925(P)32(arall)-1(el)-384(en)32(viron)1(m)-1(en)32(t)-383(routi)-1(n)1(e)-1(s)]TJ +/F8 9.9626 Tf 238.4301 375.4389 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ ET -1 0 0 1 314.6808 334.241 cm +1 0 0 1 484.4533 375.4389 cm 0 g 0 G -1 0 0 1 -314.6808 -334.241 cm +1 0 0 1 -484.4533 -375.4389 cm BT -/F29 9.9626 Tf 482.959 334.241 Td[(89)]TJ +/F8 9.9626 Tf 484.4533 375.4389 Td[(91)]TJ ET -1 0 0 1 165.6488 320.8713 cm +1 0 0 1 494.4159 375.4389 cm +0 g 0 G +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -320.8713 cm +1 0 0 1 -165.6488 -363.1911 cm BT -/F8 9.9626 Tf 165.6488 320.8713 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 363.1911 Td[(psb)]TJ ET -1 0 0 1 181.2459 320.8713 cm +1 0 0 1 181.2459 363.1911 cm q []0 d 0 J @@ -3492,31 +3589,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -320.8713 cm +1 0 0 1 -181.2459 -363.1911 cm BT -/F8 9.9626 Tf 184.2347 320.8713 Td[(in)1(it)]TJ +/F8 9.9626 Tf 184.2347 363.1911 Td[(ms)-1(or)1(t)]TJ ET -1 0 0 1 199.1787 320.8713 cm +1 0 0 1 209.2244 363.1911 cm 0 g 0 G -1 0 0 1 -199.1787 -320.8713 cm +1 0 0 1 -209.2244 -363.1911 cm BT -/F8 9.9626 Tf 207.4357 320.8713 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +/F8 9.9626 Tf 215.1843 363.1911 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ ET -1 0 0 1 484.4533 320.8713 cm +1 0 0 1 484.4533 363.1911 cm 0 g 0 G -1 0 0 1 -484.4533 -320.8713 cm +1 0 0 1 -484.4533 -363.1911 cm BT -/F8 9.9626 Tf 484.4533 320.8713 Td[(90)]TJ +/F8 9.9626 Tf 484.4533 363.1911 Td[(91)]TJ ET -1 0 0 1 494.4159 320.8713 cm +1 0 0 1 494.4159 363.1911 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -307.5016 cm +1 0 0 1 -165.6488 -350.9433 cm BT -/F8 9.9626 Tf 165.6488 307.5016 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 350.9433 Td[(psb)]TJ ET -1 0 0 1 181.2459 307.5016 cm +1 0 0 1 181.2459 350.9433 cm q []0 d 0 J @@ -3525,31 +3622,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -307.5016 cm +1 0 0 1 -181.2459 -350.9433 cm BT -/F8 9.9626 Tf 184.2347 307.5016 Td[(in)1(fo)]TJ +/F8 9.9626 Tf 184.2347 350.9433 Td[(qsort)]TJ ET -1 0 0 1 200.5625 307.5016 cm +1 0 0 1 206.1803 350.9433 cm 0 g 0 G -1 0 0 1 -200.5625 -307.5016 cm +1 0 0 1 -206.1803 -350.9433 cm BT -/F8 9.9626 Tf 207.4357 307.5016 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +/F8 9.9626 Tf 215.1843 350.9433 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ ET -1 0 0 1 484.4533 307.5016 cm +1 0 0 1 484.4533 350.9433 cm 0 g 0 G -1 0 0 1 -484.4533 -307.5016 cm +1 0 0 1 -484.4533 -350.9433 cm BT -/F8 9.9626 Tf 484.4533 307.5016 Td[(91)]TJ +/F8 9.9626 Tf 484.4533 350.9433 Td[(91)]TJ ET -1 0 0 1 494.4159 307.5016 cm +1 0 0 1 494.4159 350.9433 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -294.1319 cm +1 0 0 1 -165.6488 -338.6955 cm BT -/F8 9.9626 Tf 165.6488 294.1319 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 338.6955 Td[(psb)]TJ ET -1 0 0 1 181.2459 294.1319 cm +1 0 0 1 181.2459 338.6955 cm q []0 d 0 J @@ -3558,31 +3655,43 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -294.1319 cm +1 0 0 1 -181.2459 -338.6955 cm BT -/F8 9.9626 Tf 184.2347 294.1319 Td[(exit)]TJ +/F8 9.9626 Tf 184.2347 338.6955 Td[(hsort)]TJ ET -1 0 0 1 200.5624 294.1319 cm +1 0 0 1 206.457 338.6955 cm 0 g 0 G -1 0 0 1 -200.5624 -294.1319 cm +1 0 0 1 -206.457 -338.6955 cm BT -/F8 9.9626 Tf 207.4357 294.1319 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +/F8 9.9626 Tf 215.1843 338.6955 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ ET -1 0 0 1 484.4533 294.1319 cm +1 0 0 1 484.4533 338.6955 cm 0 g 0 G -1 0 0 1 -484.4533 -294.1319 cm +1 0 0 1 -484.4533 -338.6955 cm BT -/F8 9.9626 Tf 484.4533 294.1319 Td[(92)]TJ +/F8 9.9626 Tf 484.4533 338.6955 Td[(91)]TJ ET -1 0 0 1 494.4159 294.1319 cm +1 0 0 1 494.4159 338.6955 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -343.7111 -22.4055 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -280.7621 cm +1 0 0 1 -150.7048 -316.29 cm BT -/F8 9.9626 Tf 165.6488 280.7621 Td[(psb)]TJ +/F29 9.9626 Tf 150.7048 316.29 Td[(7)-925(P)32(arall)-1(el)-384(en)32(viron)1(m)-1(en)32(t)-383(routi)-1(n)1(e)-1(s)]TJ ET -1 0 0 1 181.2459 280.7621 cm +1 0 0 1 314.6808 316.29 cm +0 g 0 G +1 0 0 1 -314.6808 -316.29 cm +BT +/F29 9.9626 Tf 482.959 316.29 Td[(93)]TJ +ET +1 0 0 1 165.6488 304.0422 cm +0 0 1 rg 0 0 1 RG +1 0 0 1 -165.6488 -304.0422 cm +BT +/F8 9.9626 Tf 165.6488 304.0422 Td[(psb)]TJ +ET +1 0 0 1 181.2459 304.0422 cm q []0 d 0 J @@ -3591,11 +3700,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -280.7621 cm +1 0 0 1 -181.2459 -304.0422 cm +BT +/F8 9.9626 Tf 184.2347 304.0422 Td[(in)1(it)]TJ +ET +1 0 0 1 199.1787 304.0422 cm +0 g 0 G +1 0 0 1 -199.1787 -304.0422 cm +BT +/F8 9.9626 Tf 207.4357 304.0422 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +ET +1 0 0 1 484.4533 304.0422 cm +0 g 0 G +1 0 0 1 -484.4533 -304.0422 cm +BT +/F8 9.9626 Tf 484.4533 304.0422 Td[(94)]TJ +ET +1 0 0 1 494.4159 304.0422 cm +0 g 0 G +1 0 0 1 -328.7671 -12.2478 cm +0 0 1 rg 0 0 1 RG +1 0 0 1 -165.6488 -291.7945 cm BT -/F8 9.9626 Tf 184.2347 280.7621 Td[(get)]TJ +/F8 9.9626 Tf 165.6488 291.7945 Td[(psb)]TJ ET -1 0 0 1 198.116 280.7621 cm +1 0 0 1 181.2459 291.7945 cm q []0 d 0 J @@ -3604,31 +3733,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -198.116 -280.7621 cm +1 0 0 1 -181.2459 -291.7945 cm BT -/F8 9.9626 Tf 201.1048 280.7621 Td[(mpicomm)]TJ +/F8 9.9626 Tf 184.2347 291.7945 Td[(in)1(fo)]TJ ET -1 0 0 1 243.7229 280.7621 cm +1 0 0 1 200.5625 291.7945 cm 0 g 0 G -1 0 0 1 -243.7229 -280.7621 cm +1 0 0 1 -200.5625 -291.7945 cm BT -/F8 9.9626 Tf 253.9274 280.7621 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)]TJ +/F8 9.9626 Tf 207.4357 291.7945 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ ET -1 0 0 1 484.4533 280.7621 cm +1 0 0 1 484.4533 291.7945 cm 0 g 0 G -1 0 0 1 -484.4533 -280.7621 cm +1 0 0 1 -484.4533 -291.7945 cm BT -/F8 9.9626 Tf 484.4533 280.7621 Td[(93)]TJ +/F8 9.9626 Tf 484.4533 291.7945 Td[(95)]TJ ET -1 0 0 1 494.4159 280.7621 cm +1 0 0 1 494.4159 291.7945 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -267.3924 cm +1 0 0 1 -165.6488 -279.5467 cm BT -/F8 9.9626 Tf 165.6488 267.3924 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 279.5467 Td[(psb)]TJ ET -1 0 0 1 181.2459 267.3924 cm +1 0 0 1 181.2459 279.5467 cm q []0 d 0 J @@ -3637,11 +3766,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -267.3924 cm +1 0 0 1 -181.2459 -279.5467 cm +BT +/F8 9.9626 Tf 184.2347 279.5467 Td[(exit)]TJ +ET +1 0 0 1 200.5624 279.5467 cm +0 g 0 G +1 0 0 1 -200.5624 -279.5467 cm BT -/F8 9.9626 Tf 184.2347 267.3924 Td[(get)]TJ +/F8 9.9626 Tf 207.4357 279.5467 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ ET -1 0 0 1 198.116 267.3924 cm +1 0 0 1 484.4533 279.5467 cm +0 g 0 G +1 0 0 1 -484.4533 -279.5467 cm +BT +/F8 9.9626 Tf 484.4533 279.5467 Td[(96)]TJ +ET +1 0 0 1 494.4159 279.5467 cm +0 g 0 G +1 0 0 1 -328.7671 -12.2478 cm +0 0 1 rg 0 0 1 RG +1 0 0 1 -165.6488 -267.2989 cm +BT +/F8 9.9626 Tf 165.6488 267.2989 Td[(psb)]TJ +ET +1 0 0 1 181.2459 267.2989 cm q []0 d 0 J @@ -3650,31 +3799,90 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -198.116 -267.3924 cm +1 0 0 1 -181.2459 -267.2989 cm BT -/F8 9.9626 Tf 201.1048 267.3924 Td[(ran)1(k)]TJ +/F8 9.9626 Tf 184.2347 267.2989 Td[(get)]TJ ET -1 0 0 1 220.7811 267.3924 cm +1 0 0 1 198.116 267.2989 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +2.9888 0.1992 l +S +Q +1 0 0 1 -198.116 -267.2989 cm +BT +/F8 9.9626 Tf 201.1048 267.2989 Td[(mpicomm)]TJ +ET +1 0 0 1 243.7229 267.2989 cm +0 g 0 G +1 0 0 1 -243.7229 -267.2989 cm +BT +/F8 9.9626 Tf 253.9274 267.2989 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)]TJ +ET +1 0 0 1 484.4533 267.2989 cm +0 g 0 G +1 0 0 1 -484.4533 -267.2989 cm +BT +/F8 9.9626 Tf 484.4533 267.2989 Td[(97)]TJ +ET +1 0 0 1 494.4159 267.2989 cm +0 g 0 G +1 0 0 1 -328.7671 -12.2478 cm +0 0 1 rg 0 0 1 RG +1 0 0 1 -165.6488 -255.0511 cm +BT +/F8 9.9626 Tf 165.6488 255.0511 Td[(psb)]TJ +ET +1 0 0 1 181.2459 255.0511 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +2.9888 0.1992 l +S +Q +1 0 0 1 -181.2459 -255.0511 cm +BT +/F8 9.9626 Tf 184.2347 255.0511 Td[(get)]TJ +ET +1 0 0 1 198.116 255.0511 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +2.9888 0.1992 l +S +Q +1 0 0 1 -198.116 -255.0511 cm +BT +/F8 9.9626 Tf 201.1048 255.0511 Td[(ran)1(k)]TJ +ET +1 0 0 1 220.7811 255.0511 cm 0 g 0 G -1 0 0 1 -220.7811 -267.3924 cm +1 0 0 1 -220.7811 -255.0511 cm BT -/F8 9.9626 Tf 230.6815 267.3924 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)]TJ +/F8 9.9626 Tf 230.6815 255.0511 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)]TJ ET -1 0 0 1 484.4533 267.3924 cm +1 0 0 1 484.4533 255.0511 cm 0 g 0 G -1 0 0 1 -484.4533 -267.3924 cm +1 0 0 1 -484.4533 -255.0511 cm BT -/F8 9.9626 Tf 484.4533 267.3924 Td[(94)]TJ +/F8 9.9626 Tf 484.4533 255.0511 Td[(98)]TJ ET -1 0 0 1 494.4159 267.3924 cm +1 0 0 1 494.4159 255.0511 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2477 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -254.0227 cm +1 0 0 1 -165.6488 -242.8034 cm BT -/F8 9.9626 Tf 165.6488 254.0227 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 242.8034 Td[(psb)]TJ ET -1 0 0 1 181.2459 254.0227 cm +1 0 0 1 181.2459 242.8034 cm q []0 d 0 J @@ -3683,31 +3891,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -254.0227 cm +1 0 0 1 -181.2459 -242.8034 cm BT -/F8 9.9626 Tf 184.2347 254.0227 Td[(wtime)]TJ +/F8 9.9626 Tf 184.2347 242.8034 Td[(wtime)]TJ ET -1 0 0 1 210.8018 254.0227 cm +1 0 0 1 210.8018 242.8034 cm 0 g 0 G -1 0 0 1 -210.8018 -254.0227 cm +1 0 0 1 -210.8018 -242.8034 cm BT -/F8 9.9626 Tf 215.1843 254.0227 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ +/F8 9.9626 Tf 215.1843 242.8034 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ ET -1 0 0 1 484.4533 254.0227 cm +1 0 0 1 484.4533 242.8034 cm 0 g 0 G -1 0 0 1 -484.4533 -254.0227 cm +1 0 0 1 -484.4533 -242.8034 cm BT -/F8 9.9626 Tf 484.4533 254.0227 Td[(95)]TJ +/F8 9.9626 Tf 484.4533 242.8034 Td[(99)]TJ ET -1 0 0 1 494.4159 254.0227 cm +1 0 0 1 494.4159 242.8034 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -240.653 cm +1 0 0 1 -165.6488 -230.5556 cm BT -/F8 9.9626 Tf 165.6488 240.653 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 230.5556 Td[(psb)]TJ ET -1 0 0 1 181.2459 240.653 cm +1 0 0 1 181.2459 230.5556 cm q []0 d 0 J @@ -3716,31 +3924,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -240.653 cm +1 0 0 1 -181.2459 -230.5556 cm BT -/F8 9.9626 Tf 184.2347 240.653 Td[(bar)1(rier)]TJ +/F8 9.9626 Tf 184.2347 230.5556 Td[(bar)1(rier)]TJ ET -1 0 0 1 213.6522 240.653 cm +1 0 0 1 213.6522 230.5556 cm 0 g 0 G -1 0 0 1 -213.6522 -240.653 cm +1 0 0 1 -213.6522 -230.5556 cm BT -/F8 9.9626 Tf 222.9329 240.653 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)]TJ +/F8 9.9626 Tf 222.9329 230.5556 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)]TJ ET -1 0 0 1 484.4533 240.653 cm +1 0 0 1 479.4719 230.5556 cm 0 g 0 G -1 0 0 1 -484.4533 -240.653 cm +1 0 0 1 -479.4719 -230.5556 cm BT -/F8 9.9626 Tf 484.4533 240.653 Td[(96)]TJ +/F8 9.9626 Tf 479.4719 230.5556 Td[(100)]TJ ET -1 0 0 1 494.4159 240.653 cm +1 0 0 1 494.4159 230.5556 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -227.2833 cm +1 0 0 1 -165.6488 -218.3078 cm BT -/F8 9.9626 Tf 165.6488 227.2833 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 218.3078 Td[(psb)]TJ ET -1 0 0 1 181.2459 227.2833 cm +1 0 0 1 181.2459 218.3078 cm q []0 d 0 J @@ -3749,31 +3957,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -227.2833 cm +1 0 0 1 -181.2459 -218.3078 cm BT -/F8 9.9626 Tf 184.2347 227.2833 Td[(ab)-27(ort)]TJ +/F8 9.9626 Tf 184.2347 218.3078 Td[(ab)-27(ort)]TJ ET -1 0 0 1 207.7854 227.2833 cm +1 0 0 1 207.7854 218.3078 cm 0 g 0 G -1 0 0 1 -207.7854 -227.2833 cm +1 0 0 1 -207.7854 -218.3078 cm BT -/F8 9.9626 Tf 215.1843 227.2833 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ +/F8 9.9626 Tf 215.1843 218.3078 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ ET -1 0 0 1 484.4533 227.2833 cm +1 0 0 1 479.4719 218.3078 cm 0 g 0 G -1 0 0 1 -484.4533 -227.2833 cm +1 0 0 1 -479.4719 -218.3078 cm BT -/F8 9.9626 Tf 484.4533 227.2833 Td[(97)]TJ +/F8 9.9626 Tf 479.4719 218.3078 Td[(101)]TJ ET -1 0 0 1 494.4159 227.2833 cm +1 0 0 1 494.4159 218.3078 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -213.9136 cm +1 0 0 1 -165.6488 -206.06 cm BT -/F8 9.9626 Tf 165.6488 213.9136 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 206.06 Td[(psb)]TJ ET -1 0 0 1 181.2459 213.9136 cm +1 0 0 1 181.2459 206.06 cm q []0 d 0 J @@ -3782,31 +3990,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -213.9136 cm +1 0 0 1 -181.2459 -206.06 cm BT -/F8 9.9626 Tf 184.2347 213.9136 Td[(b)-27(c)-1(ast)]TJ +/F8 9.9626 Tf 184.2347 206.06 Td[(b)-27(c)-1(ast)]TJ ET -1 0 0 1 207.2596 213.9136 cm +1 0 0 1 207.2596 206.06 cm 0 g 0 G -1 0 0 1 -207.2596 -213.9136 cm +1 0 0 1 -207.2596 -206.06 cm BT -/F8 9.9626 Tf 215.1843 213.9136 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ +/F8 9.9626 Tf 215.1843 206.06 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)]TJ ET -1 0 0 1 484.4533 213.9136 cm +1 0 0 1 479.4719 206.06 cm 0 g 0 G -1 0 0 1 -484.4533 -213.9136 cm +1 0 0 1 -479.4719 -206.06 cm BT -/F8 9.9626 Tf 484.4533 213.9136 Td[(98)]TJ +/F8 9.9626 Tf 479.4719 206.06 Td[(102)]TJ ET -1 0 0 1 494.4159 213.9136 cm +1 0 0 1 494.4159 206.06 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -200.5439 cm +1 0 0 1 -165.6488 -193.8123 cm BT -/F8 9.9626 Tf 165.6488 200.5439 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 193.8123 Td[(psb)]TJ ET -1 0 0 1 181.2459 200.5439 cm +1 0 0 1 181.2459 193.8123 cm q []0 d 0 J @@ -3815,31 +4023,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -200.5439 cm +1 0 0 1 -181.2459 -193.8123 cm BT -/F8 9.9626 Tf 184.2347 200.5439 Td[(sum)]TJ +/F8 9.9626 Tf 184.2347 193.8123 Td[(sum)]TJ ET -1 0 0 1 202.0015 200.5439 cm +1 0 0 1 202.0015 193.8123 cm 0 g 0 G -1 0 0 1 -202.0015 -200.5439 cm +1 0 0 1 -202.0015 -193.8123 cm BT -/F8 9.9626 Tf 207.4357 200.5439 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +/F8 9.9626 Tf 207.4357 193.8123 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ ET -1 0 0 1 484.4533 200.5439 cm +1 0 0 1 479.4719 193.8123 cm 0 g 0 G -1 0 0 1 -484.4533 -200.5439 cm +1 0 0 1 -479.4719 -193.8123 cm BT -/F8 9.9626 Tf 484.4533 200.5439 Td[(99)]TJ +/F8 9.9626 Tf 479.4719 193.8123 Td[(103)]TJ ET -1 0 0 1 494.4159 200.5439 cm +1 0 0 1 494.4159 193.8123 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -187.1742 cm +1 0 0 1 -165.6488 -181.5645 cm BT -/F8 9.9626 Tf 165.6488 187.1742 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 181.5645 Td[(psb)]TJ ET -1 0 0 1 181.2459 187.1742 cm +1 0 0 1 181.2459 181.5645 cm q []0 d 0 J @@ -3848,31 +4056,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -187.1742 cm +1 0 0 1 -181.2459 -181.5645 cm BT -/F8 9.9626 Tf 184.2347 187.1742 Td[(max)]TJ +/F8 9.9626 Tf 184.2347 181.5645 Td[(max)]TJ ET -1 0 0 1 202.7764 187.1742 cm +1 0 0 1 202.7764 181.5645 cm 0 g 0 G -1 0 0 1 -202.7764 -187.1742 cm +1 0 0 1 -202.7764 -181.5645 cm BT -/F8 9.9626 Tf 207.4357 187.1742 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +/F8 9.9626 Tf 207.4357 181.5645 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ ET -1 0 0 1 479.4719 187.1742 cm +1 0 0 1 479.4719 181.5645 cm 0 g 0 G -1 0 0 1 -479.4719 -187.1742 cm +1 0 0 1 -479.4719 -181.5645 cm BT -/F8 9.9626 Tf 479.4719 187.1742 Td[(100)]TJ +/F8 9.9626 Tf 479.4719 181.5645 Td[(104)]TJ ET -1 0 0 1 494.4159 187.1742 cm +1 0 0 1 494.4159 181.5645 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -173.8045 cm +1 0 0 1 -165.6488 -169.3167 cm BT -/F8 9.9626 Tf 165.6488 173.8045 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 169.3167 Td[(psb)]TJ ET -1 0 0 1 181.2459 173.8045 cm +1 0 0 1 181.2459 169.3167 cm q []0 d 0 J @@ -3881,31 +4089,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -173.8045 cm +1 0 0 1 -181.2459 -169.3167 cm BT -/F8 9.9626 Tf 184.2347 173.8045 Td[(min)]TJ +/F8 9.9626 Tf 184.2347 169.3167 Td[(min)]TJ ET -1 0 0 1 200.8392 173.8045 cm +1 0 0 1 200.8392 169.3167 cm 0 g 0 G -1 0 0 1 -200.8392 -173.8045 cm +1 0 0 1 -200.8392 -169.3167 cm BT -/F8 9.9626 Tf 207.4357 173.8045 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +/F8 9.9626 Tf 207.4357 169.3167 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ ET -1 0 0 1 479.4719 173.8045 cm +1 0 0 1 479.4719 169.3167 cm 0 g 0 G -1 0 0 1 -479.4719 -173.8045 cm +1 0 0 1 -479.4719 -169.3167 cm BT -/F8 9.9626 Tf 479.4719 173.8045 Td[(101)]TJ +/F8 9.9626 Tf 479.4719 169.3167 Td[(105)]TJ ET -1 0 0 1 494.4159 173.8045 cm +1 0 0 1 494.4159 169.3167 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -160.4348 cm +1 0 0 1 -165.6488 -157.0689 cm BT -/F8 9.9626 Tf 165.6488 160.4348 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 157.0689 Td[(psb)]TJ ET -1 0 0 1 181.2459 160.4348 cm +1 0 0 1 181.2459 157.0689 cm q []0 d 0 J @@ -3914,31 +4122,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -160.4348 cm +1 0 0 1 -181.2459 -157.0689 cm BT -/F8 9.9626 Tf 184.2347 160.4348 Td[(amx)]TJ +/F8 9.9626 Tf 184.2347 157.0689 Td[(amx)]TJ ET -1 0 0 1 202.7764 160.4348 cm +1 0 0 1 202.7764 157.0689 cm 0 g 0 G -1 0 0 1 -202.7764 -160.4348 cm +1 0 0 1 -202.7764 -157.0689 cm BT -/F8 9.9626 Tf 207.4357 160.4348 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +/F8 9.9626 Tf 207.4357 157.0689 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ ET -1 0 0 1 479.4719 160.4348 cm +1 0 0 1 479.4719 157.0689 cm 0 g 0 G -1 0 0 1 -479.4719 -160.4348 cm +1 0 0 1 -479.4719 -157.0689 cm BT -/F8 9.9626 Tf 479.4719 160.4348 Td[(102)]TJ +/F8 9.9626 Tf 479.4719 157.0689 Td[(106)]TJ ET -1 0 0 1 494.4159 160.4348 cm +1 0 0 1 494.4159 157.0689 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -147.0651 cm +1 0 0 1 -165.6488 -144.8211 cm BT -/F8 9.9626 Tf 165.6488 147.0651 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 144.8211 Td[(psb)]TJ ET -1 0 0 1 181.2459 147.0651 cm +1 0 0 1 181.2459 144.8211 cm q []0 d 0 J @@ -3947,31 +4155,31 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -147.0651 cm +1 0 0 1 -181.2459 -144.8211 cm BT -/F8 9.9626 Tf 184.2347 147.0651 Td[(amn)]TJ +/F8 9.9626 Tf 184.2347 144.8211 Td[(amn)]TJ ET -1 0 0 1 203.0531 147.0651 cm +1 0 0 1 203.0531 144.8211 cm 0 g 0 G -1 0 0 1 -203.0531 -147.0651 cm +1 0 0 1 -203.0531 -144.8211 cm BT -/F8 9.9626 Tf 207.4357 147.0651 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +/F8 9.9626 Tf 207.4357 144.8211 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ ET -1 0 0 1 479.4719 147.0651 cm +1 0 0 1 479.4719 144.8211 cm 0 g 0 G -1 0 0 1 -479.4719 -147.0651 cm +1 0 0 1 -479.4719 -144.8211 cm BT -/F8 9.9626 Tf 479.4719 147.0651 Td[(103)]TJ +/F8 9.9626 Tf 479.4719 144.8211 Td[(107)]TJ ET -1 0 0 1 494.4159 147.0651 cm +1 0 0 1 494.4159 144.8211 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG -1 0 0 1 -165.6488 -133.6953 cm +1 0 0 1 -165.6488 -132.5734 cm BT -/F8 9.9626 Tf 165.6488 133.6953 Td[(psb)]TJ +/F8 9.9626 Tf 165.6488 132.5734 Td[(psb)]TJ ET -1 0 0 1 181.2459 133.6953 cm +1 0 0 1 181.2459 132.5734 cm q []0 d 0 J @@ -3980,25 +4188,25 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -181.2459 -133.6953 cm +1 0 0 1 -181.2459 -132.5734 cm BT -/F8 9.9626 Tf 184.2347 133.6953 Td[(snd)]TJ +/F8 9.9626 Tf 184.2347 132.5734 Td[(snd)]TJ ET -1 0 0 1 199.2341 133.6953 cm +1 0 0 1 199.2341 132.5734 cm 0 g 0 G -1 0 0 1 -199.2341 -133.6953 cm +1 0 0 1 -199.2341 -132.5734 cm BT -/F8 9.9626 Tf 207.4357 133.6953 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ +/F8 9.9626 Tf 207.4357 132.5734 Td[(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-500(.)-499(.)-500(.)-500(.)-500(.)-499(.)-500(.)]TJ ET -1 0 0 1 479.4719 133.6953 cm +1 0 0 1 479.4719 132.5734 cm 0 g 0 G -1 0 0 1 -479.4719 -133.6953 cm +1 0 0 1 -479.4719 -132.5734 cm BT -/F8 9.9626 Tf 479.4719 133.6953 Td[(104)]TJ +/F8 9.9626 Tf 479.4719 132.5734 Td[(108)]TJ ET -1 0 0 1 494.4159 133.6953 cm +1 0 0 1 494.4159 132.5734 cm 0 g 0 G -1 0 0 1 -328.7671 -13.3697 cm +1 0 0 1 -328.7671 -12.2478 cm 0 0 1 rg 0 0 1 RG 1 0 0 1 -165.6488 -120.3256 cm BT @@ -4027,7 +4235,7 @@ ET 0 g 0 G 1 0 0 1 -479.4719 -120.3256 cm BT -/F8 9.9626 Tf 479.4719 120.3256 Td[(105)]TJ +/F8 9.9626 Tf 479.4719 120.3256 Td[(109)]TJ ET 1 0 0 1 494.4159 120.3256 cm 0 g 0 G @@ -4041,330 +4249,358 @@ ET 0 g 0 G endstream endobj -487 0 obj << +503 0 obj << /Type /Page -/Contents 488 0 R -/Resources 486 0 R +/Contents 504 0 R +/Resources 502 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 435 0 R -/Annots [ 490 0 R 491 0 R 492 0 R 493 0 R 494 0 R 495 0 R 496 0 R 497 0 R 498 0 R 499 0 R 500 0 R 501 0 R 502 0 R 503 0 R 504 0 R 505 0 R 506 0 R 507 0 R 508 0 R 509 0 R 510 0 R 511 0 R 512 0 R 513 0 R 514 0 R 515 0 R 516 0 R 517 0 R 518 0 R 519 0 R 520 0 R 521 0 R 522 0 R 523 0 R 524 0 R 525 0 R 526 0 R 527 0 R 528 0 R 529 0 R 530 0 R 531 0 R 532 0 R 533 0 R ] +/Parent 451 0 R +/Annots [ 506 0 R 507 0 R 508 0 R 509 0 R 510 0 R 511 0 R 512 0 R 513 0 R 514 0 R 515 0 R 516 0 R 517 0 R 518 0 R 519 0 R 520 0 R 521 0 R 522 0 R 523 0 R 524 0 R 525 0 R 526 0 R 527 0 R 528 0 R 529 0 R 530 0 R 531 0 R 532 0 R 533 0 R 534 0 R 535 0 R 536 0 R 537 0 R 538 0 R 539 0 R 540 0 R 541 0 R 542 0 R 543 0 R 544 0 R 545 0 R 546 0 R 547 0 R 548 0 R 549 0 R 550 0 R 551 0 R 552 0 R 553 0 R ] >> endobj -490 0 obj << +506 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [149.7086 703.1954 302.5804 714.0436] /Subtype /Link /A << /S /GoTo /D (section.6) >> >> endobj -491 0 obj << +507 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 689.8257 205.7098 700.6739] +/Rect [164.6526 690.9476 205.7098 701.7958] /Subtype /Link /A << /S /GoTo /D (section*.60) >> >> endobj -492 0 obj << +508 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 676.456 207.4256 687.3042] +/Rect [164.6526 678.6999 207.4256 689.5481] /Subtype /Link /A << /S /GoTo /D (section*.63) >> >> endobj -493 0 obj << +509 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 663.0863 209.6395 673.9345] +/Rect [164.6526 666.4521 209.6395 677.3003] /Subtype /Link /A << /S /GoTo /D (section*.66) >> >> endobj -494 0 obj << +510 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 649.7166 210.1376 660.5648] +/Rect [164.6526 654.2043 210.1376 665.0525] /Subtype /Link /A << /S /GoTo /D (section*.69) >> >> endobj -495 0 obj << +511 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 636.3469 210.9955 647.1951] +/Rect [164.6526 641.9565 210.9955 652.8047] /Subtype /Link /A << /S /GoTo /D (section*.71) >> >> endobj -496 0 obj << +512 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 622.9772 222.591 633.8254] +/Rect [164.6526 629.7088 222.591 640.557] /Subtype /Link /A << /S /GoTo /D (section*.73) >> >> endobj -497 0 obj << +513 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 609.6074 205.2117 620.4556] +/Rect [164.6526 617.461 205.2117 628.3092] /Subtype /Link /A << /S /GoTo /D (section*.76) >> >> endobj -498 0 obj << +514 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 596.2377 206.9275 607.0859] +/Rect [164.6526 605.2132 206.9275 616.0614] /Subtype /Link /A << /S /GoTo /D (section*.79) >> >> endobj -499 0 obj << +515 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 582.868 209.1414 593.7162] +/Rect [164.6526 592.9654 209.1414 603.8136] /Subtype /Link /A << /S /GoTo /D (section*.82) >> >> endobj -500 0 obj << +516 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 569.4983 210.4974 580.3465] +/Rect [164.6526 580.7176 210.4974 591.5659] /Subtype /Link /A << /S /GoTo /D (section*.85) >> >> endobj -501 0 obj << +517 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 556.1286 204.1324 566.9768] +/Rect [164.6526 568.4699 204.1324 579.3181] /Subtype /Link /A << /S /GoTo /D (section*.87) >> >> endobj -502 0 obj << +518 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 542.7589 205.1563 553.6071] +/Rect [164.6526 556.2221 205.1563 567.0703] /Subtype /Link /A << /S /GoTo /D (section*.90) >> >> endobj -503 0 obj << +519 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 529.3892 206.8721 540.2374] +/Rect [164.6526 543.9743 206.8721 554.8225] /Subtype /Link /A << /S /GoTo /D (section*.92) >> >> endobj -504 0 obj << +520 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 516.0195 209.086 526.8677] +/Rect [164.6526 531.7265 209.086 542.5748] /Subtype /Link /A << /S /GoTo /D (section*.95) >> >> endobj -505 0 obj << +521 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 502.6498 210.442 513.498] +/Rect [164.6526 519.4788 210.442 530.327] /Subtype /Link /A << /S /GoTo /D (section*.97) >> >> endobj -506 0 obj << +522 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 489.2801 202.9424 500.1283] +/Rect [164.6526 507.231 202.9424 518.0792] /Subtype /Link /A << /S /GoTo /D (section*.99) >> >> endobj -507 0 obj << +523 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 475.9103 231.978 486.7585] +/Rect [164.6526 494.9832 231.978 505.8314] /Subtype /Link /A << /S /GoTo /D (section*.101) >> >> endobj -508 0 obj << +524 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 462.5406 231.978 473.3888] +/Rect [164.6526 482.7354 231.978 493.5836] /Subtype /Link /A << /S /GoTo /D (section*.104) >> >> endobj -509 0 obj << +525 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 449.1709 243.6399 460.0191] +/Rect [164.6526 470.4877 222.912 481.3359] /Subtype /Link /A << /S /GoTo /D (section*.106) >> >> endobj -510 0 obj << +526 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 435.8012 233.4005 446.6494] +/Rect [164.6526 458.2399 239.7378 469.0881] /Subtype /Link /A << /S /GoTo /D (section*.109) >> >> endobj -511 0 obj << +527 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 422.4315 227.3675 433.2797] +/Rect [164.6526 445.9921 215.7167 456.8403] /Subtype /Link /A << /S /GoTo /D (section*.112) >> >> endobj -512 0 obj << +528 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 409.0618 208.8093 419.91] +/Rect [164.6526 433.7443 232.5426 444.5925] /Subtype /Link /A << /S /GoTo /D (section*.115) >> >> endobj -513 0 obj << -/Type /Annot -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 395.6921 234.2528 406.5403] -/Subtype /Link -/A << /S /GoTo /D (section*.117) >> ->> endobj -514 0 obj << +529 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 382.3224 210.2207 393.1706] +/Rect [164.6526 421.4966 243.6399 432.3448] /Subtype /Link /A << /S /GoTo /D (section*.118) >> >> endobj -515 0 obj << +530 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 368.9527 207.1765 379.8009] +/Rect [164.6526 409.2488 233.4005 420.097] /Subtype /Link -/A << /S /GoTo /D (section*.119) >> +/A << /S /GoTo /D (section*.121) >> >> endobj -516 0 obj << +531 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 355.5829 207.4533 366.4312] +/Rect [164.6526 397.001 227.3675 407.8492] /Subtype /Link -/A << /S /GoTo /D (section*.120) >> +/A << /S /GoTo /D (section*.124) >> >> endobj -517 0 obj << +532 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [149.7086 333.2447 315.6771 342.1557] +/Rect [164.6526 384.7532 208.8093 395.6014] /Subtype /Link -/A << /S /GoTo /D (section.7) >> +/A << /S /GoTo /D (section*.127) >> >> endobj -518 0 obj << +533 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 317.9378 200.175 328.786] +/Rect [164.6526 372.5054 234.2528 383.3537] /Subtype /Link -/A << /S /GoTo /D (section*.123) >> +/A << /S /GoTo /D (section*.129) >> >> endobj -519 0 obj << +534 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 304.5681 201.5587 315.4163] +/Rect [164.6526 360.2577 210.2207 371.1059] /Subtype /Link -/A << /S /GoTo /D (section*.126) >> +/A << /S /GoTo /D (section*.130) >> >> endobj -520 0 obj << +535 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 291.1984 201.5587 302.0466] +/Rect [164.6526 348.0099 207.1765 358.8581] /Subtype /Link -/A << /S /GoTo /D (section*.129) >> +/A << /S /GoTo /D (section*.131) >> >> endobj -521 0 obj << +536 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 277.8287 244.7192 288.6769] +/Rect [164.6526 335.7621 207.4533 346.6103] /Subtype /Link /A << /S /GoTo /D (section*.132) >> >> endobj -522 0 obj << +537 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 264.459 221.7774 275.3072] +/Rect [149.7086 315.2938 315.6771 324.2048] /Subtype /Link -/A << /S /GoTo /D (section*.134) >> +/A << /S /GoTo /D (section.7) >> >> endobj -523 0 obj << +538 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 251.0893 211.7981 261.9375] +/Rect [164.6526 301.1088 200.175 311.957] /Subtype /Link -/A << /S /GoTo /D (section*.136) >> +/A << /S /GoTo /D (section*.135) >> >> endobj -524 0 obj << +539 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 237.7196 214.6485 248.5678] +/Rect [164.6526 288.861 201.5587 299.7093] /Subtype /Link /A << /S /GoTo /D (section*.138) >> >> endobj -525 0 obj << +540 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 224.3499 208.7816 235.1981] +/Rect [164.6526 276.6133 201.5587 287.4615] /Subtype /Link -/A << /S /GoTo /D (section*.140) >> +/A << /S /GoTo /D (section*.141) >> >> endobj -526 0 obj << +541 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 210.9802 208.2558 221.8284] +/Rect [164.6526 264.3655 244.7192 275.2137] /Subtype /Link -/A << /S /GoTo /D (section*.142) >> +/A << /S /GoTo /D (section*.144) >> >> endobj -527 0 obj << +542 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 197.6104 202.9977 208.4586] +/Rect [164.6526 252.1177 221.7774 262.9659] /Subtype /Link -/A << /S /GoTo /D (section*.144) >> +/A << /S /GoTo /D (section*.146) >> >> endobj -528 0 obj << +543 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 184.2407 203.7726 195.0889] +/Rect [164.6526 239.8699 211.7981 250.7181] /Subtype /Link -/A << /S /GoTo /D (section*.147) >> +/A << /S /GoTo /D (section*.148) >> >> endobj -529 0 obj << +544 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 170.871 201.8354 181.7192] +/Rect [164.6526 227.6222 214.6485 238.4704] /Subtype /Link /A << /S /GoTo /D (section*.150) >> >> endobj -530 0 obj << +545 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 157.5013 203.7726 168.3495] +/Rect [164.6526 215.3744 208.7816 226.2226] /Subtype /Link -/A << /S /GoTo /D (section*.153) >> +/A << /S /GoTo /D (section*.152) >> >> endobj -531 0 obj << +546 0 obj << +/Type /Annot +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [164.6526 203.1266 208.2558 213.9748] +/Subtype /Link +/A << /S /GoTo /D (section*.154) >> +>> endobj +547 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 144.1316 204.0494 154.9798] +/Rect [164.6526 190.8788 202.9977 201.727] /Subtype /Link /A << /S /GoTo /D (section*.156) >> >> endobj -532 0 obj << +548 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 130.7619 200.2303 141.6101] +/Rect [164.6526 178.6311 203.7726 189.4793] /Subtype /Link /A << /S /GoTo /D (section*.159) >> >> endobj -533 0 obj << +549 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [164.6526 117.3922 198.819 128.2404] +/Rect [164.6526 166.3833 201.8354 177.2315] /Subtype /Link /A << /S /GoTo /D (section*.162) >> >> endobj -489 0 obj << -/D [487 0 R /XYZ 150.7049 740.9981 null] +550 0 obj << +/Type /Annot +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [164.6526 154.1355 203.7726 164.9837] +/Subtype /Link +/A << /S /GoTo /D (section*.165) >> >> endobj -486 0 obj << -/Font << /F29 431 0 R /F8 434 0 R >> +551 0 obj << +/Type /Annot +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [164.6526 141.8877 204.0494 152.7359] +/Subtype /Link +/A << /S /GoTo /D (section*.168) >> +>> endobj +552 0 obj << +/Type /Annot +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [164.6526 129.6399 200.2303 140.4882] +/Subtype /Link +/A << /S /GoTo /D (section*.171) >> +>> endobj +553 0 obj << +/Type /Annot +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [164.6526 117.3922 198.819 128.2404] +/Subtype /Link +/A << /S /GoTo /D (section*.174) >> +>> endobj +505 0 obj << +/D [503 0 R /XYZ 150.7049 740.9981 null] +>> endobj +502 0 obj << +/Font << /F29 447 0 R /F8 450 0 R >> /ProcSet [ /PDF /Text ] >> endobj -536 0 obj << +556 0 obj << /Length 12396 >> stream @@ -4382,7 +4618,7 @@ ET 0 g 0 G 1 0 0 1 -189.1921 -706.1289 cm BT -/F29 9.9626 Tf 426.421 706.1289 Td[(106)]TJ +/F29 9.9626 Tf 426.421 706.1289 Td[(110)]TJ ET 1 0 0 1 114.8394 694.1737 cm 0 0 1 rg 0 0 1 RG @@ -4413,7 +4649,7 @@ ET 0 g 0 G 1 0 0 1 -428.6625 -694.1737 cm BT -/F8 9.9626 Tf 428.6625 694.1737 Td[(108)]TJ +/F8 9.9626 Tf 428.6625 694.1737 Td[(112)]TJ ET 1 0 0 1 443.6065 694.1737 cm 0 g 0 G @@ -4446,7 +4682,7 @@ ET 0 g 0 G 1 0 0 1 -428.6625 -682.2185 cm BT -/F8 9.9626 Tf 428.6625 682.2185 Td[(109)]TJ +/F8 9.9626 Tf 428.6625 682.2185 Td[(113)]TJ ET 1 0 0 1 443.6065 682.2185 cm 0 g 0 G @@ -4492,7 +4728,7 @@ ET 0 g 0 G 1 0 0 1 -428.6625 -670.2634 cm BT -/F8 9.9626 Tf 428.6625 670.2634 Td[(110)]TJ +/F8 9.9626 Tf 428.6625 670.2634 Td[(114)]TJ ET 1 0 0 1 443.6065 670.2634 cm 0 g 0 G @@ -4538,7 +4774,7 @@ ET 0 g 0 G 1 0 0 1 -428.6625 -658.3082 cm BT -/F8 9.9626 Tf 428.6625 658.3082 Td[(111)]TJ +/F8 9.9626 Tf 428.6625 658.3082 Td[(115)]TJ ET 1 0 0 1 443.6065 658.3082 cm 0 g 0 G @@ -4552,7 +4788,7 @@ ET 0 g 0 G 1 0 0 1 -155.0647 -636.3904 cm BT -/F29 9.9626 Tf 426.421 636.3904 Td[(112)]TJ +/F29 9.9626 Tf 426.421 636.3904 Td[(116)]TJ ET 1 0 0 1 114.8394 624.4352 cm 0 0 1 rg 0 0 1 RG @@ -4583,7 +4819,7 @@ ET 0 g 0 G 1 0 0 1 -428.6625 -624.4352 cm BT -/F8 9.9626 Tf 428.6625 624.4352 Td[(113)]TJ +/F8 9.9626 Tf 428.6625 624.4352 Td[(117)]TJ ET 1 0 0 1 443.6065 624.4352 cm 0 g 0 G @@ -4616,7 +4852,7 @@ ET 0 g 0 G 1 0 0 1 -428.6625 -612.48 cm BT -/F8 9.9626 Tf 428.6625 612.48 Td[(114)]TJ +/F8 9.9626 Tf 428.6625 612.48 Td[(118)]TJ ET 1 0 0 1 443.6065 612.48 cm 0 g 0 G @@ -4662,7 +4898,7 @@ ET 0 g 0 G 1 0 0 1 -428.6625 -600.5249 cm BT -/F8 9.9626 Tf 428.6625 600.5249 Td[(115)]TJ +/F8 9.9626 Tf 428.6625 600.5249 Td[(119)]TJ ET 1 0 0 1 443.6065 600.5249 cm 0 g 0 G @@ -4708,7 +4944,7 @@ ET 0 g 0 G 1 0 0 1 -428.6625 -588.5697 cm BT -/F8 9.9626 Tf 428.6625 588.5697 Td[(116)]TJ +/F8 9.9626 Tf 428.6625 588.5697 Td[(120)]TJ ET 1 0 0 1 443.6065 588.5697 cm 0 g 0 G @@ -4722,7 +4958,7 @@ ET 0 g 0 G 1 0 0 1 -233.4786 -566.6519 cm BT -/F29 9.9626 Tf 426.421 566.6519 Td[(117)]TJ +/F29 9.9626 Tf 426.421 566.6519 Td[(121)]TJ ET 1 0 0 1 114.8394 554.6967 cm 0 0 1 rg 0 0 1 RG @@ -4753,7 +4989,7 @@ ET 0 g 0 G 1 0 0 1 -428.6625 -554.6967 cm BT -/F8 9.9626 Tf 428.6625 554.6967 Td[(118)]TJ +/F8 9.9626 Tf 428.6625 554.6967 Td[(122)]TJ ET 1 0 0 1 443.6065 554.6967 cm 0 g 0 G @@ -4786,7 +5022,7 @@ ET 0 g 0 G 1 0 0 1 -428.6625 -542.7415 cm BT -/F8 9.9626 Tf 428.6625 542.7415 Td[(119)]TJ +/F8 9.9626 Tf 428.6625 542.7415 Td[(123)]TJ ET 1 0 0 1 443.6065 542.7415 cm 0 g 0 G @@ -4819,7 +5055,7 @@ ET 0 g 0 G 1 0 0 1 -428.6625 -530.7863 cm BT -/F8 9.9626 Tf 428.6625 530.7863 Td[(120)]TJ +/F8 9.9626 Tf 428.6625 530.7863 Td[(124)]TJ ET 1 0 0 1 443.6065 530.7863 cm 0 g 0 G @@ -4865,7 +5101,7 @@ ET 0 g 0 G 1 0 0 1 -428.6625 -518.8312 cm BT -/F8 9.9626 Tf 428.6625 518.8312 Td[(121)]TJ +/F8 9.9626 Tf 428.6625 518.8312 Td[(125)]TJ ET 1 0 0 1 443.6065 518.8312 cm 0 g 0 G @@ -4879,7 +5115,7 @@ ET 0 g 0 G 1 0 0 1 -205.4934 -496.9134 cm BT -/F29 9.9626 Tf 426.421 496.9134 Td[(122)]TJ +/F29 9.9626 Tf 426.421 496.9134 Td[(126)]TJ ET 1 0 0 1 114.8394 484.9582 cm 0 0 1 rg 0 0 1 RG @@ -4910,7 +5146,7 @@ ET 0 g 0 G 1 0 0 1 -428.6625 -484.9582 cm BT -/F8 9.9626 Tf 428.6625 484.9582 Td[(123)]TJ +/F8 9.9626 Tf 428.6625 484.9582 Td[(127)]TJ ET 1 0 0 1 443.6065 484.9582 cm 0 g 0 G @@ -4924,141 +5160,141 @@ ET 0 g 0 G endstream endobj -535 0 obj << +555 0 obj << /Type /Page -/Contents 536 0 R -/Resources 534 0 R +/Contents 556 0 R +/Resources 554 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 435 0 R -/Annots [ 538 0 R 539 0 R 540 0 R 541 0 R 542 0 R 543 0 R 544 0 R 545 0 R 546 0 R 547 0 R 548 0 R 549 0 R 550 0 R 551 0 R 552 0 R 553 0 R 554 0 R ] +/Parent 451 0 R +/Annots [ 558 0 R 559 0 R 560 0 R 561 0 R 562 0 R 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 ] >> endobj -538 0 obj << +558 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [98.8991 703.1954 190.1884 714.0436] /Subtype /Link /A << /S /GoTo /D (section.8) >> >> endobj -539 0 obj << +559 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 691.2402 167.1876 702.0885] /Subtype /Link -/A << /S /GoTo /D (section*.165) >> +/A << /S /GoTo /D (section*.177) >> >> endobj -540 0 obj << +560 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 679.2851 155.5368 690.1333] /Subtype /Link -/A << /S /GoTo /D (section*.167) >> +/A << /S /GoTo /D (section*.179) >> >> endobj -541 0 obj << +561 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 667.3299 202.1289 678.1781] /Subtype /Link -/A << /S /GoTo /D (section*.169) >> +/A << /S /GoTo /D (section*.181) >> >> endobj -542 0 obj << +562 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 655.3747 189.039 666.2229] /Subtype /Link -/A << /S /GoTo /D (section*.171) >> +/A << /S /GoTo /D (section*.183) >> >> endobj -543 0 obj << +563 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [98.8991 635.3941 156.061 644.3051] /Subtype /Link /A << /S /GoTo /D (section.9) >> >> endobj -544 0 obj << +564 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 623.4389 149.0611 632.35] /Subtype /Link -/A << /S /GoTo /D (section*.173) >> +/A << /S /GoTo /D (section*.185) >> >> endobj -545 0 obj << +565 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 611.4838 152.382 620.3948] /Subtype /Link -/A << /S /GoTo /D (section*.175) >> +/A << /S /GoTo /D (section*.187) >> >> endobj -546 0 obj << +566 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 599.5286 175.6172 608.4396] /Subtype /Link -/A << /S /GoTo /D (section*.177) >> +/A << /S /GoTo /D (section*.189) >> >> endobj -547 0 obj << +567 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 587.5734 178.938 596.2196] /Subtype /Link -/A << /S /GoTo /D (section*.179) >> +/A << /S /GoTo /D (section*.191) >> >> endobj -548 0 obj << +568 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [98.8991 565.6556 234.4749 574.5666] /Subtype /Link /A << /S /GoTo /D (section.10) >> >> endobj -549 0 obj << +569 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 551.7633 167.6581 562.6115] /Subtype /Link -/A << /S /GoTo /D (section*.181) >> +/A << /S /GoTo /D (section*.193) >> >> endobj -550 0 obj << +570 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 539.8081 166.5511 550.6563] /Subtype /Link -/A << /S /GoTo /D (section*.184) >> +/A << /S /GoTo /D (section*.196) >> >> endobj -551 0 obj << +571 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 527.8529 171.2557 538.7011] /Subtype /Link -/A << /S /GoTo /D (section*.186) >> +/A << /S /GoTo /D (section*.198) >> >> endobj -552 0 obj << +572 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 515.8978 178.5229 526.746] /Subtype /Link -/A << /S /GoTo /D (section*.188) >> +/A << /S /GoTo /D (section*.200) >> >> endobj -553 0 obj << +573 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [98.8991 495.9171 206.4896 504.8281] /Subtype /Link /A << /S /GoTo /D (section.11) >> >> endobj -554 0 obj << +574 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [113.8431 482.0248 164.8907 492.873] /Subtype /Link -/A << /S /GoTo /D (section*.190) >> +/A << /S /GoTo /D (section*.202) >> >> endobj -537 0 obj << -/D [535 0 R /XYZ 99.8954 740.9981 null] +557 0 obj << +/D [555 0 R /XYZ 99.8954 740.9981 null] >> endobj -534 0 obj << -/Font << /F29 431 0 R /F8 434 0 R >> +554 0 obj << +/Font << /F29 447 0 R /F8 450 0 R >> /ProcSet [ /PDF /Text ] >> endobj -557 0 obj << +577 0 obj << /Length 219 >> stream @@ -5076,21 +5312,21 @@ ET 0 g 0 G endstream endobj -556 0 obj << +576 0 obj << /Type /Page -/Contents 557 0 R -/Resources 555 0 R +/Contents 577 0 R +/Resources 575 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 435 0 R +/Parent 451 0 R >> endobj -558 0 obj << -/D [556 0 R /XYZ 150.7049 740.9981 null] +578 0 obj << +/D [576 0 R /XYZ 150.7049 740.9981 null] >> endobj -555 0 obj << -/Font << /F8 434 0 R >> +575 0 obj << +/Font << /F8 450 0 R >> /ProcSet [ /PDF /Text ] >> endobj -561 0 obj << +581 0 obj << /Length 11464 >> stream @@ -5196,57 +5432,57 @@ ET 0 g 0 G endstream endobj -560 0 obj << +580 0 obj << /Type /Page -/Contents 561 0 R -/Resources 559 0 R +/Contents 581 0 R +/Resources 579 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 572 0 R -/Annots [ 562 0 R 563 0 R 564 0 R 565 0 R 566 0 R 567 0 R 568 0 R ] +/Parent 592 0 R +/Annots [ 582 0 R 583 0 R 584 0 R 585 0 R 586 0 R 587 0 R 588 0 R ] >> endobj -562 0 obj << +582 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[0 1 0] /Rect [408.3372 572.3677 420.2924 580.7806] /Subtype /Link /A << /S /GoTo /D (cite.metcalf) >> >> endobj -563 0 obj << +583 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[0 1 0] /Rect [223.6012 536.5022 235.5564 544.9151] /Subtype /Link /A << /S /GoTo /D (cite.machiels) >> >> endobj -564 0 obj << +584 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[0 1 0] /Rect [132.5064 404.9953 139.4802 413.4082] /Subtype /Link /A << /S /GoTo /D (cite.sblas97) >> >> endobj -565 0 obj << +585 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[0 1 0] /Rect [144.8046 404.9953 151.7784 413.4082] /Subtype /Link /A << /S /GoTo /D (cite.sblas02) >> >> endobj -566 0 obj << +586 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[0 1 0] /Rect [141.6002 393.0402 153.5554 401.453] /Subtype /Link /A << /S /GoTo /D (cite.BLAS1) >> >> endobj -567 0 obj << +587 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[0 1 0] /Rect [157.6511 393.0402 164.625 401.453] /Subtype /Link /A << /S /GoTo /D (cite.BLAS2) >> >> endobj -568 0 obj << +588 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[0 1 0] /Rect [168.7208 393.0402 175.6946 401.453] @@ -5254,13 +5490,13 @@ endobj /A << /S /GoTo /D (cite.BLAS3) >> >> endobj 10 0 obj << -/D [560 0 R /XYZ 99.8954 716.0915 null] +/D [580 0 R /XYZ 99.8954 716.0915 null] >> endobj -559 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R >> +579 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R >> /ProcSet [ /PDF /Text ] >> endobj -583 0 obj << +603 0 obj << /Length 7618 >> stream @@ -5346,30 +5582,30 @@ ET 0 g 0 G endstream endobj -582 0 obj << +602 0 obj << /Type /Page -/Contents 583 0 R -/Resources 581 0 R +/Contents 603 0 R +/Resources 601 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 572 0 R -/Annots [ 587 0 R 588 0 R 589 0 R ] +/Parent 592 0 R +/Annots [ 607 0 R 608 0 R 609 0 R ] >> endobj -580 0 obj << +600 0 obj << /Type /XObject /Subtype /Form /FormType 1 /PTEX.FileName (./figures/psblas.pdf) /PTEX.PageNumber 1 -/PTEX.InfoDict 591 0 R +/PTEX.InfoDict 611 0 R /Matrix [1.00000000 0.00000000 0.00000000 1.00000000 0.00000000 0.00000000] /BBox [0.00000000 0.00000000 283.00000000 264.00000000] /Resources << /ProcSet [ /PDF /Text ] /ExtGState << -/R7 592 0 R ->>/Font << /R8 593 0 R >> +/R7 612 0 R +>>/Font << /R8 613 0 R >> >> -/Length 594 0 R +/Length 614 0 R /Filter /FlateDecode >> stream @@ -5378,44 +5614,44 @@ x zîÀ˜:ÿ¾4É p[Ë&ÈØ;ØñA·F Z,¹Õ&:Owo mY½åžlÞ§æóK.ž¶Þ±ÿÕçÿþ$æ×KòØxA•©ÆÏÑ7÷÷Ç»iÿp÷åTŸ¢ 7ï“Ü$¼}ñð-¯Ìë-¿3%+`fy Ž &Nà‘Ó^¡?m«y}šnºýýp¹ìoòz¹ÜnYã+$Ía¡Ê0«ÞõÕxʾkzÔendstream endobj -591 0 obj +611 0 obj << /Producer (ESP Ghostscript 815.04) /CreationDate (D:20071019142653) /ModDate (D:20071019142653) >> endobj -592 0 obj +612 0 obj << /Type /ExtGState /OPM 1 >> endobj -593 0 obj +613 0 obj << /BaseFont /Times-Roman /Type /Font /Subtype /Type1 >> endobj -594 0 obj +614 0 obj 1086 endobj -587 0 obj << +607 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [327.1313 584.7682 334.1052 595.6164] /Subtype /Link /A << /S /GoTo /D (figure.1) >> >> endobj -588 0 obj << +608 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[0 1 0] /Rect [284.6553 514.9743 291.6291 523.3872] /Subtype /Link /A << /S /GoTo /D (cite.BLACS) >> >> endobj -589 0 obj << +609 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [387.982 440.2342 394.9559 452.1894] @@ -5423,17 +5659,17 @@ endobj /A << /S /GoTo /D (section.7) >> >> endobj 14 0 obj << -/D [582 0 R /XYZ 150.7049 716.0915 null] +/D [602 0 R /XYZ 150.7049 716.0915 null] >> endobj -590 0 obj << -/D [582 0 R /XYZ 258.7025 228.4056 null] +610 0 obj << +/D [602 0 R /XYZ 258.7025 228.4056 null] >> endobj -581 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F11 586 0 R >> -/XObject << /Im1 580 0 R >> +601 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F11 606 0 R >> +/XObject << /Im1 600 0 R >> /ProcSet [ /PDF /Text ] >> endobj -598 0 obj << +618 0 obj << /Length 11774 >> stream @@ -5544,52 +5780,52 @@ ET 0 g 0 G endstream endobj -597 0 obj << +617 0 obj << /Type /Page -/Contents 598 0 R -/Resources 596 0 R +/Contents 618 0 R +/Resources 616 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 572 0 R -/Annots [ 603 0 R 604 0 R 614 0 R ] +/Parent 592 0 R +/Annots [ 623 0 R 624 0 R 634 0 R ] >> endobj -603 0 obj << +623 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[0 1 0] /Rect [277.9309 573.6257 289.8861 582.0386] /Subtype /Link /A << /S /GoTo /D (cite.METIS) >> >> endobj -604 0 obj << +624 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [214.6258 499.9576 221.0877 511.9969] /Subtype /Link /A << /S /GoTo /D (Hfootnote.1) >> >> endobj -614 0 obj << +634 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [155.9077 171.7348 162.3696 183.7741] /Subtype /Link /A << /S /GoTo /D (Hfootnote.2) >> >> endobj -599 0 obj << -/D [597 0 R /XYZ 99.8954 740.9981 null] +619 0 obj << +/D [617 0 R /XYZ 99.8954 740.9981 null] >> endobj 18 0 obj << -/D [597 0 R /XYZ 99.8954 475.5418 null] +/D [617 0 R /XYZ 99.8954 475.5418 null] >> endobj -618 0 obj << -/D [597 0 R /XYZ 115.1385 167.688 null] +638 0 obj << +/D [617 0 R /XYZ 115.1385 167.688 null] >> endobj -622 0 obj << -/D [597 0 R /XYZ 115.1385 158.1837 null] +642 0 obj << +/D [617 0 R /XYZ 115.1385 158.1837 null] >> endobj -596 0 obj << -/Font << /F8 434 0 R /F19 571 0 R /F32 602 0 R /F7 607 0 R /F18 425 0 R /F11 586 0 R /F10 610 0 R /F14 613 0 R /F29 431 0 R /F34 617 0 R /F33 621 0 R >> +616 0 obj << +/Font << /F8 450 0 R /F19 591 0 R /F32 622 0 R /F7 627 0 R /F18 441 0 R /F11 606 0 R /F10 630 0 R /F14 633 0 R /F29 447 0 R /F34 637 0 R /F33 641 0 R >> /ProcSet [ /PDF /Text ] >> endobj -627 0 obj << +647 0 obj << /Length 7619 >> stream @@ -5747,88 +5983,88 @@ ET 0 g 0 G endstream endobj -626 0 obj << +646 0 obj << /Type /Page -/Contents 627 0 R -/Resources 625 0 R +/Contents 647 0 R +/Resources 645 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 572 0 R -/Annots [ 629 0 R 630 0 R ] +/Parent 592 0 R +/Annots [ 649 0 R 650 0 R ] >> endobj -624 0 obj << +644 0 obj << /Type /XObject /Subtype /Form /FormType 1 /PTEX.FileName (./figures/points.pdf) /PTEX.PageNumber 1 -/PTEX.InfoDict 632 0 R +/PTEX.InfoDict 652 0 R /Matrix [1.00000000 0.00000000 0.00000000 1.00000000 0.00000000 0.00000000] /BBox [0.00000000 0.00000000 274.00000000 308.00000000] /Resources << /ProcSet [ /PDF /Text ] /ExtGState << -/R7 633 0 R ->>/Font << /R8 634 0 R >> +/R7 653 0 R +>>/Font << /R8 654 0 R >> >> -/Length 635 0 R +/Length 655 0 R /Filter /FlateDecode >> stream xœÝYËŽ5Ý÷Wô’ q±Ën»ï6 – 󣄠¹3ÊBü=®§«æ±bA‡HŒ}Ï©c·í²»?­é”ׄÿäïÍeùö]_?ü¾¤Ó©d êwßGüðaù´d"®òçæ²¾¾ä}ÍíëÕûe4­ß ,äýÔ×sÿ»º,_ýx÷Ç/w×·¯®~[¾»ZÞ.ø›Œ1¸ð™âuóâ¯ïÿ¼ûùúáoO*žþx/þÃõí½Î22Tø<ᜇd†&Âoî/×ïV˜âÿõèCê1V^õd¨æõãR ¬Û9ŸÎç¶^–ºµÓ¾ÍšÚýÝz¦zõ¯7‹!€S®ûj짔êJÚR¿–ðWZSöN•m˜´ ide«3çûfyÿõROÛú×|J_F¿~]~z2ò–}×òVÐÕämë¦Î€sQ<I<³¦uiüd¸r͵9.Ö¤¢ÆR’ÉÑãY~ОÐCÑÝ¥Ÿ}öçÙ^â<3LA ‰c‹YÒ¶®ôçY¯qž&mCÙØâÌû懣ç—Ñ#|H–_rƧšÇÒ³,wš0s>}yüÇ5ÒNóË p%U¤ –ðW@E’§$§•|¡pxõE`&ÆøåU ™¤ó«›%AÝIUÍ0Gš]ý‘&ûÖM’ î Jšx÷¬…T.ù)~¼C²8˜}~‚­ÛÍWÛ¢íÁvKÑö¶K,8ÛÍ—&†`[C*—ü¨ONÔÇs­ƒ ½m‚ê ò9؆Áu¶!×`{P9¦m‚êKI7oÛB*—ü¨O샹~ñ̳·Ç'­¡Á^ÝIaÏvRy!œzw'ó¤`Íx"0.Ѥb'…iÄù|ùÌs¼žP:-%X/[´^º“#Àa°há…dÞPÓY/)Z‡Ýqˆ&-VŠÖ½ON¬Çtnƒ®G±À¹ÍY–& é›Ë’וB¿Ìœ¤¡¹M…ÁnngäŽ%¤Ò#ØœÃÉÙÇ‚"d;’Àô)ùÃ(˜\X‹³Ž¥²£0}Z¡pø#`Ó†Sò‹%Hvt§Ð̧f£`ú`-Î+”ÐŽQ4ó9ƒ…Ç,x›O/,îf,z»âißn«ªÝìv«$½úæ-ÜŒå`?›“禩™|,ˆ7cïó™;Ìñº@!osõé]Š¦?ݲta0€yýÒ¥¤Zdy›«OïRÜ<%9­äƒ€[}拇ú6m8uõIPžþhǃf>m))…YÞæê“ Ò<%9­äƒ€[}ækçÿÜæ“WO’rõ= A} £ Ñ0'Ë 9‘S,irêÕ÷+\_ã­uâÝ¿›ÑÆE?æóé{¦ƒÙÇá'È‹ÎB#4_²$&†`[–’qq‘‘&/> Mõ5^_'†`[Bý˜OõºÖÁ–%©¡ ª/]07o[šqq ’&/M Íõ5^_'nÞ¶†4.ú1Ÿ6ØsýÜ¥%]Š!ƒCÞgVe@Ù–‹’…$)š5-ƒÃØ5}‡ä²?ÖLg+‡ |>{é>hO‘jøX5~,ê>–0àxÕ},1’š¬ác ”ø±ŠûX€5‹ûXb$3òø³ Ú…t¡í¡=Å>tpº8Õ‡’Ô$iÎ>´-ö¡Ç%ÀšTÔXJR#ÞgL¼í“-J/0®jãȶw.Þâªick£Z,”Ô¤š^”Ñk·ì«éUÝ ‹¯WjÇ‚µÛçƒ.ÁºUE³zÉgýãPˆ,é"›Ñe±ûÌ‹:t˜!*%~ Ö *«QÊÒ@emPMÓ1:¾Þ’àX¼÷(˜®4æ ¤Nƒ¾]þÎJ¦'endstream endobj -632 0 obj +652 0 obj << /Producer (ESP Ghostscript 815.03) /CreationDate (D:20070123225315) /ModDate (D:20070123225315) >> endobj -633 0 obj +653 0 obj << /Type /ExtGState /OPM 1 >> endobj -634 0 obj +654 0 obj << /BaseFont /Times-Roman /Type /Font /Subtype /Type1 >> endobj -635 0 obj +655 0 obj 1397 endobj -629 0 obj << +649 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[0 1 0] /Rect [294.6652 618.2081 301.6391 626.621] /Subtype /Link /A << /S /GoTo /D (cite.2007c) >> >> endobj -630 0 obj << +650 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[0 1 0] /Rect [305.7348 618.2081 312.7087 626.621] /Subtype /Link /A << /S /GoTo /D (cite.2007d) >> >> endobj -628 0 obj << -/D [626 0 R /XYZ 150.7049 740.9981 null] +648 0 obj << +/D [646 0 R /XYZ 150.7049 740.9981 null] >> endobj -631 0 obj << -/D [626 0 R /XYZ 303.5622 327.3386 null] +651 0 obj << +/D [646 0 R /XYZ 303.5622 327.3386 null] >> endobj 22 0 obj << -/D [626 0 R /XYZ 150.7049 252.5944 null] +/D [646 0 R /XYZ 150.7049 252.5944 null] >> endobj -625 0 obj << -/Font << /F8 434 0 R /F29 431 0 R /F14 613 0 R /F11 586 0 R /F10 610 0 R /F18 425 0 R >> -/XObject << /Im2 624 0 R >> +645 0 obj << +/Font << /F8 450 0 R /F29 447 0 R /F14 633 0 R /F11 606 0 R /F10 630 0 R /F18 441 0 R >> +/XObject << /Im2 644 0 R >> /ProcSet [ /PDF /Text ] >> endobj -640 0 obj << +660 0 obj << /Length 10457 >> stream @@ -6082,39 +6318,39 @@ ET 0 g 0 G endstream endobj -639 0 obj << +659 0 obj << /Type /Page -/Contents 640 0 R -/Resources 638 0 R +/Contents 660 0 R +/Resources 658 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 572 0 R -/Annots [ 642 0 R 643 0 R ] +/Parent 592 0 R +/Annots [ 662 0 R 663 0 R ] >> endobj -642 0 obj << +662 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [406.3576 377.1538 413.3315 389.109] /Subtype /Link /A << /S /GoTo /D (section.3) >> >> endobj -643 0 obj << +663 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [173.8633 344.7387 180.8371 356.6939] /Subtype /Link /A << /S /GoTo /D (section.6) >> >> endobj -641 0 obj << -/D [639 0 R /XYZ 99.8954 740.9981 null] +661 0 obj << +/D [659 0 R /XYZ 99.8954 740.9981 null] >> endobj 26 0 obj << -/D [639 0 R /XYZ 99.8954 210.3303 null] +/D [659 0 R /XYZ 99.8954 210.3303 null] >> endobj -638 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F14 613 0 R /F32 602 0 R /F18 425 0 R /F11 586 0 R >> +658 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F14 633 0 R /F32 622 0 R /F18 441 0 R /F11 606 0 R >> /ProcSet [ /PDF /Text ] >> endobj -646 0 obj << +666 0 obj << /Length 11593 >> stream @@ -6256,51 +6492,51 @@ ET 0 g 0 G endstream endobj -645 0 obj << +665 0 obj << /Type /Page -/Contents 646 0 R -/Resources 644 0 R +/Contents 666 0 R +/Resources 664 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 572 0 R +/Parent 592 0 R >> endobj -647 0 obj << -/D [645 0 R /XYZ 150.7049 740.9981 null] +667 0 obj << +/D [665 0 R /XYZ 150.7049 740.9981 null] >> endobj -651 0 obj << -/D [645 0 R /XYZ 150.7049 376.4002 null] +671 0 obj << +/D [665 0 R /XYZ 150.7049 376.4002 null] >> endobj -652 0 obj << -/D [645 0 R /XYZ 150.7049 356.381 null] +672 0 obj << +/D [665 0 R /XYZ 150.7049 356.381 null] >> endobj -653 0 obj << -/D [645 0 R /XYZ 150.7049 336.085 null] +673 0 obj << +/D [665 0 R /XYZ 150.7049 336.085 null] >> endobj -654 0 obj << -/D [645 0 R /XYZ 150.7049 315.789 null] +674 0 obj << +/D [665 0 R /XYZ 150.7049 315.789 null] >> endobj -655 0 obj << -/D [645 0 R /XYZ 150.7049 283.5379 null] +675 0 obj << +/D [665 0 R /XYZ 150.7049 283.5379 null] >> endobj -656 0 obj << -/D [645 0 R /XYZ 150.7049 263.3706 null] +676 0 obj << +/D [665 0 R /XYZ 150.7049 263.3706 null] >> endobj -657 0 obj << -/D [645 0 R /XYZ 150.7049 244.7544 null] +677 0 obj << +/D [665 0 R /XYZ 150.7049 244.7544 null] >> endobj -658 0 obj << -/D [645 0 R /XYZ 150.7049 228.6288 null] +678 0 obj << +/D [665 0 R /XYZ 150.7049 228.6288 null] >> endobj -659 0 obj << -/D [645 0 R /XYZ 150.7049 210.418 null] +679 0 obj << +/D [665 0 R /XYZ 150.7049 210.418 null] >> endobj -660 0 obj << -/D [645 0 R /XYZ 150.7049 178.4436 null] +680 0 obj << +/D [665 0 R /XYZ 150.7049 178.4436 null] >> endobj -644 0 obj << -/Font << /F8 434 0 R /F32 602 0 R /F11 586 0 R /F9 650 0 R /F19 571 0 R >> +664 0 obj << +/Font << /F8 450 0 R /F32 622 0 R /F11 606 0 R /F9 670 0 R /F19 591 0 R >> /ProcSet [ /PDF /Text ] >> endobj -663 0 obj << +683 0 obj << /Length 10805 >> stream @@ -6450,57 +6686,57 @@ ET 0 g 0 G endstream endobj -662 0 obj << +682 0 obj << /Type /Page -/Contents 663 0 R -/Resources 661 0 R +/Contents 683 0 R +/Resources 681 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 676 0 R +/Parent 696 0 R >> endobj -664 0 obj << -/D [662 0 R /XYZ 99.8954 740.9981 null] +684 0 obj << +/D [682 0 R /XYZ 99.8954 740.9981 null] >> endobj -665 0 obj << -/D [662 0 R /XYZ 99.8954 716.0915 null] +685 0 obj << +/D [682 0 R /XYZ 99.8954 716.0915 null] >> endobj -666 0 obj << -/D [662 0 R /XYZ 99.8954 699.8644 null] +686 0 obj << +/D [682 0 R /XYZ 99.8954 699.8644 null] >> endobj -667 0 obj << -/D [662 0 R /XYZ 99.8954 679.8083 null] +687 0 obj << +/D [682 0 R /XYZ 99.8954 679.8083 null] >> endobj -668 0 obj << -/D [662 0 R /XYZ 99.8954 647.797 null] +688 0 obj << +/D [682 0 R /XYZ 99.8954 647.797 null] >> endobj -669 0 obj << -/D [662 0 R /XYZ 99.8954 627.7409 null] +689 0 obj << +/D [682 0 R /XYZ 99.8954 627.7409 null] >> endobj -670 0 obj << -/D [662 0 R /XYZ 99.8954 607.6848 null] +690 0 obj << +/D [682 0 R /XYZ 99.8954 607.6848 null] >> endobj -671 0 obj << -/D [662 0 R /XYZ 99.8954 585.8802 null] +691 0 obj << +/D [682 0 R /XYZ 99.8954 585.8802 null] >> endobj -672 0 obj << -/D [662 0 R /XYZ 99.8954 557.9194 null] +692 0 obj << +/D [682 0 R /XYZ 99.8954 557.9194 null] >> endobj -673 0 obj << -/D [662 0 R /XYZ 99.8954 529.6818 null] +693 0 obj << +/D [682 0 R /XYZ 99.8954 529.6818 null] >> endobj -674 0 obj << -/D [662 0 R /XYZ 99.8954 513.3994 null] +694 0 obj << +/D [682 0 R /XYZ 99.8954 513.3994 null] >> endobj -675 0 obj << -/D [662 0 R /XYZ 99.8954 497.3938 null] +695 0 obj << +/D [682 0 R /XYZ 99.8954 497.3938 null] >> endobj 30 0 obj << -/D [662 0 R /XYZ 99.8954 258.481 null] +/D [682 0 R /XYZ 99.8954 258.481 null] >> endobj -661 0 obj << -/Font << /F8 434 0 R /F32 602 0 R /F18 425 0 R /F19 571 0 R >> +681 0 obj << +/Font << /F8 450 0 R /F32 622 0 R /F18 441 0 R /F19 591 0 R >> /ProcSet [ /PDF /Text ] >> endobj -679 0 obj << +699 0 obj << /Length 2750 >> stream @@ -6558,29 +6794,29 @@ ET 0 g 0 G endstream endobj -678 0 obj << +698 0 obj << /Type /Page -/Contents 679 0 R -/Resources 677 0 R +/Contents 699 0 R +/Resources 697 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 676 0 R -/Annots [ 681 0 R ] +/Parent 696 0 R +/Annots [ 701 0 R ] >> endobj -681 0 obj << +701 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [169.4542 703.1954 184.1768 714.0436] /Subtype /Link /A << /S /GoTo /D (subsection.3.4) >> >> endobj -680 0 obj << -/D [678 0 R /XYZ 150.7049 740.9981 null] +700 0 obj << +/D [698 0 R /XYZ 150.7049 740.9981 null] >> endobj -677 0 obj << -/Font << /F8 434 0 R /F29 431 0 R >> +697 0 obj << +/Font << /F8 450 0 R /F29 447 0 R >> /ProcSet [ /PDF /Text ] >> endobj -684 0 obj << +704 0 obj << /Length 11047 >> stream @@ -6858,63 +7094,63 @@ ET 0 g 0 G endstream endobj -683 0 obj << +703 0 obj << /Type /Page -/Contents 684 0 R -/Resources 682 0 R +/Contents 704 0 R +/Resources 702 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 676 0 R -/Annots [ 687 0 R 688 0 R ] +/Parent 696 0 R +/Annots [ 707 0 R 708 0 R ] >> endobj -687 0 obj << +707 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [355.7293 457.4661 362.7032 468.3143] /Subtype /Link /A << /S /GoTo /D (section.6) >> >> endobj -688 0 obj << +708 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [311.9336 445.5109 326.6562 456.3591] /Subtype /Link /A << /S /GoTo /D (subsection.3.4) >> >> endobj -685 0 obj << -/D [683 0 R /XYZ 99.8954 740.9981 null] +705 0 obj << +/D [703 0 R /XYZ 99.8954 740.9981 null] >> endobj 34 0 obj << -/D [683 0 R /XYZ 99.8954 716.0915 null] +/D [703 0 R /XYZ 99.8954 716.0915 null] >> endobj 38 0 obj << -/D [683 0 R /XYZ 99.8954 551.1631 null] +/D [703 0 R /XYZ 99.8954 551.1631 null] >> endobj -686 0 obj << -/D [683 0 R /XYZ 342.4274 508.3725 null] +706 0 obj << +/D [703 0 R /XYZ 342.4274 508.3725 null] >> endobj -689 0 obj << -/D [683 0 R /XYZ 99.8954 327.4254 null] +709 0 obj << +/D [703 0 R /XYZ 99.8954 327.4254 null] >> endobj -690 0 obj << -/D [683 0 R /XYZ 99.8954 311.1807 null] +710 0 obj << +/D [703 0 R /XYZ 99.8954 311.1807 null] >> endobj -691 0 obj << -/D [683 0 R /XYZ 99.8954 294.9359 null] +711 0 obj << +/D [703 0 R /XYZ 99.8954 294.9359 null] >> endobj -692 0 obj << -/D [683 0 R /XYZ 99.8954 278.6911 null] +712 0 obj << +/D [703 0 R /XYZ 99.8954 278.6911 null] >> endobj -693 0 obj << -/D [683 0 R /XYZ 99.8954 262.4464 null] +713 0 obj << +/D [703 0 R /XYZ 99.8954 262.4464 null] >> endobj -694 0 obj << -/D [683 0 R /XYZ 99.8954 132.4884 null] +714 0 obj << +/D [703 0 R /XYZ 99.8954 132.4884 null] >> endobj -682 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F32 602 0 R /F29 431 0 R >> +702 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F32 622 0 R /F29 447 0 R >> /ProcSet [ /PDF /Text ] >> endobj -697 0 obj << +717 0 obj << /Length 9395 >> stream @@ -7238,45 +7474,45 @@ ET 0 g 0 G endstream endobj -696 0 obj << +716 0 obj << /Type /Page -/Contents 697 0 R -/Resources 695 0 R +/Contents 717 0 R +/Resources 715 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 676 0 R +/Parent 696 0 R >> endobj -698 0 obj << -/D [696 0 R /XYZ 150.7049 740.9981 null] +718 0 obj << +/D [716 0 R /XYZ 150.7049 740.9981 null] >> endobj -699 0 obj << -/D [696 0 R /XYZ 150.7049 716.0915 null] +719 0 obj << +/D [716 0 R /XYZ 150.7049 716.0915 null] >> endobj -700 0 obj << -/D [696 0 R /XYZ 150.7049 701.976 null] +720 0 obj << +/D [716 0 R /XYZ 150.7049 701.976 null] >> endobj -701 0 obj << -/D [696 0 R /XYZ 150.7049 685.5893 null] +721 0 obj << +/D [716 0 R /XYZ 150.7049 685.5893 null] >> endobj -702 0 obj << -/D [696 0 R /XYZ 150.7049 669.2027 null] +722 0 obj << +/D [716 0 R /XYZ 150.7049 669.2027 null] >> endobj -703 0 obj << -/D [696 0 R /XYZ 150.7049 538.1097 null] +723 0 obj << +/D [716 0 R /XYZ 150.7049 538.1097 null] >> endobj -704 0 obj << -/D [696 0 R /XYZ 150.7049 521.7231 null] +724 0 obj << +/D [716 0 R /XYZ 150.7049 521.7231 null] >> endobj -705 0 obj << -/D [696 0 R /XYZ 150.7049 505.3365 null] +725 0 obj << +/D [716 0 R /XYZ 150.7049 505.3365 null] >> endobj -706 0 obj << -/D [696 0 R /XYZ 198.2214 224.9995 null] +726 0 obj << +/D [716 0 R /XYZ 198.2214 224.9995 null] >> endobj -695 0 obj << -/Font << /F8 434 0 R /F29 431 0 R /F11 586 0 R /F32 602 0 R >> +715 0 obj << +/Font << /F8 450 0 R /F29 447 0 R /F11 606 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -709 0 obj << +729 0 obj << /Length 12389 >> stream @@ -7750,38 +7986,38 @@ ET 0 g 0 G endstream endobj -708 0 obj << +728 0 obj << /Type /Page -/Contents 709 0 R -/Resources 707 0 R +/Contents 729 0 R +/Resources 727 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 676 0 R -/Annots [ 711 0 R ] +/Parent 696 0 R +/Annots [ 731 0 R ] >> endobj -711 0 obj << +731 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [384.0525 599.1613 398.7751 610.0095] /Subtype /Link /A << /S /GoTo /D (subsection.3.4) >> >> endobj -710 0 obj << -/D [708 0 R /XYZ 99.8954 740.9981 null] +730 0 obj << +/D [728 0 R /XYZ 99.8954 740.9981 null] >> endobj 42 0 obj << -/D [708 0 R /XYZ 99.8954 585.6103 null] +/D [728 0 R /XYZ 99.8954 585.6103 null] >> endobj 46 0 obj << -/D [708 0 R /XYZ 99.8954 376.4049 null] +/D [728 0 R /XYZ 99.8954 376.4049 null] >> endobj -712 0 obj << -/D [708 0 R /XYZ 119.6419 345.602 null] +732 0 obj << +/D [728 0 R /XYZ 119.6419 345.602 null] >> endobj -707 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F32 602 0 R /F18 425 0 R >> +727 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F32 622 0 R /F18 441 0 R >> /ProcSet [ /PDF /Text ] >> endobj -715 0 obj << +735 0 obj << /Length 9997 >> stream @@ -8073,35 +8309,35 @@ ET 0 g 0 G endstream endobj -714 0 obj << +734 0 obj << /Type /Page -/Contents 715 0 R -/Resources 713 0 R +/Contents 735 0 R +/Resources 733 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 676 0 R -/Annots [ 717 0 R ] +/Parent 696 0 R +/Annots [ 737 0 R ] >> endobj -717 0 obj << +737 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [354.8562 406.4656 361.8301 417.3138] /Subtype /Link /A << /S /GoTo /D (figure.4) >> >> endobj -716 0 obj << -/D [714 0 R /XYZ 150.7049 740.9981 null] +736 0 obj << +/D [734 0 R /XYZ 150.7049 740.9981 null] >> endobj -718 0 obj << -/D [714 0 R /XYZ 206.3709 248.1257 null] +738 0 obj << +/D [734 0 R /XYZ 206.3709 248.1257 null] >> endobj -719 0 obj << -/D [714 0 R /XYZ 150.7049 170.5652 null] +739 0 obj << +/D [734 0 R /XYZ 150.7049 170.5652 null] >> endobj -713 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F32 602 0 R /F11 586 0 R /F14 613 0 R >> +733 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F32 622 0 R /F11 606 0 R /F14 633 0 R >> /ProcSet [ /PDF /Text ] >> endobj -722 0 obj << +742 0 obj << /Length 12863 >> stream @@ -8523,47 +8759,47 @@ ET 0 g 0 G endstream endobj -721 0 obj << +741 0 obj << /Type /Page -/Contents 722 0 R -/Resources 720 0 R +/Contents 742 0 R +/Resources 740 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 729 0 R -/Annots [ 728 0 R ] +/Parent 749 0 R +/Annots [ 748 0 R ] >> endobj -728 0 obj << +748 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [126.8753 176.8913 133.8492 188.0162] /Subtype /Link /A << /S /GoTo /D (figure.5) >> >> endobj -723 0 obj << -/D [721 0 R /XYZ 99.8954 740.9981 null] +743 0 obj << +/D [741 0 R /XYZ 99.8954 740.9981 null] >> endobj -724 0 obj << -/D [721 0 R /XYZ 99.8954 716.0915 null] +744 0 obj << +/D [741 0 R /XYZ 99.8954 716.0915 null] >> endobj -725 0 obj << -/D [721 0 R /XYZ 99.8954 659.7338 null] +745 0 obj << +/D [741 0 R /XYZ 99.8954 659.7338 null] >> endobj -726 0 obj << -/D [721 0 R /XYZ 99.8954 641.9079 null] +746 0 obj << +/D [741 0 R /XYZ 99.8954 641.9079 null] >> endobj 50 0 obj << -/D [721 0 R /XYZ 99.8954 443.4427 null] +/D [741 0 R /XYZ 99.8954 443.4427 null] >> endobj 54 0 obj << -/D [721 0 R /XYZ 99.8954 249.4537 null] +/D [741 0 R /XYZ 99.8954 249.4537 null] >> endobj -727 0 obj << -/D [721 0 R /XYZ 257.5625 192.0566 null] +747 0 obj << +/D [741 0 R /XYZ 257.5625 192.0566 null] >> endobj -720 0 obj << -/Font << /F8 434 0 R /F32 602 0 R /F11 586 0 R /F14 613 0 R /F29 431 0 R /F18 425 0 R >> +740 0 obj << +/Font << /F8 450 0 R /F32 622 0 R /F11 606 0 R /F14 633 0 R /F29 447 0 R /F18 441 0 R >> /ProcSet [ /PDF /Text ] >> endobj -733 0 obj << +753 0 obj << /Length 8811 >> stream @@ -8975,54 +9211,54 @@ ET 0 g 0 G endstream endobj -732 0 obj << +752 0 obj << /Type /Page -/Contents 733 0 R -/Resources 731 0 R +/Contents 753 0 R +/Resources 751 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 729 0 R -/Annots [ 739 0 R 740 0 R ] +/Parent 749 0 R +/Annots [ 759 0 R 760 0 R ] >> endobj -739 0 obj << +759 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 314.0601 412.5881 325.185] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -740 0 obj << +760 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [351.2306 258.9311 358.2044 270.8863] /Subtype /Link /A << /S /GoTo /D (section.1) >> >> endobj -734 0 obj << -/D [732 0 R /XYZ 150.7049 740.9981 null] +754 0 obj << +/D [752 0 R /XYZ 150.7049 740.9981 null] >> endobj -730 0 obj << -/D [732 0 R /XYZ 206.2879 563.9177 null] +750 0 obj << +/D [752 0 R /XYZ 206.2879 563.9177 null] >> endobj 58 0 obj << -/D [732 0 R /XYZ 150.7049 529.799 null] +/D [752 0 R /XYZ 150.7049 529.799 null] >> endobj 62 0 obj << -/D [732 0 R /XYZ 150.7049 467.9163 null] +/D [752 0 R /XYZ 150.7049 467.9163 null] >> endobj -738 0 obj << -/D [732 0 R /XYZ 150.7049 439.3726 null] +758 0 obj << +/D [752 0 R /XYZ 150.7049 439.3726 null] >> endobj 66 0 obj << -/D [732 0 R /XYZ 150.7049 182.0958 null] +/D [752 0 R /XYZ 150.7049 182.0958 null] >> endobj -741 0 obj << -/D [732 0 R /XYZ 150.7049 153.5522 null] +761 0 obj << +/D [752 0 R /XYZ 150.7049 153.5522 null] >> endobj -731 0 obj << -/Font << /F48 737 0 R /F8 434 0 R /F18 425 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R /F14 613 0 R /F10 610 0 R >> +751 0 obj << +/Font << /F48 757 0 R /F8 450 0 R /F18 441 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R /F14 633 0 R /F10 630 0 R >> /ProcSet [ /PDF /Text ] >> endobj -744 0 obj << +764 0 obj << /Length 9748 >> stream @@ -9466,55 +9702,55 @@ ET 0 g 0 G endstream endobj -743 0 obj << +763 0 obj << /Type /Page -/Contents 744 0 R -/Resources 742 0 R +/Contents 764 0 R +/Resources 762 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 729 0 R -/Annots [ 746 0 R 747 0 R 749 0 R ] +/Parent 749 0 R +/Annots [ 766 0 R 767 0 R 769 0 R ] >> endobj -746 0 obj << +766 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 632.8309 361.7786 643.9558] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -747 0 obj << +767 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [135.5307 562.7025 142.5045 574.6577] /Subtype /Link /A << /S /GoTo /D (section.1) >> >> endobj -749 0 obj << +769 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 321.9965 361.7786 333.1215] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -745 0 obj << -/D [743 0 R /XYZ 99.8954 740.9981 null] +765 0 obj << +/D [763 0 R /XYZ 99.8954 740.9981 null] >> endobj 70 0 obj << -/D [743 0 R /XYZ 99.8954 480.5761 null] +/D [763 0 R /XYZ 99.8954 480.5761 null] >> endobj -748 0 obj << -/D [743 0 R /XYZ 99.8954 451.223 null] +768 0 obj << +/D [763 0 R /XYZ 99.8954 451.223 null] >> endobj 74 0 obj << -/D [743 0 R /XYZ 99.8954 205.6072 null] +/D [763 0 R /XYZ 99.8954 205.6072 null] >> endobj -750 0 obj << -/D [743 0 R /XYZ 99.8954 176.2542 null] +770 0 obj << +/D [763 0 R /XYZ 99.8954 176.2542 null] >> endobj -742 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F32 602 0 R /F14 613 0 R /F10 610 0 R /F18 425 0 R /F19 571 0 R >> +762 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F32 622 0 R /F14 633 0 R /F10 630 0 R /F18 441 0 R /F19 591 0 R >> /ProcSet [ /PDF /Text ] >> endobj -753 0 obj << +773 0 obj << /Length 8259 >> stream @@ -9920,48 +10156,48 @@ ET 0 g 0 G endstream endobj -752 0 obj << +772 0 obj << /Type /Page -/Contents 753 0 R -/Resources 751 0 R +/Contents 773 0 R +/Resources 771 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 729 0 R -/Annots [ 755 0 R 757 0 R ] +/Parent 749 0 R +/Annots [ 775 0 R 777 0 R ] >> endobj -755 0 obj << +775 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 655.098 412.5881 666.2229] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -757 0 obj << +777 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 369.1702 412.5881 380.2952] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -754 0 obj << -/D [752 0 R /XYZ 150.7049 740.9981 null] +774 0 obj << +/D [772 0 R /XYZ 150.7049 740.9981 null] >> endobj 78 0 obj << -/D [752 0 R /XYZ 150.7049 531.7136 null] +/D [772 0 R /XYZ 150.7049 531.7136 null] >> endobj -756 0 obj << -/D [752 0 R /XYZ 150.7049 501.6814 null] +776 0 obj << +/D [772 0 R /XYZ 150.7049 501.6814 null] >> endobj 82 0 obj << -/D [752 0 R /XYZ 150.7049 231.8382 null] +/D [772 0 R /XYZ 150.7049 231.8382 null] >> endobj -758 0 obj << -/D [752 0 R /XYZ 150.7049 201.8059 null] +778 0 obj << +/D [772 0 R /XYZ 150.7049 201.8059 null] >> endobj -751 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F32 602 0 R /F18 425 0 R /F19 571 0 R >> +771 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F32 622 0 R /F18 441 0 R /F19 591 0 R >> /ProcSet [ /PDF /Text ] >> endobj -761 0 obj << +781 0 obj << /Length 8400 >> stream @@ -10343,41 +10579,41 @@ ET 0 g 0 G endstream endobj -760 0 obj << +780 0 obj << /Type /Page -/Contents 761 0 R -/Resources 759 0 R +/Contents 781 0 R +/Resources 779 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 729 0 R -/Annots [ 765 0 R ] +/Parent 749 0 R +/Annots [ 785 0 R ] >> endobj -765 0 obj << +785 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 227.3132 367.009 238.4381] /Subtype /Link /A << /S /GoTo /D (spdata) >> >> endobj -762 0 obj << -/D [760 0 R /XYZ 99.8954 740.9981 null] +782 0 obj << +/D [780 0 R /XYZ 99.8954 740.9981 null] >> endobj 86 0 obj << -/D [760 0 R /XYZ 99.8954 651.5986 null] +/D [780 0 R /XYZ 99.8954 651.5986 null] >> endobj -763 0 obj << -/D [760 0 R /XYZ 99.8954 622.81 null] +783 0 obj << +/D [780 0 R /XYZ 99.8954 622.81 null] >> endobj 90 0 obj << -/D [760 0 R /XYZ 99.8954 382.5986 null] +/D [780 0 R /XYZ 99.8954 382.5986 null] >> endobj -764 0 obj << -/D [760 0 R /XYZ 99.8954 353.81 null] +784 0 obj << +/D [780 0 R /XYZ 99.8954 353.81 null] >> endobj -759 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +779 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -768 0 obj << +788 0 obj << /Length 7981 >> stream @@ -10715,54 +10951,54 @@ ET 0 g 0 G endstream endobj -767 0 obj << +787 0 obj << /Type /Page -/Contents 768 0 R -/Resources 766 0 R +/Contents 788 0 R +/Resources 786 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 729 0 R -/Annots [ 771 0 R 773 0 R ] +/Parent 749 0 R +/Annots [ 791 0 R 793 0 R ] >> endobj -771 0 obj << +791 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 569.5162 417.8184 580.6411] /Subtype /Link /A << /S /GoTo /D (spdata) >> >> endobj -773 0 obj << +793 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 298.1796 417.8184 309.3046] /Subtype /Link /A << /S /GoTo /D (spdata) >> >> endobj -769 0 obj << -/D [767 0 R /XYZ 150.7049 740.9981 null] +789 0 obj << +/D [787 0 R /XYZ 150.7049 740.9981 null] >> endobj 94 0 obj << -/D [767 0 R /XYZ 150.7049 716.0915 null] +/D [787 0 R /XYZ 150.7049 716.0915 null] >> endobj -770 0 obj << -/D [767 0 R /XYZ 150.7049 693.4736 null] +790 0 obj << +/D [787 0 R /XYZ 150.7049 693.4736 null] >> endobj 98 0 obj << -/D [767 0 R /XYZ 150.7049 450.4004 null] +/D [787 0 R /XYZ 150.7049 450.4004 null] >> endobj -772 0 obj << -/D [767 0 R /XYZ 150.7049 422.137 null] +792 0 obj << +/D [787 0 R /XYZ 150.7049 422.137 null] >> endobj -774 0 obj << -/D [767 0 R /XYZ 150.7049 227.2166 null] +794 0 obj << +/D [787 0 R /XYZ 150.7049 227.2166 null] >> endobj -775 0 obj << -/D [767 0 R /XYZ 150.7049 231.2017 null] +795 0 obj << +/D [787 0 R /XYZ 150.7049 231.2017 null] >> endobj -766 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +786 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -778 0 obj << +798 0 obj << /Length 356 >> stream @@ -10784,24 +11020,24 @@ ET 0 g 0 G endstream endobj -777 0 obj << +797 0 obj << /Type /Page -/Contents 778 0 R -/Resources 776 0 R +/Contents 798 0 R +/Resources 796 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 780 0 R +/Parent 800 0 R >> endobj -779 0 obj << -/D [777 0 R /XYZ 99.8954 740.9981 null] +799 0 obj << +/D [797 0 R /XYZ 99.8954 740.9981 null] >> endobj 102 0 obj << -/D [777 0 R /XYZ 99.8954 716.0915 null] +/D [797 0 R /XYZ 99.8954 716.0915 null] >> endobj -776 0 obj << -/Font << /F18 425 0 R /F8 434 0 R >> +796 0 obj << +/Font << /F18 441 0 R /F8 450 0 R >> /ProcSet [ /PDF /Text ] >> endobj -783 0 obj << +803 0 obj << /Length 8539 >> stream @@ -11057,59 +11293,59 @@ ET 0 g 0 G endstream endobj -782 0 obj << +802 0 obj << /Type /Page -/Contents 783 0 R -/Resources 781 0 R +/Contents 803 0 R +/Resources 801 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 780 0 R -/Annots [ 787 0 R 788 0 R 789 0 R 790 0 R ] +/Parent 800 0 R +/Annots [ 807 0 R 808 0 R 809 0 R 810 0 R ] >> endobj -787 0 obj << +807 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [432.8971 346.0749 439.871 356.9231] /Subtype /Link /A << /S /GoTo /D (table.1) >> >> endobj -788 0 obj << +808 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [213.6356 265.8623 220.6095 276.7105] /Subtype /Link /A << /S /GoTo /D (table.1) >> >> endobj -789 0 obj << +809 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [432.8971 197.6048 439.871 208.453] /Subtype /Link /A << /S /GoTo /D (table.1) >> >> endobj -790 0 obj << +810 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [256.8071 117.3922 263.781 128.2404] /Subtype /Link /A << /S /GoTo /D (table.1) >> >> endobj -784 0 obj << -/D [782 0 R /XYZ 150.7049 740.9981 null] +804 0 obj << +/D [802 0 R /XYZ 150.7049 740.9981 null] >> endobj 106 0 obj << -/D [782 0 R /XYZ 150.7049 658.7232 null] +/D [802 0 R /XYZ 150.7049 658.7232 null] >> endobj -785 0 obj << -/D [782 0 R /XYZ 150.7049 572.3849 null] +805 0 obj << +/D [802 0 R /XYZ 150.7049 572.3849 null] >> endobj -786 0 obj << -/D [782 0 R /XYZ 318.4508 483.6166 null] +806 0 obj << +/D [802 0 R /XYZ 318.4508 483.6166 null] >> endobj -781 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F11 586 0 R /F14 613 0 R /F19 571 0 R /F29 431 0 R >> +801 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F11 606 0 R /F14 633 0 R /F19 591 0 R /F29 447 0 R >> /ProcSet [ /PDF /Text ] >> endobj -793 0 obj << +813 0 obj << /Length 3831 >> stream @@ -11234,36 +11470,36 @@ ET 0 g 0 G endstream endobj -792 0 obj << +812 0 obj << /Type /Page -/Contents 793 0 R -/Resources 791 0 R +/Contents 813 0 R +/Resources 811 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 780 0 R -/Annots [ 795 0 R 796 0 R ] +/Parent 800 0 R +/Annots [ 815 0 R 816 0 R ] >> endobj -795 0 obj << +815 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 655.098 361.7786 666.2229] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -796 0 obj << +816 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [205.9977 555.693 212.9715 564.604] /Subtype /Link /A << /S /GoTo /D (table.1) >> >> endobj -794 0 obj << -/D [792 0 R /XYZ 99.8954 740.9981 null] +814 0 obj << +/D [812 0 R /XYZ 99.8954 740.9981 null] >> endobj -791 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F32 602 0 R /F11 586 0 R >> +811 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F32 622 0 R /F11 606 0 R >> /ProcSet [ /PDF /Text ] >> endobj -799 0 obj << +819 0 obj << /Length 8863 >> stream @@ -11542,52 +11778,52 @@ ET 0 g 0 G endstream endobj -798 0 obj << +818 0 obj << /Type /Page -/Contents 799 0 R -/Resources 797 0 R +/Contents 819 0 R +/Resources 817 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 780 0 R -/Annots [ 803 0 R 804 0 R 805 0 R ] +/Parent 800 0 R +/Annots [ 823 0 R 824 0 R 825 0 R ] >> endobj -803 0 obj << +823 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [253.8183 284.4772 260.7922 295.3255] /Subtype /Link /A << /S /GoTo /D (table.2) >> >> endobj -804 0 obj << +824 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [253.8183 204.8719 260.7922 215.7201] /Subtype /Link /A << /S /GoTo /D (table.2) >> >> endobj -805 0 obj << +825 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 136.945 412.5881 148.0699] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -800 0 obj << -/D [798 0 R /XYZ 150.7049 740.9981 null] +820 0 obj << +/D [818 0 R /XYZ 150.7049 740.9981 null] >> endobj 110 0 obj << -/D [798 0 R /XYZ 150.7049 659.9836 null] +/D [818 0 R /XYZ 150.7049 659.9836 null] >> endobj -801 0 obj << -/D [798 0 R /XYZ 150.7049 520.2018 null] +821 0 obj << +/D [818 0 R /XYZ 150.7049 520.2018 null] >> endobj -802 0 obj << -/D [798 0 R /XYZ 318.4508 431.7851 null] +822 0 obj << +/D [818 0 R /XYZ 318.4508 431.7851 null] >> endobj -797 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F11 586 0 R /F14 613 0 R /F10 610 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +817 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F11 606 0 R /F14 633 0 R /F10 630 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -808 0 obj << +828 0 obj << /Length 1950 >> stream @@ -11641,29 +11877,29 @@ ET 0 g 0 G endstream endobj -807 0 obj << +827 0 obj << /Type /Page -/Contents 808 0 R -/Resources 806 0 R +/Contents 828 0 R +/Resources 826 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 780 0 R -/Annots [ 810 0 R ] +/Parent 800 0 R +/Annots [ 830 0 R ] >> endobj -810 0 obj << +830 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [382.0877 679.2851 389.0615 690.1333] /Subtype /Link /A << /S /GoTo /D (table.2) >> >> endobj -809 0 obj << -/D [807 0 R /XYZ 99.8954 740.9981 null] +829 0 obj << +/D [827 0 R /XYZ 99.8954 740.9981 null] >> endobj -806 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F11 586 0 R >> +826 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F11 606 0 R >> /ProcSet [ /PDF /Text ] >> endobj -813 0 obj << +833 0 obj << /Length 9221 >> stream @@ -11942,52 +12178,52 @@ ET 0 g 0 G endstream endobj -812 0 obj << +832 0 obj << /Type /Page -/Contents 813 0 R -/Resources 811 0 R +/Contents 833 0 R +/Resources 831 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 780 0 R -/Annots [ 817 0 R 818 0 R 819 0 R ] +/Parent 800 0 R +/Annots [ 837 0 R 838 0 R 839 0 R ] >> endobj -817 0 obj << +837 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [253.8183 289.3496 260.7922 300.1978] /Subtype /Link /A << /S /GoTo /D (table.3) >> >> endobj -818 0 obj << +838 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [253.8183 208.1201 260.7922 218.9683] /Subtype /Link /A << /S /GoTo /D (table.3) >> >> endobj -819 0 obj << +839 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 138.5691 412.5881 149.694] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -814 0 obj << -/D [812 0 R /XYZ 150.7049 740.9981 null] +834 0 obj << +/D [832 0 R /XYZ 150.7049 740.9981 null] >> endobj 114 0 obj << -/D [812 0 R /XYZ 150.7049 656.979 null] +/D [832 0 R /XYZ 150.7049 656.979 null] >> endobj -815 0 obj << -/D [812 0 R /XYZ 150.7049 531.428 null] +835 0 obj << +/D [832 0 R /XYZ 150.7049 531.428 null] >> endobj -816 0 obj << -/D [812 0 R /XYZ 318.4508 442.1513 null] +836 0 obj << +/D [832 0 R /XYZ 318.4508 442.1513 null] >> endobj -811 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F11 586 0 R /F14 613 0 R /F10 610 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +831 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F11 606 0 R /F14 633 0 R /F10 630 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -822 0 obj << +842 0 obj << /Length 2106 >> stream @@ -12041,29 +12277,29 @@ ET 0 g 0 G endstream endobj -821 0 obj << +841 0 obj << /Type /Page -/Contents 822 0 R -/Resources 820 0 R +/Contents 842 0 R +/Resources 840 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 825 0 R -/Annots [ 824 0 R ] +/Parent 845 0 R +/Annots [ 844 0 R ] >> endobj -824 0 obj << +844 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [151.2031 657.3119 158.1769 666.2229] /Subtype /Link /A << /S /GoTo /D (table.2) >> >> endobj -823 0 obj << -/D [821 0 R /XYZ 99.8954 740.9981 null] +843 0 obj << +/D [841 0 R /XYZ 99.8954 740.9981 null] >> endobj -820 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F11 586 0 R >> +840 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F11 606 0 R >> /ProcSet [ /PDF /Text ] >> endobj -828 0 obj << +848 0 obj << /Length 9030 >> stream @@ -12342,45 +12578,45 @@ ET 0 g 0 G endstream endobj -827 0 obj << +847 0 obj << /Type /Page -/Contents 828 0 R -/Resources 826 0 R +/Contents 848 0 R +/Resources 846 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 825 0 R -/Annots [ 832 0 R 833 0 R ] +/Parent 845 0 R +/Annots [ 852 0 R 853 0 R ] >> endobj -832 0 obj << +852 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [213.6356 318.4063 220.6095 327.3174] /Subtype /Link /A << /S /GoTo /D (table.4) >> >> endobj -833 0 obj << +853 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 250.3043 412.5881 261.4292] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -829 0 obj << -/D [827 0 R /XYZ 150.7049 740.9981 null] +849 0 obj << +/D [847 0 R /XYZ 150.7049 740.9981 null] >> endobj 118 0 obj << -/D [827 0 R /XYZ 150.7049 667.0317 null] +/D [847 0 R /XYZ 150.7049 667.0317 null] >> endobj -830 0 obj << -/D [827 0 R /XYZ 150.7049 540.7406 null] +850 0 obj << +/D [847 0 R /XYZ 150.7049 540.7406 null] >> endobj -831 0 obj << -/D [827 0 R /XYZ 318.4508 454.0858 null] +851 0 obj << +/D [847 0 R /XYZ 318.4508 454.0858 null] >> endobj -826 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F11 586 0 R /F14 613 0 R /F10 610 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +846 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F11 606 0 R /F14 633 0 R /F10 630 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -836 0 obj << +856 0 obj << /Length 8220 >> stream @@ -12659,45 +12895,45 @@ ET 0 g 0 G endstream endobj -835 0 obj << +855 0 obj << /Type /Page -/Contents 836 0 R -/Resources 834 0 R +/Contents 856 0 R +/Resources 854 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 825 0 R -/Annots [ 840 0 R 841 0 R ] +/Parent 845 0 R +/Annots [ 860 0 R 861 0 R ] >> endobj -840 0 obj << +860 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [162.8262 341.7844 169.8 350.6954] /Subtype /Link /A << /S /GoTo /D (table.5) >> >> endobj -841 0 obj << +861 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 271.9249 361.7786 283.0499] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -837 0 obj << -/D [835 0 R /XYZ 99.8954 740.9981 null] +857 0 obj << +/D [855 0 R /XYZ 99.8954 740.9981 null] >> endobj 122 0 obj << -/D [835 0 R /XYZ 99.8954 660.0023 null] +/D [855 0 R /XYZ 99.8954 660.0023 null] >> endobj -838 0 obj << -/D [835 0 R /XYZ 99.8954 575.5415 null] +858 0 obj << +/D [855 0 R /XYZ 99.8954 575.5415 null] >> endobj -839 0 obj << -/D [835 0 R /XYZ 267.6413 487.1294 null] +859 0 obj << +/D [855 0 R /XYZ 267.6413 487.1294 null] >> endobj -834 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F11 586 0 R /F14 613 0 R /F10 610 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +854 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F11 606 0 R /F14 633 0 R /F10 630 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -844 0 obj << +864 0 obj << /Length 8630 >> stream @@ -12976,45 +13212,45 @@ ET 0 g 0 G endstream endobj -843 0 obj << +863 0 obj << /Type /Page -/Contents 844 0 R -/Resources 842 0 R +/Contents 864 0 R +/Resources 862 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 825 0 R -/Annots [ 848 0 R 849 0 R ] +/Parent 845 0 R +/Annots [ 868 0 R 869 0 R ] >> endobj -848 0 obj << +868 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [213.6356 319.172 220.6095 328.083] /Subtype /Link /A << /S /GoTo /D (table.6) >> >> endobj -849 0 obj << +869 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 250.9521 412.5881 262.077] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -845 0 obj << -/D [843 0 R /XYZ 150.7049 740.9981 null] +865 0 obj << +/D [863 0 R /XYZ 150.7049 740.9981 null] >> endobj 126 0 obj << -/D [843 0 R /XYZ 150.7049 666.5606 null] +/D [863 0 R /XYZ 150.7049 666.5606 null] >> endobj -846 0 obj << -/D [843 0 R /XYZ 150.7049 542.2718 null] +866 0 obj << +/D [863 0 R /XYZ 150.7049 542.2718 null] >> endobj -847 0 obj << -/D [843 0 R /XYZ 318.4508 455.4993 null] +867 0 obj << +/D [863 0 R /XYZ 318.4508 455.4993 null] >> endobj -842 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F11 586 0 R /F14 613 0 R /F10 610 0 R /F7 607 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +862 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F11 606 0 R /F14 633 0 R /F10 630 0 R /F7 627 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -852 0 obj << +872 0 obj << /Length 9062 >> stream @@ -13281,45 +13517,45 @@ ET 0 g 0 G endstream endobj -851 0 obj << +871 0 obj << /Type /Page -/Contents 852 0 R -/Resources 850 0 R +/Contents 872 0 R +/Resources 870 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 825 0 R -/Annots [ 856 0 R 857 0 R ] +/Parent 845 0 R +/Annots [ 876 0 R 877 0 R ] >> endobj -856 0 obj << +876 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [162.8262 259.8019 169.8 268.713] /Subtype /Link /A << /S /GoTo /D (table.7) >> >> endobj -857 0 obj << +877 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 190.8385 361.7786 201.9635] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -853 0 obj << -/D [851 0 R /XYZ 99.8954 740.9981 null] +873 0 obj << +/D [871 0 R /XYZ 99.8954 740.9981 null] >> endobj 130 0 obj << -/D [851 0 R /XYZ 99.8954 663.5865 null] +/D [871 0 R /XYZ 99.8954 663.5865 null] >> endobj -854 0 obj << -/D [851 0 R /XYZ 99.8954 487.7347 null] +874 0 obj << +/D [871 0 R /XYZ 99.8954 487.7347 null] >> endobj -855 0 obj << -/D [851 0 R /XYZ 267.6413 400.2186 null] +875 0 obj << +/D [871 0 R /XYZ 267.6413 400.2186 null] >> endobj -850 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F11 586 0 R /F14 613 0 R /F10 610 0 R /F7 607 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +870 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F11 606 0 R /F14 633 0 R /F10 630 0 R /F7 627 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -860 0 obj << +880 0 obj << /Length 942 >> stream @@ -13349,21 +13585,21 @@ ET 0 g 0 G endstream endobj -859 0 obj << +879 0 obj << /Type /Page -/Contents 860 0 R -/Resources 858 0 R +/Contents 880 0 R +/Resources 878 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 825 0 R +/Parent 845 0 R >> endobj -861 0 obj << -/D [859 0 R /XYZ 150.7049 740.9981 null] +881 0 obj << +/D [879 0 R /XYZ 150.7049 740.9981 null] >> endobj -858 0 obj << -/Font << /F29 431 0 R /F8 434 0 R >> +878 0 obj << +/Font << /F29 447 0 R /F8 450 0 R >> /ProcSet [ /PDF /Text ] >> endobj -864 0 obj << +884 0 obj << /Length 8034 >> stream @@ -13660,45 +13896,45 @@ ET 0 g 0 G endstream endobj -863 0 obj << +883 0 obj << /Type /Page -/Contents 864 0 R -/Resources 862 0 R +/Contents 884 0 R +/Resources 882 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 870 0 R -/Annots [ 868 0 R 869 0 R ] +/Parent 890 0 R +/Annots [ 888 0 R 889 0 R ] >> endobj -868 0 obj << +888 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [162.8262 270.0118 169.8 278.9228] /Subtype /Link /A << /S /GoTo /D (table.8) >> >> endobj -869 0 obj << +889 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 197.6451 361.7786 208.7701] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -865 0 obj << -/D [863 0 R /XYZ 99.8954 740.9981 null] +885 0 obj << +/D [883 0 R /XYZ 99.8954 740.9981 null] >> endobj 134 0 obj << -/D [863 0 R /XYZ 99.8954 655.4723 null] +/D [883 0 R /XYZ 99.8954 655.4723 null] >> endobj -866 0 obj << -/D [863 0 R /XYZ 267.6413 484.6617 null] +886 0 obj << +/D [883 0 R /XYZ 267.6413 484.6617 null] >> endobj -867 0 obj << -/D [863 0 R /XYZ 99.8954 409.1258 null] +887 0 obj << +/D [883 0 R /XYZ 99.8954 409.1258 null] >> endobj -862 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F11 586 0 R /F14 613 0 R /F10 610 0 R /F29 431 0 R /F19 571 0 R /F32 602 0 R >> +882 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F11 606 0 R /F14 633 0 R /F10 630 0 R /F29 447 0 R /F19 591 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -873 0 obj << +893 0 obj << /Length 942 >> stream @@ -13728,21 +13964,21 @@ ET 0 g 0 G endstream endobj -872 0 obj << +892 0 obj << /Type /Page -/Contents 873 0 R -/Resources 871 0 R +/Contents 893 0 R +/Resources 891 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 870 0 R +/Parent 890 0 R >> endobj -874 0 obj << -/D [872 0 R /XYZ 150.7049 740.9981 null] +894 0 obj << +/D [892 0 R /XYZ 150.7049 740.9981 null] >> endobj -871 0 obj << -/Font << /F29 431 0 R /F8 434 0 R >> +891 0 obj << +/Font << /F29 447 0 R /F8 450 0 R >> /ProcSet [ /PDF /Text ] >> endobj -877 0 obj << +897 0 obj << /Length 8941 >> stream @@ -14035,45 +14271,45 @@ ET 0 g 0 G endstream endobj -876 0 obj << +896 0 obj << /Type /Page -/Contents 877 0 R -/Resources 875 0 R +/Contents 897 0 R +/Resources 895 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 870 0 R -/Annots [ 881 0 R 882 0 R ] +/Parent 890 0 R +/Annots [ 901 0 R 902 0 R ] >> endobj -881 0 obj << +901 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [162.8262 259.539 169.8 268.45] /Subtype /Link /A << /S /GoTo /D (table.9) >> >> endobj -882 0 obj << +902 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 190.6632 361.7786 201.7882] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -878 0 obj << -/D [876 0 R /XYZ 99.8954 740.9981 null] +898 0 obj << +/D [896 0 R /XYZ 99.8954 740.9981 null] >> endobj 138 0 obj << -/D [876 0 R /XYZ 99.8954 663.9371 null] +/D [896 0 R /XYZ 99.8954 663.9371 null] >> endobj -879 0 obj << -/D [876 0 R /XYZ 99.8954 486.902 null] +899 0 obj << +/D [896 0 R /XYZ 99.8954 486.902 null] >> endobj -880 0 obj << -/D [876 0 R /XYZ 267.6413 399.4736 null] +900 0 obj << +/D [896 0 R /XYZ 267.6413 399.4736 null] >> endobj -875 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F11 586 0 R /F14 613 0 R /F10 610 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +895 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F11 606 0 R /F14 633 0 R /F10 630 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -885 0 obj << +905 0 obj << /Length 942 >> stream @@ -14103,21 +14339,21 @@ ET 0 g 0 G endstream endobj -884 0 obj << +904 0 obj << /Type /Page -/Contents 885 0 R -/Resources 883 0 R +/Contents 905 0 R +/Resources 903 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 870 0 R +/Parent 890 0 R >> endobj -886 0 obj << -/D [884 0 R /XYZ 150.7049 740.9981 null] +906 0 obj << +/D [904 0 R /XYZ 150.7049 740.9981 null] >> endobj -883 0 obj << -/Font << /F29 431 0 R /F8 434 0 R >> +903 0 obj << +/Font << /F29 447 0 R /F8 450 0 R >> /ProcSet [ /PDF /Text ] >> endobj -889 0 obj << +909 0 obj << /Length 8088 >> stream @@ -14438,45 +14674,45 @@ ET 0 g 0 G endstream endobj -888 0 obj << +908 0 obj << /Type /Page -/Contents 889 0 R -/Resources 887 0 R +/Contents 909 0 R +/Resources 907 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 870 0 R -/Annots [ 896 0 R 897 0 R ] +/Parent 890 0 R +/Annots [ 916 0 R 917 0 R ] >> endobj -896 0 obj << +916 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 322.3396 367.009 333.4645] /Subtype /Link /A << /S /GoTo /D (spdata) >> >> endobj -897 0 obj << +917 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 255.5057 361.7786 266.6307] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -890 0 obj << -/D [888 0 R /XYZ 99.8954 740.9981 null] +910 0 obj << +/D [908 0 R /XYZ 99.8954 740.9981 null] >> endobj 142 0 obj << -/D [888 0 R /XYZ 99.8954 663.2489 null] +/D [908 0 R /XYZ 99.8954 663.2489 null] >> endobj -894 0 obj << -/D [888 0 R /XYZ 270.132 512.6796 null] +914 0 obj << +/D [908 0 R /XYZ 270.132 512.6796 null] >> endobj -895 0 obj << -/D [888 0 R /XYZ 99.8954 444.4728 null] +915 0 obj << +/D [908 0 R /XYZ 99.8954 444.4728 null] >> endobj -887 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F11 586 0 R /F14 613 0 R /F13 893 0 R /F29 431 0 R /F19 571 0 R /F32 602 0 R >> +907 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F11 606 0 R /F14 633 0 R /F13 913 0 R /F29 447 0 R /F19 591 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -900 0 obj << +920 0 obj << /Length 9840 >> stream @@ -14824,54 +15060,54 @@ ET 0 g 0 G endstream endobj -899 0 obj << +919 0 obj << /Type /Page -/Contents 900 0 R -/Resources 898 0 R +/Contents 920 0 R +/Resources 918 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 870 0 R -/Annots [ 907 0 R 908 0 R ] +/Parent 890 0 R +/Annots [ 927 0 R 928 0 R ] >> endobj -907 0 obj << +927 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [432.8971 185.0447 444.8523 195.8929] /Subtype /Link /A << /S /GoTo /D (table.11) >> >> endobj -908 0 obj << +928 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 117.1154 417.8184 128.2404] /Subtype /Link /A << /S /GoTo /D (spdata) >> >> endobj -901 0 obj << -/D [899 0 R /XYZ 150.7049 740.9981 null] +921 0 obj << +/D [919 0 R /XYZ 150.7049 740.9981 null] >> endobj 146 0 obj << -/D [899 0 R /XYZ 150.7049 644.8313 null] +/D [919 0 R /XYZ 150.7049 644.8313 null] >> endobj -902 0 obj << -/D [899 0 R /XYZ 279.9819 620.9209 null] +922 0 obj << +/D [919 0 R /XYZ 279.9819 620.9209 null] >> endobj -903 0 obj << -/D [899 0 R /XYZ 276.8438 603.1284 null] +923 0 obj << +/D [919 0 R /XYZ 276.8438 603.1284 null] >> endobj -904 0 obj << -/D [899 0 R /XYZ 276.2037 585.3358 null] +924 0 obj << +/D [919 0 R /XYZ 276.2037 585.3358 null] >> endobj -905 0 obj << -/D [899 0 R /XYZ 320.9415 401.8264 null] +925 0 obj << +/D [919 0 R /XYZ 320.9415 401.8264 null] >> endobj -906 0 obj << -/D [899 0 R /XYZ 150.7049 332.4487 null] +926 0 obj << +/D [919 0 R /XYZ 150.7049 332.4487 null] >> endobj -898 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F11 586 0 R /F14 613 0 R /F10 610 0 R /F7 607 0 R /F29 431 0 R /F19 571 0 R /F32 602 0 R >> +918 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F11 606 0 R /F14 633 0 R /F10 630 0 R /F7 627 0 R /F29 447 0 R /F19 591 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -911 0 obj << +931 0 obj << /Length 10563 >> stream @@ -15144,78 +15380,78 @@ ET 0 g 0 G endstream endobj -910 0 obj << +930 0 obj << /Type /Page -/Contents 911 0 R -/Resources 909 0 R +/Contents 931 0 R +/Resources 929 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 921 0 R -/Annots [ 913 0 R 914 0 R 915 0 R 916 0 R 917 0 R 918 0 R 919 0 R 920 0 R ] +/Parent 941 0 R +/Annots [ 933 0 R 934 0 R 935 0 R 936 0 R 937 0 R 938 0 R 939 0 R 940 0 R ] >> endobj -913 0 obj << +933 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [162.8262 643.4196 174.7814 654.2678] /Subtype /Link /A << /S /GoTo /D (table.11) >> >> endobj -914 0 obj << +934 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [382.0877 576.3982 394.0429 587.2464] /Subtype /Link /A << /S /GoTo /D (table.11) >> >> endobj -915 0 obj << +935 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [162.8262 497.4216 174.7814 508.2698] /Subtype /Link /A << /S /GoTo /D (table.11) >> >> endobj -916 0 obj << +936 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 430.1235 361.7786 441.2484] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -917 0 obj << +937 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [346.3891 391.9988 353.363 402.847] /Subtype /Link /A << /S /GoTo /D (equation.1) >> >> endobj -918 0 obj << +938 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.3929 376.7831 352.3667 387.6313] /Subtype /Link /A << /S /GoTo /D (equation.2) >> >> endobj -919 0 obj << +939 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.6973 361.5674 352.6712 372.4156] /Subtype /Link /A << /S /GoTo /D (equation.3) >> >> endobj -920 0 obj << +940 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [203.0089 117.3922 214.9641 128.2404] /Subtype /Link /A << /S /GoTo /D (table.11) >> >> endobj -912 0 obj << -/D [910 0 R /XYZ 99.8954 740.9981 null] +932 0 obj << +/D [930 0 R /XYZ 99.8954 740.9981 null] >> endobj -909 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F11 586 0 R /F32 602 0 R >> +929 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F11 606 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -924 0 obj << +944 0 obj << /Length 942 >> stream @@ -15245,21 +15481,21 @@ ET 0 g 0 G endstream endobj -923 0 obj << +943 0 obj << /Type /Page -/Contents 924 0 R -/Resources 922 0 R +/Contents 944 0 R +/Resources 942 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 921 0 R +/Parent 941 0 R >> endobj -925 0 obj << -/D [923 0 R /XYZ 150.7049 740.9981 null] +945 0 obj << +/D [943 0 R /XYZ 150.7049 740.9981 null] >> endobj -922 0 obj << -/Font << /F29 431 0 R /F8 434 0 R >> +942 0 obj << +/Font << /F29 447 0 R /F8 450 0 R >> /ProcSet [ /PDF /Text ] >> endobj -928 0 obj << +948 0 obj << /Length 9979 >> stream @@ -15505,30 +15741,30 @@ ET 0 g 0 G endstream endobj -927 0 obj << +947 0 obj << /Type /Page -/Contents 928 0 R -/Resources 926 0 R +/Contents 948 0 R +/Resources 946 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 921 0 R +/Parent 941 0 R >> endobj -929 0 obj << -/D [927 0 R /XYZ 99.8954 740.9981 null] +949 0 obj << +/D [947 0 R /XYZ 99.8954 740.9981 null] >> endobj 150 0 obj << -/D [927 0 R /XYZ 99.8954 658.4134 null] +/D [947 0 R /XYZ 99.8954 658.4134 null] >> endobj -930 0 obj << -/D [927 0 R /XYZ 99.8954 299.8518 null] +950 0 obj << +/D [947 0 R /XYZ 99.8954 299.8518 null] >> endobj -931 0 obj << -/D [927 0 R /XYZ 270.132 187.0828 null] +951 0 obj << +/D [947 0 R /XYZ 270.132 187.0828 null] >> endobj -926 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F11 586 0 R /F14 613 0 R /F10 610 0 R /F13 893 0 R /F7 607 0 R /F19 571 0 R /F29 431 0 R >> +946 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F11 606 0 R /F14 633 0 R /F10 630 0 R /F13 913 0 R /F7 627 0 R /F19 591 0 R /F29 447 0 R >> /ProcSet [ /PDF /Text ] >> endobj -934 0 obj << +954 0 obj << /Length 10676 >> stream @@ -15801,64 +16037,64 @@ ET 0 g 0 G endstream endobj -933 0 obj << +953 0 obj << /Type /Page -/Contents 934 0 R -/Resources 932 0 R +/Contents 954 0 R +/Resources 952 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 921 0 R -/Annots [ 936 0 R 937 0 R 938 0 R 939 0 R 940 0 R 941 0 R ] +/Parent 941 0 R +/Annots [ 956 0 R 957 0 R 958 0 R 959 0 R 960 0 R 961 0 R ] >> endobj -936 0 obj << +956 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [432.8971 655.3747 444.8523 666.2229] /Subtype /Link /A << /S /GoTo /D (table.12) >> >> endobj -937 0 obj << +957 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [393.7383 587.9609 400.7122 598.8091] /Subtype /Link /A << /S /GoTo /D (section.3) >> >> endobj -938 0 obj << +958 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [213.6356 508.5918 225.5908 519.4401] /Subtype /Link /A << /S /GoTo /D (table.12) >> >> endobj -939 0 obj << +959 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [432.8971 441.178 444.8523 452.0262] /Subtype /Link /A << /S /GoTo /D (table.12) >> >> endobj -940 0 obj << +960 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [213.6356 361.8089 225.5908 372.6571] /Subtype /Link /A << /S /GoTo /D (table.12) >> >> endobj -941 0 obj << +961 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 294.1183 412.5881 305.2433] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -935 0 obj << -/D [933 0 R /XYZ 150.7049 740.9981 null] +955 0 obj << +/D [953 0 R /XYZ 150.7049 740.9981 null] >> endobj -932 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F11 586 0 R /F14 613 0 R /F32 602 0 R /F19 571 0 R >> +952 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F11 606 0 R /F14 633 0 R /F32 622 0 R /F19 591 0 R >> /ProcSet [ /PDF /Text ] >> endobj -944 0 obj << +964 0 obj << /Length 7412 >> stream @@ -16024,36 +16260,36 @@ ET 0 g 0 G endstream endobj -943 0 obj << +963 0 obj << /Type /Page -/Contents 944 0 R -/Resources 942 0 R +/Contents 964 0 R +/Resources 962 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 921 0 R -/Annots [ 946 0 R 947 0 R ] +/Parent 941 0 R +/Annots [ 966 0 R 967 0 R ] >> endobj -946 0 obj << +966 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [162.8262 376.6547 174.7814 385.5657] /Subtype /Link /A << /S /GoTo /D (table.12) >> >> endobj -947 0 obj << +967 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [203.0089 196.1506 214.9641 206.9988] /Subtype /Link /A << /S /GoTo /D (table.12) >> >> endobj -945 0 obj << -/D [943 0 R /XYZ 99.8954 740.9981 null] +965 0 obj << +/D [963 0 R /XYZ 99.8954 740.9981 null] >> endobj -942 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F11 586 0 R /F32 602 0 R >> +962 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F11 606 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -950 0 obj << +970 0 obj << /Length 1173 >> stream @@ -16087,32 +16323,32 @@ ET 0 g 0 G endstream endobj -949 0 obj << +969 0 obj << /Type /Page -/Contents 950 0 R -/Resources 948 0 R +/Contents 970 0 R +/Resources 968 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 921 0 R -/Annots [ 952 0 R ] +/Parent 941 0 R +/Annots [ 972 0 R ] >> endobj -952 0 obj << +972 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [350.3454 657.4642 357.3192 668.3124] /Subtype /Link /A << /S /GoTo /D (section.6) >> >> endobj -951 0 obj << -/D [949 0 R /XYZ 150.7049 740.9981 null] +971 0 obj << +/D [969 0 R /XYZ 150.7049 740.9981 null] >> endobj 154 0 obj << -/D [949 0 R /XYZ 150.7049 716.0915 null] +/D [969 0 R /XYZ 150.7049 716.0915 null] >> endobj -948 0 obj << -/Font << /F18 425 0 R /F8 434 0 R >> +968 0 obj << +/Font << /F18 441 0 R /F8 450 0 R >> /ProcSet [ /PDF /Text ] >> endobj -955 0 obj << +975 0 obj << /Length 8068 >> stream @@ -16425,52 +16661,52 @@ ET 0 g 0 G endstream endobj -954 0 obj << +974 0 obj << /Type /Page -/Contents 955 0 R -/Resources 953 0 R +/Contents 975 0 R +/Resources 973 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 962 0 R -/Annots [ 959 0 R 960 0 R 961 0 R ] +/Parent 982 0 R +/Annots [ 979 0 R 980 0 R 981 0 R ] >> endobj -959 0 obj << +979 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [310.744 265.932 322.6992 276.7802] /Subtype /Link /A << /S /GoTo /D (table.13) >> >> endobj -960 0 obj << +980 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 197.3629 361.7786 208.4879] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -961 0 obj << +981 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [382.0877 117.3922 394.0429 128.2404] /Subtype /Link /A << /S /GoTo /D (table.13) >> >> endobj -956 0 obj << -/D [954 0 R /XYZ 99.8954 740.9981 null] +976 0 obj << +/D [974 0 R /XYZ 99.8954 740.9981 null] >> endobj 158 0 obj << -/D [954 0 R /XYZ 99.8954 658.6635 null] +/D [974 0 R /XYZ 99.8954 658.6635 null] >> endobj -957 0 obj << -/D [954 0 R /XYZ 270.132 497.1978 null] +977 0 obj << +/D [974 0 R /XYZ 270.132 497.1978 null] >> endobj -958 0 obj << -/D [954 0 R /XYZ 99.8954 426.7074 null] +978 0 obj << +/D [974 0 R /XYZ 99.8954 426.7074 null] >> endobj -953 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F11 586 0 R /F14 613 0 R /F29 431 0 R /F19 571 0 R /F32 602 0 R >> +973 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F11 606 0 R /F14 633 0 R /F29 447 0 R /F19 591 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -966 0 obj << +986 0 obj << /Length 4922 >> stream @@ -16580,30 +16816,30 @@ ET 0 g 0 G endstream endobj -965 0 obj << +985 0 obj << /Type /Page -/Contents 966 0 R -/Resources 964 0 R +/Contents 986 0 R +/Resources 984 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 962 0 R -/Annots [ 968 0 R ] +/Parent 982 0 R +/Annots [ 988 0 R ] >> endobj -963 0 obj << +983 0 obj << /Type /XObject /Subtype /Form /FormType 1 /PTEX.FileName (./figures/try8x8.pdf) /PTEX.PageNumber 1 -/PTEX.InfoDict 970 0 R +/PTEX.InfoDict 990 0 R /Matrix [1.00000000 0.00000000 0.00000000 1.00000000 0.00000000 0.00000000] /BBox [0.00000000 0.00000000 436.00000000 496.00000000] /Resources << /ProcSet [ /PDF /Text ] /ExtGState << -/R7 971 0 R ->>/Font << /R8 972 0 R /R9 973 0 R >> +/R7 991 0 R +>>/Font << /R8 992 0 R /R9 993 0 R >> >> -/Length 974 0 R +/Length 994 0 R /Filter /FlateDecode >> stream @@ -16618,55 +16854,55 @@ J QI*éÊ'ˆX“?ûý•X•äüèßøË=ñ­™C|ž1„WF Oo&?•¤’þn*w ‚JV¿Å~GJT’ó£ã/÷Ì—²2/*±ÿ‘ªõfÚVI*é39¢GVÆ~G2T’|èßøË=ñ­ÿ|=ö?’ÌÞL8+I%#r"Ldõ{ìw¤¡A%9?ú7þrO|kt?üÃÔã½\#,„õØ¿ð H¾þ¤¹"•$ßLÏg†ORɱDÌ”Ž% d)eI%}QÉ'?+ä°~I*écÂ\‚?XO#~Ã[!©äX‚?fJÇüÁaî‹J8ù9â÷%©¤ s‰ù`=ø Ÿ× ,ªƒ1Œ|?ª$6ŠázžAª@}¡J¢¿R©’#‡z|]ñd•9ÔãýL G„z8¯—÷¬’Ï€äcD¾P%ùàgÌcå‘#<¾®x²J2³jˆÏÕpD„ó¢¼g•mø»ãoÇßþžŸúö§Ç6Úë¸w¶W~ûùñéØ?ûçãK߯åÌÞ>Øíƒ]?Øeµûü`ŸìqÛ{éÏ/m;±ù"×~¢WëÖëj¾Z…3lï²ÛÂ?|Ïz¼Ú½m[{힦„iÿb¬m»¦øóe•Ï¿{üáÛã¯×¿ÿ-3‡àendstream endobj -970 0 obj +990 0 obj << /Producer (ESP Ghostscript 815.03) /CreationDate (D:20070118112257) /ModDate (D:20070118112257) >> endobj -971 0 obj +991 0 obj << /Type /ExtGState /OPM 1 >> endobj -972 0 obj +992 0 obj << /BaseFont /Times-Roman /Type /Font /Subtype /Type1 >> endobj -973 0 obj +993 0 obj << /BaseFont /Times-Bold /Type /Font /Subtype /Type1 >> endobj -974 0 obj +994 0 obj 3571 endobj -968 0 obj << +988 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [213.6356 456.6647 225.5908 465.5757] /Subtype /Link /A << /S /GoTo /D (table.13) >> >> endobj -967 0 obj << -/D [965 0 R /XYZ 150.7049 740.9981 null] +987 0 obj << +/D [985 0 R /XYZ 150.7049 740.9981 null] >> endobj -969 0 obj << -/D [965 0 R /XYZ 283.6922 146.9535 null] +989 0 obj << +/D [985 0 R /XYZ 283.6922 146.9535 null] >> endobj -964 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F11 586 0 R /F32 602 0 R >> -/XObject << /Im3 963 0 R >> +984 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F11 606 0 R /F32 622 0 R >> +/XObject << /Im3 983 0 R >> /ProcSet [ /PDF /Text ] >> endobj -977 0 obj << +997 0 obj << /Length 2065 >> stream @@ -16700,32 +16936,32 @@ ET 0 g 0 G endstream endobj -976 0 obj << +996 0 obj << /Type /Page -/Contents 977 0 R -/Resources 975 0 R +/Contents 997 0 R +/Resources 995 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 962 0 R -/Annots [ 980 0 R ] +/Parent 982 0 R +/Annots [ 1000 0 R ] >> endobj -980 0 obj << +1000 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [311.8669 681.3745 318.8408 692.2227] /Subtype /Link /A << /S /GoTo /D (figure.6) >> >> endobj -978 0 obj << -/D [976 0 R /XYZ 99.8954 740.9981 null] +998 0 obj << +/D [996 0 R /XYZ 99.8954 740.9981 null] >> endobj -979 0 obj << -/D [976 0 R /XYZ 99.8954 693.4736 null] +999 0 obj << +/D [996 0 R /XYZ 99.8954 693.4736 null] >> endobj -975 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F11 586 0 R /F32 602 0 R >> +995 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F11 606 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -983 0 obj << +1003 0 obj << /Length 3515 >> stream @@ -16754,21 +16990,21 @@ ET 0 g 0 G endstream endobj -982 0 obj << +1002 0 obj << /Type /Page -/Contents 983 0 R -/Resources 981 0 R +/Contents 1003 0 R +/Resources 1001 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 962 0 R +/Parent 982 0 R >> endobj -984 0 obj << -/D [982 0 R /XYZ 150.7049 740.9981 null] +1004 0 obj << +/D [1002 0 R /XYZ 150.7049 740.9981 null] >> endobj -981 0 obj << -/Font << /F47 987 0 R /F8 434 0 R >> +1001 0 obj << +/Font << /F47 1007 0 R /F8 450 0 R >> /ProcSet [ /PDF /Text ] >> endobj -990 0 obj << +1010 0 obj << /Length 9725 >> stream @@ -17196,45 +17432,45 @@ ET 0 g 0 G endstream endobj -989 0 obj << +1009 0 obj << /Type /Page -/Contents 990 0 R -/Resources 988 0 R +/Contents 1010 0 R +/Resources 1008 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 962 0 R -/Annots [ 994 0 R 995 0 R ] +/Parent 982 0 R +/Annots [ 1014 0 R 1015 0 R ] >> endobj -994 0 obj << +1014 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [162.8262 269.0802 174.7814 277.9912] /Subtype /Link /A << /S /GoTo /D (table.14) >> >> endobj -995 0 obj << +1015 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 199.4566 361.7786 210.5815] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -991 0 obj << -/D [989 0 R /XYZ 99.8954 740.9981 null] +1011 0 obj << +/D [1009 0 R /XYZ 99.8954 740.9981 null] >> endobj 162 0 obj << -/D [989 0 R /XYZ 99.8954 660.9456 null] +/D [1009 0 R /XYZ 99.8954 660.9456 null] >> endobj -992 0 obj << -/D [989 0 R /XYZ 270.132 495.0471 null] +1012 0 obj << +/D [1009 0 R /XYZ 270.132 495.0471 null] >> endobj -993 0 obj << -/D [989 0 R /XYZ 99.8954 426.0167 null] +1013 0 obj << +/D [1009 0 R /XYZ 99.8954 426.0167 null] >> endobj -988 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F11 586 0 R /F14 613 0 R /F10 610 0 R /F29 431 0 R /F19 571 0 R /F32 602 0 R >> +1008 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F11 606 0 R /F14 633 0 R /F10 630 0 R /F29 447 0 R /F19 591 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -999 0 obj << +1019 0 obj << /Length 9573 >> stream @@ -17411,58 +17647,58 @@ ET 0 g 0 G endstream endobj -998 0 obj << +1018 0 obj << /Type /Page -/Contents 999 0 R -/Resources 997 0 R +/Contents 1019 0 R +/Resources 1017 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 962 0 R -/Annots [ 1001 0 R 1007 0 R 1008 0 R ] +/Parent 982 0 R +/Annots [ 1021 0 R 1027 0 R 1028 0 R ] >> endobj -1001 0 obj << +1021 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [253.8183 492.6141 265.7735 503.4623] /Subtype /Link /A << /S /GoTo /D (table.14) >> >> endobj -1007 0 obj << +1027 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [362.6764 215.5242 369.6502 226.3724] /Subtype /Link /A << /S /GoTo /D (figure.7) >> >> endobj -1008 0 obj << +1028 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [245.8625 191.6138 252.8364 202.4621] /Subtype /Link /A << /S /GoTo /D (figure.6) >> >> endobj -1000 0 obj << -/D [998 0 R /XYZ 150.7049 740.9981 null] +1020 0 obj << +/D [1018 0 R /XYZ 150.7049 740.9981 null] >> endobj -1002 0 obj << -/D [998 0 R /XYZ 150.7049 384.3996 null] +1022 0 obj << +/D [1018 0 R /XYZ 150.7049 384.3996 null] >> endobj -1003 0 obj << -/D [998 0 R /XYZ 150.7049 387.616 null] +1023 0 obj << +/D [1018 0 R /XYZ 150.7049 387.616 null] >> endobj -1004 0 obj << -/D [998 0 R /XYZ 150.7049 358.1252 null] +1024 0 obj << +/D [1018 0 R /XYZ 150.7049 358.1252 null] >> endobj -1005 0 obj << -/D [998 0 R /XYZ 150.7049 315.8268 null] +1025 0 obj << +/D [1018 0 R /XYZ 150.7049 315.8268 null] >> endobj -1006 0 obj << -/D [998 0 R /XYZ 150.7049 227.6233 null] +1026 0 obj << +/D [1018 0 R /XYZ 150.7049 227.6233 null] >> endobj -997 0 obj << -/Font << /F8 434 0 R /F29 431 0 R /F11 586 0 R /F18 425 0 R /F10 610 0 R /F32 602 0 R >> +1017 0 obj << +/Font << /F8 450 0 R /F29 447 0 R /F11 606 0 R /F18 441 0 R /F10 630 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1012 0 obj << +1032 0 obj << /Length 4244 >> stream @@ -17491,21 +17727,21 @@ ET 0 g 0 G endstream endobj -1011 0 obj << +1031 0 obj << /Type /Page -/Contents 1012 0 R -/Resources 1010 0 R +/Contents 1032 0 R +/Resources 1030 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1014 0 R +/Parent 1034 0 R >> endobj -1013 0 obj << -/D [1011 0 R /XYZ 99.8954 740.9981 null] +1033 0 obj << +/D [1031 0 R /XYZ 99.8954 740.9981 null] >> endobj -1010 0 obj << -/Font << /F33 621 0 R /F8 434 0 R >> +1030 0 obj << +/Font << /F33 641 0 R /F8 450 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1017 0 obj << +1037 0 obj << /Length 653 >> stream @@ -17547,29 +17783,29 @@ ET 0 g 0 G endstream endobj -1016 0 obj << +1036 0 obj << /Type /Page -/Contents 1017 0 R -/Resources 1015 0 R +/Contents 1037 0 R +/Resources 1035 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1014 0 R +/Parent 1034 0 R >> endobj -996 0 obj << +1016 0 obj << /Type /XObject /Subtype /Form /FormType 1 /PTEX.FileName (./figures/try8x8_ov.pdf) /PTEX.PageNumber 1 -/PTEX.InfoDict 1019 0 R +/PTEX.InfoDict 1039 0 R /Matrix [1.00000000 0.00000000 0.00000000 1.00000000 0.00000000 0.00000000] /BBox [0.00000000 0.00000000 436.00000000 514.00000000] /Resources << /ProcSet [ /PDF /Text ] /ExtGState << -/R7 1020 0 R ->>/Font << /R8 1021 0 R /R9 1022 0 R >> +/R7 1040 0 R +>>/Font << /R8 1041 0 R /R9 1042 0 R >> >> -/Length 1023 0 R +/Length 1043 0 R /Filter /FlateDecode >> stream @@ -17582,48 +17818,48 @@ V >+>O|¾ñÙðÙ¿ùéË_¥¯÷\ñûgê|~ùùñé]¿ùòÏÇç³ÞáL.äー·U>ǹ۔ëv>?¥Dñ ÷«ã4«[};Z‡»l7©øÏ_ßýa}ùÌøý€¼_Ç2㣿lñ}Îù§¿í óá!Zäÿ/L)ÇÇ8ú:ß=þ êë¼®endstream endobj -1019 0 obj +1039 0 obj << /Producer (ESP Ghostscript 815.03) /CreationDate (D:20070118114343) /ModDate (D:20070118114343) >> endobj -1020 0 obj +1040 0 obj << /Type /ExtGState /OPM 1 >> endobj -1021 0 obj +1041 0 obj << /BaseFont /Times-Roman /Type /Font /Subtype /Type1 >> endobj -1022 0 obj +1042 0 obj << /BaseFont /Times-Bold /Type /Font /Subtype /Type1 >> endobj -1023 0 obj +1043 0 obj 3652 endobj -1018 0 obj << -/D [1016 0 R /XYZ 150.7049 740.9981 null] +1038 0 obj << +/D [1036 0 R /XYZ 150.7049 740.9981 null] >> endobj -1009 0 obj << -/D [1016 0 R /XYZ 283.6922 275.514 null] +1029 0 obj << +/D [1036 0 R /XYZ 283.6922 275.514 null] >> endobj -1015 0 obj << -/Font << /F8 434 0 R >> -/XObject << /Im4 996 0 R >> +1035 0 obj << +/Font << /F8 450 0 R >> +/XObject << /Im4 1016 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1026 0 obj << +1046 0 obj << /Length 10046 >> stream @@ -18079,48 +18315,48 @@ ET 0 g 0 G endstream endobj -1025 0 obj << +1045 0 obj << /Type /Page -/Contents 1026 0 R -/Resources 1024 0 R +/Contents 1046 0 R +/Resources 1044 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1014 0 R -/Annots [ 1031 0 R 1032 0 R ] +/Parent 1034 0 R +/Annots [ 1051 0 R 1052 0 R ] >> endobj -1031 0 obj << +1051 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [205.9977 188.3685 217.9529 197.2795] /Subtype /Link /A << /S /GoTo /D (table.15) >> >> endobj -1032 0 obj << +1052 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 117.1154 361.7786 128.2404] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1027 0 obj << -/D [1025 0 R /XYZ 99.8954 740.9981 null] +1047 0 obj << +/D [1045 0 R /XYZ 99.8954 740.9981 null] >> endobj 166 0 obj << -/D [1025 0 R /XYZ 99.8954 657.3825 null] +/D [1045 0 R /XYZ 99.8954 657.3825 null] >> endobj -1028 0 obj << -/D [1025 0 R /XYZ 270.132 451.0528 null] +1048 0 obj << +/D [1045 0 R /XYZ 270.132 451.0528 null] >> endobj -1029 0 obj << -/D [1025 0 R /XYZ 99.8954 377.2872 null] +1049 0 obj << +/D [1045 0 R /XYZ 99.8954 377.2872 null] >> endobj -1030 0 obj << -/D [1025 0 R /XYZ 99.8954 324.9767 null] +1050 0 obj << +/D [1045 0 R /XYZ 99.8954 324.9767 null] >> endobj -1024 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F11 586 0 R /F14 613 0 R /F10 610 0 R /F7 607 0 R /F29 431 0 R /F19 571 0 R /F32 602 0 R >> +1044 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F11 606 0 R /F14 633 0 R /F10 630 0 R /F7 627 0 R /F29 447 0 R /F19 591 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1035 0 obj << +1055 0 obj << /Length 3560 >> stream @@ -18195,21 +18431,21 @@ ET 0 g 0 G endstream endobj -1034 0 obj << +1054 0 obj << /Type /Page -/Contents 1035 0 R -/Resources 1033 0 R +/Contents 1055 0 R +/Resources 1053 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1014 0 R +/Parent 1034 0 R >> endobj -1036 0 obj << -/D [1034 0 R /XYZ 150.7049 740.9981 null] +1056 0 obj << +/D [1054 0 R /XYZ 150.7049 740.9981 null] >> endobj -1033 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F11 586 0 R /F14 613 0 R >> +1053 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F11 606 0 R /F14 633 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1039 0 obj << +1059 0 obj << /Length 9417 >> stream @@ -18640,41 +18876,41 @@ ET 0 g 0 G endstream endobj -1038 0 obj << +1058 0 obj << /Type /Page -/Contents 1039 0 R -/Resources 1037 0 R +/Contents 1059 0 R +/Resources 1057 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1014 0 R -/Annots [ 1044 0 R ] +/Parent 1034 0 R +/Annots [ 1064 0 R ] >> endobj -1044 0 obj << +1064 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 117.1154 361.7786 128.2404] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1040 0 obj << -/D [1038 0 R /XYZ 99.8954 740.9981 null] +1060 0 obj << +/D [1058 0 R /XYZ 99.8954 740.9981 null] >> endobj 170 0 obj << -/D [1038 0 R /XYZ 99.8954 655.7383 null] +/D [1058 0 R /XYZ 99.8954 655.7383 null] >> endobj -1041 0 obj << -/D [1038 0 R /XYZ 270.132 444.3763 null] +1061 0 obj << +/D [1058 0 R /XYZ 270.132 444.3763 null] >> endobj -1042 0 obj << -/D [1038 0 R /XYZ 99.8954 368.8933 null] +1062 0 obj << +/D [1058 0 R /XYZ 99.8954 368.8933 null] >> endobj -1043 0 obj << -/D [1038 0 R /XYZ 99.8954 316.1368 null] +1063 0 obj << +/D [1058 0 R /XYZ 99.8954 316.1368 null] >> endobj -1037 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F11 586 0 R /F10 610 0 R /F14 613 0 R /F7 607 0 R /F29 431 0 R /F19 571 0 R /F32 602 0 R >> +1057 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F11 606 0 R /F10 630 0 R /F14 633 0 R /F7 627 0 R /F29 447 0 R /F19 591 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1047 0 obj << +1067 0 obj << /Length 4148 >> stream @@ -18774,29 +19010,29 @@ ET 0 g 0 G endstream endobj -1046 0 obj << +1066 0 obj << /Type /Page -/Contents 1047 0 R -/Resources 1045 0 R +/Contents 1067 0 R +/Resources 1065 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1014 0 R -/Annots [ 1049 0 R ] +/Parent 1034 0 R +/Annots [ 1069 0 R ] >> endobj -1049 0 obj << +1069 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [256.8071 545.7304 268.7623 554.6414] /Subtype /Link /A << /S /GoTo /D (table.16) >> >> endobj -1048 0 obj << -/D [1046 0 R /XYZ 150.7049 740.9981 null] +1068 0 obj << +/D [1066 0 R /XYZ 150.7049 740.9981 null] >> endobj -1045 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F11 586 0 R /F14 613 0 R >> +1065 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F11 606 0 R /F14 633 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1052 0 obj << +1072 0 obj << /Length 366 >> stream @@ -18818,24 +19054,24 @@ ET 0 g 0 G endstream endobj -1051 0 obj << +1071 0 obj << /Type /Page -/Contents 1052 0 R -/Resources 1050 0 R +/Contents 1072 0 R +/Resources 1070 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1054 0 R +/Parent 1074 0 R >> endobj -1053 0 obj << -/D [1051 0 R /XYZ 99.8954 740.9981 null] +1073 0 obj << +/D [1071 0 R /XYZ 99.8954 740.9981 null] >> endobj 174 0 obj << -/D [1051 0 R /XYZ 99.8954 716.0915 null] +/D [1071 0 R /XYZ 99.8954 716.0915 null] >> endobj -1050 0 obj << -/Font << /F18 425 0 R /F8 434 0 R >> +1070 0 obj << +/Font << /F18 441 0 R /F8 450 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1057 0 obj << +1077 0 obj << /Length 9099 >> stream @@ -19083,27 +19319,27 @@ ET 0 g 0 G endstream endobj -1056 0 obj << +1076 0 obj << /Type /Page -/Contents 1057 0 R -/Resources 1055 0 R +/Contents 1077 0 R +/Resources 1075 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1054 0 R +/Parent 1074 0 R >> endobj -1058 0 obj << -/D [1056 0 R /XYZ 150.7049 740.9981 null] +1078 0 obj << +/D [1076 0 R /XYZ 150.7049 740.9981 null] >> endobj 178 0 obj << -/D [1056 0 R /XYZ 150.7049 646.2525 null] +/D [1076 0 R /XYZ 150.7049 646.2525 null] >> endobj -1059 0 obj << -/D [1056 0 R /XYZ 150.7049 618.454 null] +1079 0 obj << +/D [1076 0 R /XYZ 150.7049 618.454 null] >> endobj -1055 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F32 602 0 R /F29 431 0 R /F11 586 0 R /F14 613 0 R >> +1075 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F32 622 0 R /F29 447 0 R /F11 606 0 R /F14 633 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1062 0 obj << +1082 0 obj << /Length 8742 >> stream @@ -19308,35 +19544,35 @@ ET 0 g 0 G endstream endobj -1061 0 obj << +1081 0 obj << /Type /Page -/Contents 1062 0 R -/Resources 1060 0 R +/Contents 1082 0 R +/Resources 1080 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1054 0 R -/Annots [ 1064 0 R ] +/Parent 1074 0 R +/Annots [ 1084 0 R ] >> endobj -1064 0 obj << +1084 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 431.3671 361.7786 442.492] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1063 0 obj << -/D [1061 0 R /XYZ 99.8954 740.9981 null] +1083 0 obj << +/D [1081 0 R /XYZ 99.8954 740.9981 null] >> endobj -1065 0 obj << -/D [1061 0 R /XYZ 99.8954 324.3903 null] +1085 0 obj << +/D [1081 0 R /XYZ 99.8954 324.3903 null] >> endobj -1066 0 obj << -/D [1061 0 R /XYZ 99.8954 328.2458 null] +1086 0 obj << +/D [1081 0 R /XYZ 99.8954 328.2458 null] >> endobj -1060 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F32 602 0 R /F18 425 0 R >> +1080 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F32 622 0 R /F18 441 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1069 0 obj << +1089 0 obj << /Length 7365 >> stream @@ -19450,24 +19686,24 @@ ET 0 g 0 G endstream endobj -1068 0 obj << +1088 0 obj << /Type /Page -/Contents 1069 0 R -/Resources 1067 0 R +/Contents 1089 0 R +/Resources 1087 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1054 0 R +/Parent 1074 0 R >> endobj -1070 0 obj << -/D [1068 0 R /XYZ 150.7049 740.9981 null] +1090 0 obj << +/D [1088 0 R /XYZ 150.7049 740.9981 null] >> endobj -1071 0 obj << -/D [1068 0 R /XYZ 150.7049 411.2901 null] +1091 0 obj << +/D [1088 0 R /XYZ 150.7049 411.2901 null] >> endobj -1067 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F32 602 0 R /F14 613 0 R /F11 586 0 R /F10 610 0 R >> +1087 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F32 622 0 R /F14 633 0 R /F11 606 0 R /F10 630 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1074 0 obj << +1094 0 obj << /Length 7309 >> stream @@ -19670,35 +19906,35 @@ ET 0 g 0 G endstream endobj -1073 0 obj << +1093 0 obj << /Type /Page -/Contents 1074 0 R -/Resources 1072 0 R +/Contents 1094 0 R +/Resources 1092 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1054 0 R -/Annots [ 1077 0 R ] +/Parent 1074 0 R +/Annots [ 1097 0 R ] >> endobj -1077 0 obj << +1097 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 189.9545 361.7786 201.0795] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1075 0 obj << -/D [1073 0 R /XYZ 99.8954 740.9981 null] +1095 0 obj << +/D [1093 0 R /XYZ 99.8954 740.9981 null] >> endobj 182 0 obj << -/D [1073 0 R /XYZ 99.8954 639.044 null] +/D [1093 0 R /XYZ 99.8954 639.044 null] >> endobj -1076 0 obj << -/D [1073 0 R /XYZ 99.8954 606.9876 null] +1096 0 obj << +/D [1093 0 R /XYZ 99.8954 606.9876 null] >> endobj -1072 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F11 586 0 R /F32 602 0 R >> +1092 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F11 606 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1080 0 obj << +1100 0 obj << /Length 1436 >> stream @@ -19744,30 +19980,30 @@ ET 0 g 0 G endstream endobj -1079 0 obj << +1099 0 obj << /Type /Page -/Contents 1080 0 R -/Resources 1078 0 R +/Contents 1100 0 R +/Resources 1098 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1054 0 R +/Parent 1074 0 R >> endobj -1081 0 obj << -/D [1079 0 R /XYZ 150.7049 740.9981 null] +1101 0 obj << +/D [1099 0 R /XYZ 150.7049 740.9981 null] >> endobj -1082 0 obj << -/D [1079 0 R /XYZ 150.7049 696.2631 null] +1102 0 obj << +/D [1099 0 R /XYZ 150.7049 696.2631 null] >> endobj -1083 0 obj << -/D [1079 0 R /XYZ 150.7049 700.2482 null] +1103 0 obj << +/D [1099 0 R /XYZ 150.7049 700.2482 null] >> endobj -1084 0 obj << -/D [1079 0 R /XYZ 150.7049 678.3857 null] +1104 0 obj << +/D [1099 0 R /XYZ 150.7049 678.3857 null] >> endobj -1078 0 obj << -/Font << /F18 425 0 R /F8 434 0 R >> +1098 0 obj << +/Font << /F18 441 0 R /F8 450 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1087 0 obj << +1107 0 obj << /Length 5921 >> stream @@ -20009,48 +20245,48 @@ ET 0 g 0 G endstream endobj -1086 0 obj << +1106 0 obj << /Type /Page -/Contents 1087 0 R -/Resources 1085 0 R +/Contents 1107 0 R +/Resources 1105 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1094 0 R -/Annots [ 1090 0 R 1091 0 R ] +/Parent 1114 0 R +/Annots [ 1110 0 R 1111 0 R ] >> endobj -1090 0 obj << +1110 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 489.9119 361.7786 501.0369] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1091 0 obj << +1111 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 400.2482 361.7786 411.3731] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1088 0 obj << -/D [1086 0 R /XYZ 99.8954 740.9981 null] +1108 0 obj << +/D [1106 0 R /XYZ 99.8954 740.9981 null] >> endobj 186 0 obj << -/D [1086 0 R /XYZ 99.8954 644.4574 null] +/D [1106 0 R /XYZ 99.8954 644.4574 null] >> endobj -1089 0 obj << -/D [1086 0 R /XYZ 99.8954 613.8693 null] +1109 0 obj << +/D [1106 0 R /XYZ 99.8954 613.8693 null] >> endobj -1092 0 obj << -/D [1086 0 R /XYZ 99.8954 292.9008 null] +1112 0 obj << +/D [1106 0 R /XYZ 99.8954 292.9008 null] >> endobj -1093 0 obj << -/D [1086 0 R /XYZ 99.8954 296.8859 null] +1113 0 obj << +/D [1106 0 R /XYZ 99.8954 296.8859 null] >> endobj -1085 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +1105 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1097 0 obj << +1117 0 obj << /Length 5676 >> stream @@ -20293,42 +20529,42 @@ ET 0 g 0 G endstream endobj -1096 0 obj << +1116 0 obj << /Type /Page -/Contents 1097 0 R -/Resources 1095 0 R +/Contents 1117 0 R +/Resources 1115 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1094 0 R -/Annots [ 1100 0 R 1101 0 R ] +/Parent 1114 0 R +/Annots [ 1120 0 R 1121 0 R ] >> endobj -1100 0 obj << +1120 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 507.8447 412.5881 518.9696] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1101 0 obj << +1121 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 418.1809 412.5881 429.3059] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1098 0 obj << -/D [1096 0 R /XYZ 150.7049 740.9981 null] +1118 0 obj << +/D [1116 0 R /XYZ 150.7049 740.9981 null] >> endobj 190 0 obj << -/D [1096 0 R /XYZ 150.7049 659.6006 null] +/D [1116 0 R /XYZ 150.7049 659.6006 null] >> endobj -1099 0 obj << -/D [1096 0 R /XYZ 150.7049 631.8021 null] +1119 0 obj << +/D [1116 0 R /XYZ 150.7049 631.8021 null] >> endobj -1095 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +1115 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1104 0 obj << +1124 0 obj << /Length 3994 >> stream @@ -20495,35 +20731,35 @@ ET 0 g 0 G endstream endobj -1103 0 obj << +1123 0 obj << /Type /Page -/Contents 1104 0 R -/Resources 1102 0 R +/Contents 1124 0 R +/Resources 1122 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1094 0 R -/Annots [ 1107 0 R ] +/Parent 1114 0 R +/Annots [ 1127 0 R ] >> endobj -1107 0 obj << +1127 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 507.8447 361.7786 518.9696] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1105 0 obj << -/D [1103 0 R /XYZ 99.8954 740.9981 null] +1125 0 obj << +/D [1123 0 R /XYZ 99.8954 740.9981 null] >> endobj 194 0 obj << -/D [1103 0 R /XYZ 99.8954 659.6006 null] +/D [1123 0 R /XYZ 99.8954 659.6006 null] >> endobj -1106 0 obj << -/D [1103 0 R /XYZ 99.8954 631.8021 null] +1126 0 obj << +/D [1123 0 R /XYZ 99.8954 631.8021 null] >> endobj -1102 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +1122 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1110 0 obj << +1130 0 obj << /Length 8588 >> stream @@ -20802,42 +21038,42 @@ ET 0 g 0 G endstream endobj -1109 0 obj << +1129 0 obj << /Type /Page -/Contents 1110 0 R -/Resources 1108 0 R +/Contents 1130 0 R +/Resources 1128 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1094 0 R -/Annots [ 1113 0 R 1114 0 R ] +/Parent 1114 0 R +/Annots [ 1133 0 R 1134 0 R ] >> endobj -1113 0 obj << +1133 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 387.9755 417.8184 399.1004] /Subtype /Link /A << /S /GoTo /D (spdata) >> >> endobj -1114 0 obj << +1134 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 149.3696 412.5881 160.4946] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1111 0 obj << -/D [1109 0 R /XYZ 150.7049 740.9981 null] +1131 0 obj << +/D [1129 0 R /XYZ 150.7049 740.9981 null] >> endobj 198 0 obj << -/D [1109 0 R /XYZ 150.7049 641.0268 null] +/D [1129 0 R /XYZ 150.7049 641.0268 null] >> endobj -1112 0 obj << -/D [1109 0 R /XYZ 150.7049 613.0543 null] +1132 0 obj << +/D [1129 0 R /XYZ 150.7049 613.0543 null] >> endobj -1108 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F32 602 0 R /F29 431 0 R /F11 586 0 R /F14 613 0 R >> +1128 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F32 622 0 R /F29 447 0 R /F11 606 0 R /F14 633 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1117 0 obj << +1137 0 obj << /Length 2773 >> stream @@ -20883,30 +21119,30 @@ ET 0 g 0 G endstream endobj -1116 0 obj << +1136 0 obj << /Type /Page -/Contents 1117 0 R -/Resources 1115 0 R +/Contents 1137 0 R +/Resources 1135 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1094 0 R +/Parent 1114 0 R >> endobj -1118 0 obj << -/D [1116 0 R /XYZ 99.8954 740.9981 null] +1138 0 obj << +/D [1136 0 R /XYZ 99.8954 740.9981 null] >> endobj -1119 0 obj << -/D [1116 0 R /XYZ 99.8954 639.4069 null] +1139 0 obj << +/D [1136 0 R /XYZ 99.8954 639.4069 null] >> endobj -1120 0 obj << -/D [1116 0 R /XYZ 99.8954 643.392 null] +1140 0 obj << +/D [1136 0 R /XYZ 99.8954 643.392 null] >> endobj -1121 0 obj << -/D [1116 0 R /XYZ 99.8954 585.664 null] +1141 0 obj << +/D [1136 0 R /XYZ 99.8954 585.664 null] >> endobj -1115 0 obj << -/Font << /F8 434 0 R /F29 431 0 R /F18 425 0 R /F32 602 0 R >> +1135 0 obj << +/Font << /F8 450 0 R /F29 447 0 R /F18 441 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1124 0 obj << +1144 0 obj << /Length 8009 >> stream @@ -21171,54 +21407,54 @@ ET 0 g 0 G endstream endobj -1123 0 obj << +1143 0 obj << /Type /Page -/Contents 1124 0 R -/Resources 1122 0 R +/Contents 1144 0 R +/Resources 1142 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1094 0 R -/Annots [ 1127 0 R 1128 0 R ] +/Parent 1114 0 R +/Annots [ 1147 0 R 1148 0 R ] >> endobj -1127 0 obj << +1147 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 507.8447 412.5881 518.9696] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1128 0 obj << +1148 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 338.4798 417.8184 349.6048] /Subtype /Link /A << /S /GoTo /D (spdata) >> >> endobj -1125 0 obj << -/D [1123 0 R /XYZ 150.7049 740.9981 null] +1145 0 obj << +/D [1143 0 R /XYZ 150.7049 740.9981 null] >> endobj 202 0 obj << -/D [1123 0 R /XYZ 150.7049 659.6006 null] +/D [1143 0 R /XYZ 150.7049 659.6006 null] >> endobj -1126 0 obj << -/D [1123 0 R /XYZ 150.7049 631.8021 null] +1146 0 obj << +/D [1143 0 R /XYZ 150.7049 631.8021 null] >> endobj -1129 0 obj << -/D [1123 0 R /XYZ 150.7049 231.1324 null] +1149 0 obj << +/D [1143 0 R /XYZ 150.7049 231.1324 null] >> endobj -1130 0 obj << -/D [1123 0 R /XYZ 150.7049 235.1175 null] +1150 0 obj << +/D [1143 0 R /XYZ 150.7049 235.1175 null] >> endobj -1131 0 obj << -/D [1123 0 R /XYZ 150.7049 213.255 null] +1151 0 obj << +/D [1143 0 R /XYZ 150.7049 213.255 null] >> endobj -1132 0 obj << -/D [1123 0 R /XYZ 150.7049 193.3297 null] +1152 0 obj << +/D [1143 0 R /XYZ 150.7049 193.3297 null] >> endobj -1122 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R /F11 586 0 R >> +1142 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R /F11 606 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1135 0 obj << +1155 0 obj << /Length 8163 >> stream @@ -21471,42 +21707,42 @@ ET 0 g 0 G endstream endobj -1134 0 obj << +1154 0 obj << /Type /Page -/Contents 1135 0 R -/Resources 1133 0 R +/Contents 1155 0 R +/Resources 1153 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1140 0 R -/Annots [ 1138 0 R 1139 0 R ] +/Parent 1160 0 R +/Annots [ 1158 0 R 1159 0 R ] >> endobj -1138 0 obj << +1158 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [261.1521 218.7677 328.21 229.8926] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1139 0 obj << +1159 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 117.1154 367.009 128.2404] /Subtype /Link /A << /S /GoTo /D (spdata) >> >> endobj -1136 0 obj << -/D [1134 0 R /XYZ 99.8954 740.9981 null] +1156 0 obj << +/D [1154 0 R /XYZ 99.8954 740.9981 null] >> endobj 206 0 obj << -/D [1134 0 R /XYZ 99.8954 641.6352 null] +/D [1154 0 R /XYZ 99.8954 641.6352 null] >> endobj -1137 0 obj << -/D [1134 0 R /XYZ 99.8954 613.8278 null] +1157 0 obj << +/D [1154 0 R /XYZ 99.8954 613.8278 null] >> endobj -1133 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F11 586 0 R /F32 602 0 R >> +1153 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F11 606 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1143 0 obj << +1163 0 obj << /Length 6325 >> stream @@ -21671,50 +21907,50 @@ ET 0 g 0 G endstream endobj -1142 0 obj << +1162 0 obj << /Type /Page -/Contents 1143 0 R -/Resources 1141 0 R +/Contents 1163 0 R +/Resources 1161 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1140 0 R -/Annots [ 1145 0 R ] +/Parent 1160 0 R +/Annots [ 1165 0 R ] >> endobj -1145 0 obj << +1165 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [311.9616 655.098 379.0195 666.2229] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1144 0 obj << -/D [1142 0 R /XYZ 150.7049 740.9981 null] +1164 0 obj << +/D [1162 0 R /XYZ 150.7049 740.9981 null] >> endobj -1146 0 obj << -/D [1142 0 R /XYZ 150.7049 535.7955 null] +1166 0 obj << +/D [1162 0 R /XYZ 150.7049 535.7955 null] >> endobj -1147 0 obj << -/D [1142 0 R /XYZ 150.7049 539.7805 null] +1167 0 obj << +/D [1162 0 R /XYZ 150.7049 539.7805 null] >> endobj -1148 0 obj << -/D [1142 0 R /XYZ 150.7049 507.9001 null] +1168 0 obj << +/D [1162 0 R /XYZ 150.7049 507.9001 null] >> endobj -1149 0 obj << -/D [1142 0 R /XYZ 150.7049 474.0824 null] +1169 0 obj << +/D [1162 0 R /XYZ 150.7049 474.0824 null] >> endobj -1150 0 obj << -/D [1142 0 R /XYZ 150.7049 406.3365 null] +1170 0 obj << +/D [1162 0 R /XYZ 150.7049 406.3365 null] >> endobj -1151 0 obj << -/D [1142 0 R /XYZ 150.7049 374.456 null] +1171 0 obj << +/D [1162 0 R /XYZ 150.7049 374.456 null] >> endobj -1152 0 obj << -/D [1142 0 R /XYZ 150.7049 330.6204 null] +1172 0 obj << +/D [1162 0 R /XYZ 150.7049 330.6204 null] >> endobj -1141 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F32 602 0 R /F18 425 0 R >> +1161 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F32 622 0 R /F18 441 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1155 0 obj << +1175 0 obj << /Length 8110 >> stream @@ -21967,42 +22203,42 @@ ET 0 g 0 G endstream endobj -1154 0 obj << +1174 0 obj << /Type /Page -/Contents 1155 0 R -/Resources 1153 0 R +/Contents 1175 0 R +/Resources 1173 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1140 0 R -/Annots [ 1158 0 R 1159 0 R ] +/Parent 1160 0 R +/Annots [ 1178 0 R 1179 0 R ] >> endobj -1158 0 obj << +1178 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 500.7991 361.7786 511.9241] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1159 0 obj << +1179 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 188.3888 367.009 199.5137] /Subtype /Link /A << /S /GoTo /D (spdata) >> >> endobj -1156 0 obj << -/D [1154 0 R /XYZ 99.8954 740.9981 null] +1176 0 obj << +/D [1174 0 R /XYZ 99.8954 740.9981 null] >> endobj 210 0 obj << -/D [1154 0 R /XYZ 99.8954 656.8729 null] +/D [1174 0 R /XYZ 99.8954 656.8729 null] >> endobj -1157 0 obj << -/D [1154 0 R /XYZ 99.8954 628.3345 null] +1177 0 obj << +/D [1174 0 R /XYZ 99.8954 628.3345 null] >> endobj -1153 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +1173 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1162 0 obj << +1182 0 obj << /Length 3452 >> stream @@ -22084,39 +22320,39 @@ ET 0 g 0 G endstream endobj -1161 0 obj << +1181 0 obj << /Type /Page -/Contents 1162 0 R -/Resources 1160 0 R +/Contents 1182 0 R +/Resources 1180 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1140 0 R +/Parent 1160 0 R >> endobj -1163 0 obj << -/D [1161 0 R /XYZ 150.7049 740.9981 null] +1183 0 obj << +/D [1181 0 R /XYZ 150.7049 740.9981 null] >> endobj -1164 0 obj << -/D [1161 0 R /XYZ 150.7049 696.2631 null] +1184 0 obj << +/D [1181 0 R /XYZ 150.7049 696.2631 null] >> endobj -1165 0 obj << -/D [1161 0 R /XYZ 150.7049 700.2482 null] +1185 0 obj << +/D [1181 0 R /XYZ 150.7049 700.2482 null] >> endobj -1166 0 obj << -/D [1161 0 R /XYZ 150.7049 666.1538 null] +1186 0 obj << +/D [1181 0 R /XYZ 150.7049 666.1538 null] >> endobj -1167 0 obj << -/D [1161 0 R /XYZ 150.7049 646.5052 null] +1187 0 obj << +/D [1181 0 R /XYZ 150.7049 646.5052 null] >> endobj -1168 0 obj << -/D [1161 0 R /XYZ 150.7049 602.6696 null] +1188 0 obj << +/D [1181 0 R /XYZ 150.7049 602.6696 null] >> endobj -1169 0 obj << -/D [1161 0 R /XYZ 150.7049 558.834 null] +1189 0 obj << +/D [1181 0 R /XYZ 150.7049 558.834 null] >> endobj -1160 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F32 602 0 R >> +1180 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1172 0 obj << +1192 0 obj << /Length 5241 >> stream @@ -22333,42 +22569,42 @@ ET 0 g 0 G endstream endobj -1171 0 obj << +1191 0 obj << /Type /Page -/Contents 1172 0 R -/Resources 1170 0 R +/Contents 1192 0 R +/Resources 1190 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1140 0 R -/Annots [ 1175 0 R 1176 0 R ] +/Parent 1160 0 R +/Annots [ 1195 0 R 1196 0 R ] >> endobj -1175 0 obj << +1195 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 507.8447 367.009 518.9696] /Subtype /Link /A << /S /GoTo /D (spdata) >> >> endobj -1176 0 obj << +1196 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 440.0987 361.7786 451.2237] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1173 0 obj << -/D [1171 0 R /XYZ 99.8954 740.9981 null] +1193 0 obj << +/D [1191 0 R /XYZ 99.8954 740.9981 null] >> endobj 214 0 obj << -/D [1171 0 R /XYZ 99.8954 659.6006 null] +/D [1191 0 R /XYZ 99.8954 659.6006 null] >> endobj -1174 0 obj << -/D [1171 0 R /XYZ 99.8954 631.8021 null] +1194 0 obj << +/D [1191 0 R /XYZ 99.8954 631.8021 null] >> endobj -1170 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +1190 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1179 0 obj << +1199 0 obj << /Length 6561 >> stream @@ -22609,48 +22845,48 @@ ET 0 g 0 G endstream endobj -1178 0 obj << +1198 0 obj << /Type /Page -/Contents 1179 0 R -/Resources 1177 0 R +/Contents 1199 0 R +/Resources 1197 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1140 0 R -/Annots [ 1182 0 R 1183 0 R ] +/Parent 1160 0 R +/Annots [ 1202 0 R 1203 0 R ] >> endobj -1182 0 obj << +1202 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 489.9119 417.8184 501.0369] /Subtype /Link /A << /S /GoTo /D (spdata) >> >> endobj -1183 0 obj << +1203 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 422.166 412.5881 433.2909] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1180 0 obj << -/D [1178 0 R /XYZ 150.7049 740.9981 null] +1200 0 obj << +/D [1198 0 R /XYZ 150.7049 740.9981 null] >> endobj 218 0 obj << -/D [1178 0 R /XYZ 150.7049 641.6678 null] +/D [1198 0 R /XYZ 150.7049 641.6678 null] >> endobj -1181 0 obj << -/D [1178 0 R /XYZ 150.7049 613.8693 null] +1201 0 obj << +/D [1198 0 R /XYZ 150.7049 613.8693 null] >> endobj -1184 0 obj << -/D [1178 0 R /XYZ 150.7049 225.1548 null] +1204 0 obj << +/D [1198 0 R /XYZ 150.7049 225.1548 null] >> endobj -1185 0 obj << -/D [1178 0 R /XYZ 150.7049 229.1399 null] +1205 0 obj << +/D [1198 0 R /XYZ 150.7049 229.1399 null] >> endobj -1177 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +1197 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1188 0 obj << +1208 0 obj << /Length 7044 >> stream @@ -22853,35 +23089,35 @@ ET 0 g 0 G endstream endobj -1187 0 obj << +1207 0 obj << /Type /Page -/Contents 1188 0 R -/Resources 1186 0 R +/Contents 1208 0 R +/Resources 1206 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1192 0 R -/Annots [ 1191 0 R ] +/Parent 1212 0 R +/Annots [ 1211 0 R ] >> endobj -1191 0 obj << +1211 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [261.1521 507.8447 328.21 518.9696] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1189 0 obj << -/D [1187 0 R /XYZ 99.8954 740.9981 null] +1209 0 obj << +/D [1207 0 R /XYZ 99.8954 740.9981 null] >> endobj 222 0 obj << -/D [1187 0 R /XYZ 99.8954 659.6006 null] +/D [1207 0 R /XYZ 99.8954 659.6006 null] >> endobj -1190 0 obj << -/D [1187 0 R /XYZ 99.8954 631.8021 null] +1210 0 obj << +/D [1207 0 R /XYZ 99.8954 631.8021 null] >> endobj -1186 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R /F11 586 0 R >> +1206 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R /F11 606 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1195 0 obj << +1215 0 obj << /Length 8266 >> stream @@ -23096,35 +23332,35 @@ ET 0 g 0 G endstream endobj -1194 0 obj << +1214 0 obj << /Type /Page -/Contents 1195 0 R -/Resources 1193 0 R +/Contents 1215 0 R +/Resources 1213 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1192 0 R -/Annots [ 1198 0 R ] +/Parent 1212 0 R +/Annots [ 1218 0 R ] >> endobj -1198 0 obj << +1218 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 296.5075 412.5881 307.6325] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1196 0 obj << -/D [1194 0 R /XYZ 150.7049 740.9981 null] +1216 0 obj << +/D [1214 0 R /XYZ 150.7049 740.9981 null] >> endobj 226 0 obj << -/D [1194 0 R /XYZ 150.7049 661.3143 null] +/D [1214 0 R /XYZ 150.7049 661.3143 null] >> endobj -1197 0 obj << -/D [1194 0 R /XYZ 150.7049 633.5158 null] +1217 0 obj << +/D [1214 0 R /XYZ 150.7049 633.5158 null] >> endobj -1193 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F11 586 0 R /F32 602 0 R >> +1213 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F11 606 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1201 0 obj << +1221 0 obj << /Length 1853 >> stream @@ -23178,30 +23414,30 @@ ET 0 g 0 G endstream endobj -1200 0 obj << +1220 0 obj << /Type /Page -/Contents 1201 0 R -/Resources 1199 0 R +/Contents 1221 0 R +/Resources 1219 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1192 0 R +/Parent 1212 0 R >> endobj -1202 0 obj << -/D [1200 0 R /XYZ 99.8954 740.9981 null] +1222 0 obj << +/D [1220 0 R /XYZ 99.8954 740.9981 null] >> endobj -1203 0 obj << -/D [1200 0 R /XYZ 99.8954 615.4966 null] +1223 0 obj << +/D [1220 0 R /XYZ 99.8954 615.4966 null] >> endobj -1204 0 obj << -/D [1200 0 R /XYZ 99.8954 619.4816 null] +1224 0 obj << +/D [1220 0 R /XYZ 99.8954 619.4816 null] >> endobj -1205 0 obj << -/D [1200 0 R /XYZ 99.8954 597.0657 null] +1225 0 obj << +/D [1220 0 R /XYZ 99.8954 597.0657 null] >> endobj -1199 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F18 425 0 R >> +1219 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F18 441 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1208 0 obj << +1228 0 obj << /Length 4852 >> stream @@ -23380,35 +23616,35 @@ ET 0 g 0 G endstream endobj -1207 0 obj << +1227 0 obj << /Type /Page -/Contents 1208 0 R -/Resources 1206 0 R +/Contents 1228 0 R +/Resources 1226 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1192 0 R -/Annots [ 1211 0 R ] +/Parent 1212 0 R +/Annots [ 1231 0 R ] >> endobj -1211 0 obj << +1231 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [311.9616 507.8447 379.0195 518.9696] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1209 0 obj << -/D [1207 0 R /XYZ 150.7049 740.9981 null] +1229 0 obj << +/D [1227 0 R /XYZ 150.7049 740.9981 null] >> endobj 230 0 obj << -/D [1207 0 R /XYZ 150.7049 659.6006 null] +/D [1227 0 R /XYZ 150.7049 659.6006 null] >> endobj -1210 0 obj << -/D [1207 0 R /XYZ 150.7049 631.8021 null] +1230 0 obj << +/D [1227 0 R /XYZ 150.7049 631.8021 null] >> endobj -1206 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +1226 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1214 0 obj << +1234 0 obj << /Length 4811 >> stream @@ -23587,35 +23823,35 @@ ET 0 g 0 G endstream endobj -1213 0 obj << +1233 0 obj << /Type /Page -/Contents 1214 0 R -/Resources 1212 0 R +/Contents 1234 0 R +/Resources 1232 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1192 0 R -/Annots [ 1217 0 R ] +/Parent 1212 0 R +/Annots [ 1237 0 R ] >> endobj -1217 0 obj << +1237 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [261.1521 416.1884 328.21 427.3133] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1215 0 obj << -/D [1213 0 R /XYZ 99.8954 740.9981 null] +1235 0 obj << +/D [1233 0 R /XYZ 99.8954 740.9981 null] >> endobj 234 0 obj << -/D [1213 0 R /XYZ 99.8954 659.6006 null] +/D [1233 0 R /XYZ 99.8954 659.6006 null] >> endobj -1216 0 obj << -/D [1213 0 R /XYZ 99.8954 631.8021 null] +1236 0 obj << +/D [1233 0 R /XYZ 99.8954 631.8021 null] >> endobj -1212 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +1232 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1220 0 obj << +1240 0 obj << /Length 5176 >> stream @@ -23742,27 +23978,27 @@ ET 0 g 0 G endstream endobj -1219 0 obj << +1239 0 obj << /Type /Page -/Contents 1220 0 R -/Resources 1218 0 R +/Contents 1240 0 R +/Resources 1238 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1192 0 R +/Parent 1212 0 R >> endobj -1221 0 obj << -/D [1219 0 R /XYZ 150.7049 740.9981 null] +1241 0 obj << +/D [1239 0 R /XYZ 150.7049 740.9981 null] >> endobj 238 0 obj << -/D [1219 0 R /XYZ 150.7049 644.4574 null] +/D [1239 0 R /XYZ 150.7049 644.4574 null] >> endobj -1222 0 obj << -/D [1219 0 R /XYZ 150.7049 613.8693 null] +1242 0 obj << +/D [1239 0 R /XYZ 150.7049 613.8693 null] >> endobj -1218 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F11 586 0 R /F10 610 0 R >> +1238 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F11 606 0 R /F10 630 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1225 0 obj << +1245 0 obj << /Length 9789 >> stream @@ -24081,35 +24317,35 @@ ET 0 g 0 G endstream endobj -1224 0 obj << +1244 0 obj << /Type /Page -/Contents 1225 0 R -/Resources 1223 0 R +/Contents 1245 0 R +/Resources 1243 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1229 0 R -/Annots [ 1228 0 R ] +/Parent 1249 0 R +/Annots [ 1248 0 R ] >> endobj -1228 0 obj << +1248 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 392.399 361.7786 403.5239] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1226 0 obj << -/D [1224 0 R /XYZ 99.8954 740.9981 null] +1246 0 obj << +/D [1244 0 R /XYZ 99.8954 740.9981 null] >> endobj 242 0 obj << -/D [1224 0 R /XYZ 99.8954 647.9422 null] +/D [1244 0 R /XYZ 99.8954 647.9422 null] >> endobj -1227 0 obj << -/D [1224 0 R /XYZ 99.8954 617.3542 null] +1247 0 obj << +/D [1244 0 R /XYZ 99.8954 617.3542 null] >> endobj -1223 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R /F11 586 0 R >> +1243 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R /F11 606 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1232 0 obj << +1252 0 obj << /Length 2057 >> stream @@ -24163,30 +24399,30 @@ ET 0 g 0 G endstream endobj -1231 0 obj << +1251 0 obj << /Type /Page -/Contents 1232 0 R -/Resources 1230 0 R +/Contents 1252 0 R +/Resources 1250 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1229 0 R +/Parent 1249 0 R >> endobj -1233 0 obj << -/D [1231 0 R /XYZ 150.7049 740.9981 null] +1253 0 obj << +/D [1251 0 R /XYZ 150.7049 740.9981 null] >> endobj -1234 0 obj << -/D [1231 0 R /XYZ 150.7049 615.4966 null] +1254 0 obj << +/D [1251 0 R /XYZ 150.7049 615.4966 null] >> endobj -1235 0 obj << -/D [1231 0 R /XYZ 150.7049 619.4816 null] +1255 0 obj << +/D [1251 0 R /XYZ 150.7049 619.4816 null] >> endobj -1236 0 obj << -/D [1231 0 R /XYZ 150.7049 585.664 null] +1256 0 obj << +/D [1251 0 R /XYZ 150.7049 585.664 null] >> endobj -1230 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F18 425 0 R /F32 602 0 R >> +1250 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F18 441 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1239 0 obj << +1259 0 obj << /Length 9455 >> stream @@ -24505,36 +24741,36 @@ ET 0 g 0 G endstream endobj -1238 0 obj << +1258 0 obj << /Type /Page -/Contents 1239 0 R -/Resources 1237 0 R +/Contents 1259 0 R +/Resources 1257 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1229 0 R -/Annots [ 1242 0 R ] +/Parent 1249 0 R +/Annots [ 1262 0 R ] >> endobj -1242 0 obj << +1262 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 396.6523 361.7786 407.7772] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1240 0 obj << -/D [1238 0 R /XYZ 99.8954 740.9981 null] +1260 0 obj << +/D [1258 0 R /XYZ 99.8954 740.9981 null] >> endobj 246 0 obj << -/D [1238 0 R /XYZ 99.8954 650.3727 null] +/D [1258 0 R /XYZ 99.8954 650.3727 null] >> endobj -1241 0 obj << -/D [1238 0 R /XYZ 99.8954 619.7846 null] +1261 0 obj << +/D [1258 0 R /XYZ 99.8954 619.7846 null] >> endobj -1237 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R /F11 586 0 R >> +1257 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R /F11 606 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1245 0 obj << -/Length 6286 +1265 0 obj << +/Length 5635 >> stream 1 0 0 1 150.7049 740.9981 cm @@ -24559,9 +24795,9 @@ S Q 1 0 0 1 -175.972 -680.226 cm BT -/F18 14.3462 Tf 180.8139 680.226 Td[(g)-1(et)]TJ +/F18 14.3462 Tf 180.8139 680.226 Td[(is)]TJ ET -1 0 0 1 203.4925 680.226 cm +1 0 0 1 192.6316 680.226 cm q []0 d 0 J @@ -24570,11 +24806,11 @@ q 4.8419 0.1992 l S Q -1 0 0 1 -203.4925 -680.226 cm +1 0 0 1 -192.6316 -680.226 cm BT -/F18 14.3462 Tf 208.3343 680.226 Td[(b)-31(o)-1(undary|Ext)-1(ract)-375(l)-1(ist)-376(of)-375(b)-31(o)-1(undary)]TJ -57.6294 -17.9328 Td[(el)-1(em)-1(en)31(ts)]TJ 0 -35.7686 Td[(Syn)32(t)-1(ax)]TJ/F8 9.9626 Tf 83.3016 -21.8209 Td[(call)-333(psb)]TJ +/F18 14.3462 Tf 197.4734 680.226 Td[(o)31(w)-1(ned|)]TJ -46.7685 -35.7686 Td[(Syn)32(t)-1(ax)]TJ/F8 9.9626 Tf 109.8896 -21.8209 Td[(call)-333(psb)]TJ ET -1 0 0 1 267.8684 604.7037 cm +1 0 0 1 294.4564 622.6364 cm q []0 d 0 J @@ -24583,11 +24819,11 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -267.8684 -604.7037 cm +1 0 0 1 -294.4564 -622.6364 cm BT -/F8 9.9626 Tf 270.8572 604.7037 Td[(get)]TJ +/F8 9.9626 Tf 297.4453 622.6364 Td[(is)]TJ ET -1 0 0 1 284.7385 604.7037 cm +1 0 0 1 304.7401 622.6364 cm q []0 d 0 J @@ -24596,62 +24832,87 @@ q 2.9888 0.1992 l S Q -1 0 0 1 -284.7385 -604.7037 cm +1 0 0 1 -304.7401 -622.6364 cm BT -/F8 9.9626 Tf 287.7273 604.7037 Td[(b)-27(oun)1(dary)-333(\050)]TJ/F19 9.9626 Tf 48.7341 0 Td[(bndel,)-357(desc,)-358(i)1(n)-1(f)1(o)]TJ/F8 9.9626 Tf 70.7786 0 Td[(\051)]TJ +/F8 9.9626 Tf 307.7289 622.6364 Td[(o)28(wned)-333(\050)]TJ/F19 9.9626 Tf 34.5926 0 Td[(x,)-357(desc)]TJ ET -1 0 0 1 145.7235 580.7934 cm +1 0 0 1 372.5047 622.6364 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +3.0552 0.1992 l +S +Q +1 0 0 1 -372.5047 -622.6364 cm +BT +/F19 9.9626 Tf 375.56 622.6364 Td[(a)]TJ/F8 9.9626 Tf 5.092 0 Td[(\051)]TJ +ET +1 0 0 1 145.7235 598.7261 cm 0 g 0 G -1 0 0 1 -145.7235 -580.7934 cm +1 0 0 1 -145.7235 -598.7261 cm BT -/F29 9.9626 Tf 150.7049 580.7934 Td[(T)32(yp)-32(e:)]TJ +/F29 9.9626 Tf 150.7049 598.7261 Td[(T)32(yp)-32(e:)]TJ ET -1 0 0 1 179.5203 580.7934 cm +1 0 0 1 179.5203 598.7261 cm 0 g 0 G -1 0 0 1 -179.5203 -580.7934 cm +1 0 0 1 -179.5203 -598.7261 cm BT -/F8 9.9626 Tf 184.5016 580.7934 Td[(Async)28(hron)1(ous.)]TJ +/F8 9.9626 Tf 184.5016 598.7261 Td[(Async)28(hron)1(ous.)]TJ ET -1 0 0 1 145.7235 560.8681 cm +1 0 0 1 145.7235 578.8008 cm 0 g 0 G -1 0 0 1 -145.7235 -560.8681 cm +1 0 0 1 -145.7235 -578.8008 cm BT -/F29 9.9626 Tf 150.7049 560.8681 Td[(On)-383(En)32(tr)1(y)]TJ +/F29 9.9626 Tf 150.7049 578.8008 Td[(On)-383(En)32(tr)1(y)]TJ ET -1 0 0 1 198.2901 560.8681 cm +1 0 0 1 198.2901 578.8008 cm 0 g 0 G 1 0 0 1 -52.5665 -19.9253 cm 0 g 0 G -1 0 0 1 -145.7236 -540.9428 cm +1 0 0 1 -145.7236 -558.8755 cm BT -/F29 9.9626 Tf 150.7049 540.9428 Td[(desc)]TJ +/F29 9.9626 Tf 150.7049 558.8755 Td[(x)]TJ ET -1 0 0 1 171.9321 540.9428 cm +1 0 0 1 156.7516 558.8755 cm 0 g 0 G -1 0 0 1 -171.9321 -540.9428 cm +1 0 0 1 -156.7516 -558.8755 cm BT -/F8 9.9626 Tf 176.9134 540.9428 Td[(th)1(e)-334(c)-1(omm)27(u)1(ni)1(c)-1(ation)-332(des)-1(crip)1(tor.)]TJ -1.3019 -11.9552 Td[(Scop)-27(e)-1(:)]TJ/F29 9.9626 Tf 27.9508 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf 23.0731 0 Td[(.)]TJ -51.0239 -11.9551 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 25.1834 0 Td[(required)]TJ/F8 9.9626 Tf 41.8983 0 Td[(.)]TJ -67.0817 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(in)]TJ/F8 9.9626 Tf 9.5475 0 Td[(.)]TJ -43.0331 -11.9552 Td[(Sp)-27(ec)-1(i\014)1(e)-1(d)-332(as)-1(:)-444(a)-333(s)-1(tr)1(uctured)-333(dat)1(a)-334(of)-333(t)28(yp)-27(e)]TJ +/F8 9.9626 Tf 161.7329 558.8755 Td[(In)28(tege)-1(r)-333(i)1(ndex.)]TJ 13.8786 -11.9551 Td[(Scop)-27(e)-1(:)]TJ/F29 9.9626 Tf 32.3786 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf -32.3786 -11.9552 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 29.6112 0 Td[(required)]TJ/F8 9.9626 Tf -29.6112 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(in)]TJ/F8 9.9626 Tf 9.5475 0 Td[(.)]TJ -43.0331 -11.9551 Td[(Sp)-27(ec)-1(i\014)1(e)-1(d)-332(as)-1(:)-444(a)-333(s)-1(calar)-333(in)28(tege)-1(r)1(.)]TJ ET -1 0 0 1 346.5264 493.1221 cm -0 0 1 rg 0 0 1 RG -1 0 0 1 -346.5264 -493.1221 cm +1 0 0 1 145.7235 479.1744 cm +0 g 0 G +1 0 0 1 -145.7235 -479.1744 cm BT -/F32 9.9626 Tf 346.5264 493.1221 Td[(psb)]TJ +/F29 9.9626 Tf 150.7049 479.1744 Td[(desc)]TJ ET -1 0 0 1 362.8451 493.1221 cm +1 0 0 1 172.6195 479.1744 cm q []0 d 0 J 0.3985 w 0 0.1992 m -3.1382 0.1992 l +3.4371 0.1992 l S Q -1 0 0 1 -362.8451 -493.1221 cm +1 0 0 1 -172.6195 -479.1744 cm BT -/F32 9.9626 Tf 365.9833 493.1221 Td[(desc)]TJ +/F29 9.9626 Tf 176.0566 479.1744 Td[(a)]TJ ET -1 0 0 1 387.5322 493.1221 cm +1 0 0 1 181.6259 479.1744 cm +0 g 0 G +1 0 0 1 -181.6259 -479.1744 cm +BT +/F8 9.9626 Tf 186.6072 479.1744 Td[(th)1(e)-334(c)-1(omm)27(u)1(ni)1(c)-1(ation)-332(des)-1(crip)1(tor.)]TJ -10.9957 -11.9552 Td[(Scop)-27(e)-1(:)]TJ/F29 9.9626 Tf 27.9508 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf 23.0731 0 Td[(.)]TJ -51.0239 -11.9551 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 25.1834 0 Td[(required)]TJ/F8 9.9626 Tf 41.8983 0 Td[(.)]TJ -67.0817 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(in)]TJ/F8 9.9626 Tf 9.5475 0 Td[(.)]TJ -43.0331 -11.9552 Td[(Sp)-27(ec)-1(i\014)1(e)-1(d)-332(as)-1(:)-444(a)-333(s)-1(tr)1(uctured)-333(dat)1(a)-334(of)-333(t)28(yp)-27(e)]TJ +ET +1 0 0 1 346.5264 431.3538 cm +0 0 1 rg 0 0 1 RG +1 0 0 1 -346.5264 -431.3538 cm +BT +/F32 9.9626 Tf 346.5264 431.3538 Td[(psb)]TJ +ET +1 0 0 1 362.8451 431.3538 cm q []0 d 0 J @@ -24660,71 +24921,60 @@ q 3.1382 0.1992 l S Q -1 0 0 1 -387.5322 -493.1221 cm +1 0 0 1 -362.8451 -431.3538 cm BT -/F32 9.9626 Tf 390.6705 493.1221 Td[(type)]TJ -ET -1 0 0 1 411.5918 493.1221 cm -0 g 0 G -1 0 0 1 -411.5918 -493.1221 cm -BT -/F8 9.9626 Tf 411.5918 493.1221 Td[(.)]TJ +/F32 9.9626 Tf 365.9833 431.3538 Td[(desc)]TJ ET -1 0 0 1 145.7235 471.2043 cm -0 g 0 G -1 0 0 1 -145.7235 -471.2043 cm -BT -/F29 9.9626 Tf 150.7049 471.2043 Td[(On)-383(R)-1(etur)1(n)]TJ -ET -1 0 0 1 205.2431 471.2043 cm -0 g 0 G -1 0 0 1 -59.5196 -19.9253 cm -0 g 0 G -1 0 0 1 -145.7235 -451.279 cm +1 0 0 1 387.5322 431.3538 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +3.1382 0.1992 l +S +Q +1 0 0 1 -387.5322 -431.3538 cm BT -/F29 9.9626 Tf 150.7049 451.279 Td[(bndel)]TJ +/F32 9.9626 Tf 390.6705 431.3538 Td[(type)]TJ ET -1 0 0 1 178.2334 451.279 cm +1 0 0 1 411.5918 431.3538 cm 0 g 0 G -1 0 0 1 -178.2334 -451.279 cm +1 0 0 1 -411.5918 -431.3538 cm BT -/F8 9.9626 Tf 183.2148 451.279 Td[(The)-268(li)1(s)-1(t)-267(of)-267(b)-28(ou)1(nd)1(ary)-267(e)-1(leme)-1(n)28(t)1(s)-268(on)-268(t)1(he)-268(callin)1(g)-268(p)1(ro)-28(ce)-1(ss)-1(,)-280(in)-267(lo)-28(cal)-267(n)28(um)28(b)-28(erin)1(g.)]TJ -7.6033 -11.9552 Td[(Scop)-27(e)-1(:)]TJ/F29 9.9626 Tf 32.3786 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf -32.3786 -11.9551 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 29.6112 0 Td[(required)]TJ/F8 9.9626 Tf -29.6112 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(out)]TJ/F8 9.9626 Tf 16.549 0 Td[(.)]TJ -50.0346 -11.9552 Td[(Sp)-27(ec)-1(i\014)1(e)-1(d)-456(as:)-691(a)-456(rank)-456(on)1(e)-457(arra)28(y)-456(w)-1(i)1(th)-456(the)-457(ALLOCA)84(T)83(AB)-1(LE)-456(att)1(ribu)1(te,)-488(of)]TJ 0 -11.9551 Td[(t)28(yp)-27(e)-334(in)28(t)1(e)-1(ger.)]TJ +/F8 9.9626 Tf 411.5918 431.3538 Td[(.)]TJ ET -1 0 0 1 145.7235 359.6227 cm +1 0 0 1 145.7235 409.4359 cm 0 g 0 G -1 0 0 1 -145.7235 -359.6227 cm +1 0 0 1 -145.7235 -409.4359 cm BT -/F29 9.9626 Tf 150.7049 359.6227 Td[(inf)-1(o)]TJ +/F29 9.9626 Tf 150.7049 409.4359 Td[(On)-383(R)-1(etur)1(n)]TJ ET -1 0 0 1 169.4816 359.6227 cm +1 0 0 1 205.2431 409.4359 cm 0 g 0 G -1 0 0 1 -169.4816 -359.6227 cm -BT -/F8 9.9626 Tf 174.4629 359.6227 Td[(Er)1(ror)-333(co)-28(de.)]TJ 1.1486 -11.9552 Td[(Scop)-27(e)-1(:)]TJ/F29 9.9626 Tf 32.3786 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf -32.3786 -11.9551 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 29.6112 0 Td[(required)]TJ/F8 9.9626 Tf -29.6112 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(out)]TJ/F8 9.9626 Tf 16.549 0 Td[(.)]TJ -50.0346 -11.9552 Td[(An)-333(in)29(te)-1(ger)-333(v)56(alue;)-333(0)-334(means)-334(n)1(o)-334(error)-333(h)1(as)-334(b)-27(e)-1(en)-333(detec)-1(ted.)]TJ/F18 14.3462 Tf -24.9066 -32.9458 Td[(Not)-1(es)]TJ -ET -1 0 0 1 150.7049 257.0353 cm +1 0 0 1 -59.5196 -19.9252 cm 0 g 0 G -1 0 0 1 -150.7049 -257.0353 cm +1 0 0 1 -145.7235 -389.5107 cm BT -/F8 9.9626 Tf 162.8814 257.0353 Td[(1.)]TJ +/F29 9.9626 Tf 150.7049 389.5107 Td[(F)96(unction)-384(v)64(alue)]TJ ET -1 0 0 1 170.6302 257.0353 cm +1 0 0 1 224.1097 389.5107 cm 0 g 0 G -1 0 0 1 -170.6302 -257.0353 cm +1 0 0 1 -224.1097 -389.5107 cm BT -/F8 9.9626 Tf 175.6115 257.0353 Td[(If)-269(th)1(e)-1(r)1(e)-270(are)-269(no)-269(b)-27(oun)1(dar)1(y)-269(e)-1(leme)-1(n)28(t)1(s)-270(\050i.)1(e)-1(.,)-281(if)-269(th)1(e)-270(lo)-27(c)-1(al)-269(p)1(art)-269(of)-269(t)1(he)-270(conn)1(e)-1(ctiv)1(it)28(y)]TJ 0 -11.9552 Td[(grap)1(h)-449(is)-450(se)-1(lf)1(-)-1(con)28(tai)1(ned\051)-449(the)-450(ou)1(tpu)1(t)-450(v)28(ec)-1(tor)-449(i)1(s)-450(s)-1(et)-450(to)-449(the)-449(\134not)-449(allo)-28(cate)-1(d)1(")]TJ 0 -11.9551 Td[(state)-1(.)]TJ +/F8 9.9626 Tf 229.0911 389.5107 Td[(A)-302(l)1(ogic)-1(al)-301(mas)-1(k)-301(w)-1(h)1(ic)27(h)-301(is)-302(tr)1(ue)-302(if)]TJ/F11 9.9626 Tf 134.0854 0 Td[(x)]TJ/F8 9.9626 Tf 8.6992 0 Td[(is)-302(o)28(wned)-302(b)29(y)-302(th)1(e)-302(c)-1(u)1(rren)28(t)-301(pro-)]TJ -196.2642 -11.9552 Td[(ce)-1(ss)-334(Scop)-27(e)-1(:)]TJ/F29 9.9626 Tf 52.4146 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf -52.4146 -11.9552 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 29.6112 0 Td[(required)]TJ/F8 9.9626 Tf -29.6112 -11.9551 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(out)]TJ/F8 9.9626 Tf 16.549 0 Td[(.)]TJ/F18 14.3462 Tf -74.9412 -44.901 Td[(Not)-1(es)]TJ ET -1 0 0 1 150.7049 213.1997 cm +1 0 0 1 150.7049 286.9232 cm 0 g 0 G -1 0 0 1 -150.7049 -213.1997 cm +1 0 0 1 -150.7049 -286.9232 cm BT -/F8 9.9626 Tf 162.8814 213.1997 Td[(2.)]TJ +/F8 9.9626 Tf 162.8814 286.9232 Td[(1.)]TJ ET -1 0 0 1 170.6302 213.1997 cm +1 0 0 1 170.6302 286.9232 cm 0 g 0 G -1 0 0 1 -170.6302 -213.1997 cm +1 0 0 1 -170.6302 -286.9232 cm BT -/F8 9.9626 Tf 175.6115 213.1997 Td[(Oth)1(e)-1(r)1(w)-1(i)1(s)-1(e)-288(the)-289(size)-289(of)]TJ/F32 9.9626 Tf 92.71 0 Td[(bndel)]TJ/F8 9.9626 Tf 29.0234 0 Td[(will)-288(b)-27(e)-289(exac)-1(t)1(ly)-288(e)-1(q)1(ual)-288(to)-288(the)-288(n)28(um)28(b)-28(er)-288(of)-288(b)-27(oun)1(d-)]TJ -121.7334 -11.9552 Td[(ary)-333(elem)-1(en)28(ts.)]TJ +/F8 9.9626 Tf 175.6115 286.9232 Td[(This)-300(r)1(outin)1(e)-300(re)-1(t)1(urn)1(s)-301(a)]TJ/F32 9.9626 Tf 98.4833 0 Td[(.true.)]TJ/F8 9.9626 Tf 34.3687 0 Td[(v)56(alue)-300(f)1(or)-300(an)-299(in)1(de)-1(x)-299(that)-299(is)-300(s)-1(tr)1(ictly)-300(o)28(wned)-299(b)28(y)]TJ -132.852 -11.9552 Td[(th)1(e)-334(c)-1(u)1(rren)28(t)-333(pr)1(o)-28(ce)-1(ss)-1(,)-333(exc)-1(l)1(ud)1(ing)-333(the)-333(halo)-333(in)1(dice)-1(s)]TJ ET 1 0 0 1 150.7049 90.4377 cm 0 g 0 G @@ -24736,45 +24986,1083 @@ ET 0 g 0 G endstream endobj -1244 0 obj << +1264 0 obj << /Type /Page -/Contents 1245 0 R -/Resources 1243 0 R +/Contents 1265 0 R +/Resources 1263 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1229 0 R -/Annots [ 1248 0 R ] +/Parent 1249 0 R +/Annots [ 1268 0 R ] >> endobj -1248 0 obj << +1268 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] -/Rect [345.5302 489.9119 412.5881 501.0369] +/Rect [345.5302 428.1436 412.5881 439.2685] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1246 0 obj << -/D [1244 0 R /XYZ 150.7049 740.9981 null] +1266 0 obj << +/D [1264 0 R /XYZ 150.7049 740.9981 null] >> endobj 250 0 obj << -/D [1244 0 R /XYZ 150.7049 644.4574 null] +/D [1264 0 R /XYZ 150.7049 659.6006 null] >> endobj -1247 0 obj << -/D [1244 0 R /XYZ 150.7049 613.8693 null] ->> endobj -1249 0 obj << -/D [1244 0 R /XYZ 150.7049 268.9905 null] +1267 0 obj << +/D [1264 0 R /XYZ 150.7049 631.8021 null] >> endobj -1250 0 obj << -/D [1244 0 R /XYZ 150.7049 272.9755 null] +1269 0 obj << +/D [1264 0 R /XYZ 150.7049 298.8784 null] >> endobj -1251 0 obj << -/D [1244 0 R /XYZ 150.7049 229.1399 null] +1270 0 obj << +/D [1264 0 R /XYZ 150.7049 302.8634 null] >> endobj -1243 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +1263 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R /F11 606 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1254 0 obj << -/Length 6045 +1273 0 obj << +/Length 7839 +>> +stream +1 0 0 1 99.8954 740.9981 cm +0 g 0 G +1 0 0 1 343.7111 0 cm +0 g 0 G +1 0 0 1 -348.6924 -60.7721 cm +0 g 0 G +0 g 0 G +1 0 0 1 -94.9141 -680.226 cm +BT +/F18 14.3462 Tf 99.8954 680.226 Td[(psb)]TJ +ET +1 0 0 1 125.1626 680.226 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +4.8419 0.1992 l +S +Q +1 0 0 1 -125.1626 -680.226 cm +BT +/F18 14.3462 Tf 130.0045 680.226 Td[(o)31(w)-1(ned)]TJ +ET +1 0 0 1 175.5472 680.226 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +4.8419 0.1992 l +S +Q +1 0 0 1 -175.5472 -680.226 cm +BT +/F18 14.3462 Tf 180.3891 680.226 Td[(inde)-1(x|)]TJ -80.4937 -35.7686 Td[(Syn)32(t)-1(ax)]TJ/F8 9.9626 Tf 84.0367 -21.8209 Td[(call)-333(psb)]TJ +ET +1 0 0 1 217.794 622.6364 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +2.9888 0.1992 l +S +Q +1 0 0 1 -217.794 -622.6364 cm +BT +/F8 9.9626 Tf 220.7828 622.6364 Td[(o)28(wned)]TJ +ET +1 0 0 1 248.7779 622.6364 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +2.9888 0.1992 l +S +Q +1 0 0 1 -248.7779 -622.6364 cm +BT +/F8 9.9626 Tf 251.7667 622.6364 Td[(in)1(dex)-333(\050)]TJ/F19 9.9626 Tf 30.7182 0 Td[(y,)-357(x,)-357(desc)]TJ +ET +1 0 0 1 324.1251 622.6364 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +3.0552 0.1992 l +S +Q +1 0 0 1 -324.1251 -622.6364 cm +BT +/F19 9.9626 Tf 327.1803 622.6364 Td[(a,)-358(i)1(nfo)]TJ/F8 9.9626 Tf 28.5151 0 Td[(\051)]TJ +ET +1 0 0 1 94.9141 598.7261 cm +0 g 0 G +1 0 0 1 -94.9141 -598.7261 cm +BT +/F29 9.9626 Tf 99.8954 598.7261 Td[(T)32(yp)-32(e:)]TJ +ET +1 0 0 1 128.7108 598.7261 cm +0 g 0 G +1 0 0 1 -128.7108 -598.7261 cm +BT +/F8 9.9626 Tf 133.6921 598.7261 Td[(Async)28(hron)1(ous.)]TJ +ET +1 0 0 1 94.9141 578.8008 cm +0 g 0 G +1 0 0 1 -94.9141 -578.8008 cm +BT +/F29 9.9626 Tf 99.8954 578.8008 Td[(On)-383(En)32(tr)1(y)]TJ +ET +1 0 0 1 147.4806 578.8008 cm +0 g 0 G +1 0 0 1 -52.5665 -19.9253 cm +0 g 0 G +1 0 0 1 -94.9141 -558.8755 cm +BT +/F29 9.9626 Tf 99.8954 558.8755 Td[(x)]TJ +ET +1 0 0 1 105.9421 558.8755 cm +0 g 0 G +1 0 0 1 -105.9421 -558.8755 cm +BT +/F8 9.9626 Tf 110.9235 558.8755 Td[(In)28(tege)-1(r)-333(i)1(ndi)1(c)-1(es)-1(.)]TJ 13.8785 -11.9551 Td[(Scop)-27(e)-1(:)]TJ/F29 9.9626 Tf 32.3787 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf -32.3787 -11.9552 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 29.6112 0 Td[(required)]TJ/F8 9.9626 Tf -29.6112 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(in,)-384(i)-1(n)1(out)]TJ/F8 9.9626 Tf 42.6454 0 Td[(.)]TJ -76.131 -11.9551 Td[(Sp)-27(ec)-1(i\014)1(e)-1(d)-332(as)-1(:)-444(a)-333(s)-1(calar)-333(or)-333(a)-333(rank)-333(on)1(e)-334(in)28(tege)-1(r)-333(ar)1(ra)28(y)83(.)]TJ +ET +1 0 0 1 94.9141 479.1744 cm +0 g 0 G +1 0 0 1 -94.9141 -479.1744 cm +BT +/F29 9.9626 Tf 99.8954 479.1744 Td[(desc)]TJ +ET +1 0 0 1 121.81 479.1744 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +3.4371 0.1992 l +S +Q +1 0 0 1 -121.81 -479.1744 cm +BT +/F29 9.9626 Tf 125.2471 479.1744 Td[(a)]TJ +ET +1 0 0 1 130.8165 479.1744 cm +0 g 0 G +1 0 0 1 -130.8165 -479.1744 cm +BT +/F8 9.9626 Tf 135.7978 479.1744 Td[(th)1(e)-334(c)-1(omm)27(u)1(ni)1(c)-1(ation)-332(des)-1(crip)1(tor.)]TJ -10.9958 -11.9552 Td[(Scop)-27(e)-1(:)]TJ/F29 9.9626 Tf 27.9508 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf 23.0731 0 Td[(.)]TJ -51.0239 -11.9551 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 25.1834 0 Td[(required)]TJ/F8 9.9626 Tf 41.8983 0 Td[(.)]TJ -67.0817 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(in)]TJ/F8 9.9626 Tf 9.5475 0 Td[(.)]TJ -43.0331 -11.9552 Td[(Sp)-27(ec)-1(i\014)1(e)-1(d)-332(as)-1(:)-444(a)-333(s)-1(tr)1(uctured)-333(dat)1(a)-334(of)-333(t)28(yp)-27(e)]TJ +ET +1 0 0 1 295.717 431.3538 cm +0 0 1 rg 0 0 1 RG +1 0 0 1 -295.717 -431.3538 cm +BT +/F32 9.9626 Tf 295.717 431.3538 Td[(psb)]TJ +ET +1 0 0 1 312.0356 431.3538 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +3.1382 0.1992 l +S +Q +1 0 0 1 -312.0356 -431.3538 cm +BT +/F32 9.9626 Tf 315.1738 431.3538 Td[(desc)]TJ +ET +1 0 0 1 336.7228 431.3538 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +3.1382 0.1992 l +S +Q +1 0 0 1 -336.7228 -431.3538 cm +BT +/F32 9.9626 Tf 339.861 431.3538 Td[(type)]TJ +ET +1 0 0 1 360.7824 431.3538 cm +0 g 0 G +1 0 0 1 -360.7824 -431.3538 cm +BT +/F8 9.9626 Tf 360.7824 431.3538 Td[(.)]TJ +ET +1 0 0 1 94.9141 411.4285 cm +0 g 0 G +1 0 0 1 -94.9141 -411.4285 cm +BT +/F29 9.9626 Tf 99.8954 411.4285 Td[(iac)-1(t)]TJ +ET +1 0 0 1 118.1947 411.4285 cm +0 g 0 G +1 0 0 1 -118.1947 -411.4285 cm +BT +/F8 9.9626 Tf 123.176 411.4285 Td[(sp)-28(ec)-1(i)1(\014es)-334(ac)-1(ti)1(on)-333(to)-333(b)-28(e)-334(t)1(ak)28(e)-1(n)-333(in)-333(case)-334(of)-333(ran)1(ge)-334(e)-1(r)1(rors.)-444(Scop)-28(e:)]TJ/F29 9.9626 Tf 257.1472 0 Td[(global)]TJ/F8 9.9626 Tf -255.5212 -11.9552 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 29.6112 0 Td[(opti)-1(on)1(al)]TJ/F8 9.9626 Tf -29.6112 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(in)]TJ/F8 9.9626 Tf 9.5475 0 Td[(.)]TJ -43.0331 -11.9551 Td[(Sp)-27(ec)-1(i\014)1(e)-1(d)-254(as)-1(:)-405(a)-255(c)27(h)1(aracte)-1(r)-255(v)56(ari)1(able)]TJ/F32 9.9626 Tf 143.584 0 Td[(I)]TJ/F8 9.9626 Tf 5.2303 0 Td[(gnor)1(e)-1(,)]TJ/F32 9.9626 Tf 29.2928 0 Td[(W)]TJ/F8 9.9626 Tf 5.2304 0 Td[(arn)1(ing)-255(or)]TJ/F32 9.9626 Tf 41.6697 0 Td[(A)]TJ/F8 9.9626 Tf 5.2303 0 Td[(b)-27(ort,)-270(de)-1(f)1(aul)1(t)]TJ/F32 9.9626 Tf 56.7418 0 Td[(I)]TJ/F8 9.9626 Tf 5.2304 0 Td[(gnor)1(e)-1(.)]TJ +ET +1 0 0 1 94.9141 353.6452 cm +0 g 0 G +1 0 0 1 -94.9141 -353.6452 cm +BT +/F29 9.9626 Tf 99.8954 353.6452 Td[(On)-383(R)-1(etur)1(n)]TJ +ET +1 0 0 1 154.4337 353.6452 cm +0 g 0 G +1 0 0 1 -59.5196 -19.9253 cm +0 g 0 G +1 0 0 1 -94.9141 -333.7199 cm +BT +/F29 9.9626 Tf 99.8954 333.7199 Td[(y)]TJ +ET +1 0 0 1 105.9421 333.7199 cm +0 g 0 G +1 0 0 1 -105.9421 -333.7199 cm +BT +/F8 9.9626 Tf 110.9235 333.7199 Td[(A)-294(logical)-294(mas)-1(k)-293(w)-1(h)1(ic)27(h)-293(is)-294(tru)1(e)-295(f)1(or)-294(all)-294(corr)1(e)-1(sp)-28(on)1(din)1(g)-294(e)-1(n)29(tries)-295(of)]TJ/F11 9.9626 Tf 259.2287 0 Td[(x)]TJ/F8 9.9626 Tf 8.6229 0 Td[(th)1(at)-294(are)-294(o)27(wn)1(e)-1(d)]TJ -253.9731 -11.9552 Td[(b)28(y)-333(th)1(e)-334(c)-1(u)1(rr)1(e)-1(n)28(t)-333(p)1(ro)-28(ce)-1(ss)-334(Scop)-27(e)-1(:)]TJ/F29 9.9626 Tf 132.7524 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf -132.7524 -11.9551 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 29.6112 0 Td[(required)]TJ/F8 9.9626 Tf -29.6112 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(out)]TJ/F8 9.9626 Tf 16.549 0 Td[(.)]TJ -50.0346 -11.9552 Td[(Sp)-27(ec)-1(i\014)1(e)-1(d)-332(as)-1(:)-444(a)-333(s)-1(calar)-333(or)-333(ran)1(k)-334(on)1(e)-334(logi)1(c)-1(al)-333(arr)1(a)27(y)84(.)]TJ +ET +1 0 0 1 94.9141 265.9739 cm +0 g 0 G +1 0 0 1 -94.9141 -265.9739 cm +BT +/F29 9.9626 Tf 99.8954 265.9739 Td[(inf)-1(o)]TJ +ET +1 0 0 1 118.6721 265.9739 cm +0 g 0 G +1 0 0 1 -118.6721 -265.9739 cm +BT +/F8 9.9626 Tf 123.6534 265.9739 Td[(Er)1(ror)-333(co)-28(de.)]TJ 1.1486 -11.9552 Td[(Scop)-27(e)-1(:)]TJ/F29 9.9626 Tf 32.3787 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf -32.3787 -11.9551 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 29.6112 0 Td[(required)]TJ/F8 9.9626 Tf -29.6112 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(out)]TJ/F8 9.9626 Tf 16.549 0 Td[(.)]TJ -50.0346 -11.9552 Td[(An)-333(in)29(te)-1(ger)-333(v)56(alue;)-333(0)-334(means)-334(n)1(o)-334(error)-333(h)1(as)-334(b)-27(e)-1(en)-333(detec)-1(ted.)]TJ/F18 14.3462 Tf -24.9066 -32.9458 Td[(Not)-1(es)]TJ +ET +1 0 0 1 99.8954 163.3865 cm +0 g 0 G +1 0 0 1 -99.8954 -163.3865 cm +BT +/F8 9.9626 Tf 112.072 163.3865 Td[(1.)]TJ +ET +1 0 0 1 119.8207 163.3865 cm +0 g 0 G +1 0 0 1 -119.8207 -163.3865 cm +BT +/F8 9.9626 Tf 124.802 163.3865 Td[(This)-475(r)1(outin)1(e)-475(re)-1(t)1(urn)1(s)-475(a)]TJ/F32 9.9626 Tf 105.4556 0 Td[(.true.)]TJ/F8 9.9626 Tf 36.1118 0 Td[(v)56(alue)-475(f)1(or)-475(th)1(os)-1(e)-475(in)1(dices)-476(t)1(hat)-475(ar)1(e)-476(stri)1(c)-1(tl)1(y)]TJ -141.5674 -11.9552 Td[(o)28(wned)-333(b)28(y)-333(the)-333(c)-1(u)1(rren)28(t)-333(pr)1(o)-28(c)-1(es)-1(s,)-333(e)-1(x)1(c)-1(lu)1(din)1(g)-333(the)-334(h)1(alo)-333(ind)1(ice)-1(s)]TJ +ET +1 0 0 1 99.8954 90.4377 cm +0 g 0 G +1 0 0 1 -99.8954 -90.4377 cm +BT +/F8 9.9626 Tf 266.7696 90.4377 Td[(83)]TJ +ET +1 0 0 1 443.6065 90.4377 cm +0 g 0 G +endstream +endobj +1272 0 obj << +/Type /Page +/Contents 1273 0 R +/Resources 1271 0 R +/MediaBox [0 0 595.2756 841.8898] +/Parent 1249 0 R +/Annots [ 1276 0 R ] +>> endobj +1276 0 obj << +/Type /Annot +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [294.7207 428.1436 361.7786 439.2685] +/Subtype /Link +/A << /S /GoTo /D (descdata) >> +>> endobj +1274 0 obj << +/D [1272 0 R /XYZ 99.8954 740.9981 null] +>> endobj +254 0 obj << +/D [1272 0 R /XYZ 99.8954 659.6006 null] +>> endobj +1275 0 obj << +/D [1272 0 R /XYZ 99.8954 631.8021 null] +>> endobj +1277 0 obj << +/D [1272 0 R /XYZ 99.8954 175.3416 null] +>> endobj +1278 0 obj << +/D [1272 0 R /XYZ 99.8954 179.3267 null] +>> endobj +1271 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R /F11 606 0 R >> +/ProcSet [ /PDF /Text ] +>> endobj +1281 0 obj << +/Length 5626 +>> +stream +1 0 0 1 150.7049 740.9981 cm +0 g 0 G +1 0 0 1 343.7111 0 cm +0 g 0 G +1 0 0 1 -348.6924 -60.7721 cm +0 g 0 G +0 g 0 G +1 0 0 1 -145.7236 -680.226 cm +BT +/F18 14.3462 Tf 150.7049 680.226 Td[(psb)]TJ +ET +1 0 0 1 175.972 680.226 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +4.8419 0.1992 l +S +Q +1 0 0 1 -175.972 -680.226 cm +BT +/F18 14.3462 Tf 180.8139 680.226 Td[(is)]TJ +ET +1 0 0 1 192.6316 680.226 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +4.8419 0.1992 l +S +Q +1 0 0 1 -192.6316 -680.226 cm +BT +/F18 14.3462 Tf 197.4734 680.226 Td[(l)-1(o)-31(cal)-1(|)]TJ -46.7685 -35.7686 Td[(Syn)32(t)-1(ax)]TJ/F8 9.9626 Tf 113.4872 -21.8209 Td[(call)-333(psb)]TJ +ET +1 0 0 1 298.0541 622.6364 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +2.9888 0.1992 l +S +Q +1 0 0 1 -298.0541 -622.6364 cm +BT +/F8 9.9626 Tf 301.0429 622.6364 Td[(is)]TJ +ET +1 0 0 1 308.3377 622.6364 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +2.9888 0.1992 l +S +Q +1 0 0 1 -308.3377 -622.6364 cm +BT +/F8 9.9626 Tf 311.3265 622.6364 Td[(lo)-28(cal)-333(\050)]TJ/F19 9.9626 Tf 27.3974 0 Td[(x,)-357(desc)]TJ +ET +1 0 0 1 368.9071 622.6364 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +3.0552 0.1992 l +S +Q +1 0 0 1 -368.9071 -622.6364 cm +BT +/F19 9.9626 Tf 371.9623 622.6364 Td[(a)]TJ/F8 9.9626 Tf 5.092 0 Td[(\051)]TJ +ET +1 0 0 1 145.7235 598.7261 cm +0 g 0 G +1 0 0 1 -145.7235 -598.7261 cm +BT +/F29 9.9626 Tf 150.7049 598.7261 Td[(T)32(yp)-32(e:)]TJ +ET +1 0 0 1 179.5203 598.7261 cm +0 g 0 G +1 0 0 1 -179.5203 -598.7261 cm +BT +/F8 9.9626 Tf 184.5016 598.7261 Td[(Async)28(hron)1(ous.)]TJ +ET +1 0 0 1 145.7235 578.8008 cm +0 g 0 G +1 0 0 1 -145.7235 -578.8008 cm +BT +/F29 9.9626 Tf 150.7049 578.8008 Td[(On)-383(En)32(tr)1(y)]TJ +ET +1 0 0 1 198.2901 578.8008 cm +0 g 0 G +1 0 0 1 -52.5665 -19.9253 cm +0 g 0 G +1 0 0 1 -145.7236 -558.8755 cm +BT +/F29 9.9626 Tf 150.7049 558.8755 Td[(x)]TJ +ET +1 0 0 1 156.7516 558.8755 cm +0 g 0 G +1 0 0 1 -156.7516 -558.8755 cm +BT +/F8 9.9626 Tf 161.7329 558.8755 Td[(In)28(tege)-1(r)-333(i)1(ndex.)]TJ 13.8786 -11.9551 Td[(Scop)-27(e)-1(:)]TJ/F29 9.9626 Tf 32.3786 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf -32.3786 -11.9552 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 29.6112 0 Td[(required)]TJ/F8 9.9626 Tf -29.6112 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(in)]TJ/F8 9.9626 Tf 9.5475 0 Td[(.)]TJ -43.0331 -11.9551 Td[(Sp)-27(ec)-1(i\014)1(e)-1(d)-332(as)-1(:)-444(a)-333(s)-1(calar)-333(in)28(tege)-1(r)1(.)]TJ +ET +1 0 0 1 145.7235 479.1744 cm +0 g 0 G +1 0 0 1 -145.7235 -479.1744 cm +BT +/F29 9.9626 Tf 150.7049 479.1744 Td[(desc)]TJ +ET +1 0 0 1 172.6195 479.1744 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +3.4371 0.1992 l +S +Q +1 0 0 1 -172.6195 -479.1744 cm +BT +/F29 9.9626 Tf 176.0566 479.1744 Td[(a)]TJ +ET +1 0 0 1 181.6259 479.1744 cm +0 g 0 G +1 0 0 1 -181.6259 -479.1744 cm +BT +/F8 9.9626 Tf 186.6072 479.1744 Td[(th)1(e)-334(c)-1(omm)27(u)1(ni)1(c)-1(ation)-332(des)-1(crip)1(tor.)]TJ -10.9957 -11.9552 Td[(Scop)-27(e)-1(:)]TJ/F29 9.9626 Tf 27.9508 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf 23.0731 0 Td[(.)]TJ -51.0239 -11.9551 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 25.1834 0 Td[(required)]TJ/F8 9.9626 Tf 41.8983 0 Td[(.)]TJ -67.0817 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(in)]TJ/F8 9.9626 Tf 9.5475 0 Td[(.)]TJ -43.0331 -11.9552 Td[(Sp)-27(ec)-1(i\014)1(e)-1(d)-332(as)-1(:)-444(a)-333(s)-1(tr)1(uctured)-333(dat)1(a)-334(of)-333(t)28(yp)-27(e)]TJ +ET +1 0 0 1 346.5264 431.3538 cm +0 0 1 rg 0 0 1 RG +1 0 0 1 -346.5264 -431.3538 cm +BT +/F32 9.9626 Tf 346.5264 431.3538 Td[(psb)]TJ +ET +1 0 0 1 362.8451 431.3538 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +3.1382 0.1992 l +S +Q +1 0 0 1 -362.8451 -431.3538 cm +BT +/F32 9.9626 Tf 365.9833 431.3538 Td[(desc)]TJ +ET +1 0 0 1 387.5322 431.3538 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +3.1382 0.1992 l +S +Q +1 0 0 1 -387.5322 -431.3538 cm +BT +/F32 9.9626 Tf 390.6705 431.3538 Td[(type)]TJ +ET +1 0 0 1 411.5918 431.3538 cm +0 g 0 G +1 0 0 1 -411.5918 -431.3538 cm +BT +/F8 9.9626 Tf 411.5918 431.3538 Td[(.)]TJ +ET +1 0 0 1 145.7235 409.4359 cm +0 g 0 G +1 0 0 1 -145.7235 -409.4359 cm +BT +/F29 9.9626 Tf 150.7049 409.4359 Td[(On)-383(R)-1(etur)1(n)]TJ +ET +1 0 0 1 205.2431 409.4359 cm +0 g 0 G +1 0 0 1 -59.5196 -19.9252 cm +0 g 0 G +1 0 0 1 -145.7235 -389.5107 cm +BT +/F29 9.9626 Tf 150.7049 389.5107 Td[(F)96(unction)-384(v)64(alue)]TJ +ET +1 0 0 1 224.1097 389.5107 cm +0 g 0 G +1 0 0 1 -224.1097 -389.5107 cm +BT +/F8 9.9626 Tf 229.0911 389.5107 Td[(A)-264(logical)-265(mask)-265(whi)1(c)27(h)-264(is)-265(tr)1(ue)-265(if)]TJ/F11 9.9626 Tf 131.4924 0 Td[(x)]TJ/F8 9.9626 Tf 8.3288 0 Td[(is)-265(l)1(o)-28(c)-1(al)-264(to)-264(the)-265(cur)1(re)-1(n)29(t)-265(p)1(ro)-28(ce)-1(ss)]TJ -193.3008 -11.9552 Td[(Scop)-27(e)-1(:)]TJ/F29 9.9626 Tf 32.3786 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf -32.3786 -11.9552 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 29.6112 0 Td[(required)]TJ/F8 9.9626 Tf -29.6112 -11.9551 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(out)]TJ/F8 9.9626 Tf 16.549 0 Td[(.)]TJ/F18 14.3462 Tf -74.9412 -44.901 Td[(Not)-1(es)]TJ +ET +1 0 0 1 150.7049 286.9232 cm +0 g 0 G +1 0 0 1 -150.7049 -286.9232 cm +BT +/F8 9.9626 Tf 162.8814 286.9232 Td[(1.)]TJ +ET +1 0 0 1 170.6302 286.9232 cm +0 g 0 G +1 0 0 1 -170.6302 -286.9232 cm +BT +/F8 9.9626 Tf 175.6115 286.9232 Td[(This)-239(rou)1(tin)1(e)-240(r)1(e)-1(tu)1(rn)1(s)-240(a)]TJ/F32 9.9626 Tf 96.0565 0 Td[(.true.)]TJ/F8 9.9626 Tf 33.762 0 Td[(v)56(alue)-239(f)1(or)-239(an)-238(ind)1(e)-1(x)-238(that)-239(i)1(s)-240(lo)-27(c)-1(al)-239(t)1(o)-239(the)-239(c)-1(u)1(rr)1(e)-1(n)28(t)]TJ -129.8185 -11.9552 Td[(pr)1(o)-28(ce)-1(ss)-1(,)-333(in)1(c)-1(l)1(udi)1(ng)-333(the)-333(halo)-333(ind)1(ice)-1(s)]TJ +ET +1 0 0 1 150.7049 90.4377 cm +0 g 0 G +1 0 0 1 -150.7049 -90.4377 cm +BT +/F8 9.9626 Tf 317.5791 90.4377 Td[(84)]TJ +ET +1 0 0 1 494.4159 90.4377 cm +0 g 0 G +endstream +endobj +1280 0 obj << +/Type /Page +/Contents 1281 0 R +/Resources 1279 0 R +/MediaBox [0 0 595.2756 841.8898] +/Parent 1249 0 R +/Annots [ 1284 0 R ] +>> endobj +1284 0 obj << +/Type /Annot +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [345.5302 428.1436 412.5881 439.2685] +/Subtype /Link +/A << /S /GoTo /D (descdata) >> +>> endobj +1282 0 obj << +/D [1280 0 R /XYZ 150.7049 740.9981 null] +>> endobj +258 0 obj << +/D [1280 0 R /XYZ 150.7049 659.6006 null] +>> endobj +1283 0 obj << +/D [1280 0 R /XYZ 150.7049 631.8021 null] +>> endobj +1285 0 obj << +/D [1280 0 R /XYZ 150.7049 298.8784 null] +>> endobj +1286 0 obj << +/D [1280 0 R /XYZ 150.7049 302.8634 null] +>> endobj +1279 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R /F11 606 0 R >> +/ProcSet [ /PDF /Text ] +>> endobj +1289 0 obj << +/Length 7790 +>> +stream +1 0 0 1 99.8954 740.9981 cm +0 g 0 G +1 0 0 1 343.7111 0 cm +0 g 0 G +1 0 0 1 -348.6924 -60.7721 cm +0 g 0 G +0 g 0 G +1 0 0 1 -94.9141 -680.226 cm +BT +/F18 14.3462 Tf 99.8954 680.226 Td[(psb)]TJ +ET +1 0 0 1 125.1626 680.226 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +4.8419 0.1992 l +S +Q +1 0 0 1 -125.1626 -680.226 cm +BT +/F18 14.3462 Tf 130.0045 680.226 Td[(lo)-32(cal)]TJ +ET +1 0 0 1 163.4758 680.226 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +4.8419 0.1992 l +S +Q +1 0 0 1 -163.4758 -680.226 cm +BT +/F18 14.3462 Tf 168.3177 680.226 Td[(inde)-1(x|)]TJ -68.4223 -35.7686 Td[(Syn)32(t)-1(ax)]TJ/F8 9.9626 Tf 87.6343 -21.8209 Td[(call)-333(psb)]TJ +ET +1 0 0 1 221.3916 622.6364 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +2.9888 0.1992 l +S +Q +1 0 0 1 -221.3916 -622.6364 cm +BT +/F8 9.9626 Tf 224.3805 622.6364 Td[(lo)-28(cal)]TJ +ET +1 0 0 1 245.1803 622.6364 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +2.9888 0.1992 l +S +Q +1 0 0 1 -245.1803 -622.6364 cm +BT +/F8 9.9626 Tf 248.1691 622.6364 Td[(in)1(dex)-333(\050)]TJ/F19 9.9626 Tf 30.7182 0 Td[(y,)-357(x,)-357(desc)]TJ +ET +1 0 0 1 320.5275 622.6364 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +3.0552 0.1992 l +S +Q +1 0 0 1 -320.5275 -622.6364 cm +BT +/F19 9.9626 Tf 323.5827 622.6364 Td[(a,)-358(i)1(nfo)]TJ/F8 9.9626 Tf 28.5151 0 Td[(\051)]TJ +ET +1 0 0 1 94.9141 598.7261 cm +0 g 0 G +1 0 0 1 -94.9141 -598.7261 cm +BT +/F29 9.9626 Tf 99.8954 598.7261 Td[(T)32(yp)-32(e:)]TJ +ET +1 0 0 1 128.7108 598.7261 cm +0 g 0 G +1 0 0 1 -128.7108 -598.7261 cm +BT +/F8 9.9626 Tf 133.6921 598.7261 Td[(Async)28(hron)1(ous.)]TJ +ET +1 0 0 1 94.9141 578.8008 cm +0 g 0 G +1 0 0 1 -94.9141 -578.8008 cm +BT +/F29 9.9626 Tf 99.8954 578.8008 Td[(On)-383(En)32(tr)1(y)]TJ +ET +1 0 0 1 147.4806 578.8008 cm +0 g 0 G +1 0 0 1 -52.5665 -19.9253 cm +0 g 0 G +1 0 0 1 -94.9141 -558.8755 cm +BT +/F29 9.9626 Tf 99.8954 558.8755 Td[(x)]TJ +ET +1 0 0 1 105.9421 558.8755 cm +0 g 0 G +1 0 0 1 -105.9421 -558.8755 cm +BT +/F8 9.9626 Tf 110.9235 558.8755 Td[(In)28(tege)-1(r)-333(i)1(ndi)1(c)-1(es)-1(.)]TJ 13.8785 -11.9551 Td[(Scop)-27(e)-1(:)]TJ/F29 9.9626 Tf 32.3787 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf -32.3787 -11.9552 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 29.6112 0 Td[(required)]TJ/F8 9.9626 Tf -29.6112 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(in,)-384(i)-1(n)1(out)]TJ/F8 9.9626 Tf 42.6454 0 Td[(.)]TJ -76.131 -11.9551 Td[(Sp)-27(ec)-1(i\014)1(e)-1(d)-332(as)-1(:)-444(a)-333(s)-1(calar)-333(or)-333(a)-333(rank)-333(on)1(e)-334(in)28(tege)-1(r)-333(ar)1(ra)28(y)83(.)]TJ +ET +1 0 0 1 94.9141 479.1744 cm +0 g 0 G +1 0 0 1 -94.9141 -479.1744 cm +BT +/F29 9.9626 Tf 99.8954 479.1744 Td[(desc)]TJ +ET +1 0 0 1 121.81 479.1744 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +3.4371 0.1992 l +S +Q +1 0 0 1 -121.81 -479.1744 cm +BT +/F29 9.9626 Tf 125.2471 479.1744 Td[(a)]TJ +ET +1 0 0 1 130.8165 479.1744 cm +0 g 0 G +1 0 0 1 -130.8165 -479.1744 cm +BT +/F8 9.9626 Tf 135.7978 479.1744 Td[(th)1(e)-334(c)-1(omm)27(u)1(ni)1(c)-1(ation)-332(des)-1(crip)1(tor.)]TJ -10.9958 -11.9552 Td[(Scop)-27(e)-1(:)]TJ/F29 9.9626 Tf 27.9508 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf 23.0731 0 Td[(.)]TJ -51.0239 -11.9551 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 25.1834 0 Td[(required)]TJ/F8 9.9626 Tf 41.8983 0 Td[(.)]TJ -67.0817 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(in)]TJ/F8 9.9626 Tf 9.5475 0 Td[(.)]TJ -43.0331 -11.9552 Td[(Sp)-27(ec)-1(i\014)1(e)-1(d)-332(as)-1(:)-444(a)-333(s)-1(tr)1(uctured)-333(dat)1(a)-334(of)-333(t)28(yp)-27(e)]TJ +ET +1 0 0 1 295.717 431.3538 cm +0 0 1 rg 0 0 1 RG +1 0 0 1 -295.717 -431.3538 cm +BT +/F32 9.9626 Tf 295.717 431.3538 Td[(psb)]TJ +ET +1 0 0 1 312.0356 431.3538 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +3.1382 0.1992 l +S +Q +1 0 0 1 -312.0356 -431.3538 cm +BT +/F32 9.9626 Tf 315.1738 431.3538 Td[(desc)]TJ +ET +1 0 0 1 336.7228 431.3538 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +3.1382 0.1992 l +S +Q +1 0 0 1 -336.7228 -431.3538 cm +BT +/F32 9.9626 Tf 339.861 431.3538 Td[(type)]TJ +ET +1 0 0 1 360.7824 431.3538 cm +0 g 0 G +1 0 0 1 -360.7824 -431.3538 cm +BT +/F8 9.9626 Tf 360.7824 431.3538 Td[(.)]TJ +ET +1 0 0 1 94.9141 411.4285 cm +0 g 0 G +1 0 0 1 -94.9141 -411.4285 cm +BT +/F29 9.9626 Tf 99.8954 411.4285 Td[(iac)-1(t)]TJ +ET +1 0 0 1 118.1947 411.4285 cm +0 g 0 G +1 0 0 1 -118.1947 -411.4285 cm +BT +/F8 9.9626 Tf 123.176 411.4285 Td[(sp)-28(ec)-1(i)1(\014es)-334(ac)-1(ti)1(on)-333(to)-333(b)-28(e)-334(t)1(ak)28(e)-1(n)-333(in)-333(case)-334(of)-333(ran)1(ge)-334(e)-1(r)1(rors.)-444(Scop)-28(e:)]TJ/F29 9.9626 Tf 257.1472 0 Td[(global)]TJ/F8 9.9626 Tf -255.5212 -11.9552 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 29.6112 0 Td[(opti)-1(on)1(al)]TJ/F8 9.9626 Tf -29.6112 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(in)]TJ/F8 9.9626 Tf 9.5475 0 Td[(.)]TJ -43.0331 -11.9551 Td[(Sp)-27(ec)-1(i\014)1(e)-1(d)-254(as)-1(:)-405(a)-255(c)27(h)1(aracte)-1(r)-255(v)56(ari)1(able)]TJ/F32 9.9626 Tf 143.584 0 Td[(I)]TJ/F8 9.9626 Tf 5.2303 0 Td[(gnor)1(e)-1(,)]TJ/F32 9.9626 Tf 29.2928 0 Td[(W)]TJ/F8 9.9626 Tf 5.2304 0 Td[(arn)1(ing)-255(or)]TJ/F32 9.9626 Tf 41.6697 0 Td[(A)]TJ/F8 9.9626 Tf 5.2303 0 Td[(b)-27(ort,)-270(de)-1(f)1(aul)1(t)]TJ/F32 9.9626 Tf 56.7418 0 Td[(I)]TJ/F8 9.9626 Tf 5.2304 0 Td[(gnor)1(e)-1(.)]TJ +ET +1 0 0 1 94.9141 353.6452 cm +0 g 0 G +1 0 0 1 -94.9141 -353.6452 cm +BT +/F29 9.9626 Tf 99.8954 353.6452 Td[(On)-383(R)-1(etur)1(n)]TJ +ET +1 0 0 1 154.4337 353.6452 cm +0 g 0 G +1 0 0 1 -59.5196 -19.9253 cm +0 g 0 G +1 0 0 1 -94.9141 -333.7199 cm +BT +/F29 9.9626 Tf 99.8954 333.7199 Td[(y)]TJ +ET +1 0 0 1 105.9421 333.7199 cm +0 g 0 G +1 0 0 1 -105.9421 -333.7199 cm +BT +/F8 9.9626 Tf 110.9235 333.7199 Td[(A)-346(l)1(ogic)-1(al)-345(mas)-1(k)-345(whic)28(h)-345(is)-346(tru)1(e)-346(for)-345(all)-345(c)-1(orr)1(e)-1(sp)-27(ondi)1(ng)-345(e)-1(n)28(tr)1(ies)-346(of)]TJ/F11 9.9626 Tf 264.8821 0 Td[(x)]TJ/F8 9.9626 Tf 9.1369 0 Td[(th)1(at)-346(are)-346(l)1(o)-28(c)-1(al)]TJ -260.1405 -11.9552 Td[(to)-333(the)-333(c)-1(u)1(rren)28(t)-333(pr)1(o)-28(c)-1(es)-1(s)-333(Scop)-28(e:)]TJ/F29 9.9626 Tf 131.0919 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf -131.0919 -11.9551 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 29.6112 0 Td[(required)]TJ/F8 9.9626 Tf -29.6112 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(out)]TJ/F8 9.9626 Tf 16.549 0 Td[(.)]TJ -50.0346 -11.9552 Td[(Sp)-27(ec)-1(i\014)1(e)-1(d)-332(as)-1(:)-444(a)-333(s)-1(calar)-333(or)-333(ran)1(k)-334(on)1(e)-334(logi)1(c)-1(al)-333(arr)1(a)27(y)84(.)]TJ +ET +1 0 0 1 94.9141 265.9739 cm +0 g 0 G +1 0 0 1 -94.9141 -265.9739 cm +BT +/F29 9.9626 Tf 99.8954 265.9739 Td[(inf)-1(o)]TJ +ET +1 0 0 1 118.6721 265.9739 cm +0 g 0 G +1 0 0 1 -118.6721 -265.9739 cm +BT +/F8 9.9626 Tf 123.6534 265.9739 Td[(Er)1(ror)-333(co)-28(de.)]TJ 1.1486 -11.9552 Td[(Scop)-27(e)-1(:)]TJ/F29 9.9626 Tf 32.3787 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf -32.3787 -11.9551 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 29.6112 0 Td[(required)]TJ/F8 9.9626 Tf -29.6112 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(out)]TJ/F8 9.9626 Tf 16.549 0 Td[(.)]TJ -50.0346 -11.9552 Td[(An)-333(in)29(te)-1(ger)-333(v)56(alue;)-333(0)-334(means)-334(n)1(o)-334(error)-333(h)1(as)-334(b)-27(e)-1(en)-333(detec)-1(ted.)]TJ/F18 14.3462 Tf -24.9066 -32.9458 Td[(Not)-1(es)]TJ +ET +1 0 0 1 99.8954 163.3865 cm +0 g 0 G +1 0 0 1 -99.8954 -163.3865 cm +BT +/F8 9.9626 Tf 112.072 163.3865 Td[(1.)]TJ +ET +1 0 0 1 119.8207 163.3865 cm +0 g 0 G +1 0 0 1 -119.8207 -163.3865 cm +BT +/F8 9.9626 Tf 124.802 163.3865 Td[(This)-308(rout)1(ine)-309(r)1(e)-1(tu)1(rn)1(s)-309(a)]TJ/F32 9.9626 Tf 98.8239 0 Td[(.true.)]TJ/F8 9.9626 Tf 34.4539 0 Td[(v)56(alue)-308(for)-308(th)1(os)-1(e)-309(i)1(nd)1(ic)-1(es)-309(th)1(at)-309(ar)1(e)-309(lo)-28(cal)-308(to)-308(the)]TJ -133.2778 -11.9552 Td[(curr)1(e)-1(n)28(t)-333(p)1(ro)-28(ce)-1(ss)-1(,)-333(i)1(nclud)1(ing)-333(the)-333(halo)-333(in)1(dice)-1(s.)]TJ +ET +1 0 0 1 99.8954 90.4377 cm +0 g 0 G +1 0 0 1 -99.8954 -90.4377 cm +BT +/F8 9.9626 Tf 266.7696 90.4377 Td[(85)]TJ +ET +1 0 0 1 443.6065 90.4377 cm +0 g 0 G +endstream +endobj +1288 0 obj << +/Type /Page +/Contents 1289 0 R +/Resources 1287 0 R +/MediaBox [0 0 595.2756 841.8898] +/Parent 1295 0 R +/Annots [ 1292 0 R ] +>> endobj +1292 0 obj << +/Type /Annot +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [294.7207 428.1436 361.7786 439.2685] +/Subtype /Link +/A << /S /GoTo /D (descdata) >> +>> endobj +1290 0 obj << +/D [1288 0 R /XYZ 99.8954 740.9981 null] +>> endobj +262 0 obj << +/D [1288 0 R /XYZ 99.8954 659.6006 null] +>> endobj +1291 0 obj << +/D [1288 0 R /XYZ 99.8954 631.8021 null] +>> endobj +1293 0 obj << +/D [1288 0 R /XYZ 99.8954 175.3416 null] +>> endobj +1294 0 obj << +/D [1288 0 R /XYZ 99.8954 179.3267 null] +>> endobj +1287 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R /F11 606 0 R >> +/ProcSet [ /PDF /Text ] +>> endobj +1298 0 obj << +/Length 6286 +>> +stream +1 0 0 1 150.7049 740.9981 cm +0 g 0 G +1 0 0 1 343.7111 0 cm +0 g 0 G +1 0 0 1 -348.6924 -60.7721 cm +0 g 0 G +0 g 0 G +1 0 0 1 -145.7236 -680.226 cm +BT +/F18 14.3462 Tf 150.7049 680.226 Td[(psb)]TJ +ET +1 0 0 1 175.972 680.226 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +4.8419 0.1992 l +S +Q +1 0 0 1 -175.972 -680.226 cm +BT +/F18 14.3462 Tf 180.8139 680.226 Td[(g)-1(et)]TJ +ET +1 0 0 1 203.4925 680.226 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +4.8419 0.1992 l +S +Q +1 0 0 1 -203.4925 -680.226 cm +BT +/F18 14.3462 Tf 208.3343 680.226 Td[(b)-31(o)-1(undary|Ext)-1(ract)-375(l)-1(ist)-376(of)-375(b)-31(o)-1(undary)]TJ -57.6294 -17.9328 Td[(el)-1(em)-1(en)31(ts)]TJ 0 -35.7686 Td[(Syn)32(t)-1(ax)]TJ/F8 9.9626 Tf 83.3016 -21.8209 Td[(call)-333(psb)]TJ +ET +1 0 0 1 267.8684 604.7037 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +2.9888 0.1992 l +S +Q +1 0 0 1 -267.8684 -604.7037 cm +BT +/F8 9.9626 Tf 270.8572 604.7037 Td[(get)]TJ +ET +1 0 0 1 284.7385 604.7037 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +2.9888 0.1992 l +S +Q +1 0 0 1 -284.7385 -604.7037 cm +BT +/F8 9.9626 Tf 287.7273 604.7037 Td[(b)-27(oun)1(dary)-333(\050)]TJ/F19 9.9626 Tf 48.7341 0 Td[(bndel,)-357(desc,)-358(i)1(n)-1(f)1(o)]TJ/F8 9.9626 Tf 70.7786 0 Td[(\051)]TJ +ET +1 0 0 1 145.7235 580.7934 cm +0 g 0 G +1 0 0 1 -145.7235 -580.7934 cm +BT +/F29 9.9626 Tf 150.7049 580.7934 Td[(T)32(yp)-32(e:)]TJ +ET +1 0 0 1 179.5203 580.7934 cm +0 g 0 G +1 0 0 1 -179.5203 -580.7934 cm +BT +/F8 9.9626 Tf 184.5016 580.7934 Td[(Async)28(hron)1(ous.)]TJ +ET +1 0 0 1 145.7235 560.8681 cm +0 g 0 G +1 0 0 1 -145.7235 -560.8681 cm +BT +/F29 9.9626 Tf 150.7049 560.8681 Td[(On)-383(En)32(tr)1(y)]TJ +ET +1 0 0 1 198.2901 560.8681 cm +0 g 0 G +1 0 0 1 -52.5665 -19.9253 cm +0 g 0 G +1 0 0 1 -145.7236 -540.9428 cm +BT +/F29 9.9626 Tf 150.7049 540.9428 Td[(desc)]TJ +ET +1 0 0 1 171.9321 540.9428 cm +0 g 0 G +1 0 0 1 -171.9321 -540.9428 cm +BT +/F8 9.9626 Tf 176.9134 540.9428 Td[(th)1(e)-334(c)-1(omm)27(u)1(ni)1(c)-1(ation)-332(des)-1(crip)1(tor.)]TJ -1.3019 -11.9552 Td[(Scop)-27(e)-1(:)]TJ/F29 9.9626 Tf 27.9508 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf 23.0731 0 Td[(.)]TJ -51.0239 -11.9551 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 25.1834 0 Td[(required)]TJ/F8 9.9626 Tf 41.8983 0 Td[(.)]TJ -67.0817 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(in)]TJ/F8 9.9626 Tf 9.5475 0 Td[(.)]TJ -43.0331 -11.9552 Td[(Sp)-27(ec)-1(i\014)1(e)-1(d)-332(as)-1(:)-444(a)-333(s)-1(tr)1(uctured)-333(dat)1(a)-334(of)-333(t)28(yp)-27(e)]TJ +ET +1 0 0 1 346.5264 493.1221 cm +0 0 1 rg 0 0 1 RG +1 0 0 1 -346.5264 -493.1221 cm +BT +/F32 9.9626 Tf 346.5264 493.1221 Td[(psb)]TJ +ET +1 0 0 1 362.8451 493.1221 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +3.1382 0.1992 l +S +Q +1 0 0 1 -362.8451 -493.1221 cm +BT +/F32 9.9626 Tf 365.9833 493.1221 Td[(desc)]TJ +ET +1 0 0 1 387.5322 493.1221 cm +q +[]0 d +0 J +0.3985 w +0 0.1992 m +3.1382 0.1992 l +S +Q +1 0 0 1 -387.5322 -493.1221 cm +BT +/F32 9.9626 Tf 390.6705 493.1221 Td[(type)]TJ +ET +1 0 0 1 411.5918 493.1221 cm +0 g 0 G +1 0 0 1 -411.5918 -493.1221 cm +BT +/F8 9.9626 Tf 411.5918 493.1221 Td[(.)]TJ +ET +1 0 0 1 145.7235 471.2043 cm +0 g 0 G +1 0 0 1 -145.7235 -471.2043 cm +BT +/F29 9.9626 Tf 150.7049 471.2043 Td[(On)-383(R)-1(etur)1(n)]TJ +ET +1 0 0 1 205.2431 471.2043 cm +0 g 0 G +1 0 0 1 -59.5196 -19.9253 cm +0 g 0 G +1 0 0 1 -145.7235 -451.279 cm +BT +/F29 9.9626 Tf 150.7049 451.279 Td[(bndel)]TJ +ET +1 0 0 1 178.2334 451.279 cm +0 g 0 G +1 0 0 1 -178.2334 -451.279 cm +BT +/F8 9.9626 Tf 183.2148 451.279 Td[(The)-268(li)1(s)-1(t)-267(of)-267(b)-28(ou)1(nd)1(ary)-267(e)-1(leme)-1(n)28(t)1(s)-268(on)-268(t)1(he)-268(callin)1(g)-268(p)1(ro)-28(ce)-1(ss)-1(,)-280(in)-267(lo)-28(cal)-267(n)28(um)28(b)-28(erin)1(g.)]TJ -7.6033 -11.9552 Td[(Scop)-27(e)-1(:)]TJ/F29 9.9626 Tf 32.3786 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf -32.3786 -11.9551 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 29.6112 0 Td[(required)]TJ/F8 9.9626 Tf -29.6112 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(out)]TJ/F8 9.9626 Tf 16.549 0 Td[(.)]TJ -50.0346 -11.9552 Td[(Sp)-27(ec)-1(i\014)1(e)-1(d)-456(as:)-691(a)-456(rank)-456(on)1(e)-457(arra)28(y)-456(w)-1(i)1(th)-456(the)-457(ALLOCA)84(T)83(AB)-1(LE)-456(att)1(ribu)1(te,)-488(of)]TJ 0 -11.9551 Td[(t)28(yp)-27(e)-334(in)28(t)1(e)-1(ger.)]TJ +ET +1 0 0 1 145.7235 359.6227 cm +0 g 0 G +1 0 0 1 -145.7235 -359.6227 cm +BT +/F29 9.9626 Tf 150.7049 359.6227 Td[(inf)-1(o)]TJ +ET +1 0 0 1 169.4816 359.6227 cm +0 g 0 G +1 0 0 1 -169.4816 -359.6227 cm +BT +/F8 9.9626 Tf 174.4629 359.6227 Td[(Er)1(ror)-333(co)-28(de.)]TJ 1.1486 -11.9552 Td[(Scop)-27(e)-1(:)]TJ/F29 9.9626 Tf 32.3786 0 Td[(lo)-32(ca)-1(l)]TJ/F8 9.9626 Tf -32.3786 -11.9551 Td[(T)28(yp)-28(e:)]TJ/F29 9.9626 Tf 29.6112 0 Td[(required)]TJ/F8 9.9626 Tf -29.6112 -11.9552 Td[(In)28(ten)28(t:)]TJ/F29 9.9626 Tf 33.4856 0 Td[(out)]TJ/F8 9.9626 Tf 16.549 0 Td[(.)]TJ -50.0346 -11.9552 Td[(An)-333(in)29(te)-1(ger)-333(v)56(alue;)-333(0)-334(means)-334(n)1(o)-334(error)-333(h)1(as)-334(b)-27(e)-1(en)-333(detec)-1(ted.)]TJ/F18 14.3462 Tf -24.9066 -32.9458 Td[(Not)-1(es)]TJ +ET +1 0 0 1 150.7049 257.0353 cm +0 g 0 G +1 0 0 1 -150.7049 -257.0353 cm +BT +/F8 9.9626 Tf 162.8814 257.0353 Td[(1.)]TJ +ET +1 0 0 1 170.6302 257.0353 cm +0 g 0 G +1 0 0 1 -170.6302 -257.0353 cm +BT +/F8 9.9626 Tf 175.6115 257.0353 Td[(If)-269(th)1(e)-1(r)1(e)-270(are)-269(no)-269(b)-27(oun)1(dar)1(y)-269(e)-1(leme)-1(n)28(t)1(s)-270(\050i.)1(e)-1(.,)-281(if)-269(th)1(e)-270(lo)-27(c)-1(al)-269(p)1(art)-269(of)-269(t)1(he)-270(conn)1(e)-1(ctiv)1(it)28(y)]TJ 0 -11.9552 Td[(grap)1(h)-449(is)-450(se)-1(lf)1(-)-1(con)28(tai)1(ned\051)-449(the)-450(ou)1(tpu)1(t)-450(v)28(ec)-1(tor)-449(i)1(s)-450(s)-1(et)-450(to)-449(the)-449(\134not)-449(allo)-28(cate)-1(d)1(")]TJ 0 -11.9551 Td[(state)-1(.)]TJ +ET +1 0 0 1 150.7049 213.1997 cm +0 g 0 G +1 0 0 1 -150.7049 -213.1997 cm +BT +/F8 9.9626 Tf 162.8814 213.1997 Td[(2.)]TJ +ET +1 0 0 1 170.6302 213.1997 cm +0 g 0 G +1 0 0 1 -170.6302 -213.1997 cm +BT +/F8 9.9626 Tf 175.6115 213.1997 Td[(Oth)1(e)-1(r)1(w)-1(i)1(s)-1(e)-288(the)-289(size)-289(of)]TJ/F32 9.9626 Tf 92.71 0 Td[(bndel)]TJ/F8 9.9626 Tf 29.0234 0 Td[(will)-288(b)-27(e)-289(exac)-1(t)1(ly)-288(e)-1(q)1(ual)-288(to)-288(the)-288(n)28(um)28(b)-28(er)-288(of)-288(b)-27(oun)1(d-)]TJ -121.7334 -11.9552 Td[(ary)-333(elem)-1(en)28(ts.)]TJ +ET +1 0 0 1 150.7049 90.4377 cm +0 g 0 G +1 0 0 1 -150.7049 -90.4377 cm +BT +/F8 9.9626 Tf 317.5791 90.4377 Td[(86)]TJ +ET +1 0 0 1 494.4159 90.4377 cm +0 g 0 G +endstream +endobj +1297 0 obj << +/Type /Page +/Contents 1298 0 R +/Resources 1296 0 R +/MediaBox [0 0 595.2756 841.8898] +/Parent 1295 0 R +/Annots [ 1301 0 R ] +>> endobj +1301 0 obj << +/Type /Annot +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [345.5302 489.9119 412.5881 501.0369] +/Subtype /Link +/A << /S /GoTo /D (descdata) >> +>> endobj +1299 0 obj << +/D [1297 0 R /XYZ 150.7049 740.9981 null] +>> endobj +266 0 obj << +/D [1297 0 R /XYZ 150.7049 644.4574 null] +>> endobj +1300 0 obj << +/D [1297 0 R /XYZ 150.7049 613.8693 null] +>> endobj +1302 0 obj << +/D [1297 0 R /XYZ 150.7049 268.9905 null] +>> endobj +1303 0 obj << +/D [1297 0 R /XYZ 150.7049 272.9755 null] +>> endobj +1304 0 obj << +/D [1297 0 R /XYZ 150.7049 229.1399 null] +>> endobj +1296 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> +/ProcSet [ /PDF /Text ] +>> endobj +1307 0 obj << +/Length 6045 >> stream 1 0 0 1 99.8954 740.9981 cm @@ -24970,50 +26258,50 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 266.7696 90.4377 Td[(83)]TJ +/F8 9.9626 Tf 266.7696 90.4377 Td[(87)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1253 0 obj << +1306 0 obj << /Type /Page -/Contents 1254 0 R -/Resources 1252 0 R +/Contents 1307 0 R +/Resources 1305 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1229 0 R -/Annots [ 1257 0 R ] +/Parent 1295 0 R +/Annots [ 1310 0 R ] >> endobj -1257 0 obj << +1310 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 507.8447 361.7786 518.9696] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1255 0 obj << -/D [1253 0 R /XYZ 99.8954 740.9981 null] +1308 0 obj << +/D [1306 0 R /XYZ 99.8954 740.9981 null] >> endobj -254 0 obj << -/D [1253 0 R /XYZ 99.8954 659.6006 null] +270 0 obj << +/D [1306 0 R /XYZ 99.8954 659.6006 null] >> endobj -1256 0 obj << -/D [1253 0 R /XYZ 99.8954 631.8021 null] +1309 0 obj << +/D [1306 0 R /XYZ 99.8954 631.8021 null] >> endobj -1258 0 obj << -/D [1253 0 R /XYZ 99.8954 286.9232 null] +1311 0 obj << +/D [1306 0 R /XYZ 99.8954 286.9232 null] >> endobj -1259 0 obj << -/D [1253 0 R /XYZ 99.8954 290.9083 null] +1312 0 obj << +/D [1306 0 R /XYZ 99.8954 290.9083 null] >> endobj -1260 0 obj << -/D [1253 0 R /XYZ 99.8954 259.0278 null] +1313 0 obj << +/D [1306 0 R /XYZ 99.8954 259.0278 null] >> endobj -1252 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +1305 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1263 0 obj << +1316 0 obj << /Length 7755 >> stream @@ -25222,41 +26510,41 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 317.5791 90.4377 Td[(84)]TJ +/F8 9.9626 Tf 317.5791 90.4377 Td[(88)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1262 0 obj << +1315 0 obj << /Type /Page -/Contents 1263 0 R -/Resources 1261 0 R +/Contents 1316 0 R +/Resources 1314 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1229 0 R -/Annots [ 1266 0 R ] +/Parent 1295 0 R +/Annots [ 1319 0 R ] >> endobj -1266 0 obj << +1319 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 422.0626 417.8184 433.1876] /Subtype /Link /A << /S /GoTo /D (spdata) >> >> endobj -1264 0 obj << -/D [1262 0 R /XYZ 150.7049 740.9981 null] +1317 0 obj << +/D [1315 0 R /XYZ 150.7049 740.9981 null] >> endobj -258 0 obj << -/D [1262 0 R /XYZ 150.7049 644.4247 null] +274 0 obj << +/D [1315 0 R /XYZ 150.7049 644.4247 null] >> endobj -1265 0 obj << -/D [1262 0 R /XYZ 150.7049 613.8278 null] +1318 0 obj << +/D [1315 0 R /XYZ 150.7049 613.8278 null] >> endobj -1261 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F11 586 0 R /F32 602 0 R >> +1314 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F11 606 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1269 0 obj << +1322 0 obj << /Length 6015 >> stream @@ -25352,39 +26640,39 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 266.7696 90.4377 Td[(85)]TJ +/F8 9.9626 Tf 266.7696 90.4377 Td[(89)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1268 0 obj << +1321 0 obj << /Type /Page -/Contents 1269 0 R -/Resources 1267 0 R +/Contents 1322 0 R +/Resources 1320 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1275 0 R +/Parent 1295 0 R >> endobj -1270 0 obj << -/D [1268 0 R /XYZ 99.8954 740.9981 null] +1323 0 obj << +/D [1321 0 R /XYZ 99.8954 740.9981 null] >> endobj -1271 0 obj << -/D [1268 0 R /XYZ 99.8954 412.2587 null] +1324 0 obj << +/D [1321 0 R /XYZ 99.8954 412.2587 null] >> endobj -1272 0 obj << -/D [1268 0 R /XYZ 99.8954 416.2438 null] +1325 0 obj << +/D [1321 0 R /XYZ 99.8954 416.2438 null] >> endobj -1273 0 obj << -/D [1268 0 R /XYZ 99.8954 358.5158 null] +1326 0 obj << +/D [1321 0 R /XYZ 99.8954 358.5158 null] >> endobj -1274 0 obj << -/D [1268 0 R /XYZ 99.8954 338.3138 null] +1327 0 obj << +/D [1321 0 R /XYZ 99.8954 338.3138 null] >> endobj -1267 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F32 602 0 R /F18 425 0 R /F11 586 0 R >> +1320 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F32 622 0 R /F18 441 0 R /F11 606 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1278 0 obj << +1330 0 obj << /Length 7133 >> stream @@ -25671,55 +26959,55 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 317.5791 90.4377 Td[(86)]TJ +/F8 9.9626 Tf 317.5791 90.4377 Td[(90)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1277 0 obj << +1329 0 obj << /Type /Page -/Contents 1278 0 R -/Resources 1276 0 R +/Contents 1330 0 R +/Resources 1328 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1275 0 R -/Annots [ 1281 0 R 1282 0 R 1283 0 R ] +/Parent 1295 0 R +/Annots [ 1333 0 R 1334 0 R 1335 0 R ] >> endobj -1281 0 obj << +1333 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 433.0557 417.8184 444.1807] /Subtype /Link /A << /S /GoTo /D (spdata) >> >> endobj -1282 0 obj << +1334 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 365.3098 412.5881 376.4347] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1283 0 obj << +1335 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [372.1526 309.519 439.2105 320.644] /Subtype /Link /A << /S /GoTo /D (precdata) >> >> endobj -1279 0 obj << -/D [1277 0 R /XYZ 150.7049 740.9981 null] +1331 0 obj << +/D [1329 0 R /XYZ 150.7049 740.9981 null] >> endobj -262 0 obj << -/D [1277 0 R /XYZ 150.7049 659.6006 null] +278 0 obj << +/D [1329 0 R /XYZ 150.7049 659.6006 null] >> endobj -1280 0 obj << -/D [1277 0 R /XYZ 150.7049 604.8338 null] +1332 0 obj << +/D [1329 0 R /XYZ 150.7049 604.8338 null] >> endobj -1276 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F11 586 0 R /F32 602 0 R >> +1328 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F11 606 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1286 0 obj << +1338 0 obj << /Length 6745 >> stream @@ -25905,42 +27193,42 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 266.7696 90.4377 Td[(87)]TJ +/F8 9.9626 Tf 266.7696 90.4377 Td[(91)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1285 0 obj << +1337 0 obj << /Type /Page -/Contents 1286 0 R -/Resources 1284 0 R +/Contents 1338 0 R +/Resources 1336 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1275 0 R +/Parent 1341 0 R >> endobj -1287 0 obj << -/D [1285 0 R /XYZ 99.8954 740.9981 null] +1339 0 obj << +/D [1337 0 R /XYZ 99.8954 740.9981 null] >> endobj -266 0 obj << -/D [1285 0 R /XYZ 99.8954 658.9845 null] +282 0 obj << +/D [1337 0 R /XYZ 99.8954 658.9845 null] >> endobj -270 0 obj << -/D [1285 0 R /XYZ 99.8954 604.8466 null] +286 0 obj << +/D [1337 0 R /XYZ 99.8954 604.8466 null] >> endobj -274 0 obj << -/D [1285 0 R /XYZ 99.8954 550.7087 null] +290 0 obj << +/D [1337 0 R /XYZ 99.8954 550.7087 null] >> endobj -278 0 obj << -/D [1285 0 R /XYZ 99.8954 496.5708 null] +294 0 obj << +/D [1337 0 R /XYZ 99.8954 496.5708 null] >> endobj -1288 0 obj << -/D [1285 0 R /XYZ 99.8954 468.6051 null] +1340 0 obj << +/D [1337 0 R /XYZ 99.8954 468.6051 null] >> endobj -1284 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F11 586 0 R /F29 431 0 R /F32 602 0 R >> +1336 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F11 606 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1291 0 obj << +1344 0 obj << /Length 10893 >> stream @@ -26184,54 +27472,54 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 317.5791 90.4377 Td[(88)]TJ +/F8 9.9626 Tf 317.5791 90.4377 Td[(92)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1290 0 obj << +1343 0 obj << /Type /Page -/Contents 1291 0 R -/Resources 1289 0 R +/Contents 1344 0 R +/Resources 1342 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1275 0 R +/Parent 1341 0 R >> endobj -1292 0 obj << -/D [1290 0 R /XYZ 150.7049 740.9981 null] +1345 0 obj << +/D [1343 0 R /XYZ 150.7049 740.9981 null] >> endobj -1293 0 obj << -/D [1290 0 R /XYZ 150.7049 560.9013 null] +1346 0 obj << +/D [1343 0 R /XYZ 150.7049 560.9013 null] >> endobj -1294 0 obj << -/D [1290 0 R /XYZ 150.7049 564.8864 null] +1347 0 obj << +/D [1343 0 R /XYZ 150.7049 564.8864 null] >> endobj -1295 0 obj << -/D [1290 0 R /XYZ 150.7049 521.9031 null] +1348 0 obj << +/D [1343 0 R /XYZ 150.7049 521.9031 null] >> endobj -1296 0 obj << -/D [1290 0 R /XYZ 150.7049 466.1123 null] +1349 0 obj << +/D [1343 0 R /XYZ 150.7049 466.1123 null] >> endobj -1297 0 obj << -/D [1290 0 R /XYZ 150.7049 410.3215 null] +1350 0 obj << +/D [1343 0 R /XYZ 150.7049 410.3215 null] >> endobj -1298 0 obj << -/D [1290 0 R /XYZ 150.7049 377.8876 null] +1351 0 obj << +/D [1343 0 R /XYZ 150.7049 377.8876 null] >> endobj -1299 0 obj << -/D [1290 0 R /XYZ 150.7049 334.5501 null] +1352 0 obj << +/D [1343 0 R /XYZ 150.7049 334.5501 null] >> endobj -1300 0 obj << -/D [1290 0 R /XYZ 150.7049 292.7624 null] +1353 0 obj << +/D [1343 0 R /XYZ 150.7049 292.7624 null] >> endobj -1301 0 obj << -/D [1290 0 R /XYZ 150.7049 264.867 null] +1354 0 obj << +/D [1343 0 R /XYZ 150.7049 264.867 null] >> endobj -1289 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F11 586 0 R /F18 425 0 R /F14 613 0 R /F7 607 0 R >> +1342 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F11 606 0 R /F18 441 0 R /F14 633 0 R /F7 627 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1304 0 obj << +1357 0 obj << /Length 372 >> stream @@ -26247,30 +27535,30 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 266.7696 90.4377 Td[(89)]TJ +/F8 9.9626 Tf 266.7696 90.4377 Td[(93)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1303 0 obj << +1356 0 obj << /Type /Page -/Contents 1304 0 R -/Resources 1302 0 R +/Contents 1357 0 R +/Resources 1355 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1275 0 R +/Parent 1341 0 R >> endobj -1305 0 obj << -/D [1303 0 R /XYZ 99.8954 740.9981 null] +1358 0 obj << +/D [1356 0 R /XYZ 99.8954 740.9981 null] >> endobj -282 0 obj << -/D [1303 0 R /XYZ 99.8954 716.0915 null] +298 0 obj << +/D [1356 0 R /XYZ 99.8954 716.0915 null] >> endobj -1302 0 obj << -/Font << /F18 425 0 R /F8 434 0 R >> +1355 0 obj << +/Font << /F18 441 0 R /F8 450 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1308 0 obj << +1361 0 obj << /Length 4965 >> stream @@ -26391,42 +27679,42 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 317.5791 90.4377 Td[(90)]TJ +/F8 9.9626 Tf 317.5791 90.4377 Td[(94)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1307 0 obj << +1360 0 obj << /Type /Page -/Contents 1308 0 R -/Resources 1306 0 R +/Contents 1361 0 R +/Resources 1359 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1275 0 R +/Parent 1341 0 R >> endobj -1309 0 obj << -/D [1307 0 R /XYZ 150.7049 740.9981 null] +1362 0 obj << +/D [1360 0 R /XYZ 150.7049 740.9981 null] >> endobj -286 0 obj << -/D [1307 0 R /XYZ 150.7049 644.4574 null] +302 0 obj << +/D [1360 0 R /XYZ 150.7049 644.4574 null] >> endobj -1310 0 obj << -/D [1307 0 R /XYZ 150.7049 613.8693 null] +1363 0 obj << +/D [1360 0 R /XYZ 150.7049 613.8693 null] >> endobj -1311 0 obj << -/D [1307 0 R /XYZ 150.7049 316.8111 null] +1364 0 obj << +/D [1360 0 R /XYZ 150.7049 316.8111 null] >> endobj -1312 0 obj << -/D [1307 0 R /XYZ 150.7049 320.7962 null] +1365 0 obj << +/D [1360 0 R /XYZ 150.7049 320.7962 null] >> endobj -1313 0 obj << -/D [1307 0 R /XYZ 150.7049 298.9337 null] +1366 0 obj << +/D [1360 0 R /XYZ 150.7049 298.9337 null] >> endobj -1306 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F11 586 0 R >> +1359 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F11 606 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1316 0 obj << +1369 0 obj << /Length 6763 >> stream @@ -26559,42 +27847,42 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 266.7696 90.4377 Td[(91)]TJ +/F8 9.9626 Tf 266.7696 90.4377 Td[(95)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1315 0 obj << +1368 0 obj << /Type /Page -/Contents 1316 0 R -/Resources 1314 0 R +/Contents 1369 0 R +/Resources 1367 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1322 0 R +/Parent 1341 0 R >> endobj -1317 0 obj << -/D [1315 0 R /XYZ 99.8954 740.9981 null] +1370 0 obj << +/D [1368 0 R /XYZ 99.8954 740.9981 null] >> endobj -290 0 obj << -/D [1315 0 R /XYZ 99.8954 641.6678 null] +306 0 obj << +/D [1368 0 R /XYZ 99.8954 641.6678 null] >> endobj -1318 0 obj << -/D [1315 0 R /XYZ 99.8954 613.8693 null] +1371 0 obj << +/D [1368 0 R /XYZ 99.8954 613.8693 null] >> endobj -1319 0 obj << -/D [1315 0 R /XYZ 99.8954 261.0203 null] +1372 0 obj << +/D [1368 0 R /XYZ 99.8954 261.0203 null] >> endobj -1320 0 obj << -/D [1315 0 R /XYZ 99.8954 265.0054 null] +1373 0 obj << +/D [1368 0 R /XYZ 99.8954 265.0054 null] >> endobj -1321 0 obj << -/D [1315 0 R /XYZ 99.8954 231.1878 null] +1374 0 obj << +/D [1368 0 R /XYZ 99.8954 231.1878 null] >> endobj -1314 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F14 613 0 R /F11 586 0 R /F32 602 0 R >> +1367 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F14 633 0 R /F11 606 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1325 0 obj << +1377 0 obj << /Length 6733 >> stream @@ -26732,45 +28020,45 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 317.5791 90.4377 Td[(92)]TJ +/F8 9.9626 Tf 317.5791 90.4377 Td[(96)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1324 0 obj << +1376 0 obj << /Type /Page -/Contents 1325 0 R -/Resources 1323 0 R +/Contents 1377 0 R +/Resources 1375 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1322 0 R +/Parent 1341 0 R >> endobj -1326 0 obj << -/D [1324 0 R /XYZ 150.7049 740.9981 null] +1378 0 obj << +/D [1376 0 R /XYZ 150.7049 740.9981 null] >> endobj -294 0 obj << -/D [1324 0 R /XYZ 150.7049 644.4574 null] +310 0 obj << +/D [1376 0 R /XYZ 150.7049 644.4574 null] >> endobj -1327 0 obj << -/D [1324 0 R /XYZ 150.7049 613.8693 null] +1379 0 obj << +/D [1376 0 R /XYZ 150.7049 613.8693 null] >> endobj -1328 0 obj << -/D [1324 0 R /XYZ 150.7049 326.7738 null] +1380 0 obj << +/D [1376 0 R /XYZ 150.7049 326.7738 null] >> endobj -1329 0 obj << -/D [1324 0 R /XYZ 150.7049 330.7588 null] +1381 0 obj << +/D [1376 0 R /XYZ 150.7049 330.7588 null] >> endobj -1330 0 obj << -/D [1324 0 R /XYZ 150.7049 284.986 null] +1382 0 obj << +/D [1376 0 R /XYZ 150.7049 284.986 null] >> endobj -1331 0 obj << -/D [1324 0 R /XYZ 150.7049 253.1056 null] +1383 0 obj << +/D [1376 0 R /XYZ 150.7049 253.1056 null] >> endobj -1323 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R /F11 586 0 R /F14 613 0 R >> +1375 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R /F11 606 0 R /F14 633 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1334 0 obj << +1386 0 obj << /Length 3732 >> stream @@ -26893,33 +28181,33 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 266.7696 90.4377 Td[(93)]TJ +/F8 9.9626 Tf 266.7696 90.4377 Td[(97)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1333 0 obj << +1385 0 obj << /Type /Page -/Contents 1334 0 R -/Resources 1332 0 R +/Contents 1386 0 R +/Resources 1384 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1322 0 R +/Parent 1389 0 R >> endobj -1335 0 obj << -/D [1333 0 R /XYZ 99.8954 740.9981 null] +1387 0 obj << +/D [1385 0 R /XYZ 99.8954 740.9981 null] >> endobj -298 0 obj << -/D [1333 0 R /XYZ 99.8954 659.6006 null] +314 0 obj << +/D [1385 0 R /XYZ 99.8954 659.6006 null] >> endobj -1336 0 obj << -/D [1333 0 R /XYZ 99.8954 631.8021 null] +1388 0 obj << +/D [1385 0 R /XYZ 99.8954 631.8021 null] >> endobj -1332 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R >> +1384 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1339 0 obj << +1392 0 obj << /Length 4805 >> stream @@ -27054,33 +28342,33 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 317.5791 90.4377 Td[(94)]TJ +/F8 9.9626 Tf 317.5791 90.4377 Td[(98)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1338 0 obj << +1391 0 obj << /Type /Page -/Contents 1339 0 R -/Resources 1337 0 R +/Contents 1392 0 R +/Resources 1390 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1322 0 R +/Parent 1389 0 R >> endobj -1340 0 obj << -/D [1338 0 R /XYZ 150.7049 740.9981 null] +1393 0 obj << +/D [1391 0 R /XYZ 150.7049 740.9981 null] >> endobj -302 0 obj << -/D [1338 0 R /XYZ 150.7049 659.6006 null] +318 0 obj << +/D [1391 0 R /XYZ 150.7049 659.6006 null] >> endobj -1341 0 obj << -/D [1338 0 R /XYZ 150.7049 631.8021 null] +1394 0 obj << +/D [1391 0 R /XYZ 150.7049 631.8021 null] >> endobj -1337 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F11 586 0 R /F29 431 0 R /F14 613 0 R >> +1390 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F11 606 0 R /F29 447 0 R /F14 633 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1344 0 obj << +1397 0 obj << /Length 2162 >> stream @@ -27157,34 +28445,34 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 266.7696 90.4377 Td[(95)]TJ +/F8 9.9626 Tf 266.7696 90.4377 Td[(99)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1343 0 obj << +1396 0 obj << /Type /Page -/Contents 1344 0 R -/Resources 1342 0 R +/Contents 1397 0 R +/Resources 1395 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1322 0 R +/Parent 1389 0 R >> endobj -1345 0 obj << -/D [1343 0 R /XYZ 99.8954 740.9981 null] +1398 0 obj << +/D [1396 0 R /XYZ 99.8954 740.9981 null] >> endobj -306 0 obj << -/D [1343 0 R /XYZ 99.8954 659.6006 null] +322 0 obj << +/D [1396 0 R /XYZ 99.8954 659.6006 null] >> endobj -1346 0 obj << -/D [1343 0 R /XYZ 99.8954 631.8021 null] +1399 0 obj << +/D [1396 0 R /XYZ 99.8954 631.8021 null] >> endobj -1342 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F29 431 0 R /F32 602 0 R >> +1395 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1349 0 obj << -/Length 2597 +1402 0 obj << +/Length 2598 >> stream 1 0 0 1 150.7049 740.9981 cm @@ -27260,34 +28548,34 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 317.5791 90.4377 Td[(96)]TJ +/F8 9.9626 Tf 315.0884 90.4377 Td[(100)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1348 0 obj << +1401 0 obj << /Type /Page -/Contents 1349 0 R -/Resources 1347 0 R +/Contents 1402 0 R +/Resources 1400 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1322 0 R +/Parent 1389 0 R >> endobj -1350 0 obj << -/D [1348 0 R /XYZ 150.7049 740.9981 null] +1403 0 obj << +/D [1401 0 R /XYZ 150.7049 740.9981 null] >> endobj -310 0 obj << -/D [1348 0 R /XYZ 150.7049 644.4574 null] +326 0 obj << +/D [1401 0 R /XYZ 150.7049 644.4574 null] >> endobj -1351 0 obj << -/D [1348 0 R /XYZ 150.7049 613.8693 null] +1404 0 obj << +/D [1401 0 R /XYZ 150.7049 613.8693 null] >> endobj -1347 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R >> +1400 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1354 0 obj << -/Length 2425 +1407 0 obj << +/Length 2426 >> stream 1 0 0 1 99.8954 740.9981 cm @@ -27363,34 +28651,34 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 266.7696 90.4377 Td[(97)]TJ +/F8 9.9626 Tf 264.2789 90.4377 Td[(101)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1353 0 obj << +1406 0 obj << /Type /Page -/Contents 1354 0 R -/Resources 1352 0 R +/Contents 1407 0 R +/Resources 1405 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1357 0 R +/Parent 1389 0 R >> endobj -1355 0 obj << -/D [1353 0 R /XYZ 99.8954 740.9981 null] +1408 0 obj << +/D [1406 0 R /XYZ 99.8954 740.9981 null] >> endobj -314 0 obj << -/D [1353 0 R /XYZ 99.8954 659.6006 null] +330 0 obj << +/D [1406 0 R /XYZ 99.8954 659.6006 null] >> endobj -1356 0 obj << -/D [1353 0 R /XYZ 99.8954 631.8021 null] +1409 0 obj << +/D [1406 0 R /XYZ 99.8954 631.8021 null] >> endobj -1352 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R >> +1405 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1360 0 obj << -/Length 6416 +1412 0 obj << +/Length 6417 >> stream 1 0 0 1 150.7049 740.9981 cm @@ -27510,34 +28798,34 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 317.5791 90.4377 Td[(98)]TJ +/F8 9.9626 Tf 315.0884 90.4377 Td[(102)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1359 0 obj << +1411 0 obj << /Type /Page -/Contents 1360 0 R -/Resources 1358 0 R +/Contents 1412 0 R +/Resources 1410 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1357 0 R +/Parent 1389 0 R >> endobj -1361 0 obj << -/D [1359 0 R /XYZ 150.7049 740.9981 null] +1413 0 obj << +/D [1411 0 R /XYZ 150.7049 740.9981 null] >> endobj -318 0 obj << -/D [1359 0 R /XYZ 150.7049 659.6006 null] +334 0 obj << +/D [1411 0 R /XYZ 150.7049 659.6006 null] >> endobj -1362 0 obj << -/D [1359 0 R /XYZ 150.7049 631.8021 null] +1414 0 obj << +/D [1411 0 R /XYZ 150.7049 631.8021 null] >> endobj -1358 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F11 586 0 R /F14 613 0 R >> +1410 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F11 606 0 R /F14 633 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1365 0 obj << -/Length 7025 +1417 0 obj << +/Length 7026 >> stream 1 0 0 1 99.8954 740.9981 cm @@ -27669,39 +28957,39 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 266.7696 90.4377 Td[(99)]TJ +/F8 9.9626 Tf 264.2789 90.4377 Td[(103)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1364 0 obj << +1416 0 obj << /Type /Page -/Contents 1365 0 R -/Resources 1363 0 R +/Contents 1417 0 R +/Resources 1415 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1357 0 R +/Parent 1422 0 R >> endobj -1366 0 obj << -/D [1364 0 R /XYZ 99.8954 740.9981 null] +1418 0 obj << +/D [1416 0 R /XYZ 99.8954 740.9981 null] >> endobj -322 0 obj << -/D [1364 0 R /XYZ 99.8954 659.6006 null] +338 0 obj << +/D [1416 0 R /XYZ 99.8954 659.6006 null] >> endobj -1367 0 obj << -/D [1364 0 R /XYZ 99.8954 631.8021 null] +1419 0 obj << +/D [1416 0 R /XYZ 99.8954 631.8021 null] >> endobj -1368 0 obj << -/D [1364 0 R /XYZ 99.8954 175.3416 null] +1420 0 obj << +/D [1416 0 R /XYZ 99.8954 175.3416 null] >> endobj -1369 0 obj << -/D [1364 0 R /XYZ 99.8954 179.3267 null] +1421 0 obj << +/D [1416 0 R /XYZ 99.8954 179.3267 null] >> endobj -1363 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F14 613 0 R /F11 586 0 R /F32 602 0 R >> +1415 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F14 633 0 R /F11 606 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1372 0 obj << +1425 0 obj << /Length 7098 >> stream @@ -27834,39 +29122,39 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 315.0884 90.4377 Td[(100)]TJ +/F8 9.9626 Tf 315.0884 90.4377 Td[(104)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1371 0 obj << +1424 0 obj << /Type /Page -/Contents 1372 0 R -/Resources 1370 0 R +/Contents 1425 0 R +/Resources 1423 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1357 0 R +/Parent 1422 0 R >> endobj -1373 0 obj << -/D [1371 0 R /XYZ 150.7049 740.9981 null] +1426 0 obj << +/D [1424 0 R /XYZ 150.7049 740.9981 null] >> endobj -326 0 obj << -/D [1371 0 R /XYZ 150.7049 659.6006 null] +342 0 obj << +/D [1424 0 R /XYZ 150.7049 659.6006 null] >> endobj -1374 0 obj << -/D [1371 0 R /XYZ 150.7049 631.8021 null] +1427 0 obj << +/D [1424 0 R /XYZ 150.7049 631.8021 null] >> endobj -1375 0 obj << -/D [1371 0 R /XYZ 150.7049 163.3865 null] +1428 0 obj << +/D [1424 0 R /XYZ 150.7049 163.3865 null] >> endobj -1376 0 obj << -/D [1371 0 R /XYZ 150.7049 167.3715 null] +1429 0 obj << +/D [1424 0 R /XYZ 150.7049 167.3715 null] >> endobj -1370 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F14 613 0 R /F11 586 0 R /F32 602 0 R >> +1423 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F14 633 0 R /F11 606 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1379 0 obj << +1432 0 obj << /Length 7107 >> stream @@ -27999,39 +29287,39 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 264.2789 90.4377 Td[(101)]TJ +/F8 9.9626 Tf 264.2789 90.4377 Td[(105)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1378 0 obj << +1431 0 obj << /Type /Page -/Contents 1379 0 R -/Resources 1377 0 R +/Contents 1432 0 R +/Resources 1430 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1357 0 R +/Parent 1422 0 R >> endobj -1380 0 obj << -/D [1378 0 R /XYZ 99.8954 740.9981 null] +1433 0 obj << +/D [1431 0 R /XYZ 99.8954 740.9981 null] >> endobj -330 0 obj << -/D [1378 0 R /XYZ 99.8954 659.6006 null] +346 0 obj << +/D [1431 0 R /XYZ 99.8954 659.6006 null] >> endobj -1381 0 obj << -/D [1378 0 R /XYZ 99.8954 631.8021 null] +1434 0 obj << +/D [1431 0 R /XYZ 99.8954 631.8021 null] >> endobj -1382 0 obj << -/D [1378 0 R /XYZ 99.8954 163.3865 null] +1435 0 obj << +/D [1431 0 R /XYZ 99.8954 163.3865 null] >> endobj -1383 0 obj << -/D [1378 0 R /XYZ 99.8954 167.3715 null] +1436 0 obj << +/D [1431 0 R /XYZ 99.8954 167.3715 null] >> endobj -1377 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F14 613 0 R /F11 586 0 R /F32 602 0 R >> +1430 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F14 633 0 R /F11 606 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1386 0 obj << +1439 0 obj << /Length 7100 >> stream @@ -28164,39 +29452,39 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 315.0884 90.4377 Td[(102)]TJ +/F8 9.9626 Tf 315.0884 90.4377 Td[(106)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1385 0 obj << +1438 0 obj << /Type /Page -/Contents 1386 0 R -/Resources 1384 0 R +/Contents 1439 0 R +/Resources 1437 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1357 0 R +/Parent 1422 0 R >> endobj -1387 0 obj << -/D [1385 0 R /XYZ 150.7049 740.9981 null] +1440 0 obj << +/D [1438 0 R /XYZ 150.7049 740.9981 null] >> endobj -334 0 obj << -/D [1385 0 R /XYZ 150.7049 659.6006 null] +350 0 obj << +/D [1438 0 R /XYZ 150.7049 659.6006 null] >> endobj -1388 0 obj << -/D [1385 0 R /XYZ 150.7049 631.8021 null] +1441 0 obj << +/D [1438 0 R /XYZ 150.7049 631.8021 null] >> endobj -1389 0 obj << -/D [1385 0 R /XYZ 150.7049 175.3416 null] +1442 0 obj << +/D [1438 0 R /XYZ 150.7049 175.3416 null] >> endobj -1390 0 obj << -/D [1385 0 R /XYZ 150.7049 179.3267 null] +1443 0 obj << +/D [1438 0 R /XYZ 150.7049 179.3267 null] >> endobj -1384 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F14 613 0 R /F11 586 0 R /F32 602 0 R >> +1437 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F14 633 0 R /F11 606 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1393 0 obj << +1446 0 obj << /Length 7116 >> stream @@ -28329,39 +29617,39 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 264.2789 90.4377 Td[(103)]TJ +/F8 9.9626 Tf 264.2789 90.4377 Td[(107)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1392 0 obj << +1445 0 obj << /Type /Page -/Contents 1393 0 R -/Resources 1391 0 R +/Contents 1446 0 R +/Resources 1444 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1398 0 R +/Parent 1422 0 R >> endobj -1394 0 obj << -/D [1392 0 R /XYZ 99.8954 740.9981 null] +1447 0 obj << +/D [1445 0 R /XYZ 99.8954 740.9981 null] >> endobj -338 0 obj << -/D [1392 0 R /XYZ 99.8954 659.6006 null] +354 0 obj << +/D [1445 0 R /XYZ 99.8954 659.6006 null] >> endobj -1395 0 obj << -/D [1392 0 R /XYZ 99.8954 631.8021 null] +1448 0 obj << +/D [1445 0 R /XYZ 99.8954 631.8021 null] >> endobj -1396 0 obj << -/D [1392 0 R /XYZ 99.8954 163.3865 null] +1449 0 obj << +/D [1445 0 R /XYZ 99.8954 163.3865 null] >> endobj -1397 0 obj << -/D [1392 0 R /XYZ 99.8954 167.3715 null] +1450 0 obj << +/D [1445 0 R /XYZ 99.8954 167.3715 null] >> endobj -1391 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F14 613 0 R /F11 586 0 R /F32 602 0 R >> +1444 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F14 633 0 R /F11 606 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1401 0 obj << +1453 0 obj << /Length 7487 >> stream @@ -28498,39 +29786,39 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 315.0884 90.4377 Td[(104)]TJ +/F8 9.9626 Tf 315.0884 90.4377 Td[(108)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1400 0 obj << +1452 0 obj << /Type /Page -/Contents 1401 0 R -/Resources 1399 0 R +/Contents 1453 0 R +/Resources 1451 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1398 0 R +/Parent 1422 0 R >> endobj -1402 0 obj << -/D [1400 0 R /XYZ 150.7049 740.9981 null] +1454 0 obj << +/D [1452 0 R /XYZ 150.7049 740.9981 null] >> endobj -342 0 obj << -/D [1400 0 R /XYZ 150.7049 663.6564 null] +358 0 obj << +/D [1452 0 R /XYZ 150.7049 663.6564 null] >> endobj -1403 0 obj << -/D [1400 0 R /XYZ 150.7049 635.8579 null] +1455 0 obj << +/D [1452 0 R /XYZ 150.7049 635.8579 null] >> endobj -1404 0 obj << -/D [1400 0 R /XYZ 150.7049 153.6009 null] +1456 0 obj << +/D [1452 0 R /XYZ 150.7049 153.6009 null] >> endobj -1405 0 obj << -/D [1400 0 R /XYZ 150.7049 157.079 null] +1457 0 obj << +/D [1452 0 R /XYZ 150.7049 157.079 null] >> endobj -1399 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F11 586 0 R /F14 613 0 R >> +1451 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F11 606 0 R /F14 633 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1408 0 obj << +1460 0 obj << /Length 7474 >> stream @@ -28663,39 +29951,39 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 264.2789 90.4377 Td[(105)]TJ +/F8 9.9626 Tf 264.2789 90.4377 Td[(109)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1407 0 obj << +1459 0 obj << /Type /Page -/Contents 1408 0 R -/Resources 1406 0 R +/Contents 1460 0 R +/Resources 1458 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1398 0 R +/Parent 1465 0 R >> endobj -1409 0 obj << -/D [1407 0 R /XYZ 99.8954 740.9981 null] +1461 0 obj << +/D [1459 0 R /XYZ 99.8954 740.9981 null] >> endobj -346 0 obj << -/D [1407 0 R /XYZ 99.8954 663.6564 null] +362 0 obj << +/D [1459 0 R /XYZ 99.8954 663.6564 null] >> endobj -1410 0 obj << -/D [1407 0 R /XYZ 99.8954 635.8579 null] +1462 0 obj << +/D [1459 0 R /XYZ 99.8954 635.8579 null] >> endobj -1411 0 obj << -/D [1407 0 R /XYZ 99.8954 153.6009 null] +1463 0 obj << +/D [1459 0 R /XYZ 99.8954 153.6009 null] >> endobj -1412 0 obj << -/D [1407 0 R /XYZ 99.8954 157.079 null] +1464 0 obj << +/D [1459 0 R /XYZ 99.8954 157.079 null] >> endobj -1406 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F11 586 0 R /F14 613 0 R >> +1458 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F11 606 0 R /F14 633 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1415 0 obj << +1468 0 obj << /Length 8139 >> stream @@ -28735,45 +30023,45 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 315.0884 90.4377 Td[(106)]TJ +/F8 9.9626 Tf 315.0884 90.4377 Td[(110)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1414 0 obj << +1467 0 obj << /Type /Page -/Contents 1415 0 R -/Resources 1413 0 R +/Contents 1468 0 R +/Resources 1466 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1398 0 R -/Annots [ 1417 0 R 1418 0 R ] +/Parent 1465 0 R +/Annots [ 1470 0 R 1471 0 R ] >> endobj -1417 0 obj << +1470 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [196.2861 501.7702 203.26 512.8952] /Subtype /Link /A << /S /GoTo /D (figure.8) >> >> endobj -1418 0 obj << +1471 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [196.7569 346.6298 203.7308 357.478] /Subtype /Link /A << /S /GoTo /D (figure.9) >> >> endobj -1416 0 obj << -/D [1414 0 R /XYZ 150.7049 740.9981 null] +1469 0 obj << +/D [1467 0 R /XYZ 150.7049 740.9981 null] >> endobj -350 0 obj << -/D [1414 0 R /XYZ 150.7049 716.0915 null] +366 0 obj << +/D [1467 0 R /XYZ 150.7049 716.0915 null] >> endobj -1413 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F32 602 0 R >> +1466 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1423 0 obj << +1476 0 obj << /Length 4628 >> stream @@ -28919,33 +30207,33 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 264.2789 90.4377 Td[(107)]TJ +/F8 9.9626 Tf 264.2789 90.4377 Td[(111)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1422 0 obj << +1475 0 obj << /Type /Page -/Contents 1423 0 R -/Resources 1421 0 R +/Contents 1476 0 R +/Resources 1474 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1398 0 R +/Parent 1465 0 R >> endobj -1424 0 obj << -/D [1422 0 R /XYZ 99.8954 740.9981 null] +1477 0 obj << +/D [1475 0 R /XYZ 99.8954 740.9981 null] >> endobj -1419 0 obj << -/D [1422 0 R /XYZ 143.4516 412.2365 null] +1472 0 obj << +/D [1475 0 R /XYZ 143.4516 412.2365 null] >> endobj -1420 0 obj << -/D [1422 0 R /XYZ 146.1606 171.0735 null] +1473 0 obj << +/D [1475 0 R /XYZ 146.1606 171.0735 null] >> endobj -1421 0 obj << -/Font << /F48 737 0 R /F8 434 0 R /F32 602 0 R >> +1474 0 obj << +/Font << /F48 757 0 R /F8 450 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1427 0 obj << +1480 0 obj << /Length 5421 >> stream @@ -29162,33 +30450,33 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 315.0884 90.4377 Td[(108)]TJ +/F8 9.9626 Tf 315.0884 90.4377 Td[(112)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1426 0 obj << +1479 0 obj << /Type /Page -/Contents 1427 0 R -/Resources 1425 0 R +/Contents 1480 0 R +/Resources 1478 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1398 0 R +/Parent 1465 0 R >> endobj -1428 0 obj << -/D [1426 0 R /XYZ 150.7049 740.9981 null] +1481 0 obj << +/D [1479 0 R /XYZ 150.7049 740.9981 null] >> endobj -354 0 obj << -/D [1426 0 R /XYZ 150.7049 644.4574 null] +370 0 obj << +/D [1479 0 R /XYZ 150.7049 644.4574 null] >> endobj -1429 0 obj << -/D [1426 0 R /XYZ 150.7049 613.8693 null] +1482 0 obj << +/D [1479 0 R /XYZ 150.7049 613.8693 null] >> endobj -1425 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R >> +1478 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1432 0 obj << +1485 0 obj << /Length 2165 >> stream @@ -29265,33 +30553,33 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 264.2789 90.4377 Td[(109)]TJ +/F8 9.9626 Tf 264.2789 90.4377 Td[(113)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1431 0 obj << +1484 0 obj << /Type /Page -/Contents 1432 0 R -/Resources 1430 0 R +/Contents 1485 0 R +/Resources 1483 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1435 0 R +/Parent 1465 0 R >> endobj -1433 0 obj << -/D [1431 0 R /XYZ 99.8954 740.9981 null] +1486 0 obj << +/D [1484 0 R /XYZ 99.8954 740.9981 null] >> endobj -358 0 obj << -/D [1431 0 R /XYZ 99.8954 644.4574 null] +374 0 obj << +/D [1484 0 R /XYZ 99.8954 644.4574 null] >> endobj -1434 0 obj << -/D [1431 0 R /XYZ 99.8954 613.8693 null] +1487 0 obj << +/D [1484 0 R /XYZ 99.8954 613.8693 null] >> endobj -1430 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R >> +1483 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1438 0 obj << +1490 0 obj << /Length 2473 >> stream @@ -29394,33 +30682,33 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 315.0884 90.4377 Td[(110)]TJ +/F8 9.9626 Tf 315.0884 90.4377 Td[(114)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1437 0 obj << +1489 0 obj << /Type /Page -/Contents 1438 0 R -/Resources 1436 0 R +/Contents 1490 0 R +/Resources 1488 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1435 0 R +/Parent 1465 0 R >> endobj -1439 0 obj << -/D [1437 0 R /XYZ 150.7049 740.9981 null] +1491 0 obj << +/D [1489 0 R /XYZ 150.7049 740.9981 null] >> endobj -362 0 obj << -/D [1437 0 R /XYZ 150.7049 641.6678 null] +378 0 obj << +/D [1489 0 R /XYZ 150.7049 641.6678 null] >> endobj -1440 0 obj << -/D [1437 0 R /XYZ 150.7049 613.8693 null] +1492 0 obj << +/D [1489 0 R /XYZ 150.7049 613.8693 null] >> endobj -1436 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R >> +1488 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1443 0 obj << +1495 0 obj << /Length 3016 >> stream @@ -29549,33 +30837,33 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 264.2789 90.4377 Td[(111)]TJ +/F8 9.9626 Tf 264.2789 90.4377 Td[(115)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1442 0 obj << +1494 0 obj << /Type /Page -/Contents 1443 0 R -/Resources 1441 0 R +/Contents 1495 0 R +/Resources 1493 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1435 0 R +/Parent 1498 0 R >> endobj -1444 0 obj << -/D [1442 0 R /XYZ 99.8954 740.9981 null] +1496 0 obj << +/D [1494 0 R /XYZ 99.8954 740.9981 null] >> endobj -366 0 obj << -/D [1442 0 R /XYZ 99.8954 641.6678 null] +382 0 obj << +/D [1494 0 R /XYZ 99.8954 641.6678 null] >> endobj -1445 0 obj << -/D [1442 0 R /XYZ 99.8954 613.8693 null] +1497 0 obj << +/D [1494 0 R /XYZ 99.8954 613.8693 null] >> endobj -1441 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +1493 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1448 0 obj << +1501 0 obj << /Length 791 >> stream @@ -29591,30 +30879,30 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 315.0884 90.4377 Td[(112)]TJ +/F8 9.9626 Tf 315.0884 90.4377 Td[(116)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1447 0 obj << +1500 0 obj << /Type /Page -/Contents 1448 0 R -/Resources 1446 0 R +/Contents 1501 0 R +/Resources 1499 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1435 0 R +/Parent 1498 0 R >> endobj -1449 0 obj << -/D [1447 0 R /XYZ 150.7049 740.9981 null] +1502 0 obj << +/D [1500 0 R /XYZ 150.7049 740.9981 null] >> endobj -370 0 obj << -/D [1447 0 R /XYZ 150.7049 716.0915 null] +386 0 obj << +/D [1500 0 R /XYZ 150.7049 716.0915 null] >> endobj -1446 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F32 602 0 R >> +1499 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1452 0 obj << +1505 0 obj << /Length 6709 >> stream @@ -29797,41 +31085,41 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 264.2789 90.4377 Td[(113)]TJ +/F8 9.9626 Tf 264.2789 90.4377 Td[(117)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1451 0 obj << +1504 0 obj << /Type /Page -/Contents 1452 0 R -/Resources 1450 0 R +/Contents 1505 0 R +/Resources 1503 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1435 0 R -/Annots [ 1455 0 R ] +/Parent 1498 0 R +/Annots [ 1508 0 R ] >> endobj -1455 0 obj << +1508 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 380.3229 367.009 391.4478] /Subtype /Link /A << /S /GoTo /D (spdata) >> >> endobj -1453 0 obj << -/D [1451 0 R /XYZ 99.8954 740.9981 null] +1506 0 obj << +/D [1504 0 R /XYZ 99.8954 740.9981 null] >> endobj -374 0 obj << -/D [1451 0 R /XYZ 99.8954 641.6678 null] +390 0 obj << +/D [1504 0 R /XYZ 99.8954 641.6678 null] >> endobj -1454 0 obj << -/D [1451 0 R /XYZ 99.8954 613.8693 null] +1507 0 obj << +/D [1504 0 R /XYZ 99.8954 613.8693 null] >> endobj -1450 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +1503 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1458 0 obj << +1511 0 obj << /Length 7478 >> stream @@ -30026,41 +31314,41 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 315.0884 90.4377 Td[(114)]TJ +/F8 9.9626 Tf 315.0884 90.4377 Td[(118)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1457 0 obj << +1510 0 obj << /Type /Page -/Contents 1458 0 R -/Resources 1456 0 R +/Contents 1511 0 R +/Resources 1509 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1435 0 R -/Annots [ 1461 0 R ] +/Parent 1498 0 R +/Annots [ 1514 0 R ] >> endobj -1461 0 obj << +1514 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 513.8223 417.8184 524.9472] /Subtype /Link /A << /S /GoTo /D (spdata) >> >> endobj -1459 0 obj << -/D [1457 0 R /XYZ 150.7049 740.9981 null] +1512 0 obj << +/D [1510 0 R /XYZ 150.7049 740.9981 null] >> endobj -378 0 obj << -/D [1457 0 R /XYZ 150.7049 641.6678 null] +394 0 obj << +/D [1510 0 R /XYZ 150.7049 641.6678 null] >> endobj -1460 0 obj << -/D [1457 0 R /XYZ 150.7049 613.8693 null] +1513 0 obj << +/D [1510 0 R /XYZ 150.7049 613.8693 null] >> endobj -1456 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +1509 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1464 0 obj << +1517 0 obj << /Length 5427 >> stream @@ -30245,41 +31533,41 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 264.2789 90.4377 Td[(115)]TJ +/F8 9.9626 Tf 264.2789 90.4377 Td[(119)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1463 0 obj << +1516 0 obj << /Type /Page -/Contents 1464 0 R -/Resources 1462 0 R +/Contents 1517 0 R +/Resources 1515 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1468 0 R -/Annots [ 1467 0 R ] +/Parent 1498 0 R +/Annots [ 1520 0 R ] >> endobj -1467 0 obj << +1520 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 380.3229 367.009 391.4478] /Subtype /Link /A << /S /GoTo /D (spdata) >> >> endobj -1465 0 obj << -/D [1463 0 R /XYZ 99.8954 740.9981 null] +1518 0 obj << +/D [1516 0 R /XYZ 99.8954 740.9981 null] >> endobj -382 0 obj << -/D [1463 0 R /XYZ 99.8954 644.4574 null] +398 0 obj << +/D [1516 0 R /XYZ 99.8954 644.4574 null] >> endobj -1466 0 obj << -/D [1463 0 R /XYZ 99.8954 613.8693 null] +1519 0 obj << +/D [1516 0 R /XYZ 99.8954 613.8693 null] >> endobj -1462 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +1515 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1471 0 obj << +1523 0 obj << /Length 6074 >> stream @@ -30476,41 +31764,41 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 315.0884 90.4377 Td[(116)]TJ +/F8 9.9626 Tf 315.0884 90.4377 Td[(120)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1470 0 obj << +1522 0 obj << /Type /Page -/Contents 1471 0 R -/Resources 1469 0 R +/Contents 1523 0 R +/Resources 1521 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1468 0 R -/Annots [ 1474 0 R ] +/Parent 1498 0 R +/Annots [ 1526 0 R ] >> endobj -1474 0 obj << +1526 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 513.8223 417.8184 524.9472] /Subtype /Link /A << /S /GoTo /D (spdata) >> >> endobj -1472 0 obj << -/D [1470 0 R /XYZ 150.7049 740.9981 null] +1524 0 obj << +/D [1522 0 R /XYZ 150.7049 740.9981 null] >> endobj -386 0 obj << -/D [1470 0 R /XYZ 150.7049 644.4574 null] +402 0 obj << +/D [1522 0 R /XYZ 150.7049 644.4574 null] >> endobj -1473 0 obj << -/D [1470 0 R /XYZ 150.7049 613.8693 null] +1525 0 obj << +/D [1522 0 R /XYZ 150.7049 613.8693 null] >> endobj -1469 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +1521 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1477 0 obj << +1529 0 obj << /Length 1520 >> stream @@ -30550,30 +31838,30 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 264.2789 90.4377 Td[(117)]TJ +/F8 9.9626 Tf 264.2789 90.4377 Td[(121)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1476 0 obj << +1528 0 obj << /Type /Page -/Contents 1477 0 R -/Resources 1475 0 R +/Contents 1529 0 R +/Resources 1527 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1468 0 R +/Parent 1531 0 R >> endobj -1478 0 obj << -/D [1476 0 R /XYZ 99.8954 740.9981 null] +1530 0 obj << +/D [1528 0 R /XYZ 99.8954 740.9981 null] >> endobj -390 0 obj << -/D [1476 0 R /XYZ 99.8954 716.0915 null] +406 0 obj << +/D [1528 0 R /XYZ 99.8954 716.0915 null] >> endobj -1475 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F14 613 0 R /F32 602 0 R >> +1527 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F14 633 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1481 0 obj << +1534 0 obj << /Length 7348 >> stream @@ -30785,54 +32073,54 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 315.0884 90.4377 Td[(118)]TJ +/F8 9.9626 Tf 315.0884 90.4377 Td[(122)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1480 0 obj << +1533 0 obj << /Type /Page -/Contents 1481 0 R -/Resources 1479 0 R +/Contents 1534 0 R +/Resources 1532 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1468 0 R -/Annots [ 1484 0 R 1486 0 R ] +/Parent 1531 0 R +/Annots [ 1537 0 R 1539 0 R ] >> endobj -1484 0 obj << +1537 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [372.1526 444.0838 439.2105 455.2087] /Subtype /Link /A << /S /GoTo /D (precdata) >> >> endobj -1486 0 obj << +1539 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [179.0984 332.274 185.5603 342.3761] /Subtype /Link /A << /S /GoTo /D (Hfootnote.3) >> >> endobj -1482 0 obj << -/D [1480 0 R /XYZ 150.7049 740.9981 null] +1535 0 obj << +/D [1533 0 R /XYZ 150.7049 740.9981 null] >> endobj -394 0 obj << -/D [1480 0 R /XYZ 150.7049 659.6006 null] +410 0 obj << +/D [1533 0 R /XYZ 150.7049 659.6006 null] >> endobj -1483 0 obj << -/D [1480 0 R /XYZ 150.7049 631.8021 null] +1536 0 obj << +/D [1533 0 R /XYZ 150.7049 631.8021 null] >> endobj -1485 0 obj << -/D [1480 0 R /XYZ 150.7049 354.856 null] +1538 0 obj << +/D [1533 0 R /XYZ 150.7049 354.856 null] >> endobj -1487 0 obj << -/D [1480 0 R /XYZ 165.9479 129.7901 null] +1540 0 obj << +/D [1533 0 R /XYZ 165.9479 129.7901 null] >> endobj -1479 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R /F11 586 0 R /F7 607 0 R /F34 617 0 R /F33 621 0 R >> +1532 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R /F11 606 0 R /F7 627 0 R /F34 637 0 R /F33 641 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1490 0 obj << +1543 0 obj << /Length 7725 >> stream @@ -31135,62 +32423,62 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 264.2789 90.4377 Td[(119)]TJ +/F8 9.9626 Tf 264.2789 90.4377 Td[(123)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1489 0 obj << +1542 0 obj << /Type /Page -/Contents 1490 0 R -/Resources 1488 0 R +/Contents 1543 0 R +/Resources 1541 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1468 0 R -/Annots [ 1493 0 R 1494 0 R 1495 0 R 1496 0 R ] +/Parent 1531 0 R +/Annots [ 1546 0 R 1547 0 R 1548 0 R 1549 0 R ] >> endobj -1493 0 obj << +1546 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [317.8562 519.7999 390.1445 530.9248] /Subtype /Link /A << /S /GoTo /D (spdata) >> >> endobj -1494 0 obj << +1547 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [396.921 452.0539 463.9789 463.1789] /Subtype /Link /A << /S /GoTo /D (precdata) >> >> endobj -1495 0 obj << +1548 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [371.4885 384.3079 438.5464 395.4329] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1496 0 obj << +1549 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [318.5757 294.6442 385.6336 305.7691] /Subtype /Link /A << /S /GoTo /D (precdata) >> >> endobj -1491 0 obj << -/D [1489 0 R /XYZ 99.8954 740.9981 null] +1544 0 obj << +/D [1542 0 R /XYZ 99.8954 740.9981 null] >> endobj -398 0 obj << -/D [1489 0 R /XYZ 99.8954 659.6006 null] +414 0 obj << +/D [1542 0 R /XYZ 99.8954 659.6006 null] >> endobj -1492 0 obj << -/D [1489 0 R /XYZ 99.8954 631.8021 null] +1545 0 obj << +/D [1542 0 R /XYZ 99.8954 631.8021 null] >> endobj -1488 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +1541 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1499 0 obj << +1552 0 obj << /Length 8470 >> stream @@ -31475,48 +32763,48 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 315.0884 90.4377 Td[(120)]TJ +/F8 9.9626 Tf 315.0884 90.4377 Td[(124)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1498 0 obj << +1551 0 obj << /Type /Page -/Contents 1499 0 R -/Resources 1497 0 R +/Contents 1552 0 R +/Resources 1550 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1468 0 R -/Annots [ 1502 0 R 1503 0 R ] +/Parent 1531 0 R +/Annots [ 1555 0 R 1556 0 R ] >> endobj -1502 0 obj << +1555 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [372.1526 484.9013 439.2105 496.0262] /Subtype /Link /A << /S /GoTo /D (precdata) >> >> endobj -1503 0 obj << +1556 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [375.6949 375.6346 442.7528 386.7595] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1500 0 obj << -/D [1498 0 R /XYZ 150.7049 740.9981 null] +1553 0 obj << +/D [1551 0 R /XYZ 150.7049 740.9981 null] >> endobj -402 0 obj << -/D [1498 0 R /XYZ 150.7049 649.0871 null] +418 0 obj << +/D [1551 0 R /XYZ 150.7049 649.0871 null] >> endobj -1501 0 obj << -/D [1498 0 R /XYZ 150.7049 618.499 null] +1554 0 obj << +/D [1551 0 R /XYZ 150.7049 618.499 null] >> endobj -1497 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +1550 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1506 0 obj << +1559 0 obj << /Length 3031 >> stream @@ -31657,41 +32945,41 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 264.2789 90.4377 Td[(121)]TJ +/F8 9.9626 Tf 264.2789 90.4377 Td[(125)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1505 0 obj << +1558 0 obj << /Type /Page -/Contents 1506 0 R -/Resources 1504 0 R +/Contents 1559 0 R +/Resources 1557 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1510 0 R -/Annots [ 1509 0 R ] +/Parent 1531 0 R +/Annots [ 1562 0 R ] >> endobj -1509 0 obj << +1562 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [321.3431 501.8671 388.4011 512.9921] /Subtype /Link /A << /S /GoTo /D (precdata) >> >> endobj -1507 0 obj << -/D [1505 0 R /XYZ 99.8954 740.9981 null] +1560 0 obj << +/D [1558 0 R /XYZ 99.8954 740.9981 null] >> endobj -406 0 obj << -/D [1505 0 R /XYZ 99.8954 641.6678 null] +422 0 obj << +/D [1558 0 R /XYZ 99.8954 641.6678 null] >> endobj -1508 0 obj << -/D [1505 0 R /XYZ 99.8954 613.8693 null] +1561 0 obj << +/D [1558 0 R /XYZ 99.8954 613.8693 null] >> endobj -1504 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +1557 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1513 0 obj << +1565 0 obj << /Length 883 >> stream @@ -31707,30 +32995,30 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 315.0884 90.4377 Td[(122)]TJ +/F8 9.9626 Tf 315.0884 90.4377 Td[(126)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1512 0 obj << +1564 0 obj << /Type /Page -/Contents 1513 0 R -/Resources 1511 0 R +/Contents 1565 0 R +/Resources 1563 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1510 0 R +/Parent 1531 0 R >> endobj -1514 0 obj << -/D [1512 0 R /XYZ 150.7049 740.9981 null] +1566 0 obj << +/D [1564 0 R /XYZ 150.7049 740.9981 null] >> endobj -410 0 obj << -/D [1512 0 R /XYZ 150.7049 716.0915 null] +426 0 obj << +/D [1564 0 R /XYZ 150.7049 716.0915 null] >> endobj -1511 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F32 602 0 R >> +1563 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1517 0 obj << +1569 0 obj << /Length 10233 >> stream @@ -32018,48 +33306,48 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 264.2789 90.4377 Td[(123)]TJ +/F8 9.9626 Tf 264.2789 90.4377 Td[(127)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1516 0 obj << +1568 0 obj << /Type /Page -/Contents 1517 0 R -/Resources 1515 0 R +/Contents 1569 0 R +/Resources 1567 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1510 0 R -/Annots [ 1520 0 R 1521 0 R ] +/Parent 1574 0 R +/Annots [ 1572 0 R 1573 0 R ] >> endobj -1520 0 obj << +1572 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 183.7802 367.009 194.9052] /Subtype /Link /A << /S /GoTo /D (spdata) >> >> endobj -1521 0 obj << +1573 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [294.7207 117.1154 361.7786 128.2404] /Subtype /Link /A << /S /GoTo /D (precdata) >> >> endobj -1518 0 obj << -/D [1516 0 R /XYZ 99.8954 740.9981 null] +1570 0 obj << +/D [1568 0 R /XYZ 99.8954 740.9981 null] >> endobj -414 0 obj << -/D [1516 0 R /XYZ 99.8954 663.9253 null] +430 0 obj << +/D [1568 0 R /XYZ 99.8954 663.9253 null] >> endobj -1519 0 obj << -/D [1516 0 R /XYZ 99.8954 453.4241 null] +1571 0 obj << +/D [1568 0 R /XYZ 99.8954 453.4241 null] >> endobj -1515 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F11 586 0 R /F14 613 0 R /F10 610 0 R /F7 607 0 R /F19 571 0 R /F29 431 0 R /F32 602 0 R >> +1567 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F11 606 0 R /F14 633 0 R /F10 630 0 R /F7 627 0 R /F19 591 0 R /F29 447 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1524 0 obj << +1577 0 obj << /Length 7837 >> stream @@ -32226,35 +33514,35 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 315.0884 90.4377 Td[(124)]TJ +/F8 9.9626 Tf 315.0884 90.4377 Td[(128)]TJ ET 1 0 0 1 494.4159 90.4377 cm 0 g 0 G endstream endobj -1523 0 obj << +1576 0 obj << /Type /Page -/Contents 1524 0 R -/Resources 1522 0 R +/Contents 1577 0 R +/Resources 1575 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1510 0 R -/Annots [ 1526 0 R ] +/Parent 1574 0 R +/Annots [ 1579 0 R ] >> endobj -1526 0 obj << +1579 0 obj << /Type /Annot /Border[0 0 0]/H/I/C[1 0 0] /Rect [345.5302 453.3545 412.5881 464.4795] /Subtype /Link /A << /S /GoTo /D (descdata) >> >> endobj -1525 0 obj << -/D [1523 0 R /XYZ 150.7049 740.9981 null] +1578 0 obj << +/D [1576 0 R /XYZ 150.7049 740.9981 null] >> endobj -1522 0 obj << -/Font << /F29 431 0 R /F8 434 0 R /F32 602 0 R /F11 586 0 R /F14 613 0 R >> +1575 0 obj << +/Font << /F29 447 0 R /F8 450 0 R /F32 622 0 R /F11 606 0 R /F14 633 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1529 0 obj << +1582 0 obj << /Length 3067 >> stream @@ -32314,27 +33602,27 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 264.2789 90.4377 Td[(125)]TJ +/F8 9.9626 Tf 264.2789 90.4377 Td[(129)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1528 0 obj << +1581 0 obj << /Type /Page -/Contents 1529 0 R -/Resources 1527 0 R +/Contents 1582 0 R +/Resources 1580 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1510 0 R +/Parent 1574 0 R >> endobj -1530 0 obj << -/D [1528 0 R /XYZ 99.8954 740.9981 null] +1583 0 obj << +/D [1581 0 R /XYZ 99.8954 740.9981 null] >> endobj -1527 0 obj << -/Font << /F29 431 0 R /F8 434 0 R >> +1580 0 obj << +/Font << /F29 447 0 R /F8 450 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1533 0 obj << +1586 0 obj << /Length 220 >> stream @@ -32346,27 +33634,27 @@ stream 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 315.0884 90.4377 Td[(126)]TJ +/F8 9.9626 Tf 315.0884 90.4377 Td[(130)]TJ ET 1 0 0 1 494.416 90.4377 cm 0 g 0 G endstream endobj -1532 0 obj << +1585 0 obj << /Type /Page -/Contents 1533 0 R -/Resources 1531 0 R +/Contents 1586 0 R +/Resources 1584 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1510 0 R +/Parent 1574 0 R >> endobj -1534 0 obj << -/D [1532 0 R /XYZ 150.7049 740.9981 null] +1587 0 obj << +/D [1585 0 R /XYZ 150.7049 740.9981 null] >> endobj -1531 0 obj << -/Font << /F8 434 0 R >> +1584 0 obj << +/Font << /F8 450 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1537 0 obj << +1590 0 obj << /Length 10309 >> stream @@ -32526,66 +33814,66 @@ ET 0 g 0 G 1 0 0 1 -99.8954 -90.4377 cm BT -/F8 9.9626 Tf 264.2789 90.4377 Td[(127)]TJ +/F8 9.9626 Tf 264.2789 90.4377 Td[(131)]TJ ET 1 0 0 1 443.6065 90.4377 cm 0 g 0 G endstream endobj -1536 0 obj << +1589 0 obj << /Type /Page -/Contents 1537 0 R -/Resources 1535 0 R +/Contents 1590 0 R +/Resources 1588 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1543 0 R +/Parent 1574 0 R >> endobj -1538 0 obj << -/D [1536 0 R /XYZ 99.8954 740.9981 null] +1591 0 obj << +/D [1589 0 R /XYZ 99.8954 740.9981 null] >> endobj -1539 0 obj << -/D [1536 0 R /XYZ 99.8954 696.2631 null] +1592 0 obj << +/D [1589 0 R /XYZ 99.8954 696.2631 null] >> endobj -1540 0 obj << -/D [1536 0 R /XYZ 99.8954 699.6186 null] +1593 0 obj << +/D [1589 0 R /XYZ 99.8954 699.6186 null] >> endobj -637 0 obj << -/D [1536 0 R /XYZ 99.8954 643.1498 null] +657 0 obj << +/D [1589 0 R /XYZ 99.8954 643.1498 null] >> endobj -636 0 obj << -/D [1536 0 R /XYZ 99.8954 588.6182 null] +656 0 obj << +/D [1589 0 R /XYZ 99.8954 588.6182 null] >> endobj -578 0 obj << -/D [1536 0 R /XYZ 99.8954 534.0865 null] +598 0 obj << +/D [1589 0 R /XYZ 99.8954 534.0865 null] >> endobj -579 0 obj << -/D [1536 0 R /XYZ 99.8954 491.5101 null] +599 0 obj << +/D [1589 0 R /XYZ 99.8954 491.5101 null] >> endobj -595 0 obj << -/D [1536 0 R /XYZ 99.8954 448.9336 null] +615 0 obj << +/D [1589 0 R /XYZ 99.8954 448.9336 null] >> endobj -575 0 obj << -/D [1536 0 R /XYZ 99.8954 405.8037 null] +595 0 obj << +/D [1589 0 R /XYZ 99.8954 405.8037 null] >> endobj -576 0 obj << -/D [1536 0 R /XYZ 99.8954 363.2273 null] +596 0 obj << +/D [1589 0 R /XYZ 99.8954 363.2273 null] >> endobj -1541 0 obj << -/D [1536 0 R /XYZ 99.8954 320.6508 null] +1594 0 obj << +/D [1589 0 R /XYZ 99.8954 320.6508 null] >> endobj -1542 0 obj << -/D [1536 0 R /XYZ 99.8954 278.0743 null] +1595 0 obj << +/D [1589 0 R /XYZ 99.8954 278.0743 null] >> endobj -623 0 obj << -/D [1536 0 R /XYZ 99.8954 214.0782 null] +643 0 obj << +/D [1589 0 R /XYZ 99.8954 214.0782 null] >> endobj -577 0 obj << -/D [1536 0 R /XYZ 99.8954 157.3327 null] +597 0 obj << +/D [1589 0 R /XYZ 99.8954 157.3327 null] >> endobj -1535 0 obj << -/Font << /F18 425 0 R /F8 434 0 R /F19 571 0 R /F32 602 0 R >> +1588 0 obj << +/Font << /F18 441 0 R /F8 450 0 R /F19 591 0 R /F32 622 0 R >> /ProcSet [ /PDF /Text ] >> endobj -1546 0 obj << +1598 0 obj << /Length 2219 >> stream @@ -32633,36 +33921,36 @@ ET 0 g 0 G 1 0 0 1 -150.7049 -90.4377 cm BT -/F8 9.9626 Tf 315.0884 90.4377 Td[(128)]TJ +/F8 9.9626 Tf 315.0884 90.4377 Td[(132)]TJ ET 1 0 0 1 494.416 90.4377 cm 0 g 0 G endstream endobj -1545 0 obj << +1597 0 obj << /Type /Page -/Contents 1546 0 R -/Resources 1544 0 R +/Contents 1598 0 R +/Resources 1596 0 R /MediaBox [0 0 595.2756 841.8898] -/Parent 1543 0 R +/Parent 1574 0 R >> endobj -1547 0 obj << -/D [1545 0 R /XYZ 150.7049 740.9981 null] +1599 0 obj << +/D [1597 0 R /XYZ 150.7049 740.9981 null] >> endobj -574 0 obj << -/D [1545 0 R /XYZ 150.7049 716.0915 null] +594 0 obj << +/D [1597 0 R /XYZ 150.7049 716.0915 null] >> endobj -573 0 obj << -/D [1545 0 R /XYZ 150.7049 676.2963 null] +593 0 obj << +/D [1597 0 R /XYZ 150.7049 676.2963 null] >> endobj -1548 0 obj << -/D [1545 0 R /XYZ 150.7049 644.4158 null] +1600 0 obj << +/D [1597 0 R /XYZ 150.7049 644.4158 null] >> endobj -1544 0 obj << -/Font << /F8 434 0 R /F19 571 0 R >> +1596 0 obj << +/Font << /F8 450 0 R /F19 591 0 R >> /ProcSet [ /PDF /Text ] >> endobj -986 0 obj << +1006 0 obj << /Length1 1125 /Length2 4765 /Length3 532 @@ -32682,7 +33970,7 @@ stream /ItalicAngle 0 def /isFixedPitch false def end readonly def -/FontName /KVJRRS+CMR9 def +/FontName /JFUPYM+CMR9 def /PaintType 0 def /FontType 1 def /FontMatrix [0.001 0 0 0.001 0 0] readonly def @@ -32759,37 +34047,37 @@ _ cleartomark endstream endobj -987 0 obj << +1007 0 obj << /Type /Font /Subtype /Type1 -/Encoding 1549 0 R +/Encoding 1601 0 R /FirstChar 40 /LastChar 115 -/Widths 1550 0 R -/BaseFont /KVJRRS+CMR9 -/FontDescriptor 985 0 R +/Widths 1602 0 R +/BaseFont /JFUPYM+CMR9 +/FontDescriptor 1005 0 R >> endobj -985 0 obj << +1005 0 obj << /Ascent 694 /CapHeight 683 /Descent -194 -/FontName /KVJRRS+CMR9 +/FontName /JFUPYM+CMR9 /ItalicAngle 0 /StemV 74 /XHeight 431 /FontBBox [-39 -250 1036 750] /Flags 4 /CharSet (/parenleft/parenright/period/zero/one/two/three/four/five/six/seven/eight/nine/B/G/I/L/O/P/X/c/e/o/r/s) -/FontFile 986 0 R +/FontFile 1006 0 R >> endobj -1550 0 obj +1602 0 obj [400 400 0 0 0 0 285 0 514 514 514 514 514 514 514 514 514 514 0 0 0 0 0 0 0 0 728 0 0 0 0 806 0 371 0 0 642 0 0 799 699 0 0 0 0 0 0 0 771 0 0 0 0 0 0 0 0 0 0 457 0 457 0 0 0 0 0 0 0 0 0 514 0 0 402 405 ] endobj -1549 0 obj << +1601 0 obj << /Type /Encoding /Differences [ 0 /.notdef 40/parenleft/parenright 42/.notdef 46/period 47/.notdef 48/zero/one/two/three/four/five/six/seven/eight/nine 58/.notdef 66/B 67/.notdef 71/G 72/.notdef 73/I 74/.notdef 76/L 77/.notdef 79/O/P 81/.notdef 88/X 89/.notdef 99/c 100/.notdef 101/e 102/.notdef 111/o 112/.notdef 114/r/s 116/.notdef] >> endobj -892 0 obj << +912 0 obj << /Length1 766 /Length2 759 /Length3 532 @@ -32809,7 +34097,7 @@ stream /ItalicAngle -14.035 def /isFixedPitch false def end readonly def -/FontName /KJHWCB+CMSY7 def +/FontName /DZILOW+CMSY7 def /PaintType 0 def /FontType 1 def /FontMatrix [0.001 0 0 0.001 0 0] readonly def @@ -32835,37 +34123,37 @@ aaT'/D cleartomark endstream endobj -893 0 obj << +913 0 obj << /Type /Font /Subtype /Type1 -/Encoding 1551 0 R +/Encoding 1603 0 R /FirstChar 0 /LastChar 49 -/Widths 1552 0 R -/BaseFont /KJHWCB+CMSY7 -/FontDescriptor 891 0 R +/Widths 1604 0 R +/BaseFont /DZILOW+CMSY7 +/FontDescriptor 911 0 R >> endobj -891 0 obj << +911 0 obj << /Ascent 750 /CapHeight 683 /Descent -194 -/FontName /KJHWCB+CMSY7 +/FontName /DZILOW+CMSY7 /ItalicAngle -14.035 /StemV 93 /XHeight 431 /FontBBox [-15 -951 1252 782] /Flags 4 /CharSet (/minus/infinity) -/FontFile 892 0 R +/FontFile 912 0 R >> endobj -1552 0 obj +1604 0 obj [893 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 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1139 ] endobj -1551 0 obj << +1603 0 obj << /Type /Encoding /Differences [ 0 /minus 1/.notdef 49/infinity 50/.notdef] >> endobj -736 0 obj << +756 0 obj << /Length1 1289 /Length2 5599 /Length3 532 @@ -32885,7 +34173,7 @@ stream /ItalicAngle 0 def /isFixedPitch true def end readonly def -/FontName /ZKVNYI+CMTT9 def +/FontName /CPKQNU+CMTT9 def /PaintType 0 def /FontType 1 def /FontMatrix [0.001 0 0 0.001 0 0] readonly def @@ -32963,37 +34251,37 @@ z(# cleartomark endstream endobj -737 0 obj << +757 0 obj << /Type /Font /Subtype /Type1 -/Encoding 1553 0 R +/Encoding 1605 0 R /FirstChar 39 /LastChar 122 -/Widths 1554 0 R -/BaseFont /ZKVNYI+CMTT9 -/FontDescriptor 735 0 R +/Widths 1606 0 R +/BaseFont /CPKQNU+CMTT9 +/FontDescriptor 755 0 R >> endobj -735 0 obj << +755 0 obj << /Ascent 611 /CapHeight 611 /Descent -222 -/FontName /ZKVNYI+CMTT9 +/FontName /CPKQNU+CMTT9 /ItalicAngle 0 /StemV 74 /XHeight 431 /FontBBox [-6 -233 542 698] /Flags 4 /CharSet (/quoteright/parenleft/parenright/comma/period/one/two/nine/colon/equal/underscore/a/b/c/d/e/f/g/h/i/k/l/m/n/o/p/q/r/s/t/u/v/x/y/z) -/FontFile 736 0 R +/FontFile 756 0 R >> endobj -1554 0 obj +1606 0 obj [525 525 525 0 0 525 0 525 0 0 525 525 0 0 0 0 0 0 525 525 0 0 525 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 0 0 0 525 0 525 525 525 525 525 525 525 525 525 0 525 525 525 525 525 525 525 525 525 525 525 525 0 525 525 525 ] endobj -1553 0 obj << +1605 0 obj << /Type /Encoding /Differences [ 0 /.notdef 39/quoteright/parenleft/parenright 42/.notdef 44/comma 45/.notdef 46/period 47/.notdef 49/one/two 51/.notdef 57/nine/colon 59/.notdef 61/equal 62/.notdef 95/underscore 96/.notdef 97/a/b/c/d/e/f/g/h/i 106/.notdef 107/k/l/m/n/o/p/q/r/s/t/u/v 119/.notdef 120/x/y/z 123/.notdef] >> endobj -649 0 obj << +669 0 obj << /Length1 745 /Length2 1242 /Length3 532 @@ -33013,7 +34301,7 @@ stream /ItalicAngle -14.04 def /isFixedPitch false def end readonly def -/FontName /UQUHGV+CMMI5 def +/FontName /FJZYZE+CMMI5 def /PaintType 0 def /FontType 1 def /FontMatrix [0.001 0 0 0.001 0 0] readonly def @@ -33039,37 +34327,37 @@ currentfile eexec cleartomark endstream endobj -650 0 obj << +670 0 obj << /Type /Font /Subtype /Type1 -/Encoding 1555 0 R +/Encoding 1607 0 R /FirstChar 105 /LastChar 105 -/Widths 1556 0 R -/BaseFont /UQUHGV+CMMI5 -/FontDescriptor 648 0 R +/Widths 1608 0 R +/BaseFont /FJZYZE+CMMI5 +/FontDescriptor 668 0 R >> endobj -648 0 obj << +668 0 obj << /Ascent 694 /CapHeight 683 /Descent -194 -/FontName /UQUHGV+CMMI5 +/FontName /FJZYZE+CMMI5 /ItalicAngle -14.04 /StemV 90 /XHeight 431 /FontBBox [37 -250 1349 750] /Flags 4 /CharSet (/i) -/FontFile 649 0 R +/FontFile 669 0 R >> endobj -1556 0 obj +1608 0 obj [534 ] endobj -1555 0 obj << +1607 0 obj << /Type /Encoding /Differences [ 0 /.notdef 105/i 106/.notdef] >> endobj -620 0 obj << +640 0 obj << /Length1 1462 /Length2 8120 /Length3 532 @@ -33089,7 +34377,7 @@ stream /ItalicAngle 0 def /isFixedPitch false def end readonly def -/FontName /LJLBLQ+CMR8 def +/FontName /JIWEOX+CMR8 def /PaintType 0 def /FontType 1 def /FontMatrix [0.001 0 0 0.001 0 0] readonly def @@ -33186,37 +34474,37 @@ j cleartomark endstream endobj -621 0 obj << +641 0 obj << /Type /Font /Subtype /Type1 -/Encoding 1557 0 R +/Encoding 1609 0 R /FirstChar 40 /LastChar 121 -/Widths 1558 0 R -/BaseFont /LJLBLQ+CMR8 -/FontDescriptor 619 0 R +/Widths 1610 0 R +/BaseFont /JIWEOX+CMR8 +/FontDescriptor 639 0 R >> endobj -619 0 obj << +639 0 obj << /Ascent 694 /CapHeight 683 /Descent -194 -/FontName /LJLBLQ+CMR8 +/FontName /JIWEOX+CMR8 /ItalicAngle 0 /StemV 76 /XHeight 431 /FontBBox [-36 -250 1070 750] /Flags 4 /CharSet (/parenleft/parenright/comma/hyphen/period/slash/zero/one/two/three/four/five/six/seven/eight/nine/B/G/I/L/O/P/T/X/a/b/c/d/e/f/g/h/i/l/m/n/o/p/q/r/s/t/u/v/w/x/y) -/FontFile 620 0 R +/FontFile 640 0 R >> endobj -1558 0 obj +1610 0 obj [413 413 0 0 295 354 295 531 531 531 531 531 531 531 531 531 531 531 0 0 0 0 0 0 0 0 752 0 0 0 0 834 0 383 0 0 664 0 0 826 723 0 0 0 767 0 0 0 796 0 0 0 0 0 0 0 0 531 590 472 590 472 325 531 590 295 0 0 295 885 590 531 590 561 414 419 413 590 561 767 561 561 ] endobj -1557 0 obj << +1609 0 obj << /Type /Encoding /Differences [ 0 /.notdef 40/parenleft/parenright 42/.notdef 44/comma/hyphen/period/slash/zero/one/two/three/four/five/six/seven/eight/nine 58/.notdef 66/B 67/.notdef 71/G 72/.notdef 73/I 74/.notdef 76/L 77/.notdef 79/O/P 81/.notdef 84/T 85/.notdef 88/X 89/.notdef 97/a/b/c/d/e/f/g/h/i 106/.notdef 108/l/m/n/o/p/q/r/s/t/u/v/w/x/y 122/.notdef] >> endobj -616 0 obj << +636 0 obj << /Length1 769 /Length2 1408 /Length3 532 @@ -33236,7 +34524,7 @@ stream /ItalicAngle 0 def /isFixedPitch false def end readonly def -/FontName /HHIREC+CMR6 def +/FontName /EPCOIT+CMR6 def /PaintType 0 def /FontType 1 def /FontMatrix [0.001 0 0 0.001 0 0] readonly def @@ -33266,37 +34554,37 @@ currentfile eexec cleartomark endstream endobj -617 0 obj << +637 0 obj << /Type /Font /Subtype /Type1 -/Encoding 1559 0 R +/Encoding 1611 0 R /FirstChar 49 /LastChar 51 -/Widths 1560 0 R -/BaseFont /HHIREC+CMR6 -/FontDescriptor 615 0 R +/Widths 1612 0 R +/BaseFont /EPCOIT+CMR6 +/FontDescriptor 635 0 R >> endobj -615 0 obj << +635 0 obj << /Ascent 694 /CapHeight 683 /Descent -194 -/FontName /HHIREC+CMR6 +/FontName /EPCOIT+CMR6 /ItalicAngle 0 /StemV 83 /XHeight 431 /FontBBox [-20 -250 1193 750] /Flags 4 /CharSet (/one/two/three) -/FontFile 616 0 R +/FontFile 636 0 R >> endobj -1560 0 obj +1612 0 obj [611 611 611 ] endobj -1559 0 obj << +1611 0 obj << /Type /Encoding /Differences [ 0 /.notdef 49/one/two/three 52/.notdef] >> endobj -612 0 obj << +632 0 obj << /Length1 1050 /Length2 2900 /Length3 532 @@ -33316,7 +34604,7 @@ stream /ItalicAngle -14.035 def /isFixedPitch false def end readonly def -/FontName /TQFUEV+CMSY10 def +/FontName /VLRIEC+CMSY10 def /PaintType 0 def /FontType 1 def /FontMatrix [0.001 0 0 0.001 0 0] readonly def @@ -33371,37 +34659,37 @@ c cleartomark endstream endobj -613 0 obj << +633 0 obj << /Type /Font /Subtype /Type1 -/Encoding 1561 0 R +/Encoding 1613 0 R /FirstChar 0 /LastChar 120 -/Widths 1562 0 R -/BaseFont /TQFUEV+CMSY10 -/FontDescriptor 611 0 R +/Widths 1614 0 R +/BaseFont /VLRIEC+CMSY10 +/FontDescriptor 631 0 R >> endobj -611 0 obj << +631 0 obj << /Ascent 750 /CapHeight 683 /Descent -194 -/FontName /TQFUEV+CMSY10 +/FontName /VLRIEC+CMSY10 /ItalicAngle -14.035 /StemV 85 /XHeight 431 /FontBBox [-29 -960 1116 775] /Flags 4 /CharSet (/minus/bullet/lessequal/greaterequal/arrowleft/element/negationslash/B/H/I/braceleft/braceright/bar/bardbl/radical/section) -/FontFile 612 0 R +/FontFile 632 0 R >> endobj -1562 0 obj +1614 0 obj [778 0 0 0 0 0 0 0 0 0 0 0 0 0 0 500 0 0 0 0 778 778 0 0 0 0 0 0 0 0 0 0 1000 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 667 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 657 0 0 0 0 0 845 545 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 500 500 0 0 278 500 0 0 0 0 833 0 0 0 0 0 0 0 444 ] endobj -1561 0 obj << +1613 0 obj << /Type /Encoding /Differences [ 0 /minus 1/.notdef 15/bullet 16/.notdef 20/lessequal/greaterequal 22/.notdef 32/arrowleft 33/.notdef 50/element 51/.notdef 54/negationslash 55/.notdef 66/B 67/.notdef 72/H/I 74/.notdef 102/braceleft/braceright 104/.notdef 106/bar/bardbl 108/.notdef 112/radical 113/.notdef 120/section 121/.notdef] >> endobj -609 0 obj << +629 0 obj << /Length1 907 /Length2 3553 /Length3 532 @@ -33421,7 +34709,7 @@ stream /ItalicAngle -14.04 def /isFixedPitch false def end readonly def -/FontName /DICZTY+CMMI7 def +/FontName /AKHTUB+CMMI7 def /PaintType 0 def /FontType 1 def /FontMatrix [0.001 0 0 0.001 0 0] readonly def @@ -33468,37 +34756,37 @@ NØ• cleartomark endstream endobj -610 0 obj << +630 0 obj << /Type /Font /Subtype /Type1 -/Encoding 1563 0 R +/Encoding 1615 0 R /FirstChar 59 /LastChar 114 -/Widths 1564 0 R -/BaseFont /DICZTY+CMMI7 -/FontDescriptor 608 0 R +/Widths 1616 0 R +/BaseFont /AKHTUB+CMMI7 +/FontDescriptor 628 0 R >> endobj -608 0 obj << +628 0 obj << /Ascent 694 /CapHeight 683 /Descent -194 -/FontName /DICZTY+CMMI7 +/FontName /AKHTUB+CMMI7 /ItalicAngle -14.04 /StemV 81 /XHeight 431 /FontBBox [0 -250 1171 750] /Flags 4 /CharSet (/comma/H/I/T/a/c/i/j/k/m/n/r) -/FontFile 609 0 R +/FontFile 629 0 R >> endobj -1564 0 obj +1616 0 obj [339 0 0 0 0 0 0 0 0 0 0 0 0 936 506 0 0 0 0 0 0 0 0 0 0 675 0 0 0 0 0 0 0 0 0 0 0 0 620 0 511 0 0 0 0 0 404 473 607 0 1014 706 0 0 0 530 ] endobj -1563 0 obj << +1615 0 obj << /Type /Encoding /Differences [ 0 /.notdef 59/comma 60/.notdef 72/H/I 74/.notdef 84/T 85/.notdef 97/a 98/.notdef 99/c 100/.notdef 105/i/j/k 108/.notdef 109/m/n 111/.notdef 114/r 115/.notdef] >> endobj -606 0 obj << +626 0 obj << /Length1 787 /Length2 1497 /Length3 532 @@ -33518,7 +34806,7 @@ stream /ItalicAngle 0 def /isFixedPitch false def end readonly def -/FontName /IJFURC+CMR7 def +/FontName /RPAEZT+CMR7 def /PaintType 0 def /FontType 1 def /FontMatrix [0.001 0 0 0.001 0 0] readonly def @@ -33550,37 +34838,37 @@ _2 cleartomark endstream endobj -607 0 obj << +627 0 obj << /Type /Font /Subtype /Type1 -/Encoding 1565 0 R +/Encoding 1617 0 R /FirstChar 49 /LastChar 58 -/Widths 1566 0 R -/BaseFont /IJFURC+CMR7 -/FontDescriptor 605 0 R +/Widths 1618 0 R +/BaseFont /RPAEZT+CMR7 +/FontDescriptor 625 0 R >> endobj -605 0 obj << +625 0 obj << /Ascent 694 /CapHeight 683 /Descent -194 -/FontName /IJFURC+CMR7 +/FontName /RPAEZT+CMR7 /ItalicAngle 0 /StemV 79 /XHeight 431 /FontBBox [-27 -250 1122 750] /Flags 4 /CharSet (/one/two/three/colon) -/FontFile 606 0 R +/FontFile 626 0 R >> endobj -1566 0 obj +1618 0 obj [569 569 569 0 0 0 0 0 0 323 ] endobj -1565 0 obj << +1617 0 obj << /Type /Encoding /Differences [ 0 /.notdef 49/one/two/three 52/.notdef 58/colon 59/.notdef] >> endobj -601 0 obj << +621 0 obj << /Length1 1775 /Length2 11063 /Length3 532 @@ -33600,7 +34888,7 @@ stream /ItalicAngle 0 def /isFixedPitch true def end readonly def -/FontName /KWBHCD+CMTT10 def +/FontName /GELDXI+CMTT10 def /PaintType 0 def /FontType 1 def /FontMatrix [0.001 0 0 0.001 0 0] readonly def @@ -33727,37 +35015,37 @@ T cleartomark endstream endobj -602 0 obj << +622 0 obj << /Type /Font /Subtype /Type1 -/Encoding 1567 0 R +/Encoding 1619 0 R /FirstChar 40 /LastChar 126 -/Widths 1568 0 R -/BaseFont /KWBHCD+CMTT10 -/FontDescriptor 600 0 R +/Widths 1620 0 R +/BaseFont /GELDXI+CMTT10 +/FontDescriptor 620 0 R >> endobj -600 0 obj << +620 0 obj << /Ascent 611 /CapHeight 611 /Descent -222 -/FontName /KWBHCD+CMTT10 +/FontName /GELDXI+CMTT10 /ItalicAngle 0 /StemV 69 /XHeight 431 /FontBBox [-4 -235 731 800] /Flags 4 /CharSet (/parenleft/parenright/asterisk/plus/comma/hyphen/period/slash/zero/one/two/three/four/five/six/nine/colon/equal/A/B/C/D/E/F/I/K/L/M/N/O/P/R/S/T/U/W/Y/backslash/underscore/a/b/c/d/e/f/g/h/i/j/k/l/m/n/o/p/q/r/s/t/u/v/w/x/y/z/asciitilde) -/FontFile 601 0 R +/FontFile 621 0 R >> endobj -1568 0 obj +1620 0 obj [525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 0 0 525 525 0 0 525 0 0 0 525 525 525 525 525 525 0 0 525 0 525 525 525 525 525 525 0 525 525 525 525 0 525 0 525 0 0 525 0 0 525 0 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 0 0 0 525 ] endobj -1567 0 obj << +1619 0 obj << /Type /Encoding /Differences [ 0 /.notdef 40/parenleft/parenright/asterisk/plus/comma/hyphen/period/slash/zero/one/two/three/four/five/six 55/.notdef 57/nine/colon 59/.notdef 61/equal 62/.notdef 65/A/B/C/D/E/F 71/.notdef 73/I 74/.notdef 75/K/L/M/N/O/P 81/.notdef 82/R/S/T/U 86/.notdef 87/W 88/.notdef 89/Y 90/.notdef 92/backslash 93/.notdef 95/underscore 96/.notdef 97/a/b/c/d/e/f/g/h/i/j/k/l/m/n/o/p/q/r/s/t/u/v/w/x/y/z 123/.notdef 126/asciitilde 127/.notdef] >> endobj -585 0 obj << +605 0 obj << /Length1 1369 /Length2 9186 /Length3 532 @@ -33777,7 +35065,7 @@ stream /ItalicAngle -14.04 def /isFixedPitch false def end readonly def -/FontName /SJNFSP+CMMI10 def +/FontName /XGKYSH+CMMI10 def /PaintType 0 def /FontType 1 def /FontMatrix [0.001 0 0 0.001 0 0] readonly def @@ -33876,37 +35164,37 @@ r^ cleartomark endstream endobj -586 0 obj << +606 0 obj << /Type /Font /Subtype /Type1 -/Encoding 1569 0 R +/Encoding 1621 0 R /FirstChar 11 /LastChar 122 -/Widths 1570 0 R -/BaseFont /SJNFSP+CMMI10 -/FontDescriptor 584 0 R +/Widths 1622 0 R +/BaseFont /XGKYSH+CMMI10 +/FontDescriptor 604 0 R >> endobj -584 0 obj << +604 0 obj << /Ascent 694 /CapHeight 683 /Descent -194 -/FontName /SJNFSP+CMMI10 +/FontName /XGKYSH+CMMI10 /ItalicAngle -14.04 /StemV 72 /XHeight 431 /FontBBox [-32 -250 1048 750] /Flags 4 /CharSet (/alpha/beta/period/comma/less/greater/A/D/I/L/N/O/P/Q/T/U/X/a/b/c/d/e/f/g/h/i/j/k/l/m/n/o/p/r/s/t/u/v/w/x/y/z) -/FontFile 585 0 R +/FontFile 605 0 R >> endobj -1570 0 obj +1622 0 obj [640 566 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 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 278 278 778 0 778 0 0 750 0 0 828 0 0 0 0 440 0 0 681 0 803 763 642 791 0 0 584 683 0 0 828 0 0 0 0 0 0 0 0 529 429 433 520 466 490 477 576 345 412 521 298 878 600 485 503 0 451 469 361 572 485 716 572 490 465 ] endobj -1569 0 obj << +1621 0 obj << /Type /Encoding /Differences [ 0 /.notdef 11/alpha/beta 13/.notdef 58/period/comma/less 61/.notdef 62/greater 63/.notdef 65/A 66/.notdef 68/D 69/.notdef 73/I 74/.notdef 76/L 77/.notdef 78/N/O/P/Q 82/.notdef 84/T/U 86/.notdef 88/X 89/.notdef 97/a/b/c/d/e/f/g/h/i/j/k/l/m/n/o/p 113/.notdef 114/r/s/t/u/v/w/x/y/z 123/.notdef] >> endobj -570 0 obj << +590 0 obj << /Length1 1653 /Length2 13157 /Length3 532 @@ -33926,7 +35214,7 @@ stream /ItalicAngle -14.04 def /isFixedPitch false def end readonly def -/FontName /RFAWOQ+CMTI10 def +/FontName /CCFESC+CMTI10 def /PaintType 0 def /FontType 1 def /FontMatrix [0.001 0 0 0.001 0 0] readonly def @@ -34074,37 +35362,37 @@ P cleartomark endstream endobj -571 0 obj << +591 0 obj << /Type /Font /Subtype /Type1 -/Encoding 1571 0 R +/Encoding 1623 0 R /FirstChar 11 /LastChar 122 -/Widths 1572 0 R -/BaseFont /RFAWOQ+CMTI10 -/FontDescriptor 569 0 R +/Widths 1624 0 R +/BaseFont /CCFESC+CMTI10 +/FontDescriptor 589 0 R >> endobj -569 0 obj << +589 0 obj << /Ascent 694 /CapHeight 683 /Descent -194 -/FontName /RFAWOQ+CMTI10 +/FontName /CCFESC+CMTI10 /ItalicAngle -14.04 /StemV 68 /XHeight 431 /FontBBox [-163 -250 1146 969] /Flags 4 /CharSet (/ff/fi/fl/quoteright/comma/hyphen/period/slash/zero/one/two/three/five/nine/colon/equal/A/B/C/D/E/F/G/I/L/M/N/O/P/R/S/T/U/V/a/b/c/d/e/f/g/h/i/j/k/l/m/n/o/p/q/r/s/t/u/v/w/x/y/z) -/FontFile 570 0 R +/FontFile 590 0 R >> endobj -1572 0 obj +1624 0 obj [613 562 588 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 307 0 0 0 0 307 358 307 511 511 511 511 511 0 511 0 0 0 511 307 0 0 767 0 0 0 743 704 716 755 678 653 774 0 386 0 0 627 897 743 767 678 0 729 562 716 743 743 0 0 0 0 0 0 0 0 0 0 511 460 460 511 460 307 460 511 307 307 460 256 818 562 511 511 460 422 409 332 537 460 664 464 486 409 ] endobj -1571 0 obj << +1623 0 obj << /Type /Encoding /Differences [ 0 /.notdef 11/ff/fi/fl 14/.notdef 39/quoteright 40/.notdef 44/comma/hyphen/period/slash/zero/one/two/three 52/.notdef 53/five 54/.notdef 57/nine/colon 59/.notdef 61/equal 62/.notdef 65/A/B/C/D/E/F/G 72/.notdef 73/I 74/.notdef 76/L/M/N/O/P 81/.notdef 82/R/S/T/U/V 87/.notdef 97/a/b/c/d/e/f/g/h/i/j/k/l/m/n/o/p/q/r/s/t/u/v/w/x/y/z 123/.notdef] >> endobj -433 0 obj << +449 0 obj << /Length1 2012 /Length2 14626 /Length3 532 @@ -34124,7 +35412,7 @@ stream /ItalicAngle 0 def /isFixedPitch false def end readonly def -/FontName /NMBCXU+CMR10 def +/FontName /SGTDSX+CMR10 def /PaintType 0 def /FontType 1 def /FontMatrix [0.001 0 0 0.001 0 0] readonly def @@ -34274,37 +35562,37 @@ j% cleartomark endstream endobj -434 0 obj << +450 0 obj << /Type /Font /Subtype /Type1 -/Encoding 1573 0 R +/Encoding 1625 0 R /FirstChar 11 /LastChar 123 -/Widths 1574 0 R -/BaseFont /NMBCXU+CMR10 -/FontDescriptor 432 0 R +/Widths 1626 0 R +/BaseFont /SGTDSX+CMR10 +/FontDescriptor 448 0 R >> endobj -432 0 obj << +448 0 obj << /Ascent 694 /CapHeight 683 /Descent -194 -/FontName /NMBCXU+CMR10 +/FontName /SGTDSX+CMR10 /ItalicAngle 0 /StemV 69 /XHeight 431 /FontBBox [-251 -250 1009 969] /Flags 4 /CharSet (/ff/fi/fl/ffi/quotedblright/ampersand/quoteright/parenleft/parenright/plus/comma/hyphen/period/slash/zero/one/two/three/four/five/six/seven/eight/nine/colon/semicolon/equal/A/B/C/D/E/F/G/H/I/J/K/L/M/N/O/P/R/S/T/U/V/W/bracketleft/quotedblleft/bracketright/a/b/c/d/e/f/g/h/i/j/k/l/m/n/o/p/q/r/s/t/u/v/w/x/y/z/endash) -/FontFile 433 0 R +/FontFile 449 0 R >> endobj -1574 0 obj +1626 0 obj [583 556 556 833 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 500 0 0 0 778 278 389 389 0 778 278 333 278 500 500 500 500 500 500 500 500 500 500 500 278 278 0 778 0 0 0 750 708 722 764 681 653 785 750 361 514 778 625 917 750 778 681 0 736 556 722 750 750 1028 0 0 0 278 500 278 0 0 0 500 556 444 556 444 306 500 556 278 306 528 278 833 556 500 556 528 392 394 389 556 528 722 528 528 444 500 ] endobj -1573 0 obj << +1625 0 obj << /Type /Encoding /Differences [ 0 /.notdef 11/ff/fi/fl/ffi 15/.notdef 34/quotedblright 35/.notdef 38/ampersand/quoteright/parenleft/parenright 42/.notdef 43/plus/comma/hyphen/period/slash/zero/one/two/three/four/five/six/seven/eight/nine/colon/semicolon 60/.notdef 61/equal 62/.notdef 65/A/B/C/D/E/F/G/H/I/J/K/L/M/N/O/P 81/.notdef 82/R/S/T/U/V/W 88/.notdef 91/bracketleft/quotedblleft/bracketright 94/.notdef 97/a/b/c/d/e/f/g/h/i/j/k/l/m/n/o/p/q/r/s/t/u/v/w/x/y/z/endash 124/.notdef] >> endobj -430 0 obj << +446 0 obj << /Length1 1762 /Length2 12194 /Length3 532 @@ -34324,7 +35612,7 @@ stream /ItalicAngle 0 def /isFixedPitch false def end readonly def -/FontName /HJXRGJ+CMBX10 def +/FontName /YNCTNV+CMBX10 def /PaintType 0 def /FontType 1 def /FontMatrix [0.001 0 0 0.001 0 0] readonly def @@ -34457,37 +35745,37 @@ p cleartomark endstream endobj -431 0 obj << +447 0 obj << /Type /Font /Subtype /Type1 -/Encoding 1575 0 R +/Encoding 1627 0 R /FirstChar 12 /LastChar 123 -/Widths 1576 0 R -/BaseFont /HJXRGJ+CMBX10 -/FontDescriptor 429 0 R +/Widths 1628 0 R +/BaseFont /YNCTNV+CMBX10 +/FontDescriptor 445 0 R >> endobj -429 0 obj << +445 0 obj << /Ascent 694 /CapHeight 686 /Descent -194 -/FontName /HJXRGJ+CMBX10 +/FontName /YNCTNV+CMBX10 /ItalicAngle 0 /StemV 114 /XHeight 444 /FontBBox [-301 -250 1164 946] /Flags 4 /CharSet (/fi/fl/quotedblright/quoteright/comma/period/zero/one/two/three/four/five/six/seven/eight/nine/colon/equal/A/B/C/D/E/F/G/H/I/J/L/M/N/O/P/R/S/T/U/V/quotedblleft/a/b/c/d/e/f/g/h/i/j/k/l/m/n/o/p/q/r/s/t/u/v/w/x/y/z/endash) -/FontFile 430 0 R +/FontFile 446 0 R >> endobj -1576 0 obj +1628 0 obj [639 639 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 603 0 0 0 0 319 0 0 0 0 319 0 319 0 575 575 575 575 575 575 575 575 575 575 319 0 0 894 0 0 0 869 818 831 882 756 724 904 900 436 594 0 692 1092 900 864 786 0 862 639 800 885 869 0 0 0 0 0 603 0 0 0 0 559 639 511 639 527 351 575 639 319 351 607 319 958 639 575 639 607 474 454 447 639 607 831 607 607 511 575 ] endobj -1575 0 obj << +1627 0 obj << /Type /Encoding /Differences [ 0 /.notdef 12/fi/fl 14/.notdef 34/quotedblright 35/.notdef 39/quoteright 40/.notdef 44/comma 45/.notdef 46/period 47/.notdef 48/zero/one/two/three/four/five/six/seven/eight/nine/colon 59/.notdef 61/equal 62/.notdef 65/A/B/C/D/E/F/G/H/I/J 75/.notdef 76/L/M/N/O/P 81/.notdef 82/R/S/T/U/V 87/.notdef 92/quotedblleft 93/.notdef 97/a/b/c/d/e/f/g/h/i/j/k/l/m/n/o/p/q/r/s/t/u/v/w/x/y/z/endash 124/.notdef] >> endobj -427 0 obj << +443 0 obj << /Length1 1067 /Length2 5106 /Length3 532 @@ -34507,7 +35795,7 @@ stream /ItalicAngle -14.04 def /isFixedPitch false def end readonly def -/FontName /IQNFHM+CMTI12 def +/FontName /UCFMZL+CMTI12 def /PaintType 0 def /FontType 1 def /FontMatrix [0.001 0 0 0.001 0 0] readonly def @@ -34570,37 +35858,37 @@ Hn4*/ cleartomark endstream endobj -428 0 obj << +444 0 obj << /Type /Font /Subtype /Type1 -/Encoding 1577 0 R +/Encoding 1629 0 R /FirstChar 65 /LastChar 121 -/Widths 1578 0 R -/BaseFont /IQNFHM+CMTI12 -/FontDescriptor 426 0 R +/Widths 1630 0 R +/BaseFont /UCFMZL+CMTI12 +/FontDescriptor 442 0 R >> endobj -426 0 obj << +442 0 obj << /Ascent 694 /CapHeight 683 /Descent -194 -/FontName /IQNFHM+CMTI12 +/FontName /UCFMZL+CMTI12 /ItalicAngle -14.04 /StemV 63 /XHeight 431 /FontBBox [-36 -251 1103 750] /Flags 4 /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 427 0 R +/FontFile 443 0 R >> endobj -1578 0 obj +1630 0 obj [727 688 0 0 0 0 0 0 0 0 0 613 0 0 0 663 0 0 550 0 0 0 0 0 0 0 0 0 0 0 0 0 500 450 450 500 450 300 450 500 300 0 0 250 0 550 500 500 0 413 400 325 525 0 0 0 475 ] endobj -1577 0 obj << +1629 0 obj << /Type /Encoding /Differences [ 0 /.notdef 65/A/B 67/.notdef 76/L 77/.notdef 80/P 81/.notdef 83/S 84/.notdef 97/a/b/c/d/e/f/g/h/i 106/.notdef 108/l 109/.notdef 110/n/o/p 113/.notdef 114/r/s/t/u 118/.notdef 121/y 122/.notdef] >> endobj -424 0 obj << +440 0 obj << /Length1 1734 /Length2 10564 /Length3 532 @@ -34620,7 +35908,7 @@ stream /ItalicAngle 0 def /isFixedPitch false def end readonly def -/FontName /TTYHWT+CMBX12 def +/FontName /EZOVVX+CMBX12 def /PaintType 0 def /FontType 1 def /FontMatrix [0.001 0 0 0.001 0 0] readonly def @@ -34738,456 +36026,484 @@ BO cleartomark endstream endobj -425 0 obj << +441 0 obj << /Type /Font /Subtype /Type1 -/Encoding 1579 0 R +/Encoding 1631 0 R /FirstChar 12 /LastChar 124 -/Widths 1580 0 R -/BaseFont /TTYHWT+CMBX12 -/FontDescriptor 423 0 R +/Widths 1632 0 R +/BaseFont /EZOVVX+CMBX12 +/FontDescriptor 439 0 R >> endobj -423 0 obj << +439 0 obj << /Ascent 694 /CapHeight 686 /Descent -194 -/FontName /TTYHWT+CMBX12 +/FontName /EZOVVX+CMBX12 /ItalicAngle 0 /StemV 109 /XHeight 444 /FontBBox [-53 -251 1139 750] /Flags 4 /CharSet (/fi/quoteright/parenleft/parenright/hyphen/period/zero/one/two/three/four/five/six/seven/eight/nine/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/f/g/h/i/k/l/m/n/o/p/q/r/s/t/u/v/w/x/y/z/endash/emdash) -/FontFile 424 0 R +/FontFile 440 0 R >> endobj -1580 0 obj +1632 0 obj [625 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 312 437 437 0 0 0 375 312 0 562 562 562 562 562 562 562 562 562 562 0 0 0 0 0 0 0 850 800 812 862 738 707 884 880 419 0 881 676 1067 880 845 769 845 839 625 782 865 850 1162 0 0 0 0 0 0 0 0 0 547 625 500 625 513 344 562 625 312 0 594 312 937 625 562 625 594 459 444 437 625 594 812 594 594 500 562 1125 ] endobj -1579 0 obj << +1631 0 obj << /Type /Encoding /Differences [ 0 /.notdef 12/fi 13/.notdef 39/quoteright/parenleft/parenright 42/.notdef 45/hyphen/period 47/.notdef 48/zero/one/two/three/four/five/six/seven/eight/nine 58/.notdef 65/A/B/C/D/E/F/G/H/I 74/.notdef 75/K/L/M/N/O/P/Q/R/S/T/U/V/W 88/.notdef 97/a/b/c/d/e/f/g/h/i 106/.notdef 107/k/l/m/n/o/p/q/r/s/t/u/v/w/x/y/z/endash/emdash 125/.notdef] >> endobj -435 0 obj << +451 0 obj << /Type /Pages /Count 6 -/Parent 1581 0 R -/Kids [418 0 R 437 0 R 441 0 R 487 0 R 535 0 R 556 0 R] +/Parent 1633 0 R +/Kids [434 0 R 453 0 R 457 0 R 503 0 R 555 0 R 576 0 R] >> endobj -572 0 obj << +592 0 obj << /Type /Pages /Count 6 -/Parent 1581 0 R -/Kids [560 0 R 582 0 R 597 0 R 626 0 R 639 0 R 645 0 R] +/Parent 1633 0 R +/Kids [580 0 R 602 0 R 617 0 R 646 0 R 659 0 R 665 0 R] >> endobj -676 0 obj << +696 0 obj << /Type /Pages /Count 6 -/Parent 1581 0 R -/Kids [662 0 R 678 0 R 683 0 R 696 0 R 708 0 R 714 0 R] +/Parent 1633 0 R +/Kids [682 0 R 698 0 R 703 0 R 716 0 R 728 0 R 734 0 R] >> endobj -729 0 obj << +749 0 obj << /Type /Pages /Count 6 -/Parent 1581 0 R -/Kids [721 0 R 732 0 R 743 0 R 752 0 R 760 0 R 767 0 R] +/Parent 1633 0 R +/Kids [741 0 R 752 0 R 763 0 R 772 0 R 780 0 R 787 0 R] >> endobj -780 0 obj << +800 0 obj << /Type /Pages /Count 6 -/Parent 1581 0 R -/Kids [777 0 R 782 0 R 792 0 R 798 0 R 807 0 R 812 0 R] +/Parent 1633 0 R +/Kids [797 0 R 802 0 R 812 0 R 818 0 R 827 0 R 832 0 R] >> endobj -825 0 obj << +845 0 obj << /Type /Pages /Count 6 -/Parent 1581 0 R -/Kids [821 0 R 827 0 R 835 0 R 843 0 R 851 0 R 859 0 R] +/Parent 1633 0 R +/Kids [841 0 R 847 0 R 855 0 R 863 0 R 871 0 R 879 0 R] >> endobj -870 0 obj << +890 0 obj << /Type /Pages /Count 6 -/Parent 1582 0 R -/Kids [863 0 R 872 0 R 876 0 R 884 0 R 888 0 R 899 0 R] +/Parent 1634 0 R +/Kids [883 0 R 892 0 R 896 0 R 904 0 R 908 0 R 919 0 R] >> endobj -921 0 obj << +941 0 obj << /Type /Pages /Count 6 -/Parent 1582 0 R -/Kids [910 0 R 923 0 R 927 0 R 933 0 R 943 0 R 949 0 R] +/Parent 1634 0 R +/Kids [930 0 R 943 0 R 947 0 R 953 0 R 963 0 R 969 0 R] >> endobj -962 0 obj << +982 0 obj << /Type /Pages /Count 6 -/Parent 1582 0 R -/Kids [954 0 R 965 0 R 976 0 R 982 0 R 989 0 R 998 0 R] +/Parent 1634 0 R +/Kids [974 0 R 985 0 R 996 0 R 1002 0 R 1009 0 R 1018 0 R] >> endobj -1014 0 obj << +1034 0 obj << /Type /Pages /Count 6 -/Parent 1582 0 R -/Kids [1011 0 R 1016 0 R 1025 0 R 1034 0 R 1038 0 R 1046 0 R] +/Parent 1634 0 R +/Kids [1031 0 R 1036 0 R 1045 0 R 1054 0 R 1058 0 R 1066 0 R] >> endobj -1054 0 obj << +1074 0 obj << /Type /Pages /Count 6 -/Parent 1582 0 R -/Kids [1051 0 R 1056 0 R 1061 0 R 1068 0 R 1073 0 R 1079 0 R] +/Parent 1634 0 R +/Kids [1071 0 R 1076 0 R 1081 0 R 1088 0 R 1093 0 R 1099 0 R] >> endobj -1094 0 obj << +1114 0 obj << /Type /Pages /Count 6 -/Parent 1582 0 R -/Kids [1086 0 R 1096 0 R 1103 0 R 1109 0 R 1116 0 R 1123 0 R] +/Parent 1634 0 R +/Kids [1106 0 R 1116 0 R 1123 0 R 1129 0 R 1136 0 R 1143 0 R] >> endobj -1140 0 obj << +1160 0 obj << /Type /Pages /Count 6 -/Parent 1583 0 R -/Kids [1134 0 R 1142 0 R 1154 0 R 1161 0 R 1171 0 R 1178 0 R] +/Parent 1635 0 R +/Kids [1154 0 R 1162 0 R 1174 0 R 1181 0 R 1191 0 R 1198 0 R] >> endobj -1192 0 obj << +1212 0 obj << /Type /Pages /Count 6 -/Parent 1583 0 R -/Kids [1187 0 R 1194 0 R 1200 0 R 1207 0 R 1213 0 R 1219 0 R] +/Parent 1635 0 R +/Kids [1207 0 R 1214 0 R 1220 0 R 1227 0 R 1233 0 R 1239 0 R] >> endobj -1229 0 obj << +1249 0 obj << /Type /Pages /Count 6 -/Parent 1583 0 R -/Kids [1224 0 R 1231 0 R 1238 0 R 1244 0 R 1253 0 R 1262 0 R] +/Parent 1635 0 R +/Kids [1244 0 R 1251 0 R 1258 0 R 1264 0 R 1272 0 R 1280 0 R] >> endobj -1275 0 obj << +1295 0 obj << /Type /Pages /Count 6 -/Parent 1583 0 R -/Kids [1268 0 R 1277 0 R 1285 0 R 1290 0 R 1303 0 R 1307 0 R] +/Parent 1635 0 R +/Kids [1288 0 R 1297 0 R 1306 0 R 1315 0 R 1321 0 R 1329 0 R] >> endobj -1322 0 obj << +1341 0 obj << /Type /Pages /Count 6 -/Parent 1583 0 R -/Kids [1315 0 R 1324 0 R 1333 0 R 1338 0 R 1343 0 R 1348 0 R] +/Parent 1635 0 R +/Kids [1337 0 R 1343 0 R 1356 0 R 1360 0 R 1368 0 R 1376 0 R] >> endobj -1357 0 obj << +1389 0 obj << /Type /Pages /Count 6 -/Parent 1583 0 R -/Kids [1353 0 R 1359 0 R 1364 0 R 1371 0 R 1378 0 R 1385 0 R] +/Parent 1635 0 R +/Kids [1385 0 R 1391 0 R 1396 0 R 1401 0 R 1406 0 R 1411 0 R] >> endobj -1398 0 obj << +1422 0 obj << /Type /Pages /Count 6 -/Parent 1584 0 R -/Kids [1392 0 R 1400 0 R 1407 0 R 1414 0 R 1422 0 R 1426 0 R] +/Parent 1636 0 R +/Kids [1416 0 R 1424 0 R 1431 0 R 1438 0 R 1445 0 R 1452 0 R] >> endobj -1435 0 obj << +1465 0 obj << /Type /Pages /Count 6 -/Parent 1584 0 R -/Kids [1431 0 R 1437 0 R 1442 0 R 1447 0 R 1451 0 R 1457 0 R] +/Parent 1636 0 R +/Kids [1459 0 R 1467 0 R 1475 0 R 1479 0 R 1484 0 R 1489 0 R] >> endobj -1468 0 obj << +1498 0 obj << /Type /Pages /Count 6 -/Parent 1584 0 R -/Kids [1463 0 R 1470 0 R 1476 0 R 1480 0 R 1489 0 R 1498 0 R] +/Parent 1636 0 R +/Kids [1494 0 R 1500 0 R 1504 0 R 1510 0 R 1516 0 R 1522 0 R] >> endobj -1510 0 obj << +1531 0 obj << /Type /Pages /Count 6 -/Parent 1584 0 R -/Kids [1505 0 R 1512 0 R 1516 0 R 1523 0 R 1528 0 R 1532 0 R] +/Parent 1636 0 R +/Kids [1528 0 R 1533 0 R 1542 0 R 1551 0 R 1558 0 R 1564 0 R] >> endobj -1543 0 obj << +1574 0 obj << /Type /Pages -/Count 2 -/Parent 1584 0 R -/Kids [1536 0 R 1545 0 R] +/Count 6 +/Parent 1636 0 R +/Kids [1568 0 R 1576 0 R 1581 0 R 1585 0 R 1589 0 R 1597 0 R] >> endobj -1581 0 obj << +1633 0 obj << /Type /Pages /Count 36 -/Parent 1585 0 R -/Kids [435 0 R 572 0 R 676 0 R 729 0 R 780 0 R 825 0 R] +/Parent 1637 0 R +/Kids [451 0 R 592 0 R 696 0 R 749 0 R 800 0 R 845 0 R] >> endobj -1582 0 obj << +1634 0 obj << /Type /Pages /Count 36 -/Parent 1585 0 R -/Kids [870 0 R 921 0 R 962 0 R 1014 0 R 1054 0 R 1094 0 R] +/Parent 1637 0 R +/Kids [890 0 R 941 0 R 982 0 R 1034 0 R 1074 0 R 1114 0 R] >> endobj -1583 0 obj << +1635 0 obj << /Type /Pages /Count 36 -/Parent 1585 0 R -/Kids [1140 0 R 1192 0 R 1229 0 R 1275 0 R 1322 0 R 1357 0 R] +/Parent 1637 0 R +/Kids [1160 0 R 1212 0 R 1249 0 R 1295 0 R 1341 0 R 1389 0 R] >> endobj -1584 0 obj << +1636 0 obj << /Type /Pages -/Count 26 -/Parent 1585 0 R -/Kids [1398 0 R 1435 0 R 1468 0 R 1510 0 R 1543 0 R] +/Count 30 +/Parent 1637 0 R +/Kids [1422 0 R 1465 0 R 1498 0 R 1531 0 R 1574 0 R] >> endobj -1585 0 obj << +1637 0 obj << /Type /Pages -/Count 134 -/Kids [1581 0 R 1582 0 R 1583 0 R 1584 0 R] +/Count 138 +/Kids [1633 0 R 1634 0 R 1635 0 R 1636 0 R] >> endobj -1586 0 obj << +1638 0 obj << /Type /Outlines /First 7 0 R /Last 7 0 R /Count 1 >> endobj +431 0 obj << +/Title 432 0 R +/A 429 0 R +/Parent 427 0 R +>> endobj +427 0 obj << +/Title 428 0 R +/A 425 0 R +/Parent 7 0 R +/Prev 407 0 R +/First 431 0 R +/Last 431 0 R +/Count -1 +>> endobj +423 0 obj << +/Title 424 0 R +/A 421 0 R +/Parent 407 0 R +/Prev 419 0 R +>> endobj +419 0 obj << +/Title 420 0 R +/A 417 0 R +/Parent 407 0 R +/Prev 415 0 R +/Next 423 0 R +>> endobj 415 0 obj << /Title 416 0 R /A 413 0 R -/Parent 411 0 R +/Parent 407 0 R +/Prev 411 0 R +/Next 419 0 R >> endobj 411 0 obj << /Title 412 0 R /A 409 0 R -/Parent 7 0 R -/Prev 391 0 R -/First 415 0 R -/Last 415 0 R -/Count -1 +/Parent 407 0 R +/Next 415 0 R >> endobj 407 0 obj << /Title 408 0 R /A 405 0 R -/Parent 391 0 R -/Prev 403 0 R +/Parent 7 0 R +/Prev 387 0 R +/Next 427 0 R +/First 411 0 R +/Last 423 0 R +/Count -4 >> endobj 403 0 obj << /Title 404 0 R /A 401 0 R -/Parent 391 0 R +/Parent 387 0 R /Prev 399 0 R -/Next 407 0 R >> endobj 399 0 obj << /Title 400 0 R /A 397 0 R -/Parent 391 0 R +/Parent 387 0 R /Prev 395 0 R /Next 403 0 R >> endobj 395 0 obj << /Title 396 0 R /A 393 0 R -/Parent 391 0 R +/Parent 387 0 R +/Prev 391 0 R /Next 399 0 R >> endobj 391 0 obj << /Title 392 0 R /A 389 0 R -/Parent 7 0 R -/Prev 371 0 R -/Next 411 0 R -/First 395 0 R -/Last 407 0 R -/Count -4 +/Parent 387 0 R +/Next 395 0 R >> endobj 387 0 obj << /Title 388 0 R /A 385 0 R -/Parent 371 0 R -/Prev 383 0 R +/Parent 7 0 R +/Prev 367 0 R +/Next 407 0 R +/First 391 0 R +/Last 403 0 R +/Count -4 >> endobj 383 0 obj << /Title 384 0 R /A 381 0 R -/Parent 371 0 R +/Parent 367 0 R /Prev 379 0 R -/Next 387 0 R >> endobj 379 0 obj << /Title 380 0 R /A 377 0 R -/Parent 371 0 R +/Parent 367 0 R /Prev 375 0 R /Next 383 0 R >> endobj 375 0 obj << /Title 376 0 R /A 373 0 R -/Parent 371 0 R +/Parent 367 0 R +/Prev 371 0 R /Next 379 0 R >> endobj 371 0 obj << /Title 372 0 R /A 369 0 R -/Parent 7 0 R -/Prev 351 0 R -/Next 391 0 R -/First 375 0 R -/Last 387 0 R -/Count -4 +/Parent 367 0 R +/Next 375 0 R >> endobj 367 0 obj << /Title 368 0 R /A 365 0 R -/Parent 351 0 R -/Prev 363 0 R +/Parent 7 0 R +/Prev 299 0 R +/Next 387 0 R +/First 371 0 R +/Last 383 0 R +/Count -4 >> endobj 363 0 obj << /Title 364 0 R /A 361 0 R -/Parent 351 0 R +/Parent 299 0 R /Prev 359 0 R -/Next 367 0 R >> endobj 359 0 obj << /Title 360 0 R /A 357 0 R -/Parent 351 0 R +/Parent 299 0 R /Prev 355 0 R /Next 363 0 R >> endobj 355 0 obj << /Title 356 0 R /A 353 0 R -/Parent 351 0 R +/Parent 299 0 R +/Prev 351 0 R /Next 359 0 R >> endobj 351 0 obj << /Title 352 0 R /A 349 0 R -/Parent 7 0 R -/Prev 283 0 R -/Next 371 0 R -/First 355 0 R -/Last 367 0 R -/Count -4 +/Parent 299 0 R +/Prev 347 0 R +/Next 355 0 R >> endobj 347 0 obj << /Title 348 0 R /A 345 0 R -/Parent 283 0 R +/Parent 299 0 R /Prev 343 0 R +/Next 351 0 R >> endobj 343 0 obj << /Title 344 0 R /A 341 0 R -/Parent 283 0 R +/Parent 299 0 R /Prev 339 0 R /Next 347 0 R >> endobj 339 0 obj << /Title 340 0 R /A 337 0 R -/Parent 283 0 R +/Parent 299 0 R /Prev 335 0 R /Next 343 0 R >> endobj 335 0 obj << /Title 336 0 R /A 333 0 R -/Parent 283 0 R +/Parent 299 0 R /Prev 331 0 R /Next 339 0 R >> endobj 331 0 obj << /Title 332 0 R /A 329 0 R -/Parent 283 0 R +/Parent 299 0 R /Prev 327 0 R /Next 335 0 R >> endobj 327 0 obj << /Title 328 0 R /A 325 0 R -/Parent 283 0 R +/Parent 299 0 R /Prev 323 0 R /Next 331 0 R >> endobj 323 0 obj << /Title 324 0 R /A 321 0 R -/Parent 283 0 R +/Parent 299 0 R /Prev 319 0 R /Next 327 0 R >> endobj 319 0 obj << /Title 320 0 R /A 317 0 R -/Parent 283 0 R +/Parent 299 0 R /Prev 315 0 R /Next 323 0 R >> endobj 315 0 obj << /Title 316 0 R /A 313 0 R -/Parent 283 0 R +/Parent 299 0 R /Prev 311 0 R /Next 319 0 R >> endobj 311 0 obj << /Title 312 0 R /A 309 0 R -/Parent 283 0 R +/Parent 299 0 R /Prev 307 0 R /Next 315 0 R >> endobj 307 0 obj << /Title 308 0 R /A 305 0 R -/Parent 283 0 R +/Parent 299 0 R /Prev 303 0 R /Next 311 0 R >> endobj 303 0 obj << /Title 304 0 R /A 301 0 R -/Parent 283 0 R -/Prev 299 0 R +/Parent 299 0 R /Next 307 0 R >> endobj 299 0 obj << /Title 300 0 R /A 297 0 R -/Parent 283 0 R -/Prev 295 0 R -/Next 303 0 R +/Parent 7 0 R +/Prev 175 0 R +/Next 367 0 R +/First 303 0 R +/Last 363 0 R +/Count -16 >> endobj 295 0 obj << /Title 296 0 R /A 293 0 R -/Parent 283 0 R +/Parent 175 0 R /Prev 291 0 R -/Next 299 0 R >> endobj 291 0 obj << /Title 292 0 R /A 289 0 R -/Parent 283 0 R +/Parent 175 0 R /Prev 287 0 R /Next 295 0 R >> endobj 287 0 obj << /Title 288 0 R /A 285 0 R -/Parent 283 0 R +/Parent 175 0 R +/Prev 283 0 R /Next 291 0 R >> endobj 283 0 obj << /Title 284 0 R /A 281 0 R -/Parent 7 0 R -/Prev 175 0 R -/Next 351 0 R -/First 287 0 R -/Last 347 0 R -/Count -16 +/Parent 175 0 R +/Prev 279 0 R +/Next 287 0 R >> endobj 279 0 obj << /Title 280 0 R /A 277 0 R /Parent 175 0 R /Prev 275 0 R +/Next 283 0 R >> endobj 275 0 obj << /Title 276 0 R @@ -35368,10 +36684,10 @@ endobj /A 173 0 R /Parent 7 0 R /Prev 155 0 R -/Next 283 0 R +/Next 299 0 R /First 179 0 R -/Last 279 0 R -/Count -26 +/Last 295 0 R +/Count -30 >> endobj 171 0 obj << /Title 172 0 R @@ -35669,1635 +36985,1687 @@ endobj 7 0 obj << /Title 8 0 R /A 5 0 R -/Parent 1586 0 R +/Parent 1638 0 R /First 11 0 R -/Last 411 0 R +/Last 427 0 R /Count -11 >> endobj -1587 0 obj << -/Names [(Doc-Start) 422 0 R (Hfootnote.1) 618 0 R (Hfootnote.2) 622 0 R (Hfootnote.3) 1487 0 R (Item.1) 651 0 R (Item.10) 660 0 R (Item.11) 665 0 R (Item.12) 666 0 R (Item.13) 667 0 R (Item.14) 668 0 R (Item.15) 669 0 R (Item.16) 670 0 R (Item.17) 671 0 R (Item.18) 672 0 R (Item.19) 673 0 R (Item.2) 652 0 R (Item.20) 674 0 R (Item.21) 675 0 R (Item.22) 689 0 R (Item.23) 690 0 R (Item.24) 691 0 R (Item.25) 692 0 R (Item.26) 693 0 R (Item.27) 694 0 R (Item.28) 699 0 R (Item.29) 700 0 R (Item.3) 653 0 R (Item.30) 701 0 R (Item.31) 702 0 R (Item.32) 703 0 R (Item.33) 704 0 R (Item.34) 705 0 R (Item.35) 719 0 R (Item.36) 724 0 R (Item.37) 725 0 R (Item.38) 726 0 R (Item.39) 775 0 R (Item.4) 654 0 R (Item.40) 1003 0 R (Item.41) 1004 0 R (Item.42) 1005 0 R (Item.43) 1066 0 R (Item.44) 1071 0 R (Item.45) 1083 0 R (Item.46) 1084 0 R (Item.47) 1093 0 R (Item.48) 1120 0 R (Item.49) 1121 0 R (Item.5) 655 0 R (Item.50) 1130 0 R (Item.51) 1131 0 R (Item.52) 1132 0 R (Item.53) 1147 0 R (Item.54) 1148 0 R (Item.55) 1149 0 R (Item.56) 1150 0 R (Item.57) 1151 0 R (Item.58) 1152 0 R (Item.59) 1165 0 R (Item.6) 656 0 R (Item.60) 1166 0 R (Item.61) 1167 0 R (Item.62) 1168 0 R (Item.63) 1169 0 R (Item.64) 1185 0 R (Item.65) 1204 0 R (Item.66) 1205 0 R (Item.67) 1235 0 R (Item.68) 1236 0 R (Item.69) 1250 0 R (Item.7) 657 0 R (Item.70) 1251 0 R (Item.71) 1259 0 R (Item.72) 1260 0 R (Item.73) 1272 0 R (Item.74) 1273 0 R (Item.75) 1274 0 R (Item.76) 1294 0 R (Item.77) 1295 0 R (Item.78) 1296 0 R (Item.79) 1297 0 R (Item.8) 658 0 R (Item.80) 1298 0 R (Item.81) 1299 0 R (Item.82) 1300 0 R (Item.83) 1301 0 R (Item.84) 1312 0 R (Item.85) 1313 0 R (Item.86) 1320 0 R (Item.87) 1321 0 R (Item.88) 1329 0 R (Item.89) 1330 0 R (Item.9) 659 0 R (Item.90) 1331 0 R (Item.91) 1369 0 R (Item.92) 1376 0 R (Item.93) 1383 0 R (Item.94) 1390 0 R (Item.95) 1397 0 R (Item.96) 1405 0 R (Item.97) 1412 0 R (cite.2007c) 636 0 R (cite.2007d) 637 0 R (cite.BLACS) 595 0 R (cite.BLAS1) 577 0 R (cite.BLAS2) 578 0 R (cite.BLAS3) 579 0 R (cite.KIVA3PSBLAS) 1542 0 R (cite.METIS) 623 0 R (cite.MPI1) 1548 0 R (cite.PARA04FOREST) 1540 0 R (cite.PSBLAS) 1541 0 R (cite.machiels) 574 0 R (cite.metcalf) 573 0 R (cite.sblas02) 576 0 R (cite.sblas97) 575 0 R (descdata) 686 0 R (equation.1) 902 0 R (equation.2) 903 0 R (equation.3) 904 0 R (figure.1) 590 0 R (figure.2) 631 0 R (figure.3) 706 0 R (figure.4) 718 0 R (figure.5) 730 0 R (figure.6) 969 0 R (figure.7) 1009 0 R (figure.8) 1419 0 R (figure.9) 1420 0 R (page.1) 421 0 R (page.10) 698 0 R (page.100) 1373 0 R (page.101) 1380 0 R (page.102) 1387 0 R (page.103) 1394 0 R (page.104) 1402 0 R (page.105) 1409 0 R (page.106) 1416 0 R (page.107) 1424 0 R (page.108) 1428 0 R (page.109) 1433 0 R (page.11) 710 0 R (page.110) 1439 0 R (page.111) 1444 0 R (page.112) 1449 0 R (page.113) 1453 0 R (page.114) 1459 0 R (page.115) 1465 0 R (page.116) 1472 0 R (page.117) 1478 0 R (page.118) 1482 0 R (page.119) 1491 0 R (page.12) 716 0 R (page.120) 1500 0 R (page.121) 1507 0 R (page.122) 1514 0 R (page.123) 1518 0 R (page.124) 1525 0 R (page.125) 1530 0 R (page.126) 1534 0 R (page.127) 1538 0 R (page.128) 1547 0 R (page.13) 723 0 R (page.14) 734 0 R (page.15) 745 0 R (page.16) 754 0 R (page.17) 762 0 R (page.18) 769 0 R (page.19) 779 0 R (page.2) 439 0 R (page.20) 784 0 R (page.21) 794 0 R (page.22) 800 0 R (page.23) 809 0 R (page.24) 814 0 R (page.25) 823 0 R (page.26) 829 0 R (page.27) 837 0 R (page.28) 845 0 R (page.29) 853 0 R (page.3) 599 0 R (page.30) 861 0 R (page.31) 865 0 R (page.32) 874 0 R (page.33) 878 0 R (page.34) 886 0 R (page.35) 890 0 R (page.36) 901 0 R (page.37) 912 0 R (page.38) 925 0 R (page.39) 929 0 R (page.4) 628 0 R (page.40) 935 0 R (page.41) 945 0 R (page.42) 951 0 R (page.43) 956 0 R (page.44) 967 0 R (page.45) 978 0 R (page.46) 984 0 R (page.47) 991 0 R (page.48) 1000 0 R (page.49) 1013 0 R (page.5) 641 0 R (page.50) 1018 0 R (page.51) 1027 0 R (page.52) 1036 0 R (page.53) 1040 0 R (page.54) 1048 0 R (page.55) 1053 0 R (page.56) 1058 0 R (page.57) 1063 0 R (page.58) 1070 0 R (page.59) 1075 0 R (page.6) 647 0 R (page.60) 1081 0 R (page.61) 1088 0 R (page.62) 1098 0 R (page.63) 1105 0 R (page.64) 1111 0 R (page.65) 1118 0 R (page.66) 1125 0 R (page.67) 1136 0 R (page.68) 1144 0 R (page.69) 1156 0 R (page.7) 664 0 R (page.70) 1163 0 R (page.71) 1173 0 R (page.72) 1180 0 R (page.73) 1189 0 R (page.74) 1196 0 R (page.75) 1202 0 R (page.76) 1209 0 R (page.77) 1215 0 R (page.78) 1221 0 R (page.79) 1226 0 R (page.8) 680 0 R (page.80) 1233 0 R (page.81) 1240 0 R (page.82) 1246 0 R (page.83) 1255 0 R (page.84) 1264 0 R (page.85) 1270 0 R (page.86) 1279 0 R (page.87) 1287 0 R (page.88) 1292 0 R (page.89) 1305 0 R (page.9) 685 0 R (page.90) 1309 0 R (page.91) 1317 0 R (page.92) 1326 0 R (page.93) 1335 0 R (page.94) 1340 0 R (page.95) 1345 0 R (page.96) 1350 0 R (page.97) 1355 0 R (page.98) 1361 0 R (page.99) 1366 0 R (page.i) 443 0 R (page.ii) 489 0 R (page.iii) 537 0 R (page.iv) 558 0 R (precdata) 727 0 R (section*.1) 444 0 R (section*.10) 78 0 R (section*.100) 1222 0 R (section*.101) 242 0 R (section*.102) 1227 0 R (section*.103) 1234 0 R (section*.104) 246 0 R (section*.105) 1241 0 R (section*.106) 250 0 R (section*.107) 1247 0 R (section*.108) 1249 0 R (section*.109) 254 0 R (section*.11) 756 0 R (section*.110) 1256 0 R (section*.111) 1258 0 R (section*.112) 258 0 R (section*.113) 1265 0 R (section*.114) 1271 0 R (section*.115) 262 0 R (section*.116) 1280 0 R (section*.117) 266 0 R (section*.118) 270 0 R (section*.119) 274 0 R (section*.12) 82 0 R (section*.120) 278 0 R (section*.121) 1288 0 R (section*.122) 1293 0 R (section*.123) 286 0 R (section*.124) 1310 0 R (section*.125) 1311 0 R (section*.126) 290 0 R (section*.127) 1318 0 R (section*.128) 1319 0 R (section*.129) 294 0 R (section*.13) 758 0 R (section*.130) 1327 0 R (section*.131) 1328 0 R (section*.132) 298 0 R (section*.133) 1336 0 R (section*.134) 302 0 R (section*.135) 1341 0 R (section*.136) 306 0 R (section*.137) 1346 0 R (section*.138) 310 0 R (section*.139) 1351 0 R (section*.14) 86 0 R (section*.140) 314 0 R (section*.141) 1356 0 R (section*.142) 318 0 R (section*.143) 1362 0 R (section*.144) 322 0 R (section*.145) 1367 0 R (section*.146) 1368 0 R (section*.147) 326 0 R (section*.148) 1374 0 R (section*.149) 1375 0 R (section*.15) 763 0 R (section*.150) 330 0 R (section*.151) 1381 0 R (section*.152) 1382 0 R (section*.153) 334 0 R (section*.154) 1388 0 R (section*.155) 1389 0 R (section*.156) 338 0 R (section*.157) 1395 0 R (section*.158) 1396 0 R (section*.159) 342 0 R (section*.16) 90 0 R (section*.160) 1403 0 R (section*.161) 1404 0 R (section*.162) 346 0 R (section*.163) 1410 0 R (section*.164) 1411 0 R (section*.165) 354 0 R (section*.166) 1429 0 R (section*.167) 358 0 R (section*.168) 1434 0 R (section*.169) 362 0 R (section*.17) 764 0 R (section*.170) 1440 0 R (section*.171) 366 0 R (section*.172) 1445 0 R (section*.173) 374 0 R (section*.174) 1454 0 R (section*.175) 378 0 R (section*.176) 1460 0 R (section*.177) 382 0 R (section*.178) 1466 0 R (section*.179) 386 0 R (section*.18) 94 0 R (section*.180) 1473 0 R (section*.181) 394 0 R (section*.182) 1483 0 R (section*.183) 1485 0 R (section*.184) 398 0 R (section*.185) 1492 0 R (section*.186) 402 0 R (section*.187) 1501 0 R (section*.188) 406 0 R (section*.189) 1508 0 R (section*.19) 770 0 R (section*.190) 414 0 R (section*.191) 1519 0 R (section*.192) 1539 0 R (section*.2) 62 0 R (section*.20) 98 0 R (section*.21) 772 0 R (section*.22) 774 0 R (section*.23) 106 0 R (section*.24) 785 0 R (section*.25) 110 0 R (section*.26) 801 0 R (section*.27) 114 0 R (section*.28) 815 0 R (section*.29) 118 0 R (section*.3) 738 0 R (section*.30) 830 0 R (section*.31) 122 0 R (section*.32) 838 0 R (section*.33) 126 0 R (section*.34) 846 0 R (section*.35) 130 0 R (section*.36) 854 0 R (section*.37) 134 0 R (section*.38) 867 0 R (section*.39) 138 0 R (section*.4) 66 0 R (section*.40) 879 0 R (section*.41) 142 0 R (section*.42) 895 0 R (section*.43) 146 0 R (section*.44) 906 0 R (section*.45) 150 0 R (section*.46) 930 0 R (section*.47) 158 0 R (section*.48) 958 0 R (section*.49) 979 0 R (section*.5) 741 0 R (section*.50) 162 0 R (section*.51) 993 0 R (section*.52) 1002 0 R (section*.53) 1006 0 R (section*.54) 166 0 R (section*.55) 1029 0 R (section*.56) 1030 0 R (section*.57) 170 0 R (section*.58) 1042 0 R (section*.59) 1043 0 R (section*.6) 70 0 R (section*.60) 178 0 R (section*.61) 1059 0 R (section*.62) 1065 0 R (section*.63) 182 0 R (section*.64) 1076 0 R (section*.65) 1082 0 R (section*.66) 186 0 R (section*.67) 1089 0 R (section*.68) 1092 0 R (section*.69) 190 0 R (section*.7) 748 0 R (section*.70) 1099 0 R (section*.71) 194 0 R (section*.72) 1106 0 R (section*.73) 198 0 R (section*.74) 1112 0 R (section*.75) 1119 0 R (section*.76) 202 0 R (section*.77) 1126 0 R (section*.78) 1129 0 R (section*.79) 206 0 R (section*.8) 74 0 R (section*.80) 1137 0 R (section*.81) 1146 0 R (section*.82) 210 0 R (section*.83) 1157 0 R (section*.84) 1164 0 R (section*.85) 214 0 R (section*.86) 1174 0 R (section*.87) 218 0 R (section*.88) 1181 0 R (section*.89) 1184 0 R (section*.9) 750 0 R (section*.90) 222 0 R (section*.91) 1190 0 R (section*.92) 226 0 R (section*.93) 1197 0 R (section*.94) 1203 0 R (section*.95) 230 0 R (section*.96) 1210 0 R (section*.97) 234 0 R (section*.98) 1216 0 R (section*.99) 238 0 R (section.1) 10 0 R (section.10) 390 0 R (section.11) 410 0 R (section.2) 14 0 R (section.3) 34 0 R (section.4) 102 0 R (section.5) 154 0 R (section.6) 174 0 R (section.7) 282 0 R (section.8) 350 0 R (section.9) 370 0 R (spdata) 712 0 R (subsection.2.1) 18 0 R (subsection.2.2) 22 0 R (subsection.2.3) 26 0 R (subsection.2.4) 30 0 R (subsection.3.1) 38 0 R (subsection.3.2) 46 0 R (subsection.3.3) 54 0 R (subsection.3.4) 58 0 R (subsubsection.3.1.1) 42 0 R (subsubsection.3.2.1) 50 0 R (table.1) 786 0 R (table.10) 894 0 R (table.11) 905 0 R (table.12) 931 0 R (table.13) 957 0 R (table.14) 992 0 R (table.15) 1028 0 R (table.16) 1041 0 R (table.2) 802 0 R (table.3) 816 0 R (table.4) 831 0 R (table.5) 839 0 R (table.6) 847 0 R (table.7) 855 0 R (table.8) 866 0 R (table.9) 880 0 R (title.0) 6 0 R] +1639 0 obj << +/Names [(Doc-Start) 438 0 R (Hfootnote.1) 638 0 R (Hfootnote.2) 642 0 R (Hfootnote.3) 1540 0 R (Item.1) 671 0 R (Item.10) 680 0 R (Item.100) 1457 0 R (Item.101) 1464 0 R (Item.11) 685 0 R (Item.12) 686 0 R (Item.13) 687 0 R (Item.14) 688 0 R (Item.15) 689 0 R (Item.16) 690 0 R (Item.17) 691 0 R (Item.18) 692 0 R (Item.19) 693 0 R (Item.2) 672 0 R (Item.20) 694 0 R (Item.21) 695 0 R (Item.22) 709 0 R (Item.23) 710 0 R (Item.24) 711 0 R (Item.25) 712 0 R (Item.26) 713 0 R (Item.27) 714 0 R (Item.28) 719 0 R (Item.29) 720 0 R (Item.3) 673 0 R (Item.30) 721 0 R (Item.31) 722 0 R (Item.32) 723 0 R (Item.33) 724 0 R (Item.34) 725 0 R (Item.35) 739 0 R (Item.36) 744 0 R (Item.37) 745 0 R (Item.38) 746 0 R (Item.39) 795 0 R (Item.4) 674 0 R (Item.40) 1023 0 R (Item.41) 1024 0 R (Item.42) 1025 0 R (Item.43) 1086 0 R (Item.44) 1091 0 R (Item.45) 1103 0 R (Item.46) 1104 0 R (Item.47) 1113 0 R (Item.48) 1140 0 R (Item.49) 1141 0 R (Item.5) 675 0 R (Item.50) 1150 0 R (Item.51) 1151 0 R (Item.52) 1152 0 R (Item.53) 1167 0 R (Item.54) 1168 0 R (Item.55) 1169 0 R (Item.56) 1170 0 R (Item.57) 1171 0 R (Item.58) 1172 0 R (Item.59) 1185 0 R (Item.6) 676 0 R (Item.60) 1186 0 R (Item.61) 1187 0 R (Item.62) 1188 0 R (Item.63) 1189 0 R (Item.64) 1205 0 R (Item.65) 1224 0 R (Item.66) 1225 0 R (Item.67) 1255 0 R (Item.68) 1256 0 R (Item.69) 1270 0 R (Item.7) 677 0 R (Item.70) 1278 0 R (Item.71) 1286 0 R (Item.72) 1294 0 R (Item.73) 1303 0 R (Item.74) 1304 0 R (Item.75) 1312 0 R (Item.76) 1313 0 R (Item.77) 1325 0 R (Item.78) 1326 0 R (Item.79) 1327 0 R (Item.8) 678 0 R (Item.80) 1347 0 R (Item.81) 1348 0 R (Item.82) 1349 0 R (Item.83) 1350 0 R (Item.84) 1351 0 R (Item.85) 1352 0 R (Item.86) 1353 0 R (Item.87) 1354 0 R (Item.88) 1365 0 R (Item.89) 1366 0 R (Item.9) 679 0 R (Item.90) 1373 0 R (Item.91) 1374 0 R (Item.92) 1381 0 R (Item.93) 1382 0 R (Item.94) 1383 0 R (Item.95) 1421 0 R (Item.96) 1429 0 R (Item.97) 1436 0 R (Item.98) 1443 0 R (Item.99) 1450 0 R (cite.2007c) 656 0 R (cite.2007d) 657 0 R (cite.BLACS) 615 0 R (cite.BLAS1) 597 0 R (cite.BLAS2) 598 0 R (cite.BLAS3) 599 0 R (cite.KIVA3PSBLAS) 1595 0 R (cite.METIS) 643 0 R (cite.MPI1) 1600 0 R (cite.PARA04FOREST) 1593 0 R (cite.PSBLAS) 1594 0 R (cite.machiels) 594 0 R (cite.metcalf) 593 0 R (cite.sblas02) 596 0 R (cite.sblas97) 595 0 R (descdata) 706 0 R (equation.1) 922 0 R (equation.2) 923 0 R (equation.3) 924 0 R (figure.1) 610 0 R (figure.2) 651 0 R (figure.3) 726 0 R (figure.4) 738 0 R (figure.5) 750 0 R (figure.6) 989 0 R (figure.7) 1029 0 R (figure.8) 1472 0 R (figure.9) 1473 0 R (page.1) 437 0 R (page.10) 718 0 R (page.100) 1403 0 R (page.101) 1408 0 R (page.102) 1413 0 R (page.103) 1418 0 R (page.104) 1426 0 R (page.105) 1433 0 R (page.106) 1440 0 R (page.107) 1447 0 R (page.108) 1454 0 R (page.109) 1461 0 R (page.11) 730 0 R (page.110) 1469 0 R (page.111) 1477 0 R (page.112) 1481 0 R (page.113) 1486 0 R (page.114) 1491 0 R (page.115) 1496 0 R (page.116) 1502 0 R (page.117) 1506 0 R (page.118) 1512 0 R (page.119) 1518 0 R (page.12) 736 0 R (page.120) 1524 0 R (page.121) 1530 0 R (page.122) 1535 0 R (page.123) 1544 0 R (page.124) 1553 0 R (page.125) 1560 0 R (page.126) 1566 0 R (page.127) 1570 0 R (page.128) 1578 0 R (page.129) 1583 0 R (page.13) 743 0 R (page.130) 1587 0 R (page.131) 1591 0 R (page.132) 1599 0 R (page.14) 754 0 R (page.15) 765 0 R (page.16) 774 0 R (page.17) 782 0 R (page.18) 789 0 R (page.19) 799 0 R (page.2) 455 0 R (page.20) 804 0 R (page.21) 814 0 R (page.22) 820 0 R (page.23) 829 0 R (page.24) 834 0 R (page.25) 843 0 R (page.26) 849 0 R (page.27) 857 0 R (page.28) 865 0 R (page.29) 873 0 R (page.3) 619 0 R (page.30) 881 0 R (page.31) 885 0 R (page.32) 894 0 R (page.33) 898 0 R (page.34) 906 0 R (page.35) 910 0 R (page.36) 921 0 R (page.37) 932 0 R (page.38) 945 0 R (page.39) 949 0 R (page.4) 648 0 R (page.40) 955 0 R (page.41) 965 0 R (page.42) 971 0 R (page.43) 976 0 R (page.44) 987 0 R (page.45) 998 0 R (page.46) 1004 0 R (page.47) 1011 0 R (page.48) 1020 0 R (page.49) 1033 0 R (page.5) 661 0 R (page.50) 1038 0 R (page.51) 1047 0 R (page.52) 1056 0 R (page.53) 1060 0 R (page.54) 1068 0 R (page.55) 1073 0 R (page.56) 1078 0 R (page.57) 1083 0 R (page.58) 1090 0 R (page.59) 1095 0 R (page.6) 667 0 R (page.60) 1101 0 R (page.61) 1108 0 R (page.62) 1118 0 R (page.63) 1125 0 R (page.64) 1131 0 R (page.65) 1138 0 R (page.66) 1145 0 R (page.67) 1156 0 R (page.68) 1164 0 R (page.69) 1176 0 R (page.7) 684 0 R (page.70) 1183 0 R (page.71) 1193 0 R (page.72) 1200 0 R (page.73) 1209 0 R (page.74) 1216 0 R (page.75) 1222 0 R (page.76) 1229 0 R (page.77) 1235 0 R (page.78) 1241 0 R (page.79) 1246 0 R (page.8) 700 0 R (page.80) 1253 0 R (page.81) 1260 0 R (page.82) 1266 0 R (page.83) 1274 0 R (page.84) 1282 0 R (page.85) 1290 0 R (page.86) 1299 0 R (page.87) 1308 0 R (page.88) 1317 0 R (page.89) 1323 0 R (page.9) 705 0 R (page.90) 1331 0 R (page.91) 1339 0 R (page.92) 1345 0 R (page.93) 1358 0 R (page.94) 1362 0 R (page.95) 1370 0 R (page.96) 1378 0 R (page.97) 1387 0 R (page.98) 1393 0 R (page.99) 1398 0 R (page.i) 459 0 R (page.ii) 505 0 R (page.iii) 557 0 R (page.iv) 578 0 R (precdata) 747 0 R (section*.1) 460 0 R (section*.10) 78 0 R (section*.100) 1242 0 R (section*.101) 242 0 R (section*.102) 1247 0 R (section*.103) 1254 0 R (section*.104) 246 0 R (section*.105) 1261 0 R (section*.106) 250 0 R (section*.107) 1267 0 R (section*.108) 1269 0 R (section*.109) 254 0 R (section*.11) 776 0 R (section*.110) 1275 0 R (section*.111) 1277 0 R (section*.112) 258 0 R (section*.113) 1283 0 R (section*.114) 1285 0 R (section*.115) 262 0 R (section*.116) 1291 0 R (section*.117) 1293 0 R (section*.118) 266 0 R (section*.119) 1300 0 R (section*.12) 82 0 R (section*.120) 1302 0 R (section*.121) 270 0 R (section*.122) 1309 0 R (section*.123) 1311 0 R (section*.124) 274 0 R (section*.125) 1318 0 R (section*.126) 1324 0 R (section*.127) 278 0 R (section*.128) 1332 0 R (section*.129) 282 0 R (section*.13) 778 0 R (section*.130) 286 0 R (section*.131) 290 0 R (section*.132) 294 0 R (section*.133) 1340 0 R (section*.134) 1346 0 R (section*.135) 302 0 R (section*.136) 1363 0 R (section*.137) 1364 0 R (section*.138) 306 0 R (section*.139) 1371 0 R (section*.14) 86 0 R (section*.140) 1372 0 R (section*.141) 310 0 R (section*.142) 1379 0 R (section*.143) 1380 0 R (section*.144) 314 0 R (section*.145) 1388 0 R (section*.146) 318 0 R (section*.147) 1394 0 R (section*.148) 322 0 R (section*.149) 1399 0 R (section*.15) 783 0 R (section*.150) 326 0 R (section*.151) 1404 0 R (section*.152) 330 0 R (section*.153) 1409 0 R (section*.154) 334 0 R (section*.155) 1414 0 R (section*.156) 338 0 R (section*.157) 1419 0 R (section*.158) 1420 0 R (section*.159) 342 0 R (section*.16) 90 0 R (section*.160) 1427 0 R (section*.161) 1428 0 R (section*.162) 346 0 R (section*.163) 1434 0 R (section*.164) 1435 0 R (section*.165) 350 0 R (section*.166) 1441 0 R (section*.167) 1442 0 R (section*.168) 354 0 R (section*.169) 1448 0 R (section*.17) 784 0 R (section*.170) 1449 0 R (section*.171) 358 0 R (section*.172) 1455 0 R (section*.173) 1456 0 R (section*.174) 362 0 R (section*.175) 1462 0 R (section*.176) 1463 0 R (section*.177) 370 0 R (section*.178) 1482 0 R (section*.179) 374 0 R (section*.18) 94 0 R (section*.180) 1487 0 R (section*.181) 378 0 R (section*.182) 1492 0 R (section*.183) 382 0 R (section*.184) 1497 0 R (section*.185) 390 0 R (section*.186) 1507 0 R (section*.187) 394 0 R (section*.188) 1513 0 R (section*.189) 398 0 R (section*.19) 790 0 R (section*.190) 1519 0 R (section*.191) 402 0 R (section*.192) 1525 0 R (section*.193) 410 0 R (section*.194) 1536 0 R (section*.195) 1538 0 R (section*.196) 414 0 R (section*.197) 1545 0 R (section*.198) 418 0 R (section*.199) 1554 0 R (section*.2) 62 0 R (section*.20) 98 0 R (section*.200) 422 0 R (section*.201) 1561 0 R (section*.202) 430 0 R (section*.203) 1571 0 R (section*.204) 1592 0 R (section*.21) 792 0 R (section*.22) 794 0 R (section*.23) 106 0 R (section*.24) 805 0 R (section*.25) 110 0 R (section*.26) 821 0 R (section*.27) 114 0 R (section*.28) 835 0 R (section*.29) 118 0 R (section*.3) 758 0 R (section*.30) 850 0 R (section*.31) 122 0 R (section*.32) 858 0 R (section*.33) 126 0 R (section*.34) 866 0 R (section*.35) 130 0 R (section*.36) 874 0 R (section*.37) 134 0 R (section*.38) 887 0 R (section*.39) 138 0 R (section*.4) 66 0 R (section*.40) 899 0 R (section*.41) 142 0 R (section*.42) 915 0 R (section*.43) 146 0 R (section*.44) 926 0 R (section*.45) 150 0 R (section*.46) 950 0 R (section*.47) 158 0 R (section*.48) 978 0 R (section*.49) 999 0 R (section*.5) 761 0 R (section*.50) 162 0 R (section*.51) 1013 0 R (section*.52) 1022 0 R (section*.53) 1026 0 R (section*.54) 166 0 R (section*.55) 1049 0 R (section*.56) 1050 0 R (section*.57) 170 0 R (section*.58) 1062 0 R (section*.59) 1063 0 R (section*.6) 70 0 R (section*.60) 178 0 R (section*.61) 1079 0 R (section*.62) 1085 0 R (section*.63) 182 0 R (section*.64) 1096 0 R (section*.65) 1102 0 R (section*.66) 186 0 R (section*.67) 1109 0 R (section*.68) 1112 0 R (section*.69) 190 0 R (section*.7) 768 0 R (section*.70) 1119 0 R (section*.71) 194 0 R (section*.72) 1126 0 R (section*.73) 198 0 R (section*.74) 1132 0 R (section*.75) 1139 0 R (section*.76) 202 0 R (section*.77) 1146 0 R (section*.78) 1149 0 R (section*.79) 206 0 R (section*.8) 74 0 R (section*.80) 1157 0 R (section*.81) 1166 0 R (section*.82) 210 0 R (section*.83) 1177 0 R (section*.84) 1184 0 R (section*.85) 214 0 R (section*.86) 1194 0 R (section*.87) 218 0 R (section*.88) 1201 0 R (section*.89) 1204 0 R (section*.9) 770 0 R (section*.90) 222 0 R (section*.91) 1210 0 R (section*.92) 226 0 R (section*.93) 1217 0 R (section*.94) 1223 0 R (section*.95) 230 0 R (section*.96) 1230 0 R (section*.97) 234 0 R (section*.98) 1236 0 R (section*.99) 238 0 R (section.1) 10 0 R (section.10) 406 0 R (section.11) 426 0 R (section.2) 14 0 R (section.3) 34 0 R (section.4) 102 0 R (section.5) 154 0 R (section.6) 174 0 R (section.7) 298 0 R (section.8) 366 0 R (section.9) 386 0 R (spdata) 732 0 R (subsection.2.1) 18 0 R (subsection.2.2) 22 0 R (subsection.2.3) 26 0 R (subsection.2.4) 30 0 R (subsection.3.1) 38 0 R (subsection.3.2) 46 0 R (subsection.3.3) 54 0 R (subsection.3.4) 58 0 R (subsubsection.3.1.1) 42 0 R (subsubsection.3.2.1) 50 0 R (table.1) 806 0 R (table.10) 914 0 R (table.11) 925 0 R (table.12) 951 0 R (table.13) 977 0 R (table.14) 1012 0 R (table.15) 1048 0 R (table.16) 1061 0 R (table.2) 822 0 R (table.3) 836 0 R (table.4) 851 0 R (table.5) 859 0 R (table.6) 867 0 R (table.7) 875 0 R (table.8) 886 0 R (table.9) 900 0 R (title.0) 6 0 R] /Limits [(Doc-Start) (title.0)] >> endobj -1588 0 obj << -/Kids [1587 0 R] +1640 0 obj << +/Kids [1639 0 R] >> endobj -1589 0 obj << -/Dests 1588 0 R +1641 0 obj << +/Dests 1640 0 R >> endobj -1590 0 obj << +1642 0 obj << /Type /Catalog -/Pages 1585 0 R -/Outlines 1586 0 R -/Names 1589 0 R +/Pages 1637 0 R +/Outlines 1638 0 R +/Names 1641 0 R /URI (http://ce.uniroma2.it/psblas) /PageMode /UseOutlines /PageLabels << /Nums [0 << /S /D >> 2 << /S /r >> 6 << /S /D >> ] >> -/OpenAction 417 0 R +/OpenAction 433 0 R >> endobj -1591 0 obj << +1643 0 obj << /Title (Parallel Sparse BLAS V. 2.2) /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: userguide.tex 1978 2007-10-19 14:51:12Z sfilippo $) /Author()/Title()/Subject()/Creator(LaTeX with hyperref package)/Producer(pdfeTeX-1.21a)/Keywords() -/CreationDate (D:20080305171431+01'00') +/CreationDate (D:20080415141457+02'00') /PTEX.Fullbanner (This is pdfeTeX, Version 3.141592-1.21a-2.2 (Web2C 7.5.4) kpathsea version 3.5.4) >> endobj xref -0 1592 +0 1644 0000000001 65535 f 0000000002 00000 f 0000000003 00000 f 0000000004 00000 f 0000000000 00000 f 0000000009 00000 n -0000010465 00000 n -0001191994 00000 n +0000010820 00000 n +0001227407 00000 n 0000000052 00000 n 0000000094 00000 n -0000122440 00000 n -0001191922 00000 n +0000127198 00000 n +0001227335 00000 n 0000000139 00000 n 0000000172 00000 n -0000132674 00000 n -0001191799 00000 n +0000137432 00000 n +0001227212 00000 n 0000000218 00000 n 0000000255 00000 n -0000145453 00000 n -0001191725 00000 n +0000150211 00000 n +0001227138 00000 n 0000000306 00000 n 0000000347 00000 n -0000156194 00000 n -0001191638 00000 n +0000160952 00000 n +0001227051 00000 n 0000000398 00000 n 0000000437 00000 n -0000167461 00000 n -0001191551 00000 n +0000172219 00000 n +0001226964 00000 n 0000000488 00000 n 0000000532 00000 n -0000191996 00000 n -0001191477 00000 n +0000196754 00000 n +0001226890 00000 n 0000000583 00000 n 0000000623 00000 n -0000207063 00000 n -0001191353 00000 n +0000211821 00000 n +0001226766 00000 n 0000000669 00000 n 0000000705 00000 n -0000207125 00000 n -0001191242 00000 n +0000211883 00000 n +0001226655 00000 n 0000000756 00000 n 0000000804 00000 n -0000230814 00000 n -0001191181 00000 n +0000235572 00000 n +0001226594 00000 n 0000000860 00000 n 0000000900 00000 n -0000230876 00000 n -0001191057 00000 n +0000235634 00000 n +0001226470 00000 n 0000000951 00000 n 0000001002 00000 n -0000255250 00000 n -0001190996 00000 n +0000260008 00000 n +0001226409 00000 n 0000001058 00000 n 0000001098 00000 n -0000255312 00000 n -0001190909 00000 n +0000260070 00000 n +0001226322 00000 n 0000001149 00000 n 0000001201 00000 n -0000265032 00000 n -0001190797 00000 n +0000269790 00000 n +0001226210 00000 n 0000001252 00000 n 0000001304 00000 n -0000265094 00000 n -0001190723 00000 n +0000269852 00000 n +0001226136 00000 n 0000001351 00000 n 0000001403 00000 n -0000265221 00000 n -0001190636 00000 n +0000269979 00000 n +0001226049 00000 n 0000001450 00000 n 0000001502 00000 n -0000276004 00000 n -0001190549 00000 n +0000280762 00000 n +0001225962 00000 n 0000001549 00000 n 0000001602 00000 n -0000276128 00000 n -0001190462 00000 n +0000280886 00000 n +0001225875 00000 n 0000001649 00000 n 0000001702 00000 n -0000285243 00000 n -0001190375 00000 n +0000290001 00000 n +0001225788 00000 n 0000001750 00000 n 0000001796 00000 n -0000285370 00000 n -0001190288 00000 n +0000290128 00000 n +0001225701 00000 n 0000001844 00000 n 0000001901 00000 n -0000294436 00000 n -0001190201 00000 n +0000299194 00000 n +0001225614 00000 n 0000001949 00000 n 0000002006 00000 n -0000294559 00000 n -0001190114 00000 n +0000299317 00000 n +0001225527 00000 n 0000002054 00000 n 0000002098 00000 n -0000303365 00000 n -0001190027 00000 n +0000308123 00000 n +0001225440 00000 n 0000002146 00000 n 0000002190 00000 n -0000303492 00000 n -0001189952 00000 n +0000308250 00000 n +0001225365 00000 n 0000002238 00000 n 0000002285 00000 n -0000304469 00000 n -0001189822 00000 n +0000309227 00000 n +0001225235 00000 n 0000002332 00000 n 0000002376 00000 n -0000314056 00000 n -0001189743 00000 n +0000318814 00000 n +0001225156 00000 n 0000002425 00000 n 0000002459 00000 n -0000328509 00000 n -0001189650 00000 n +0000333267 00000 n +0001225063 00000 n 0000002508 00000 n 0000002540 00000 n -0000341292 00000 n -0001189557 00000 n +0000346050 00000 n +0001224970 00000 n 0000002589 00000 n 0000002622 00000 n -0000353877 00000 n -0001189464 00000 n +0000358635 00000 n +0001224877 00000 n 0000002671 00000 n 0000002704 00000 n -0000363029 00000 n -0001189371 00000 n +0000367787 00000 n +0001224784 00000 n 0000002753 00000 n 0000002787 00000 n -0000372590 00000 n -0001189278 00000 n +0000377348 00000 n +0001224691 00000 n 0000002836 00000 n 0000002869 00000 n -0000382595 00000 n -0001189185 00000 n +0000387353 00000 n +0001224598 00000 n 0000002918 00000 n 0000002952 00000 n -0000392842 00000 n -0001189092 00000 n +0000397600 00000 n +0001224505 00000 n 0000003001 00000 n 0000003034 00000 n -0000403981 00000 n -0001188999 00000 n +0000408739 00000 n +0001224412 00000 n 0000003083 00000 n 0000003117 00000 n -0000414270 00000 n -0001188906 00000 n +0000419028 00000 n +0001224319 00000 n 0000003166 00000 n 0000003199 00000 n -0000425042 00000 n -0001188813 00000 n +0000429800 00000 n +0001224226 00000 n 0000003248 00000 n 0000003279 00000 n -0000449331 00000 n -0001188734 00000 n +0000454089 00000 n +0001224147 00000 n 0000003328 00000 n 0000003359 00000 n -0000471439 00000 n -0001188604 00000 n +0000476197 00000 n +0001224017 00000 n 0000003406 00000 n 0000003450 00000 n -0000480398 00000 n -0001188525 00000 n +0000485156 00000 n +0001223938 00000 n 0000003499 00000 n 0000003530 00000 n -0000507431 00000 n -0001188432 00000 n +0000512209 00000 n +0001223845 00000 n 0000003579 00000 n 0000003610 00000 n -0000539294 00000 n -0001188339 00000 n +0000544091 00000 n +0001223752 00000 n 0000003659 00000 n 0000003692 00000 n -0000553496 00000 n -0001188260 00000 n +0000558293 00000 n +0001223673 00000 n 0000003741 00000 n 0000003775 00000 n -0000559235 00000 n -0001188129 00000 n +0000564032 00000 n +0001223542 00000 n 0000003822 00000 n 0000003868 00000 n -0000568735 00000 n -0001188050 00000 n +0000573532 00000 n +0001223463 00000 n 0000003917 00000 n 0000003949 00000 n -0000593982 00000 n -0001187957 00000 n +0000598779 00000 n +0001223370 00000 n 0000003998 00000 n 0000004030 00000 n -0000602732 00000 n -0001187864 00000 n +0000607529 00000 n +0001223277 00000 n 0000004079 00000 n 0000004111 00000 n -0000609385 00000 n -0001187771 00000 n +0000614182 00000 n +0001223184 00000 n 0000004160 00000 n 0000004192 00000 n -0000614062 00000 n -0001187678 00000 n +0000618859 00000 n +0001223091 00000 n 0000004241 00000 n 0000004274 00000 n -0000623495 00000 n -0001187585 00000 n +0000628292 00000 n +0001222998 00000 n 0000004323 00000 n 0000004358 00000 n -0000635705 00000 n -0001187492 00000 n +0000640502 00000 n +0001222905 00000 n 0000004407 00000 n 0000004439 00000 n -0000644987 00000 n -0001187399 00000 n +0000649784 00000 n +0001222812 00000 n 0000004488 00000 n 0000004520 00000 n -0000661278 00000 n -0001187306 00000 n +0000666075 00000 n +0001222719 00000 n 0000004569 00000 n 0000004601 00000 n -0000671559 00000 n -0001187213 00000 n +0000676356 00000 n +0001222626 00000 n 0000004650 00000 n 0000004683 00000 n -0000678964 00000 n -0001187120 00000 n +0000683761 00000 n +0001222533 00000 n 0000004732 00000 n 0000004763 00000 n -0000686821 00000 n -0001187027 00000 n +0000691618 00000 n +0001222440 00000 n 0000004812 00000 n 0000004844 00000 n -0000695782 00000 n -0001186934 00000 n +0000700579 00000 n +0001222347 00000 n 0000004893 00000 n 0000004925 00000 n -0000703728 00000 n -0001186841 00000 n +0000708525 00000 n +0001222254 00000 n 0000004974 00000 n 0000005006 00000 n -0000709220 00000 n -0001186748 00000 n +0000714017 00000 n +0001222161 00000 n 0000005055 00000 n 0000005088 00000 n -0000714901 00000 n -0001186655 00000 n +0000719698 00000 n +0001222068 00000 n 0000005137 00000 n 0000005168 00000 n -0000725385 00000 n -0001186562 00000 n +0000730182 00000 n +0001221975 00000 n 0000005218 00000 n 0000005262 00000 n -0000738151 00000 n -0001186469 00000 n +0000742948 00000 n +0001221882 00000 n 0000005312 00000 n 0000005356 00000 n -0000745132 00000 n -0001186376 00000 n +0000749278 00000 n +0001221789 00000 n 0000005406 00000 n -0000005448 00000 n -0000752058 00000 n -0001186283 00000 n -0000005498 00000 n -0000005539 00000 n -0000760688 00000 n -0001186190 00000 n -0000005589 00000 n -0000005628 00000 n -0000775494 00000 n -0001186097 00000 n -0000005678 00000 n -0000005711 00000 n -0000782758 00000 n -0001186004 00000 n -0000005761 00000 n -0000005798 00000 n -0000782822 00000 n -0001185911 00000 n -0000005848 00000 n -0000005880 00000 n -0000782886 00000 n -0001185818 00000 n -0000005930 00000 n -0000005962 00000 n -0000782950 00000 n -0001185739 00000 n -0000006012 00000 n -0000006044 00000 n -0000795713 00000 n -0001185608 00000 n -0000006091 00000 n -0000006142 00000 n -0000801079 00000 n -0001185529 00000 n -0000006192 00000 n -0000006223 00000 n -0000808546 00000 n -0001185436 00000 n -0000006273 00000 n -0000006304 00000 n -0000816005 00000 n -0001185343 00000 n -0000006354 00000 n -0000006385 00000 n -0000820532 00000 n -0001185250 00000 n -0000006435 00000 n -0000006476 00000 n -0000825829 00000 n -0001185157 00000 n -0000006526 00000 n -0000006564 00000 n -0000828510 00000 n -0001185064 00000 n -0000006614 00000 n -0000006646 00000 n -0000831599 00000 n -0001184971 00000 n -0000006696 00000 n -0000006730 00000 n -0000834517 00000 n -0001184878 00000 n -0000006780 00000 n -0000006812 00000 n -0000841425 00000 n -0001184785 00000 n -0000006862 00000 n -0000006894 00000 n -0000848969 00000 n -0001184692 00000 n -0000006944 00000 n -0000006974 00000 n -0000856728 00000 n -0001184599 00000 n -0000007024 00000 n +0000005444 00000 n +0000757945 00000 n +0001221696 00000 n +0000005494 00000 n +0000005535 00000 n +0000764396 00000 n +0001221603 00000 n +0000005585 00000 n +0000005623 00000 n +0000773014 00000 n +0001221510 00000 n +0000005673 00000 n +0000005714 00000 n +0000780125 00000 n +0001221417 00000 n +0000005764 00000 n +0000005806 00000 n +0000787051 00000 n +0001221324 00000 n +0000005856 00000 n +0000005897 00000 n +0000795681 00000 n +0001221231 00000 n +0000005947 00000 n +0000005986 00000 n +0000810487 00000 n +0001221138 00000 n +0000006036 00000 n +0000006069 00000 n +0000817751 00000 n +0001221045 00000 n +0000006119 00000 n +0000006156 00000 n +0000817815 00000 n +0001220952 00000 n +0000006206 00000 n +0000006238 00000 n +0000817879 00000 n +0001220859 00000 n +0000006288 00000 n +0000006320 00000 n +0000817943 00000 n +0001220780 00000 n +0000006370 00000 n +0000006402 00000 n +0000830706 00000 n +0001220649 00000 n +0000006449 00000 n +0000006500 00000 n +0000836072 00000 n +0001220570 00000 n +0000006550 00000 n +0000006581 00000 n +0000843539 00000 n +0001220477 00000 n +0000006631 00000 n +0000006662 00000 n +0000850998 00000 n +0001220384 00000 n +0000006712 00000 n +0000006743 00000 n +0000855525 00000 n +0001220291 00000 n +0000006793 00000 n +0000006834 00000 n +0000860822 00000 n +0001220198 00000 n +0000006884 00000 n +0000006922 00000 n +0000863503 00000 n +0001220105 00000 n +0000006972 00000 n +0000007004 00000 n +0000866593 00000 n +0001220012 00000 n 0000007054 00000 n -0000864499 00000 n -0001184506 00000 n -0000007104 00000 n -0000007134 00000 n -0000872260 00000 n -0001184413 00000 n -0000007184 00000 n -0000007214 00000 n -0000880040 00000 n -0001184320 00000 n -0000007264 00000 n -0000007294 00000 n -0000888188 00000 n -0001184227 00000 n -0000007344 00000 n -0000007374 00000 n -0000896312 00000 n -0001184148 00000 n -0000007424 00000 n -0000007454 00000 n -0000905437 00000 n -0001184018 00000 n -0000007501 00000 n -0000007537 00000 n -0000916382 00000 n -0001183939 00000 n -0000007587 00000 n -0000007621 00000 n -0000919040 00000 n -0001183846 00000 n -0000007671 00000 n -0000007703 00000 n -0000922005 00000 n -0001183753 00000 n -0000007753 00000 n -0000007799 00000 n -0000925514 00000 n -0001183674 00000 n -0000007849 00000 n -0000007892 00000 n -0000926810 00000 n -0001183544 00000 n -0000007939 00000 n -0000007970 00000 n -0000934107 00000 n -0001183465 00000 n -0000008020 00000 n -0000008050 00000 n -0000942265 00000 n -0001183372 00000 n -0000008100 00000 n -0000008131 00000 n -0000948372 00000 n -0001183279 00000 n -0000008181 00000 n -0000008218 00000 n -0000955126 00000 n -0001183200 00000 n -0000008268 00000 n -0000008306 00000 n -0000957152 00000 n -0001183070 00000 n -0000008354 00000 n -0000008400 00000 n -0000965271 00000 n -0001182991 00000 n -0000008450 00000 n -0000008485 00000 n -0000974353 00000 n -0001182898 00000 n -0000008535 00000 n -0000008569 00000 n -0000983670 00000 n -0001182805 00000 n -0000008619 00000 n -0000008654 00000 n -0000987383 00000 n -0001182726 00000 n -0000008704 00000 n -0000008744 00000 n -0000988771 00000 n -0001182610 00000 n -0000008792 00000 n -0000008832 00000 n -0000999757 00000 n -0001182545 00000 n -0000008882 00000 n -0000008916 00000 n -0000010217 00000 n -0000010526 00000 n -0000008968 00000 n -0000010339 00000 n -0000010402 00000 n -0001177944 00000 n -0001164849 00000 n -0001177780 00000 n -0001164173 00000 n -0001157204 00000 n -0001164009 00000 n -0001155956 00000 n -0001141203 00000 n -0001155792 00000 n -0001139781 00000 n -0001122347 00000 n -0001139618 00000 n -0001179117 00000 n -0000011099 00000 n -0000010913 00000 n -0000010636 00000 n -0000011035 00000 n -0000050316 00000 n -0000043245 00000 n -0000011170 00000 n -0000050190 00000 n -0000050253 00000 n -0000043707 00000 n -0000043862 00000 n -0000044016 00000 n -0000044177 00000 n -0000044338 00000 n -0000044498 00000 n -0000044659 00000 n -0000044812 00000 n -0000044972 00000 n -0000045138 00000 n -0000045299 00000 n -0000045465 00000 n -0000045626 00000 n -0000045786 00000 n -0000045943 00000 n -0000046099 00000 n -0000046256 00000 n -0000046412 00000 n -0000046570 00000 n -0000046728 00000 n -0000046885 00000 n -0000047043 00000 n -0000047200 00000 n -0000047358 00000 n -0000047512 00000 n -0000047670 00000 n -0000047828 00000 n -0000047986 00000 n -0000048144 00000 n -0000048302 00000 n -0000048460 00000 n -0000048617 00000 n -0000048775 00000 n -0000048932 00000 n -0000049090 00000 n -0000049248 00000 n -0000049405 00000 n -0000049560 00000 n -0000049717 00000 n -0000049875 00000 n -0000050033 00000 n -0000093451 00000 n -0000085942 00000 n -0000050413 00000 n -0000093387 00000 n -0000086428 00000 n -0000086584 00000 n -0000086742 00000 n -0000086899 00000 n -0000087057 00000 n -0000087215 00000 n -0000087373 00000 n -0000087530 00000 n -0000087688 00000 n -0000087846 00000 n -0000088003 00000 n -0000088161 00000 n -0000088319 00000 n -0000088477 00000 n -0000088635 00000 n -0000088792 00000 n -0000088948 00000 n -0000089106 00000 n -0000089264 00000 n -0000089422 00000 n -0000089581 00000 n -0000089740 00000 n -0000089899 00000 n -0000090056 00000 n -0000090215 00000 n -0000090374 00000 n -0000090533 00000 n -0000090692 00000 n -0000090848 00000 n -0000091005 00000 n -0000091164 00000 n -0000091323 00000 n -0000091482 00000 n -0000091640 00000 n -0000091799 00000 n -0000091958 00000 n -0000092117 00000 n -0000092276 00000 n -0000092435 00000 n -0000092594 00000 n -0000092752 00000 n -0000092911 00000 n -0000093070 00000 n +0000007088 00000 n +0000869512 00000 n +0001219919 00000 n +0000007138 00000 n +0000007170 00000 n +0000876421 00000 n +0001219826 00000 n +0000007220 00000 n +0000007252 00000 n +0000883966 00000 n +0001219733 00000 n +0000007302 00000 n +0000007332 00000 n +0000891725 00000 n +0001219640 00000 n +0000007382 00000 n +0000007412 00000 n +0000899496 00000 n +0001219547 00000 n +0000007462 00000 n +0000007492 00000 n +0000907257 00000 n +0001219454 00000 n +0000007542 00000 n +0000007572 00000 n +0000915037 00000 n +0001219361 00000 n +0000007622 00000 n +0000007652 00000 n +0000923185 00000 n +0001219268 00000 n +0000007702 00000 n +0000007732 00000 n +0000931309 00000 n +0001219189 00000 n +0000007782 00000 n +0000007812 00000 n +0000940434 00000 n +0001219059 00000 n +0000007859 00000 n +0000007895 00000 n +0000951379 00000 n +0001218980 00000 n +0000007945 00000 n +0000007979 00000 n +0000954037 00000 n +0001218887 00000 n +0000008029 00000 n +0000008061 00000 n +0000957002 00000 n +0001218794 00000 n +0000008111 00000 n +0000008157 00000 n +0000960511 00000 n +0001218715 00000 n +0000008207 00000 n +0000008250 00000 n +0000961807 00000 n +0001218585 00000 n +0000008297 00000 n +0000008328 00000 n +0000969104 00000 n +0001218506 00000 n +0000008378 00000 n +0000008408 00000 n +0000977262 00000 n +0001218413 00000 n +0000008458 00000 n +0000008489 00000 n +0000983369 00000 n +0001218320 00000 n +0000008539 00000 n +0000008576 00000 n +0000990123 00000 n +0001218241 00000 n +0000008626 00000 n +0000008664 00000 n +0000992149 00000 n +0001218111 00000 n +0000008712 00000 n +0000008758 00000 n +0001000268 00000 n +0001218032 00000 n +0000008808 00000 n +0000008843 00000 n +0001009350 00000 n +0001217939 00000 n +0000008893 00000 n +0000008927 00000 n +0001018667 00000 n +0001217846 00000 n +0000008977 00000 n +0000009012 00000 n +0001022380 00000 n +0001217767 00000 n +0000009062 00000 n +0000009102 00000 n +0001023768 00000 n +0001217651 00000 n +0000009150 00000 n +0000009190 00000 n +0001034754 00000 n +0001217586 00000 n +0000009240 00000 n +0000009274 00000 n +0000010572 00000 n +0000010881 00000 n +0000009326 00000 n +0000010694 00000 n +0000010757 00000 n +0001212946 00000 n +0001199851 00000 n +0001212782 00000 n +0001199175 00000 n +0001192206 00000 n +0001199011 00000 n +0001190958 00000 n +0001176205 00000 n +0001190794 00000 n +0001174783 00000 n +0001157349 00000 n +0001174620 00000 n +0001214119 00000 n +0000011454 00000 n +0000011268 00000 n +0000010991 00000 n +0000011390 00000 n +0000050671 00000 n +0000043600 00000 n +0000011525 00000 n +0000050545 00000 n +0000050608 00000 n +0000044062 00000 n +0000044217 00000 n +0000044371 00000 n +0000044532 00000 n +0000044693 00000 n +0000044853 00000 n +0000045014 00000 n +0000045167 00000 n +0000045327 00000 n +0000045493 00000 n +0000045654 00000 n +0000045820 00000 n +0000045981 00000 n +0000046141 00000 n +0000046298 00000 n +0000046454 00000 n +0000046611 00000 n +0000046767 00000 n +0000046925 00000 n +0000047083 00000 n +0000047240 00000 n +0000047398 00000 n +0000047555 00000 n +0000047713 00000 n +0000047867 00000 n +0000048025 00000 n +0000048183 00000 n +0000048341 00000 n +0000048499 00000 n +0000048657 00000 n +0000048815 00000 n +0000048972 00000 n +0000049130 00000 n +0000049287 00000 n +0000049445 00000 n +0000049603 00000 n +0000049760 00000 n +0000049915 00000 n +0000050072 00000 n +0000050230 00000 n +0000050388 00000 n +0000098209 00000 n +0000090034 00000 n +0000050768 00000 n +0000098145 00000 n +0000090552 00000 n +0000090708 00000 n +0000090866 00000 n +0000091024 00000 n +0000091182 00000 n +0000091340 00000 n +0000091498 00000 n +0000091654 00000 n +0000091811 00000 n +0000091969 00000 n +0000092127 00000 n +0000092285 00000 n +0000092443 00000 n +0000092601 00000 n +0000092759 00000 n +0000092916 00000 n +0000093072 00000 n 0000093229 00000 n -0000109004 00000 n -0000105990 00000 n -0000093535 00000 n -0000108941 00000 n -0000106260 00000 n -0000106415 00000 n -0000106574 00000 n -0000106733 00000 n -0000106892 00000 n -0000107050 00000 n -0000107204 00000 n -0000107361 00000 n -0000107519 00000 n -0000107678 00000 n -0000107836 00000 n -0000107992 00000 n -0000108151 00000 n -0000108310 00000 n -0000108469 00000 n -0000108627 00000 n -0000108783 00000 n -0000109552 00000 n -0000109366 00000 n -0000109088 00000 n -0000109488 00000 n -0000122502 00000 n -0000121146 00000 n -0000109623 00000 n -0000121336 00000 n -0000121495 00000 n -0000121655 00000 n -0000121814 00000 n -0000121973 00000 n -0000122129 00000 n -0000122284 00000 n -0001121208 00000 n -0001105601 00000 n -0001121044 00000 n -0001179235 00000 n -0001026441 00000 n -0001026376 00000 n -0001023408 00000 n -0001023472 00000 n -0001023730 00000 n -0001023216 00000 n -0001023280 00000 n -0000130434 00000 n -0000132801 00000 n -0000130276 00000 n -0000122599 00000 n -0001104615 00000 n -0001093264 00000 n -0001104451 00000 n -0000132207 00000 n -0000132362 00000 n -0000132519 00000 n -0000132737 00000 n -0000131945 00000 n -0000132064 00000 n -0000132111 00000 n -0000132185 00000 n -0001023344 00000 n -0000145642 00000 n -0000144759 00000 n -0000132926 00000 n -0000145390 00000 n -0001092025 00000 n -0001078390 00000 n -0001091861 00000 n -0000144917 00000 n -0000145074 00000 n -0001078012 00000 n -0001074936 00000 n -0001077851 00000 n -0001074338 00000 n -0001069084 00000 n -0001074175 00000 n -0001068113 00000 n -0001063368 00000 n -0001067950 00000 n -0000145232 00000 n -0001063032 00000 n -0001060063 00000 n -0001062871 00000 n -0000145515 00000 n -0001059048 00000 n -0001048672 00000 n -0001058886 00000 n -0000145578 00000 n -0001023666 00000 n -0000153670 00000 n -0000156257 00000 n -0000153520 00000 n -0000145842 00000 n -0000156066 00000 n -0000155754 00000 n -0000155910 00000 n -0000156130 00000 n -0000155492 00000 n -0000155611 00000 n -0000155658 00000 n -0000155732 00000 n -0001023152 00000 n -0001023088 00000 n -0000167523 00000 n -0000166937 00000 n -0000156421 00000 n -0000167398 00000 n -0000167087 00000 n -0000167242 00000 n -0000180133 00000 n -0000179311 00000 n -0000167659 00000 n -0000179433 00000 n -0001048361 00000 n -0001045579 00000 n -0001048197 00000 n -0000179497 00000 n -0000179561 00000 n -0000179624 00000 n -0000179687 00000 n -0000179750 00000 n -0000179814 00000 n -0000179878 00000 n -0000179942 00000 n -0000180006 00000 n -0000180069 00000 n -0000192057 00000 n -0000191119 00000 n -0000180255 00000 n -0000191241 00000 n -0000191304 00000 n -0000191367 00000 n -0000191430 00000 n -0000191493 00000 n -0000191555 00000 n -0000191618 00000 n -0000191681 00000 n -0000191744 00000 n -0000191807 00000 n -0000191870 00000 n -0000191933 00000 n -0001179353 00000 n -0000195343 00000 n -0000194976 00000 n -0000192167 00000 n -0000195279 00000 n -0000195118 00000 n -0000207629 00000 n -0000206533 00000 n -0000195427 00000 n -0000207000 00000 n -0000207187 00000 n -0000206683 00000 n -0000206839 00000 n -0000207251 00000 n -0000207314 00000 n -0000207377 00000 n -0000207440 00000 n -0000207503 00000 n -0000207566 00000 n -0000217890 00000 n -0000217193 00000 n -0000207739 00000 n -0000217315 00000 n -0000217379 00000 n -0000217443 00000 n -0000217506 00000 n -0000217570 00000 n -0000217634 00000 n -0000217698 00000 n -0000217762 00000 n -0000217826 00000 n -0000231001 00000 n -0000230448 00000 n -0000218000 00000 n -0000230751 00000 n -0000230590 00000 n -0000230938 00000 n -0000241656 00000 n -0000241167 00000 n -0000231111 00000 n -0000241464 00000 n -0000241309 00000 n -0000241528 00000 n -0000241592 00000 n -0000255438 00000 n -0000254701 00000 n -0000241779 00000 n -0000254998 00000 n -0000255061 00000 n -0000255124 00000 n -0000255187 00000 n -0000255374 00000 n -0000254843 00000 n -0001179471 00000 n -0000264968 00000 n -0000265348 00000 n -0000264444 00000 n -0000255574 00000 n -0000264904 00000 n -0001044657 00000 n -0001036974 00000 n -0001044494 00000 n -0000265157 00000 n -0000264594 00000 n -0000264748 00000 n -0000265284 00000 n -0000276253 00000 n -0000275317 00000 n -0000265510 00000 n -0000275941 00000 n -0000275475 00000 n -0000275630 00000 n -0000276066 00000 n -0000275786 00000 n -0000276190 00000 n -0000285497 00000 n -0000284720 00000 n -0000276402 00000 n -0000285179 00000 n -0000284870 00000 n -0000285306 00000 n -0000285024 00000 n -0000285433 00000 n -0000294682 00000 n -0000294079 00000 n -0000285620 00000 n -0000294373 00000 n -0000294498 00000 n -0000294621 00000 n -0000294221 00000 n -0000303746 00000 n -0000302845 00000 n -0000294805 00000 n -0000303301 00000 n -0000303428 00000 n -0000302995 00000 n -0000303555 00000 n -0000303148 00000 n -0000303618 00000 n -0000303682 00000 n -0000304532 00000 n -0000304284 00000 n -0000303869 00000 n -0000304406 00000 n -0001179589 00000 n -0000314248 00000 n -0000313214 00000 n -0000304616 00000 n -0000313992 00000 n -0000314120 00000 n -0000314184 00000 n -0000313380 00000 n -0000313533 00000 n -0000313687 00000 n -0000313839 00000 n -0000318793 00000 n -0000318274 00000 n -0000314384 00000 n -0000318730 00000 n -0000318424 00000 n -0000318578 00000 n -0000328701 00000 n -0000327825 00000 n -0000318903 00000 n -0000328445 00000 n -0000328573 00000 n -0000328637 00000 n -0000327983 00000 n -0000328137 00000 n -0000328291 00000 n -0000331231 00000 n -0000330872 00000 n -0000328863 00000 n -0000331168 00000 n -0000331014 00000 n -0000341482 00000 n -0000340608 00000 n -0000331328 00000 n -0000341228 00000 n -0000341355 00000 n -0000341418 00000 n -0000340766 00000 n -0000340920 00000 n -0000341074 00000 n -0000344168 00000 n -0000343809 00000 n -0000341644 00000 n -0000344105 00000 n -0000343951 00000 n -0001179707 00000 n -0000354069 00000 n -0000353354 00000 n -0000344265 00000 n -0000353813 00000 n -0000353941 00000 n -0000354005 00000 n -0000353504 00000 n -0000353658 00000 n -0000363219 00000 n -0000362510 00000 n -0000354231 00000 n -0000362966 00000 n -0000363092 00000 n -0000363155 00000 n -0000362660 00000 n -0000362811 00000 n -0000372782 00000 n -0000372070 00000 n -0000363381 00000 n -0000372526 00000 n -0000372654 00000 n -0000372718 00000 n -0000372220 00000 n -0000372372 00000 n -0000382785 00000 n -0000382077 00000 n -0000372956 00000 n -0000382532 00000 n -0000382658 00000 n -0000382721 00000 n -0000382227 00000 n -0000382377 00000 n -0000384146 00000 n -0000383960 00000 n -0000382959 00000 n -0000384082 00000 n -0000393032 00000 n -0000392323 00000 n -0000384230 00000 n -0000392779 00000 n -0000392905 00000 n -0000392969 00000 n -0000392473 00000 n -0000392624 00000 n -0001179825 00000 n -0000394381 00000 n -0000394195 00000 n -0000393194 00000 n -0000394317 00000 n -0000404170 00000 n -0000403465 00000 n -0000394465 00000 n -0000403918 00000 n -0000404044 00000 n -0000404106 00000 n -0000403615 00000 n -0000403763 00000 n -0000405519 00000 n -0000405333 00000 n -0000404332 00000 n -0000405455 00000 n -0000414459 00000 n -0000413750 00000 n -0000405603 00000 n -0000414207 00000 n -0001036534 00000 n -0001034218 00000 n -0001036373 00000 n -0000414333 00000 n -0000414396 00000 n -0000413900 00000 n -0000414052 00000 n -0000425426 00000 n -0000424520 00000 n -0000414621 00000 n -0000424978 00000 n -0000425106 00000 n -0000425170 00000 n -0000425234 00000 n -0000425298 00000 n -0000425362 00000 n -0000424670 00000 n -0000424825 00000 n -0000437727 00000 n -0000436222 00000 n -0000425600 00000 n -0000437664 00000 n -0000436420 00000 n -0000436575 00000 n -0000436730 00000 n -0000436885 00000 n -0000437040 00000 n -0000437195 00000 n -0000437352 00000 n -0000437509 00000 n -0001179943 00000 n -0000439024 00000 n -0000438838 00000 n -0000437837 00000 n -0000438960 00000 n -0000449520 00000 n -0000449146 00000 n -0000439108 00000 n -0000449268 00000 n -0000449394 00000 n -0000449457 00000 n -0000461605 00000 n -0000460429 00000 n -0000449694 00000 n -0000461541 00000 n -0000460611 00000 n -0000460766 00000 n -0000460922 00000 n -0000461077 00000 n -0000461231 00000 n -0000461386 00000 n -0000469735 00000 n -0000469212 00000 n -0000461741 00000 n -0000469672 00000 n -0000469362 00000 n -0000469517 00000 n -0000471503 00000 n -0000471077 00000 n -0000469845 00000 n -0000471375 00000 n -0000471219 00000 n -0000480587 00000 n -0000479714 00000 n -0000471587 00000 n -0000480335 00000 n -0000480461 00000 n -0000480524 00000 n -0000479872 00000 n -0000480025 00000 n -0000480180 00000 n -0001180061 00000 n -0000485859 00000 n -0000490485 00000 n -0000485717 00000 n -0000480736 00000 n -0000490357 00000 n -0000490202 00000 n -0000490421 00000 n -0000489867 00000 n -0000489986 00000 n -0000490033 00000 n -0000490107 00000 n -0000490180 00000 n -0000493170 00000 n -0000492747 00000 n -0000490623 00000 n -0000493044 00000 n -0000493107 00000 n -0000492889 00000 n -0000497040 00000 n -0000496854 00000 n -0000493280 00000 n -0000496976 00000 n -0001033341 00000 n -0001026657 00000 n -0001033179 00000 n -0000507620 00000 n -0000506908 00000 n -0000497124 00000 n -0000507368 00000 n -0000507494 00000 n -0000507557 00000 n -0000507058 00000 n -0000507213 00000 n -0000523987 00000 n -0000518432 00000 n -0000517414 00000 n -0000507782 00000 n -0000518043 00000 n -0000517575 00000 n -0000518108 00000 n -0000518173 00000 n -0000518237 00000 n -0000518302 00000 n -0000518367 00000 n -0000517731 00000 n -0000517887 00000 n -0000528490 00000 n -0000523063 00000 n -0000522872 00000 n -0000518568 00000 n -0000522998 00000 n -0001180179 00000 n -0000528555 00000 n -0000523861 00000 n -0000523148 00000 n -0000528424 00000 n -0000528084 00000 n -0000528204 00000 n -0000528252 00000 n -0000528327 00000 n -0000528401 00000 n -0000539553 00000 n -0000538761 00000 n -0000528655 00000 n -0000539229 00000 n -0000539358 00000 n -0000539423 00000 n -0000539488 00000 n -0000538917 00000 n -0000539073 00000 n -0000543540 00000 n -0000543348 00000 n -0000539728 00000 n -0000543474 00000 n -0000553755 00000 n -0000553128 00000 n -0000543651 00000 n -0000553431 00000 n -0000553560 00000 n -0000553625 00000 n -0000553690 00000 n -0000553275 00000 n -0000558507 00000 n -0000558138 00000 n -0000553930 00000 n -0000558441 00000 n -0000558285 00000 n -0000559299 00000 n -0000559044 00000 n -0000558618 00000 n -0000559170 00000 n -0001180304 00000 n -0000568865 00000 n -0000568543 00000 n -0000559384 00000 n -0000568669 00000 n -0000568800 00000 n -0000578314 00000 n -0000577817 00000 n -0000569015 00000 n -0000578119 00000 n -0000577964 00000 n -0000578184 00000 n -0000578249 00000 n -0000586108 00000 n -0000585850 00000 n -0000578425 00000 n -0000585976 00000 n -0000586042 00000 n -0000594110 00000 n -0000593614 00000 n -0000586245 00000 n -0000593917 00000 n -0000594045 00000 n -0000593761 00000 n -0000596133 00000 n -0000595743 00000 n -0000594247 00000 n -0000595869 00000 n -0000595935 00000 n -0000596001 00000 n -0000596067 00000 n -0000602991 00000 n -0000602199 00000 n -0000596218 00000 n -0000602667 00000 n -0000602796 00000 n -0000602355 00000 n -0000602511 00000 n -0000602861 00000 n -0000602926 00000 n -0001180429 00000 n -0000609516 00000 n -0000608851 00000 n -0000603115 00000 n -0000609319 00000 n -0000609450 00000 n -0000609007 00000 n -0000609163 00000 n -0000614191 00000 n -0000613694 00000 n -0000609640 00000 n -0000613997 00000 n -0000614126 00000 n -0000613841 00000 n -0000623626 00000 n -0000622963 00000 n -0000614315 00000 n -0000623429 00000 n -0000623560 00000 n -0000623119 00000 n -0000623273 00000 n -0000626993 00000 n -0000626609 00000 n -0000623776 00000 n -0000626735 00000 n -0000626800 00000 n -0000626865 00000 n -0000626929 00000 n -0000636099 00000 n -0000635173 00000 n -0000627104 00000 n -0000635639 00000 n -0000635770 00000 n -0000635329 00000 n -0000635485 00000 n -0000635836 00000 n -0000635902 00000 n -0000635968 00000 n -0000636033 00000 n -0000645116 00000 n -0000644459 00000 n -0000636236 00000 n -0000644922 00000 n -0000645051 00000 n -0000644615 00000 n -0000644769 00000 n -0001180554 00000 n -0000652467 00000 n -0000651638 00000 n -0000645253 00000 n -0000651940 00000 n -0000651785 00000 n -0000652006 00000 n -0000652072 00000 n -0000652138 00000 n -0000652204 00000 n -0000652270 00000 n -0000652336 00000 n -0000652401 00000 n -0000661407 00000 n -0000660748 00000 n -0000652578 00000 n -0000661213 00000 n -0000661342 00000 n -0000660904 00000 n -0000661060 00000 n -0000665630 00000 n -0000665043 00000 n -0000661531 00000 n -0000665169 00000 n -0000665235 00000 n -0000665301 00000 n -0000665367 00000 n -0000665433 00000 n -0000665499 00000 n -0000665565 00000 n -0000671688 00000 n -0000671029 00000 n -0000665728 00000 n -0000671494 00000 n -0000671623 00000 n -0000671185 00000 n -0000671338 00000 n -0000679227 00000 n -0000678433 00000 n -0000671812 00000 n -0000678898 00000 n -0000679029 00000 n -0000678589 00000 n -0000678743 00000 n -0000679095 00000 n -0000679161 00000 n -0000686950 00000 n -0000686455 00000 n -0000679351 00000 n -0000686756 00000 n -0000686885 00000 n -0000686602 00000 n -0001180679 00000 n -0000695913 00000 n -0000695413 00000 n -0000687087 00000 n -0000695716 00000 n -0000695847 00000 n -0000695560 00000 n -0000698349 00000 n -0000697963 00000 n -0000696050 00000 n -0000698089 00000 n -0000698154 00000 n -0000698219 00000 n -0000698284 00000 n -0000703859 00000 n -0000703359 00000 n -0000698447 00000 n -0000703662 00000 n -0000703793 00000 n -0000703506 00000 n -0000709349 00000 n -0000708854 00000 n -0000703983 00000 n -0000709155 00000 n -0000709284 00000 n -0000709001 00000 n -0000715032 00000 n -0000714709 00000 n -0000709473 00000 n -0000714835 00000 n -0000714966 00000 n -0000725514 00000 n -0000725018 00000 n -0000715169 00000 n -0000725320 00000 n -0000725449 00000 n -0000725165 00000 n -0001180804 00000 n -0000728157 00000 n -0000727768 00000 n -0000725651 00000 n -0000727894 00000 n -0000727960 00000 n -0000728026 00000 n -0000728092 00000 n -0000738280 00000 n -0000737783 00000 n -0000728268 00000 n -0000738086 00000 n -0000738215 00000 n -0000737930 00000 n -0000745461 00000 n -0000744763 00000 n -0000738417 00000 n -0000745066 00000 n -0000745197 00000 n -0000744910 00000 n -0000745263 00000 n -0000745329 00000 n -0000745395 00000 n -0000752382 00000 n -0000751690 00000 n -0000745585 00000 n -0000751993 00000 n -0000752122 00000 n -0000751837 00000 n -0000752187 00000 n -0000752252 00000 n -0000752317 00000 n -0000760819 00000 n -0000760321 00000 n -0000752506 00000 n -0000760622 00000 n -0000760753 00000 n -0000760468 00000 n -0000767482 00000 n -0000767031 00000 n -0000760956 00000 n -0000767157 00000 n -0000767222 00000 n -0000767287 00000 n -0000767352 00000 n -0000767417 00000 n -0001180929 00000 n -0000775625 00000 n -0000774799 00000 n -0000767606 00000 n -0000775428 00000 n -0000775559 00000 n -0000774964 00000 n -0000775118 00000 n -0000775274 00000 n -0000783079 00000 n -0000782567 00000 n -0000775762 00000 n -0000782693 00000 n -0000783014 00000 n -0000794954 00000 n -0000794169 00000 n -0000783216 00000 n -0000794295 00000 n -0000794361 00000 n -0000794427 00000 n -0000794493 00000 n -0000794559 00000 n -0000794625 00000 n -0000794691 00000 n -0000794757 00000 n -0000794823 00000 n -0000794889 00000 n -0000795777 00000 n -0000795522 00000 n -0000795090 00000 n -0000795648 00000 n -0000801408 00000 n -0000800887 00000 n -0000795862 00000 n -0000801013 00000 n -0000801144 00000 n -0000801210 00000 n -0000801276 00000 n -0000801342 00000 n -0000808870 00000 n -0000808355 00000 n -0000801532 00000 n -0000808481 00000 n -0000808610 00000 n -0000808675 00000 n -0000808740 00000 n -0000808805 00000 n -0001181054 00000 n -0000816399 00000 n -0000815813 00000 n -0000809020 00000 n -0000815939 00000 n -0000816070 00000 n -0000816136 00000 n -0000816202 00000 n -0000816268 00000 n -0000816333 00000 n -0000820661 00000 n -0000820341 00000 n -0000816549 00000 n -0000820467 00000 n -0000820596 00000 n -0000825960 00000 n -0000825637 00000 n -0000820772 00000 n -0000825763 00000 n -0000825894 00000 n -0000828639 00000 n -0000828319 00000 n -0000826097 00000 n -0000828445 00000 n -0000828574 00000 n -0000831730 00000 n -0000831407 00000 n -0000828750 00000 n -0000831533 00000 n -0000831664 00000 n -0000834646 00000 n -0000834326 00000 n -0000831841 00000 n -0000834452 00000 n -0000834581 00000 n -0001181179 00000 n -0000841556 00000 n -0000841233 00000 n -0000834757 00000 n -0000841359 00000 n -0000841490 00000 n -0000849228 00000 n -0000848778 00000 n -0000841693 00000 n -0000848904 00000 n -0000849033 00000 n -0000849098 00000 n -0000849163 00000 n -0000856991 00000 n -0000856536 00000 n -0000849378 00000 n -0000856662 00000 n -0000856793 00000 n -0000856859 00000 n -0000856925 00000 n -0000864758 00000 n -0000864308 00000 n -0000857141 00000 n -0000864434 00000 n -0000864563 00000 n -0000864628 00000 n -0000864693 00000 n -0000872523 00000 n -0000872068 00000 n -0000864908 00000 n -0000872194 00000 n -0000872325 00000 n -0000872391 00000 n -0000872457 00000 n -0000880299 00000 n -0000879849 00000 n -0000872673 00000 n -0000879975 00000 n -0000880104 00000 n -0000880169 00000 n -0000880234 00000 n -0001181304 00000 n -0000888450 00000 n -0000887996 00000 n -0000880449 00000 n -0000888122 00000 n -0000888253 00000 n -0000888319 00000 n -0000888385 00000 n -0000896570 00000 n -0000896121 00000 n -0000888587 00000 n -0000896247 00000 n -0000896376 00000 n -0000896441 00000 n -0000896506 00000 n -0000905502 00000 n -0000904906 00000 n -0000896707 00000 n -0000905371 00000 n -0000905062 00000 n -0000905216 00000 n -0000910479 00000 n -0000910545 00000 n -0000910611 00000 n -0000910288 00000 n -0000905600 00000 n -0000910414 00000 n -0000916513 00000 n -0000916190 00000 n -0000910709 00000 n -0000916316 00000 n -0000916447 00000 n -0000919169 00000 n -0000918849 00000 n -0000916624 00000 n -0000918975 00000 n -0000919104 00000 n -0001181429 00000 n -0000922136 00000 n -0000921813 00000 n -0000919280 00000 n -0000921939 00000 n -0000922070 00000 n -0000925643 00000 n -0000925323 00000 n -0000922247 00000 n -0000925449 00000 n -0000925578 00000 n -0000926875 00000 n -0000926618 00000 n -0000925767 00000 n -0000926744 00000 n -0000934236 00000 n -0000933742 00000 n -0000926973 00000 n -0000934042 00000 n -0000934171 00000 n -0000933889 00000 n -0000942396 00000 n -0000941898 00000 n -0000934360 00000 n -0000942199 00000 n -0000942330 00000 n -0000942045 00000 n -0000948501 00000 n -0000948007 00000 n -0000942520 00000 n -0000948307 00000 n -0000948436 00000 n -0000948154 00000 n -0001181554 00000 n -0000955257 00000 n -0000954759 00000 n -0000948625 00000 n -0000955060 00000 n -0000955191 00000 n -0000954906 00000 n -0000957216 00000 n -0000956961 00000 n -0000955381 00000 n -0000957087 00000 n -0000965533 00000 n -0000964735 00000 n -0000957327 00000 n -0000965205 00000 n -0000965336 00000 n -0000964891 00000 n -0000965402 00000 n -0000965047 00000 n -0000965467 00000 n -0000974482 00000 n -0000973493 00000 n -0000965708 00000 n -0000974288 00000 n -0000974417 00000 n -0000973667 00000 n -0000973821 00000 n -0000973976 00000 n -0000974132 00000 n -0000983800 00000 n -0000983136 00000 n -0000974606 00000 n -0000983604 00000 n -0000983735 00000 n -0000983292 00000 n -0000983448 00000 n -0000987512 00000 n -0000987015 00000 n -0000983924 00000 n -0000987318 00000 n -0000987447 00000 n -0000987162 00000 n -0001181679 00000 n -0000988836 00000 n -0000988579 00000 n -0000987636 00000 n -0000988705 00000 n -0000999886 00000 n -0000999227 00000 n -0000988934 00000 n -0000999692 00000 n -0000999821 00000 n -0000999383 00000 n -0000999536 00000 n -0001008327 00000 n -0001007958 00000 n -0001000061 00000 n -0001008261 00000 n -0001008105 00000 n -0001011769 00000 n -0001011578 00000 n -0001008451 00000 n -0001011704 00000 n -0001012326 00000 n -0001012134 00000 n -0001011854 00000 n -0001012260 00000 n -0001023794 00000 n -0001022767 00000 n -0001012398 00000 n -0001022893 00000 n -0001022958 00000 n -0001023023 00000 n -0001023536 00000 n -0001023601 00000 n -0001181804 00000 n -0001026572 00000 n -0001026184 00000 n -0001023905 00000 n -0001026310 00000 n -0001026506 00000 n -0001033860 00000 n -0001033637 00000 n -0001036876 00000 n -0001036750 00000 n -0001045238 00000 n -0001044979 00000 n -0001048587 00000 n -0001048562 00000 n -0001059680 00000 n -0001059401 00000 n -0001063273 00000 n -0001063240 00000 n -0001068731 00000 n -0001068437 00000 n -0001074722 00000 n -0001074564 00000 n -0001078275 00000 n -0001078226 00000 n -0001092779 00000 n -0001092452 00000 n -0001105254 00000 n -0001104925 00000 n -0001121950 00000 n -0001121585 00000 n -0001140696 00000 n -0001140290 00000 n -0001156750 00000 n -0001156372 00000 n -0001164601 00000 n -0001164420 00000 n -0001178728 00000 n -0001178348 00000 n -0001181893 00000 n -0001182013 00000 n -0001182136 00000 n -0001182262 00000 n -0001182379 00000 n -0001182471 00000 n -0001192093 00000 n -0001202314 00000 n -0001202355 00000 n -0001202395 00000 n -0001202634 00000 n +0000093387 00000 n +0000093545 00000 n +0000093703 00000 n +0000093862 00000 n +0000094021 00000 n +0000094180 00000 n +0000094339 00000 n +0000094497 00000 n +0000094655 00000 n +0000094814 00000 n +0000094973 00000 n +0000095132 00000 n +0000095291 00000 n +0000095450 00000 n +0000095606 00000 n +0000095763 00000 n +0000095921 00000 n +0000096080 00000 n +0000096239 00000 n +0000096398 00000 n +0000096557 00000 n +0000096716 00000 n +0000096875 00000 n +0000097034 00000 n +0000097192 00000 n +0000097351 00000 n +0000097510 00000 n +0000097669 00000 n +0000097828 00000 n +0000097987 00000 n +0000113762 00000 n +0000110748 00000 n +0000098293 00000 n +0000113699 00000 n +0000111018 00000 n +0000111173 00000 n +0000111332 00000 n +0000111491 00000 n +0000111650 00000 n +0000111808 00000 n +0000111962 00000 n +0000112119 00000 n +0000112277 00000 n +0000112436 00000 n +0000112594 00000 n +0000112750 00000 n +0000112909 00000 n +0000113068 00000 n +0000113227 00000 n +0000113385 00000 n +0000113541 00000 n +0000114310 00000 n +0000114124 00000 n +0000113846 00000 n +0000114246 00000 n +0000127260 00000 n +0000125904 00000 n +0000114381 00000 n +0000126094 00000 n +0000126253 00000 n +0000126413 00000 n +0000126572 00000 n +0000126731 00000 n +0000126887 00000 n +0000127042 00000 n +0001156210 00000 n +0001140603 00000 n +0001156046 00000 n +0001214237 00000 n +0001061438 00000 n +0001061373 00000 n +0001058405 00000 n +0001058469 00000 n +0001058727 00000 n +0001058213 00000 n +0001058277 00000 n +0000135192 00000 n +0000137559 00000 n +0000135034 00000 n +0000127357 00000 n +0001139617 00000 n +0001128266 00000 n +0001139453 00000 n +0000136965 00000 n +0000137120 00000 n +0000137277 00000 n +0000137495 00000 n +0000136703 00000 n +0000136822 00000 n +0000136869 00000 n +0000136943 00000 n +0001058341 00000 n +0000150400 00000 n +0000149517 00000 n +0000137684 00000 n +0000150148 00000 n +0001127027 00000 n +0001113392 00000 n +0001126863 00000 n +0000149675 00000 n +0000149832 00000 n +0001113014 00000 n +0001109938 00000 n +0001112853 00000 n +0001109340 00000 n +0001104086 00000 n +0001109177 00000 n +0001103115 00000 n +0001098370 00000 n +0001102952 00000 n +0000149990 00000 n +0001098034 00000 n +0001095065 00000 n +0001097873 00000 n +0000150273 00000 n +0001094050 00000 n +0001083674 00000 n +0001093888 00000 n +0000150336 00000 n +0001058663 00000 n +0000158428 00000 n +0000161015 00000 n +0000158278 00000 n +0000150600 00000 n +0000160824 00000 n +0000160512 00000 n +0000160668 00000 n +0000160888 00000 n +0000160250 00000 n +0000160369 00000 n +0000160416 00000 n +0000160490 00000 n +0001058149 00000 n +0001058085 00000 n +0000172281 00000 n +0000171695 00000 n +0000161179 00000 n +0000172156 00000 n +0000171845 00000 n +0000172000 00000 n +0000184891 00000 n +0000184069 00000 n +0000172417 00000 n +0000184191 00000 n +0001083363 00000 n +0001080581 00000 n +0001083199 00000 n +0000184255 00000 n +0000184319 00000 n +0000184382 00000 n +0000184445 00000 n +0000184508 00000 n +0000184572 00000 n +0000184636 00000 n +0000184700 00000 n +0000184764 00000 n +0000184827 00000 n +0000196815 00000 n +0000195877 00000 n +0000185013 00000 n +0000195999 00000 n +0000196062 00000 n +0000196125 00000 n +0000196188 00000 n +0000196251 00000 n +0000196313 00000 n +0000196376 00000 n +0000196439 00000 n +0000196502 00000 n +0000196565 00000 n +0000196628 00000 n +0000196691 00000 n +0001214355 00000 n +0000200101 00000 n +0000199734 00000 n +0000196925 00000 n +0000200037 00000 n +0000199876 00000 n +0000212387 00000 n +0000211291 00000 n +0000200185 00000 n +0000211758 00000 n +0000211945 00000 n +0000211441 00000 n +0000211597 00000 n +0000212009 00000 n +0000212072 00000 n +0000212135 00000 n +0000212198 00000 n +0000212261 00000 n +0000212324 00000 n +0000222648 00000 n +0000221951 00000 n +0000212497 00000 n +0000222073 00000 n +0000222137 00000 n +0000222201 00000 n +0000222264 00000 n +0000222328 00000 n +0000222392 00000 n +0000222456 00000 n +0000222520 00000 n +0000222584 00000 n +0000235759 00000 n +0000235206 00000 n +0000222758 00000 n +0000235509 00000 n +0000235348 00000 n +0000235696 00000 n +0000246414 00000 n +0000245925 00000 n +0000235869 00000 n +0000246222 00000 n +0000246067 00000 n +0000246286 00000 n +0000246350 00000 n +0000260196 00000 n +0000259459 00000 n +0000246537 00000 n +0000259756 00000 n +0000259819 00000 n +0000259882 00000 n +0000259945 00000 n +0000260132 00000 n +0000259601 00000 n +0001214473 00000 n +0000269726 00000 n +0000270106 00000 n +0000269202 00000 n +0000260332 00000 n +0000269662 00000 n +0001079659 00000 n +0001071976 00000 n +0001079496 00000 n +0000269915 00000 n +0000269352 00000 n +0000269506 00000 n +0000270042 00000 n +0000281011 00000 n +0000280075 00000 n +0000270268 00000 n +0000280699 00000 n +0000280233 00000 n +0000280388 00000 n +0000280824 00000 n +0000280544 00000 n +0000280948 00000 n +0000290255 00000 n +0000289478 00000 n +0000281160 00000 n +0000289937 00000 n +0000289628 00000 n +0000290064 00000 n +0000289782 00000 n +0000290191 00000 n +0000299440 00000 n +0000298837 00000 n +0000290378 00000 n +0000299131 00000 n +0000299256 00000 n +0000299379 00000 n +0000298979 00000 n +0000308504 00000 n +0000307603 00000 n +0000299563 00000 n +0000308059 00000 n +0000308186 00000 n +0000307753 00000 n +0000308313 00000 n +0000307906 00000 n +0000308376 00000 n +0000308440 00000 n +0000309290 00000 n +0000309042 00000 n +0000308627 00000 n +0000309164 00000 n +0001214591 00000 n +0000319006 00000 n +0000317972 00000 n +0000309374 00000 n +0000318750 00000 n +0000318878 00000 n +0000318942 00000 n +0000318138 00000 n +0000318291 00000 n +0000318445 00000 n +0000318597 00000 n +0000323551 00000 n +0000323032 00000 n +0000319142 00000 n +0000323488 00000 n +0000323182 00000 n +0000323336 00000 n +0000333459 00000 n +0000332583 00000 n +0000323661 00000 n +0000333203 00000 n +0000333331 00000 n +0000333395 00000 n +0000332741 00000 n +0000332895 00000 n +0000333049 00000 n +0000335989 00000 n +0000335630 00000 n +0000333621 00000 n +0000335926 00000 n +0000335772 00000 n +0000346240 00000 n +0000345366 00000 n +0000336086 00000 n +0000345986 00000 n +0000346113 00000 n +0000346176 00000 n +0000345524 00000 n +0000345678 00000 n +0000345832 00000 n +0000348926 00000 n +0000348567 00000 n +0000346402 00000 n +0000348863 00000 n +0000348709 00000 n +0001214709 00000 n +0000358827 00000 n +0000358112 00000 n +0000349023 00000 n +0000358571 00000 n +0000358699 00000 n +0000358763 00000 n +0000358262 00000 n +0000358416 00000 n +0000367977 00000 n +0000367268 00000 n +0000358989 00000 n +0000367724 00000 n +0000367850 00000 n +0000367913 00000 n +0000367418 00000 n +0000367569 00000 n +0000377540 00000 n +0000376828 00000 n +0000368139 00000 n +0000377284 00000 n +0000377412 00000 n +0000377476 00000 n +0000376978 00000 n +0000377130 00000 n +0000387543 00000 n +0000386835 00000 n +0000377714 00000 n +0000387290 00000 n +0000387416 00000 n +0000387479 00000 n +0000386985 00000 n +0000387135 00000 n +0000388904 00000 n +0000388718 00000 n +0000387717 00000 n +0000388840 00000 n +0000397790 00000 n +0000397081 00000 n +0000388988 00000 n +0000397537 00000 n +0000397663 00000 n +0000397727 00000 n +0000397231 00000 n +0000397382 00000 n +0001214827 00000 n +0000399139 00000 n +0000398953 00000 n +0000397952 00000 n +0000399075 00000 n +0000408928 00000 n +0000408223 00000 n +0000399223 00000 n +0000408676 00000 n +0000408802 00000 n +0000408864 00000 n +0000408373 00000 n +0000408521 00000 n +0000410277 00000 n +0000410091 00000 n +0000409090 00000 n +0000410213 00000 n +0000419217 00000 n +0000418508 00000 n +0000410361 00000 n +0000418965 00000 n +0001071536 00000 n +0001069220 00000 n +0001071375 00000 n +0000419091 00000 n +0000419154 00000 n +0000418658 00000 n +0000418810 00000 n +0000430184 00000 n +0000429278 00000 n +0000419379 00000 n +0000429736 00000 n +0000429864 00000 n +0000429928 00000 n +0000429992 00000 n +0000430056 00000 n +0000430120 00000 n +0000429428 00000 n +0000429583 00000 n +0000442485 00000 n +0000440980 00000 n +0000430358 00000 n +0000442422 00000 n +0000441178 00000 n +0000441333 00000 n +0000441488 00000 n +0000441643 00000 n +0000441798 00000 n +0000441953 00000 n +0000442110 00000 n +0000442267 00000 n +0001214945 00000 n +0000443782 00000 n +0000443596 00000 n +0000442595 00000 n +0000443718 00000 n +0000454278 00000 n +0000453904 00000 n +0000443866 00000 n +0000454026 00000 n +0000454152 00000 n +0000454215 00000 n +0000466363 00000 n +0000465187 00000 n +0000454452 00000 n +0000466299 00000 n +0000465369 00000 n +0000465524 00000 n +0000465680 00000 n +0000465835 00000 n +0000465989 00000 n +0000466144 00000 n +0000474493 00000 n +0000473970 00000 n +0000466499 00000 n +0000474430 00000 n +0000474120 00000 n +0000474275 00000 n +0000476261 00000 n +0000475835 00000 n +0000474603 00000 n +0000476133 00000 n +0000475977 00000 n +0000485345 00000 n +0000484472 00000 n +0000476345 00000 n +0000485093 00000 n +0000485219 00000 n +0000485282 00000 n +0000484630 00000 n +0000484783 00000 n +0000484938 00000 n +0001215063 00000 n +0000490617 00000 n +0000495243 00000 n +0000490475 00000 n +0000485494 00000 n +0000495115 00000 n +0000494960 00000 n +0000495179 00000 n +0000494625 00000 n +0000494744 00000 n +0000494791 00000 n +0000494865 00000 n +0000494938 00000 n +0000497930 00000 n +0000497505 00000 n +0000495381 00000 n +0000497804 00000 n +0000497867 00000 n +0000497648 00000 n +0000501806 00000 n +0000501615 00000 n +0000498040 00000 n +0000501740 00000 n +0001068341 00000 n +0001061654 00000 n +0001068177 00000 n +0000512403 00000 n +0000511677 00000 n +0000501892 00000 n +0000512144 00000 n +0000512273 00000 n +0000512338 00000 n +0000511832 00000 n +0000511988 00000 n +0000528782 00000 n +0000523226 00000 n +0000522199 00000 n +0000512566 00000 n +0000522831 00000 n +0000522363 00000 n +0000522897 00000 n +0000522963 00000 n +0000523028 00000 n +0000523094 00000 n +0000523160 00000 n +0000522519 00000 n +0000522675 00000 n +0000533286 00000 n +0000527858 00000 n +0000527667 00000 n +0000523363 00000 n +0000527793 00000 n +0001215184 00000 n +0000533351 00000 n +0000528656 00000 n +0000527943 00000 n +0000533220 00000 n +0000532880 00000 n +0000533000 00000 n +0000533048 00000 n +0000533123 00000 n +0000533197 00000 n +0000544350 00000 n +0000543558 00000 n +0000533452 00000 n +0000544026 00000 n +0000544155 00000 n +0000544220 00000 n +0000544285 00000 n +0000543714 00000 n +0000543870 00000 n +0000548337 00000 n +0000548145 00000 n +0000544525 00000 n +0000548271 00000 n +0000558552 00000 n +0000557925 00000 n +0000548448 00000 n +0000558228 00000 n +0000558357 00000 n +0000558422 00000 n +0000558487 00000 n +0000558072 00000 n +0000563304 00000 n +0000562935 00000 n +0000558727 00000 n +0000563238 00000 n +0000563082 00000 n +0000564096 00000 n +0000563841 00000 n +0000563415 00000 n +0000563967 00000 n +0001215309 00000 n +0000573662 00000 n +0000573340 00000 n +0000564181 00000 n +0000573466 00000 n +0000573597 00000 n +0000583111 00000 n +0000582614 00000 n +0000573812 00000 n +0000582916 00000 n +0000582761 00000 n +0000582981 00000 n +0000583046 00000 n +0000590905 00000 n +0000590647 00000 n +0000583222 00000 n +0000590773 00000 n +0000590839 00000 n +0000598907 00000 n +0000598411 00000 n +0000591042 00000 n +0000598714 00000 n +0000598842 00000 n +0000598558 00000 n +0000600930 00000 n +0000600540 00000 n +0000599044 00000 n +0000600666 00000 n +0000600732 00000 n +0000600798 00000 n +0000600864 00000 n +0000607788 00000 n +0000606996 00000 n +0000601015 00000 n +0000607464 00000 n +0000607593 00000 n +0000607152 00000 n +0000607308 00000 n +0000607658 00000 n +0000607723 00000 n +0001215434 00000 n +0000614313 00000 n +0000613648 00000 n +0000607912 00000 n +0000614116 00000 n +0000614247 00000 n +0000613804 00000 n +0000613960 00000 n +0000618988 00000 n +0000618491 00000 n +0000614437 00000 n +0000618794 00000 n +0000618923 00000 n +0000618638 00000 n +0000628423 00000 n +0000627760 00000 n +0000619112 00000 n +0000628226 00000 n +0000628357 00000 n +0000627916 00000 n +0000628070 00000 n +0000631790 00000 n +0000631406 00000 n +0000628573 00000 n +0000631532 00000 n +0000631597 00000 n +0000631662 00000 n +0000631726 00000 n +0000640896 00000 n +0000639970 00000 n +0000631901 00000 n +0000640436 00000 n +0000640567 00000 n +0000640126 00000 n +0000640282 00000 n +0000640633 00000 n +0000640699 00000 n +0000640765 00000 n +0000640830 00000 n +0000649913 00000 n +0000649256 00000 n +0000641033 00000 n +0000649719 00000 n +0000649848 00000 n +0000649412 00000 n +0000649566 00000 n +0001215559 00000 n +0000657264 00000 n +0000656435 00000 n +0000650050 00000 n +0000656737 00000 n +0000656582 00000 n +0000656803 00000 n +0000656869 00000 n +0000656935 00000 n +0000657001 00000 n +0000657067 00000 n +0000657133 00000 n +0000657198 00000 n +0000666204 00000 n +0000665545 00000 n +0000657375 00000 n +0000666010 00000 n +0000666139 00000 n +0000665701 00000 n +0000665857 00000 n +0000670427 00000 n +0000669840 00000 n +0000666328 00000 n +0000669966 00000 n +0000670032 00000 n +0000670098 00000 n +0000670164 00000 n +0000670230 00000 n +0000670296 00000 n +0000670362 00000 n +0000676485 00000 n +0000675826 00000 n +0000670525 00000 n +0000676291 00000 n +0000676420 00000 n +0000675982 00000 n +0000676135 00000 n +0000684024 00000 n +0000683230 00000 n +0000676609 00000 n +0000683695 00000 n +0000683826 00000 n +0000683386 00000 n +0000683540 00000 n +0000683892 00000 n +0000683958 00000 n +0000691747 00000 n +0000691252 00000 n +0000684148 00000 n +0000691553 00000 n +0000691682 00000 n +0000691399 00000 n +0001215684 00000 n +0000700710 00000 n +0000700210 00000 n +0000691884 00000 n +0000700513 00000 n +0000700644 00000 n +0000700357 00000 n +0000703146 00000 n +0000702760 00000 n +0000700847 00000 n +0000702886 00000 n +0000702951 00000 n +0000703016 00000 n +0000703081 00000 n +0000708656 00000 n +0000708156 00000 n +0000703244 00000 n +0000708459 00000 n +0000708590 00000 n +0000708303 00000 n +0000714146 00000 n +0000713651 00000 n +0000708780 00000 n +0000713952 00000 n +0000714081 00000 n +0000713798 00000 n +0000719829 00000 n +0000719506 00000 n +0000714270 00000 n +0000719632 00000 n +0000719763 00000 n +0000730311 00000 n +0000729815 00000 n +0000719966 00000 n +0000730117 00000 n +0000730246 00000 n +0000729962 00000 n +0001215809 00000 n +0000732954 00000 n +0000732565 00000 n +0000730448 00000 n +0000732691 00000 n +0000732757 00000 n +0000732823 00000 n +0000732889 00000 n +0000743077 00000 n +0000742580 00000 n +0000733065 00000 n +0000742883 00000 n +0000743012 00000 n +0000742727 00000 n +0000749541 00000 n +0000748909 00000 n +0000743214 00000 n +0000749212 00000 n +0000749343 00000 n +0000749056 00000 n +0000749409 00000 n +0000749475 00000 n +0000758204 00000 n +0000757577 00000 n +0000749678 00000 n +0000757880 00000 n +0000758009 00000 n +0000757724 00000 n +0000758074 00000 n +0000758139 00000 n +0000764659 00000 n +0000764027 00000 n +0000758341 00000 n +0000764330 00000 n +0000764461 00000 n +0000764174 00000 n +0000764527 00000 n +0000764593 00000 n +0000773273 00000 n +0000772646 00000 n +0000764796 00000 n +0000772949 00000 n +0000773078 00000 n +0000772793 00000 n +0000773143 00000 n +0000773208 00000 n +0001215934 00000 n +0000780454 00000 n +0000779756 00000 n +0000773410 00000 n +0000780059 00000 n +0000780190 00000 n +0000779903 00000 n +0000780256 00000 n +0000780322 00000 n +0000780388 00000 n +0000787375 00000 n +0000786683 00000 n +0000780578 00000 n +0000786986 00000 n +0000787115 00000 n +0000786830 00000 n +0000787180 00000 n +0000787245 00000 n +0000787310 00000 n +0000795812 00000 n +0000795314 00000 n +0000787499 00000 n +0000795615 00000 n +0000795746 00000 n +0000795461 00000 n +0000802475 00000 n +0000802024 00000 n +0000795949 00000 n +0000802150 00000 n +0000802215 00000 n +0000802280 00000 n +0000802345 00000 n +0000802410 00000 n +0000810618 00000 n +0000809792 00000 n +0000802599 00000 n +0000810421 00000 n +0000810552 00000 n +0000809957 00000 n +0000810111 00000 n +0000810267 00000 n +0000818072 00000 n +0000817560 00000 n +0000810755 00000 n +0000817686 00000 n +0000818007 00000 n +0001216059 00000 n +0000829947 00000 n +0000829162 00000 n +0000818209 00000 n +0000829288 00000 n +0000829354 00000 n +0000829420 00000 n +0000829486 00000 n +0000829552 00000 n +0000829618 00000 n +0000829684 00000 n +0000829750 00000 n +0000829816 00000 n +0000829882 00000 n +0000830770 00000 n +0000830515 00000 n +0000830083 00000 n +0000830641 00000 n +0000836401 00000 n +0000835880 00000 n +0000830855 00000 n +0000836006 00000 n +0000836137 00000 n +0000836203 00000 n +0000836269 00000 n +0000836335 00000 n +0000843863 00000 n +0000843348 00000 n +0000836525 00000 n +0000843474 00000 n +0000843603 00000 n +0000843668 00000 n +0000843733 00000 n +0000843798 00000 n +0000851392 00000 n +0000850806 00000 n +0000844013 00000 n +0000850932 00000 n +0000851063 00000 n +0000851129 00000 n +0000851195 00000 n +0000851261 00000 n +0000851326 00000 n +0000855654 00000 n +0000855334 00000 n +0000851542 00000 n +0000855460 00000 n +0000855589 00000 n +0001216184 00000 n +0000860953 00000 n +0000860630 00000 n +0000855765 00000 n +0000860756 00000 n +0000860887 00000 n +0000863632 00000 n +0000863312 00000 n +0000861090 00000 n +0000863438 00000 n +0000863567 00000 n +0000866724 00000 n +0000866401 00000 n +0000863743 00000 n +0000866527 00000 n +0000866658 00000 n +0000869641 00000 n +0000869321 00000 n +0000866835 00000 n +0000869447 00000 n +0000869576 00000 n +0000876552 00000 n +0000876229 00000 n +0000869752 00000 n +0000876355 00000 n +0000876486 00000 n +0000884225 00000 n +0000883775 00000 n +0000876689 00000 n +0000883901 00000 n +0000884030 00000 n +0000884095 00000 n +0000884160 00000 n +0001216309 00000 n +0000891988 00000 n +0000891533 00000 n +0000884375 00000 n +0000891659 00000 n +0000891790 00000 n +0000891856 00000 n +0000891922 00000 n +0000899755 00000 n +0000899305 00000 n +0000892138 00000 n +0000899431 00000 n +0000899560 00000 n +0000899625 00000 n +0000899690 00000 n +0000907520 00000 n +0000907065 00000 n +0000899905 00000 n +0000907191 00000 n +0000907322 00000 n +0000907388 00000 n +0000907454 00000 n +0000915296 00000 n +0000914846 00000 n +0000907670 00000 n +0000914972 00000 n +0000915101 00000 n +0000915166 00000 n +0000915231 00000 n +0000923447 00000 n +0000922993 00000 n +0000915446 00000 n +0000923119 00000 n +0000923250 00000 n +0000923316 00000 n +0000923382 00000 n +0000931567 00000 n +0000931118 00000 n +0000923584 00000 n +0000931244 00000 n +0000931373 00000 n +0000931438 00000 n +0000931503 00000 n +0001216434 00000 n +0000940499 00000 n +0000939903 00000 n +0000931704 00000 n +0000940368 00000 n +0000940059 00000 n +0000940213 00000 n +0000945476 00000 n +0000945542 00000 n +0000945608 00000 n +0000945285 00000 n +0000940597 00000 n +0000945411 00000 n +0000951510 00000 n +0000951187 00000 n +0000945706 00000 n +0000951313 00000 n +0000951444 00000 n +0000954166 00000 n +0000953846 00000 n +0000951621 00000 n +0000953972 00000 n +0000954101 00000 n +0000957133 00000 n +0000956810 00000 n +0000954277 00000 n +0000956936 00000 n +0000957067 00000 n +0000960640 00000 n +0000960320 00000 n +0000957244 00000 n +0000960446 00000 n +0000960575 00000 n +0001216559 00000 n +0000961872 00000 n +0000961615 00000 n +0000960764 00000 n +0000961741 00000 n +0000969233 00000 n +0000968739 00000 n +0000961970 00000 n +0000969039 00000 n +0000969168 00000 n +0000968886 00000 n +0000977393 00000 n +0000976895 00000 n +0000969357 00000 n +0000977196 00000 n +0000977327 00000 n +0000977042 00000 n +0000983498 00000 n +0000983004 00000 n +0000977517 00000 n +0000983304 00000 n +0000983433 00000 n +0000983151 00000 n +0000990254 00000 n +0000989756 00000 n +0000983622 00000 n +0000990057 00000 n +0000990188 00000 n +0000989903 00000 n +0000992213 00000 n +0000991958 00000 n +0000990378 00000 n +0000992084 00000 n +0001216684 00000 n +0001000530 00000 n +0000999732 00000 n +0000992324 00000 n +0001000202 00000 n +0001000333 00000 n +0000999888 00000 n +0001000399 00000 n +0001000044 00000 n +0001000464 00000 n +0001009479 00000 n +0001008490 00000 n +0001000705 00000 n +0001009285 00000 n +0001009414 00000 n +0001008664 00000 n +0001008818 00000 n +0001008973 00000 n +0001009129 00000 n +0001018797 00000 n +0001018133 00000 n +0001009603 00000 n +0001018601 00000 n +0001018732 00000 n +0001018289 00000 n +0001018445 00000 n +0001022509 00000 n +0001022012 00000 n +0001018921 00000 n +0001022315 00000 n +0001022444 00000 n +0001022159 00000 n +0001023833 00000 n +0001023576 00000 n +0001022633 00000 n +0001023702 00000 n +0001034883 00000 n +0001034224 00000 n +0001023931 00000 n +0001034689 00000 n +0001034818 00000 n +0001034380 00000 n +0001034533 00000 n +0001216809 00000 n +0001043324 00000 n +0001042955 00000 n +0001035058 00000 n +0001043258 00000 n +0001043102 00000 n +0001046766 00000 n +0001046575 00000 n +0001043448 00000 n +0001046701 00000 n +0001047323 00000 n +0001047131 00000 n +0001046851 00000 n +0001047257 00000 n +0001058791 00000 n +0001057764 00000 n +0001047395 00000 n +0001057890 00000 n +0001057955 00000 n +0001058020 00000 n +0001058533 00000 n +0001058598 00000 n +0001061569 00000 n +0001061181 00000 n +0001058902 00000 n +0001061307 00000 n +0001061503 00000 n +0001068862 00000 n +0001068639 00000 n +0001071878 00000 n +0001071752 00000 n +0001080240 00000 n +0001079981 00000 n +0001083589 00000 n +0001083564 00000 n +0001094682 00000 n +0001094403 00000 n +0001098275 00000 n +0001098242 00000 n +0001103733 00000 n +0001103439 00000 n +0001109724 00000 n +0001109566 00000 n +0001113277 00000 n +0001113228 00000 n +0001127781 00000 n +0001127454 00000 n +0001140256 00000 n +0001139927 00000 n +0001156952 00000 n +0001156587 00000 n +0001175698 00000 n +0001175292 00000 n +0001191752 00000 n +0001191374 00000 n +0001199603 00000 n +0001199422 00000 n +0001213730 00000 n +0001213350 00000 n +0001216934 00000 n +0001217054 00000 n +0001217177 00000 n +0001217303 00000 n +0001217420 00000 n +0001217512 00000 n +0001227506 00000 n +0001238173 00000 n +0001238214 00000 n +0001238254 00000 n +0001238493 00000 n trailer << -/Size 1592 -/Root 1590 0 R -/Info 1591 0 R -/ID [<546A8C8DB5FCC24D4966EEEA418C0181> <546A8C8DB5FCC24D4966EEEA418C0181>] +/Size 1644 +/Root 1642 0 R +/Info 1643 0 R +/ID [ ] >> startxref -1203203 +1239062 %%EOF diff --git a/test/pargen/Makefile b/test/pargen/Makefile index cd8d1453..fa097f81 100644 --- a/test/pargen/Makefile +++ b/test/pargen/Makefile @@ -19,6 +19,10 @@ ppde: ppde.o $(F90LINK) ppde.o -o ppde $(PSBLAS_LIB) $(LDLIBS) /bin/mv ppde $(EXEDIR) +tpde: tpde.o + $(F90LINK) tpde.o -pg -o tpde $(PSBLAS_LIB) $(LDLIBS) + /bin/mv tpde $(EXEDIR) + .f90.o: $(MPF90) $(F90COPT) $(FINCLUDES) $(FDEFINES) -c $< diff --git a/test/pargen/ppde.f90 b/test/pargen/ppde.f90 index 92fcd1ce..83a86da1 100644 --- a/test/pargen/ppde.f90 +++ b/test/pargen/ppde.f90 @@ -361,14 +361,12 @@ contains end interface ! local variables type(psb_dspmat_type) :: a real(psb_dpk_) :: zt(nbmax),glob_x,glob_y,glob_z - integer :: m,n,nnz,glob_row + integer :: m,n,nnz,glob_row,loc_row integer :: x,y,z,ia,indx_owner integer :: np, iam integer :: element - integer :: nv, inv integer, allocatable :: irow(:),icol(:) real(psb_dpk_), allocatable :: val(:) - integer, allocatable :: prv(:) ! deltah dimension of each grid cell ! deltat discretization time real(psb_dpk_) :: deltah @@ -414,7 +412,7 @@ contains ! a bunch of rows per call. ! allocate(val(20*nbmax),irow(20*nbmax),& - &icol(20*nbmax),prv(np),stat=info) + &icol(20*nbmax),stat=info) if (info /= 0 ) then info=4000 call psb_errpush(info,name) @@ -430,138 +428,135 @@ contains ! icol(1)=1 do glob_row = 1, n - call parts(glob_row,n,np,prv,nv) - do inv = 1, nv - indx_owner = prv(inv) - if (indx_owner == iam) then - ! local matrix pointer - element=1 - ! compute gridpoint coordinates - if (mod(glob_row,(idim*idim)) == 0) then - x = glob_row/(idim*idim) - else - x = glob_row/(idim*idim)+1 - endif - if (mod((glob_row-(x-1)*idim*idim),idim) == 0) then - y = (glob_row-(x-1)*idim*idim)/idim - else - y = (glob_row-(x-1)*idim*idim)/idim+1 - endif - z = glob_row-(x-1)*idim*idim-(y-1)*idim - ! glob_x, glob_y, glob_x coordinates - glob_x=x*deltah - glob_y=y*deltah - glob_z=z*deltah - - ! check on boundary points - zt(1) = 0.d0 - ! internal point: build discretization - ! - ! term depending on (x-1,y,z) - ! - if (x==1) then - val(element)=-b1(glob_x,glob_y,glob_z)& - & -a1(glob_x,glob_y,glob_z) - val(element) = val(element)/(deltah*& - & deltah) - zt(1) = exp(-glob_y**2-glob_z**2)*(-val(element)) - else - val(element)=-b1(glob_x,glob_y,glob_z)& - & -a1(glob_x,glob_y,glob_z) - val(element) = val(element)/(deltah*& - & deltah) - icol(element)=(x-2)*idim*idim+(y-1)*idim+(z) - element=element+1 - endif - ! term depending on (x,y-1,z) - if (y==1) then - val(element)=-b2(glob_x,glob_y,glob_z)& - & -a2(glob_x,glob_y,glob_z) - val(element) = val(element)/(deltah*& - & deltah) - zt(1) = exp(-glob_y**2-glob_z**2)*exp(-glob_x)*(-val(element)) - else - val(element)=-b2(glob_x,glob_y,glob_z)& - & -a2(glob_x,glob_y,glob_z) - val(element) = val(element)/(deltah*& - & deltah) - icol(element)=(x-1)*idim*idim+(y-2)*idim+(z) - element=element+1 - endif - ! term depending on (x,y,z-1) - if (z==1) then - val(element)=-b3(glob_x,glob_y,glob_z)& - & -a3(glob_x,glob_y,glob_z) - val(element) = val(element)/(deltah*& - & deltah) - zt(1) = exp(-glob_y**2-glob_z**2)*exp(-glob_x)*(-val(element)) - else - val(element)=-b3(glob_x,glob_y,glob_z)& - & -a3(glob_x,glob_y,glob_z) - val(element) = val(element)/(deltah*& - & deltah) - icol(element)=(x-1)*idim*idim+(y-1)*idim+(z-1) - element=element+1 - endif - ! term depending on (x,y,z) - val(element)=2*b1(glob_x,glob_y,glob_z)& - & +2*b2(glob_x,glob_y,glob_z)& - & +2*b3(glob_x,glob_y,glob_z)& - & +a1(glob_x,glob_y,glob_z)& - & +a2(glob_x,glob_y,glob_z)& - & +a3(glob_x,glob_y,glob_z) + ! Figure out which rows are local to the current process: + if (psb_is_owned(glob_row,desc_a)) then + ! local matrix pointer + element=1 + ! compute gridpoint coordinates + if (mod(glob_row,(idim*idim)) == 0) then + x = glob_row/(idim*idim) + else + x = glob_row/(idim*idim)+1 + endif + if (mod((glob_row-(x-1)*idim*idim),idim) == 0) then + y = (glob_row-(x-1)*idim*idim)/idim + else + y = (glob_row-(x-1)*idim*idim)/idim+1 + endif + z = glob_row-(x-1)*idim*idim-(y-1)*idim + ! glob_x, glob_y, glob_x coordinates + glob_x=x*deltah + glob_y=y*deltah + glob_z=z*deltah + + ! check on boundary points + zt(1) = 0.d0 + ! internal point: build discretization + ! + ! term depending on (x-1,y,z) + ! + if (x==1) then + val(element)=-b1(glob_x,glob_y,glob_z)& + & -a1(glob_x,glob_y,glob_z) + val(element) = val(element)/(deltah*& + & deltah) + zt(1) = exp(-glob_y**2-glob_z**2)*(-val(element)) + else + val(element)=-b1(glob_x,glob_y,glob_z)& + & -a1(glob_x,glob_y,glob_z) + val(element) = val(element)/(deltah*& + & deltah) + icol(element)=(x-2)*idim*idim+(y-1)*idim+(z) + element=element+1 + endif + ! term depending on (x,y-1,z) + if (y==1) then + val(element)=-b2(glob_x,glob_y,glob_z)& + & -a2(glob_x,glob_y,glob_z) val(element) = val(element)/(deltah*& & deltah) - icol(element)=(x-1)*idim*idim+(y-1)*idim+(z) - element=element+1 - ! term depending on (x,y,z+1) - if (z==idim) then - val(element)=-b1(glob_x,glob_y,glob_z) - val(element) = val(element)/(deltah*& - & deltah) - zt(1) = exp(-glob_y**2-glob_z**2)*exp(-glob_x)*(-val(element)) - else - val(element)=-b1(glob_x,glob_y,glob_z) - val(element) = val(element)/(deltah*& - & deltah) - icol(element)=(x-1)*idim*idim+(y-1)*idim+(z+1) - element=element+1 - endif - ! term depending on (x,y+1,z) - if (y==idim) then - val(element)=-b2(glob_x,glob_y,glob_z) - val(element) = val(element)/(deltah*& - & deltah) - zt(1) = exp(-glob_y**2-glob_z**2)*exp(-glob_x)*(-val(element)) - else - val(element)=-b2(glob_x,glob_y,glob_z) - val(element) = val(element)/(deltah*& - & deltah) - icol(element)=(x-1)*idim*idim+(y)*idim+(z) - element=element+1 - endif - ! term depending on (x+1,y,z) - if (x