diff --git a/model/src/w3parall.F90 b/model/src/w3parall.F90 index e2aba9b52..3964f41e1 100644 --- a/model/src/w3parall.F90 +++ b/model/src/w3parall.F90 @@ -532,6 +532,7 @@ SUBROUTINE PROP_REFRACTION_PR3(IP, ISEA, DTG, CAD, DoLimiter) eDDDY=DDDY(1,IP) eCTHG0 = CTHG0S(ISEA) FACTH = 1.0 / DTH + CAD = 0. ! FDG = FACTH * eCTHG0 DEPTH = MAX ( DMIN , DW(ISEA) ) diff --git a/model/src/w3profsmd_pdlib.F90 b/model/src/w3profsmd_pdlib.F90 index 6759fb53e..9585cdcc8 100644 --- a/model/src/w3profsmd_pdlib.F90 +++ b/model/src/w3profsmd_pdlib.F90 @@ -865,6 +865,118 @@ SUBROUTINE PDLIB_W3XYPUG ( ISP, FACX, FACY, DTG, VGX, VGY, LCALC ) !/ End of W3SPR4 ----------------------------------------------------- / !/ END SUBROUTINE PDLIB_W3XYPUG + + SUBROUTINE PDLIB_W3XYPUG_DRIVER ( FACX, FACY, DTG, VGX, VGY, LCALC ) + !/ + !/ +-----------------------------------+ + !/ | WAVEWATCH III NOAA/NCEP | + !/ | | + !/ | Aron Roland (BGS IT&E GmbH) | + !/ | | + !/ | FORTRAN 90 | + !/ | Last update : 10-Jan-2024 | + !/ +-----------------------------------+ + !/ + !/ 16-Jan-2024 : Origination. ( version 7.xx ) + !/ + ! 1. Purpose : Explicit advection schemes driver + ! + ! Propagation in physical space for all spectral components. + ! Used for OMPH + ! + ! 2. Method : + ! + ! 3. Parameters : + ! + ! Parameter list + ! ---------------------------------------------------------------- + ! ---------------------------------------------------------------- + ! + ! Local variables. + ! ---------------------------------------------------------------- + ! ---------------------------------------------------------------- + ! + ! 4. Subroutines used : + ! + ! 5. Called by : + ! + ! W3WAVE Wave model routine. + ! + ! 6. Error messages : + ! + ! None. + ! + ! 7. Remarks : + ! make the interface for OMPH implementation + ! + ! 8. Structure : + ! + ! + ! 9. Switches : + ! + ! !/S Enable subroutine tracing. + ! + ! + ! 10. Source code : + !/ ------------------------------------------------------------------- / + !/ + ! + USE CONSTANTS + ! + USE W3TIMEMD, only: DSEC21 + ! + USE W3GDATMD, only: NX, NY, NSPEC, MAPFS, CLATS, & + FLCX, FLCY, NK, NTH, DTH, XFR, & + ECOS, ESIN, SIG, PFMOVE, & + IOBP, IOBPD, & + FSN, FSPSI, FSFCT, FSNIMP, & + GTYPE, UNGTYPE, NBND_MAP, INDEX_MAP + USE YOWNODEPOOL, only: PDLIB_IEN, PDLIB_TRIA + USE W3GDATMD, only: IOBP_LOC, IOBPD_LOC, IOBPA_LOC, IOBDP_LOC + USE YOWNODEPOOL, only: iplg, npa + USE W3WDATMD, only: TIME, VA + USE W3ODATMD, only: TBPI0, TBPIN, FLBPI + USE W3ADATMD, only: CG, CX, CY, ITIME, DW + USE W3IDATMD, only: FLCUR, FLLEV + USE W3GDATMD, only: NSEAL + USE W3ODATMD, only: IAPROC + USE W3DISPMD, only : WAVNU_LOCAL + !/ ------------------------------------------------------------------- / + !/ Parameter list + !/ + REAL, INTENT(IN) :: FACX, FACY, DTG, VGX, VGY + LOGICAL, INTENT(IN) :: LCALC + !/ + !/ ------------------------------------------------------------------- / + !/ Local PARAMETERs + INTEGER :: ISP + !/ + !/ ------------------------------------------------------------------- / + ! + ! 1. Preparations --------------------------------------------------- * + ! 1.a Set constants + ! +#ifdef W3_S + CALL STRACE (IENT, 'W3XYPUG') +#endif +#ifdef W3_DEBUGSOLVER + WRITE(740+IAPROC,*) 'Begin of PDLIB_W3XYPUG_DRIVER' + FLUSH(740+IAPROC) +#endif + +#ifdef W3_OMPH + !$OMP PARALLEL DO PRIVATE (ISP) +#endif + DO ISP=1,NSPEC + CALL PDLIB_W3XYPUG ( ISP, FACX, FACX, DTG, VGX, VGY, LCALC ) + END DO +#ifdef W3_OMPH + !$OMP END PARALLEL DO +#endif + !/ + !/ End of PDLIB_W3XYPUG ----------------------------------------------------- / + !/ + END SUBROUTINE PDLIB_W3XYPUG_DRIVER !/ ------------------------------------------------------------------- / SUBROUTINE PDLIB_W3XYPFSN2(ISP, C, LCALC, RD10, RD20, DT, AC) !/ @@ -2854,12 +2966,24 @@ SUBROUTINE PDLIB_W3XYPUG_BLOCK_EXPLICIT(IMOD, FACX, FACY, DTG, VGX, VGY, LCALC) ! USE W3ODATMD, only: IAPROC USE W3GDATMD, only: B_JGS_USE_JACOBI + USE W3TIMEMD, only: DSEC21 + USE W3ODATMD, only: TBPI0, TBPIN, FLBPI + USE W3WDATMD, only: TIME LOGICAL, INTENT(IN) :: LCALC INTEGER, INTENT(IN) :: IMOD REAL, INTENT(IN) :: FACX, FACY, DTG, VGX, VGY + REAL :: RD1, RD2 + + IF ( FLBPI ) THEN + RD1 = DSEC21 ( TBPI0, TIME ) + RD2 = DSEC21 ( TBPI0, TBPIN ) + ELSE + RD1=1. + RD2=0. + END IF - CALL PDLIB_EXPLICIT_BLOCK(IMOD, FACX, FACY, DTG, VGX, VGY, LCALC) + CALL PDLIB_EXPLICIT_BLOCK(IMOD, FACX, FACY, RD1, RD2, DTG, VGX, VGY, LCALC) !/ !/ End of W3XYPFSN ----------------------------------------------------- / !/ @@ -3644,8 +3768,15 @@ SUBROUTINE calcARRAY_JACOBI_VEC(DTG,FACX,FACY,VGX,VGY) CCOSA = FACX * ECOS(1:NTH) CSINA = FACX * ESIN(1:NTH) + call print_memcheck(memunit, 'memcheck_____:'//' WW3_JACOBI SECTION 0') +#ifdef W3_OMPH + !$OMP PARALLEL DO PRIVATE (ISP, ITH, IK, CCOS, CSIN, IP, IP_GLOB, CG1, & + !$OMP& CXY, CXYY, FL11, FL12, FL21, FL22, FL31, FL32, & + !$OMP& CRFS, LAMBDA, K, KP, DELTAL, IB1, IB2, IBR, & + !$OMP& I, J, IE, POS, DTK, I1, I2, I3) +#endif DO ISP = 1, NSPEC ITH = 1 + MOD(ISP-1,NTH) @@ -3747,6 +3878,10 @@ SUBROUTINE calcARRAY_JACOBI_VEC(DTG,FACX,FACY,VGX,VGY) END DO END DO ! ISP +#ifdef W3_OMPH + !$OMP END PARALLEL DO +#endif + call print_memcheck(memunit, 'memcheck_____:'//' WW3_JACOBI SECTION 1') #ifdef W3_DEBUGSOLVER WRITE(740+IAPROC,*) 'sum(VA)=', sum(VA) @@ -4470,28 +4605,33 @@ SUBROUTINE calcARRAY_JACOBI_SPECTRAL_1(DTG) !AR: TODO: check&report if needed ... LSIG = FLCUR .OR. FLLEV +#ifdef W3_OMPH + !$OMP PARALLEL DO PRIVATE (IP, IP_GLOB, ISEA, eSI, CAS, DMM, CP_SIG, CM_SIG, B_SIG, & + !$OMP& ISP, ITH, IK, CWNB_M2, DWNI_M2, eVal, ITH0, & + !$OMP& CAD, CP_THE, CM_THE, B_THE) +#endif DO IP = 1, np - IP_glob=iplg(IP) - ISEA=MAPFS(1,IP_glob) - eSI=PDLIB_SI(IP) + IP_glob = iplg(IP) + ISEA = MAPFS(1,IP_glob) + eSI = PDLIB_SI(IP) IF (FSFREQSHIFT .AND. LSIG) THEN IF (FreqShiftMethod .eq. 1) THEN IF (IOBP_LOC(IP).eq.1.and.IOBDP_LOC(IP).eq.1.and.IOBPA_LOC(IP).eq.0) THEN CALL PROP_FREQ_SHIFT(IP, ISEA, CAS, DMM, DTG) CP_SIG = MAX(ZERO,CAS) CM_SIG = MIN(ZERO,CAS) - B_SIG=0 + B_SIG = 0 DO ITH=1,NTH DO IK=1,NK - ISP=ITH + (IK-1)*NTH + ISP = ITH + (IK-1)*NTH B_SIG(ISP)= CP_SIG(ISP)/DMM(IK-1) - CM_SIG(ISP)/DMM(IK) END DO - ISP = ITH + (NK-1)*NTH - B_SIG(ISP)= B_SIG(ISP) + CM_SIG(ISP)/DMM(NK) * FACHFA + ISP = ITH + (NK-1)*NTH ! AR: hmm ... + B_SIG(ISP) = B_SIG(ISP) + CM_SIG(ISP)/DMM(NK) * FACHFA END DO - ASPAR_JAC(:,PDLIB_I_DIAG(IP))=ASPAR_JAC(:,PDLIB_I_DIAG(IP)) + B_SIG(:)*eSI + ASPAR_JAC(:,PDLIB_I_DIAG(IP)) = ASPAR_JAC(:,PDLIB_I_DIAG(IP)) + B_SIG(:) * eSI ELSE - CAS=0 + CAS = 0 END IF CAS_SIG(:,IP) = CAS ELSE IF (FreqShiftMethod .eq. 2) THEN @@ -4513,19 +4653,15 @@ SUBROUTINE calcARRAY_JACOBI_SPECTRAL_1(DTG) ELSE CWNB_M2 = 0 END IF - CWNB_SIG_M2(:,IP)=CWNB_M2 + CWNB_SIG_M2(:,IP) = CWNB_M2 END IF END IF - ! - ! The refraction - ! + IF (FSREFRACTION) THEN IF (IOBP_LOC(IP) .eq. 1 .and. IOBDP_LOC(IP).eq.1.and.IOBPA_LOC(IP).eq.0) THEN - ! CALL PROP_REFRACTION_PR1(ISEA,DTG,CAD) !AR: Check statuts ... - ! CALL PROP_REFRACTION_PR3(ISEA,DTG,CAD, DoLimiterRefraction) CALL PROP_REFRACTION_PR3(IP,ISEA,DTG,CAD,DoLimiterRefraction) ELSE - CAD=ZERO + CAD = ZERO END IF #ifdef W3_DEBUGREFRACTION WRITE(740+IAPROC,*) 'refraction IP=', IP, ' ISEA=', ISEA @@ -4537,7 +4673,11 @@ SUBROUTINE calcARRAY_JACOBI_SPECTRAL_1(DTG) B_THE(:) = CP_THE(:) - CM_THE(:) ASPAR_JAC(:,PDLIB_I_DIAG(IP))=ASPAR_JAC(:,PDLIB_I_DIAG(IP)) + B_THE(:)*eSI END IF - END DO + END DO ! IP +#ifdef W3_OMPH + !$OMP END PARALLEL DO +#endif + END SUBROUTINE calcARRAY_JACOBI_SPECTRAL_1 !/ ------------------------------------------------------------------- / SUBROUTINE calcARRAY_JACOBI_SPECTRAL_2(DTG,ASPAR_DIAG_LOCAL) @@ -4678,8 +4818,6 @@ SUBROUTINE calcARRAY_JACOBI_SPECTRAL_2(DTG,ASPAR_DIAG_LOCAL) ! IF (FSREFRACTION) THEN IF (IOBP_LOC(IP) .eq. 1.and.IOBDP_LOC(IP).eq.1.and.IOBPA_LOC(IP).eq.0) THEN - ! CALL PROP_REFRACTION_PR1(ISEA,DTG,CAD) !AR: Is this working? - ! CALL PROP_REFRACTION_PR3(ISEA,DTG,CAD, DoLimiterRefraction) CALL PROP_REFRACTION_PR3(IP,ISEA,DTG,CAD,DoLimiterRefraction) ELSE CAD=ZERO @@ -5546,26 +5684,26 @@ SUBROUTINE PDLIB_JACOBI_GAUSS_SEIDEL_BLOCK(IMOD, FACX, FACY, DTG, VGX, VGY, LCAL INTEGER :: nbIter, ISPnextDir, ISPprevDir INTEGER :: ISPp1, ISPm1, JP, ICOUNT1, ICOUNT2 ! for the exchange - REAL*8 :: CCOS, CSIN, CCURX, CCURY - REAL*8 :: eSum(NSPEC), FRLOCAL - REAL*8 :: eA_THE, eC_THE, eA_SIG, eC_SIG, eSI - REAL*8 :: CAD(NSPEC), CAS(NSPEC), ACLOC(NSPEC) - REAL*8 :: CP_SIG(NSPEC), CM_SIG(NSPEC) - REAL*8 :: eFactM1, eFactP1 - REAL*8 :: Sum_Prev, Sum_New, p_is_converged, DiffNew, prop_conv - REAL*8 :: Sum_L2, Sum_L2_GL + REAL :: CCOS, CSIN, CCURX, CCURY + REAL :: eSum(NSPEC), FRLOCAL + REAL :: eA_THE, eC_THE, eA_SIG, eC_SIG, eSI + REAL :: CAD(NSPEC), CAS(NSPEC), ACLOC(NSPEC) + REAL :: CP_SIG(NSPEC), CM_SIG(NSPEC) + REAL :: eFactM1, eFactP1 + REAL :: Sum_Prev, Sum_New, p_is_converged, DiffNew, prop_conv + REAL :: Sum_L2, Sum_L2_GL REAL :: DMM(0:NK2), DAM(NSPEC), DAM2(NSPEC), SPEC(NSPEC) - REAL*8 :: eDiff(NSPEC), eProd(NSPEC), eDiffB(NSPEC) - REAL*8 :: DWNI_M2(NK), CWNB_M2(1-NTH:NSPEC) + REAL :: eDiff(NSPEC), eProd(NSPEC), eDiffB(NSPEC) + REAL :: DWNI_M2(NK), CWNB_M2(1-NTH:NSPEC) REAL :: VAnew(NSPEC), VFLWN(1-NTH:NSPEC), JAC, JAC2 REAL :: VAAnew(1-NTH:NSPEC+NTH), VAAacloc(1-NTH:NSPEC+NTH) REAL :: VAinput(NSPEC), VAacloc(NSPEC), ASPAR_DIAG(NSPEC) REAL :: aspar_diag_local(nspec), aspar_off_diag_local(nspec), b_jac_local(nspec) - REAL*8 :: eDiffSing, eSumPart + REAL :: eDiffSing, eSumPart REAL :: EMEAN, FMEAN, FMEAN1, WNMEAN, AMAX, U10ABS, U10DIR, TAUA, TAUADIR REAL :: USTAR, USTDIR, TAUWX, TAUWY, CD, Z0, CHARN, FMEANWS, DLWMEAN - REAL*8 :: eVal1, eVal2 - REAL*8 :: eVA, eVO, CG2, NEWDAC, NEWAC, OLDAC, MAXDAC + REAL :: eVal1, eVal2 + REAL :: eVA, eVO, CG2, NEWDAC, NEWAC, OLDAC, MAXDAC REAL :: CG1(0:NK+1), WN1(0:NK+1) LOGICAL :: LCONVERGED(NSEAL), lexist, LLWS(NSPEC) #ifdef WEIGHTS @@ -5641,6 +5779,10 @@ SUBROUTINE PDLIB_JACOBI_GAUSS_SEIDEL_BLOCK(IMOD, FACX, FACY, DTG, VGX, VGY, LCAL CALL ALL_VA_INTEGRAL_PRINT(IMOD, "VA(np) before transform", 0) CALL ALL_VA_INTEGRAL_PRINT(IMOD, "VA(npa) before transform", 1) #endif + +#ifdef W3_OMPH + !$OMP PARALLEL DO PRIVATE (JSEA, IP, IP_GLOB, ISEA, ISP, ITH, IK, WN1, CG1) +#endif DO JSEA=1,NSEAL IP = JSEA IP_glob = iplg(IP) @@ -5656,6 +5798,10 @@ SUBROUTINE PDLIB_JACOBI_GAUSS_SEIDEL_BLOCK(IMOD, FACX, FACY, DTG, VGX, VGY, LCAL VA(ISP,JSEA) = VA(ISP,JSEA) / CG1(IK) * CLATS(ISEA) END DO END DO +#ifdef W3_OMPH + !$OMP END PARALLEL DO +#endif + VAOLD = VA(1:NSPEC,1:NSEAL) #ifdef W3_DEBUGSRC @@ -5755,6 +5901,13 @@ SUBROUTINE PDLIB_JACOBI_GAUSS_SEIDEL_BLOCK(IMOD, FACX, FACY, DTG, VGX, VGY, LCAL call print_memcheck(memunit, 'memcheck_____:'//' WW3_PROP SECTION SOLVER LOOP 1') +#ifdef W3_OMPH + !$OMP PARALLEL DO PRIVATE (IP, ISP, IP_GLOB, ISEA, IK, ITH, CG1, WN1, JSEA, eSI, ACLOC, ESUM, & + !$OMP& ASPAR_DIAG, JP, EPROD, ISPprevDir, ISPnextDir, eA_THE, eC_THE, & + !$OMP& ISPm1, ISPp1, eFactM1, eFactP1, eA_SIG, eC_SIG, CAS, CAD, CP_SIG, DMM, & + !$OMP& CWNB_M2, DWNI_M2, p_is_converged, sum_prev, sum_new, diffnew), REDUCTION(+:is_converged) +#endif + DO IP = 1, np IP_glob = iplg(IP) @@ -5806,7 +5959,7 @@ SUBROUTINE PDLIB_JACOBI_GAUSS_SEIDEL_BLOCK(IMOD, FACX, FACY, DTG, VGX, VGY, LCAL IF (IMEM == 2) THEN CALL calcARRAY_JACOBI4(IP,DTG,FACX,FACY,VGX,VGY,ASPAR_DIAG_LOCAL,ASPAR_OFF_DIAG_LOCAL,B_JAC_LOCAL) ASPAR_DIAG(1:NSPEC) = ASPAR_DIAG_LOCAL(1:NSPEC) + ASPAR_DIAG_ALL(1:NSPEC,IP) - esum = B_JAC_LOCAL - ASPAR_OFF_DIAG_LOCAL + B_JAC(1:NSPEC,IP) + esum(1:NSPEC) = B_JAC_LOCAL - ASPAR_OFF_DIAG_LOCAL + B_JAC(1:NSPEC,IP) ELSEIF (IMEM == 1) THEN eSum(1:NSPEC) = B_JAC(1:NSPEC,IP) ASPAR_DIAG(1:NSPEC) = ASPAR_JAC(1:NSPEC,PDLIB_I_DIAG(IP)) @@ -6013,6 +6166,10 @@ SUBROUTINE PDLIB_JACOBI_GAUSS_SEIDEL_BLOCK(IMOD, FACX, FACY, DTG, VGX, VGY, LCAL #endif END DO ! IP +#ifdef W3_OMPH + !$OMP END PARALLEL DO +#endif + call print_memcheck(memunit, 'memcheck_____:'//' WW3_PROP SECTION SOLVER LOOP 2') #ifdef W3_DEBUGSOLVERCOH @@ -6139,7 +6296,7 @@ SUBROUTINE PDLIB_JACOBI_GAUSS_SEIDEL_BLOCK(IMOD, FACX, FACY, DTG, VGX, VGY, LCAL #endif EXIT END IF - END IF + END IF ! TERMINATE NORM call print_memcheck(memunit, 'memcheck_____:'//' WW3_PROP SECTION SOLVER LOOP 6') nbiter = nbiter + 1 @@ -6328,7 +6485,7 @@ SUBROUTINE PDLIB_JACOBI_GAUSS_SEIDEL_BLOCK(IMOD, FACX, FACY, DTG, VGX, VGY, LCAL #endif END SUBROUTINE PDLIB_JACOBI_GAUSS_SEIDEL_BLOCK !/ ------------------------------------------------------------------- / - SUBROUTINE PDLIB_EXPLICIT_BLOCK(IMOD, FACX, FACY, DTG, VGX, VGY, LCALC) + SUBROUTINE PDLIB_EXPLICIT_BLOCK(IMOD, FACX, FACY, RD10, RD20, DTG, VGX, VGY, LCALC) !/ !/ +-----------------------------------+ !/ | WAVEWATCH III NOAA/NCEP | @@ -6402,7 +6559,7 @@ SUBROUTINE PDLIB_EXPLICIT_BLOCK(IMOD, FACX, FACY, DTG, VGX, VGY, LCALC) INTEGER, INTENT(IN) :: IMOD - REAL, INTENT(IN) :: FACX, FACY, DTG, VGX, VGY + REAL, INTENT(IN) :: FACX, FACY, DTG, VGX, VGY, RD10, RD20 REAL :: KTMP(3), UTILDE(NTH), ST(NTH,NPA) REAL :: FL11(NTH), FL12(NTH), FL21(NTH), FL22(NTH), FL31(NTH), FL32(NTH), KKSUM(NTH,NPA) @@ -6411,7 +6568,7 @@ SUBROUTINE PDLIB_EXPLICIT_BLOCK(IMOD, FACX, FACY, DTG, VGX, VGY, LCALC) REAL :: KSIG(NPA), CGSIG(NPA), CXX(NTH,NPA), CYY(NTH,NPA) REAL :: LAMBDAX(NTH), LAMBDAY(NTH) REAL :: DTMAX(NTH), DTMAXEXP(NTH), DTMAXOUT, DTMAXGL - REAL :: FIN(1), FOUT(1), REST, CFLXY, RD1, RD2, RD10, RD20 + REAL :: FIN(1), FOUT(1), REST, CFLXY, RD1, RD2 REAL :: UOLD(NTH,NPA), U(NTH,NPA) REAL, PARAMETER :: ONESIXTH = 1.0/6.0 @@ -6570,8 +6727,8 @@ SUBROUTINE PDLIB_EXPLICIT_BLOCK(IMOD, FACX, FACY, DTG, VGX, VGY, LCALC) IF ( FLBPI ) THEN DO ITH = 1, NTH ISP = ITH + (IK-1) * NTH - RD1 = RD10 - DTG * REAL(ITER(IK)-IT)/REAL(ITER(IK)) - RD2 = RD20 + RD1=RD10 - DTMAXGL * REAL(ITER(IK)-IT)/REAL(ITER(IK)) + RD2=RD20 IF ( RD2 .GT. 0.001 ) THEN RD2 = MIN(1.,MAX(0.,RD1/RD2)) RD1 = 1. - RD2 diff --git a/model/src/w3sdb1md.F90 b/model/src/w3sdb1md.F90 index 34c7ec3bf..f57171e45 100644 --- a/model/src/w3sdb1md.F90 +++ b/model/src/w3sdb1md.F90 @@ -187,6 +187,7 @@ SUBROUTINE W3SDB1 (IX, A, DEPTH, EMEAN, FMEAN, WNMEAN, CG, LBREAK, S, D ) USE W3ODATMD, ONLY: NDST USE W3GDATMD, ONLY: SIG USE W3ODATMD, only : IAPROC + USE W3PARALL, only : THR #ifdef W3_S USE W3SERVMD, ONLY: STRACE #endif @@ -218,7 +219,7 @@ SUBROUTINE W3SDB1 (IX, A, DEPTH, EMEAN, FMEAN, WNMEAN, CG, LBREAK, S, D ) INTEGER, SAVE :: IENT = 0 #endif REAL*8 :: HM, BB, ARG, Q0, QB, B, CBJ, HRMS, EB(NK) - REAL*8 :: AUX, CBJ2, RATIO, S0, S1, THR, BR1, BR2, FAK + REAL*8 :: AUX, CBJ2, RATIO, S0, S1, BR1, BR2, FAK REAL :: ETOT, FMEAN2 #ifdef W3_T0 REAL :: DOUT(NK,NTH) @@ -235,8 +236,11 @@ SUBROUTINE W3SDB1 (IX, A, DEPTH, EMEAN, FMEAN, WNMEAN, CG, LBREAK, S, D ) S = 0. D = 0. - THR = DBLE(1.E-15) - IF (SUM(A) .LT. THR) RETURN + IF (EMEAN .LT. TINY(1.d0)) THEN + S = 0 + D = 0 + RETURN + ENDIF IWB = 1 ! diff --git a/model/src/w3srcemd.F90 b/model/src/w3srcemd.F90 index e90ba88eb..d728da23c 100644 --- a/model/src/w3srcemd.F90 +++ b/model/src/w3srcemd.F90 @@ -1244,7 +1244,7 @@ SUBROUTINE W3SRCE ( srce_call, IT, ISEA, JSEA, IX, IY, IMOD, & IF (.NOT. FSSOURCE .or. LSLOC) THEN #endif #ifdef W3_TR1 - CALL W3STR1 ( SPEC, SPECOLD, CG1, WN1, DEPTH, IX, VSTR, VDTR ) + CALL W3STR1 ( SPEC, CG1, WN1, DEPTH, IX, VSTR, VDTR ) #endif #ifdef W3_PDLIB ENDIF @@ -1534,8 +1534,13 @@ SUBROUTINE W3SRCE ( srce_call, IT, ISEA, JSEA, IX, IY, IMOD, & DVS = SIGN(MIN(MAXDAC,ABS(DVS)),DVS) ENDIF PreVS = DVS / FAKS - eVS = PreVS / CG1(IK) * CLATSL - eVD = MIN(0.,VD(ISP)) + IF (IOBP_LOC(JSEA) .EQ. 3) THEN + eVS = 0 + eVD = 0 + ELSE + eVS = PreVS / CG1(IK) * CLATSL + eVD = MIN(0.,VD(ISP)) + ENDIF B_JAC(ISP,JSEA) = B_JAC(ISP,JSEA) + SIDT * (eVS - eVD*SPEC(ISP)*JAC) ASPAR_JAC(ISP,PDLIB_I_DIAG(JSEA)) = ASPAR_JAC(ISP,PDLIB_I_DIAG(JSEA)) - SIDT * eVD #ifdef W3_DB1 @@ -1548,9 +1553,9 @@ SUBROUTINE W3SRCE ( srce_call, IT, ISEA, JSEA, IX, IY, IMOD, & evS = -evS evD = 2*evD ENDIF -#endif B_JAC(ISP,JSEA) = B_JAC(ISP,JSEA) + SIDT * eVS ASPAR_JAC(ISP,PDLIB_I_DIAG(JSEA)) = ASPAR_JAC(ISP,PDLIB_I_DIAG(JSEA)) - SIDT * eVD +#endif #ifdef W3_TR1 eVS = VSTR(ISP) * JAC @@ -1562,9 +1567,9 @@ SUBROUTINE W3SRCE ( srce_call, IT, ISEA, JSEA, IX, IY, IMOD, & evS = -evS evD = 2*evD ENDIF -#endif B_JAC(ISP,JSEA) = B_JAC(ISP,JSEA) + SIDT * eVS ASPAR_JAC(ISP,PDLIB_I_DIAG(JSEA)) = ASPAR_JAC(ISP,PDLIB_I_DIAG(JSEA)) - SIDT * eVD +#endif END DO END DO diff --git a/model/src/w3str1md.F90 b/model/src/w3str1md.F90 index d8067abd7..03cad7aeb 100644 --- a/model/src/w3str1md.F90 +++ b/model/src/w3str1md.F90 @@ -180,7 +180,7 @@ MODULE W3STR1MD !> !> @author A. J. van der Westhuysen @date 13-Jan-2013 !> - SUBROUTINE W3STR1 (A, AOLD, CG, WN, DEPTH, IX, S, D) + SUBROUTINE W3STR1 (A, CG, WN, DEPTH, IX, S, D) !/ !/ +-----------------------------------+ !/ | WAVEWATCH III NOAA/NCEP | @@ -259,7 +259,6 @@ SUBROUTINE W3STR1 (A, AOLD, CG, WN, DEPTH, IX, S, D) ! CG R.A. I Group velocities. ! WN R.A. I Wavenumbers. ! DEPTH Real I Mean water depth. - ! EMEAN Real I Mean wave energy. ! FMEAN Real I Mean wave frequency. ! S R.A. O Source term (1-D version). ! D R.A. O Diagonal term of derivative (1-D version). @@ -320,7 +319,7 @@ SUBROUTINE W3STR1 (A, AOLD, CG, WN, DEPTH, IX, S, D) !/ ------------------------------------------------------------------- / !/ Parameter list !/ - REAL, INTENT(IN) :: CG(NK), WN(NK), DEPTH, A(NSPEC), AOLD(NSPEC) + REAL, INTENT(IN) :: CG(NK), WN(NK), DEPTH, A(NSPEC) INTEGER, INTENT(IN) :: IX REAL, INTENT(OUT) :: S(NSPEC), D(NSPEC) !/ @@ -391,11 +390,15 @@ SUBROUTINE W3STR1 (A, AOLD, CG, WN, DEPTH, IX, S, D) #ifdef W3_S CALL STRACE (IENT, 'W3STR1') #endif - -!AR: todo: check all PRX routines for differences, check original thesis of elderberky. ! ! 1. Integral over directions ! + IF (MAXVAL(A) .LT. TINY(1.)) THEN + S = 0 + D = 0 + RETURN + ENDIF + SIGM01 = 0. EMEAN = 0. JACEPS = 1E-12 diff --git a/model/src/w3wavemd.F90 b/model/src/w3wavemd.F90 index c144ab8d8..a2d311790 100644 --- a/model/src/w3wavemd.F90 +++ b/model/src/w3wavemd.F90 @@ -448,7 +448,7 @@ SUBROUTINE W3WAVE ( IMOD, ODAT, TEND, STAMP, NO_OUT & USE W3IOSFMD #ifdef W3_PDLIB USE PDLIB_W3PROFSMD, only : APPLY_BOUNDARY_CONDITION_VA - USE PDLIB_W3PROFSMD, only : PDLIB_W3XYPUG, PDLIB_W3XYPUG_BLOCK_IMPLICIT, PDLIB_W3XYPUG_BLOCK_EXPLICIT + USE PDLIB_W3PROFSMD, only : PDLIB_W3XYPUG_DRIVER, PDLIB_W3XYPUG_BLOCK_IMPLICIT, PDLIB_W3XYPUG_BLOCK_EXPLICIT USE PDLIB_W3PROFSMD, only : ALL_VA_INTEGRAL_PRINT, ALL_VAOLD_INTEGRAL_PRINT, ALL_FIELD_INTEGRAL_PRINT USE W3PARALL, only : PDLIB_NSEAL, PDLIB_NSEALM USE yowNodepool, only: npa, iplg, np @@ -1453,6 +1453,12 @@ SUBROUTINE W3WAVE ( IMOD, ODAT, TEND, STAMP, NO_OUT & call print_memcheck(memunit, 'memcheck_____:'//' WW3_WAVE TIME LOOP 13') ! #ifdef W3_PDLIB + + IF (LPDLIB .and. .not. FLSOU .and. .not. FSSOURCE) THEN + B_JAC = 0. + ASPAR_JAC = 0. + ENDIF + IF (LPDLIB .and. FLSOU .and. FSSOURCE) THEN #endif @@ -1484,6 +1490,8 @@ SUBROUTINE W3WAVE ( IMOD, ODAT, TEND, STAMP, NO_OUT & CALL INIT_GET_ISEA(ISEA, JSEA) + IF ((IOBP_LOC(JSEA).eq.1..or.IOBP_LOC(JSEA).eq. 3).and.IOBDP_LOC(JSEA).eq.1.and.IOBPA_LOC(JSEA).eq.0) THEN + IX = MAPSF(ISEA,1) IY = MAPSF(ISEA,2) DELA=1. @@ -1556,6 +1564,7 @@ SUBROUTINE W3WAVE ( IMOD, ODAT, TEND, STAMP, NO_OUT & WRITE(740+IAPROC,*) ' SHAVETOT=', SHAVETOT(JSEA) FLUSH(740+IAPROC) #endif + ENDIF END DO ! JSEA END IF ! PDLIB #endif @@ -1816,9 +1825,7 @@ SUBROUTINE W3WAVE ( IMOD, ODAT, TEND, STAMP, NO_OUT & #ifdef W3_PDLIB IF (FLCX .or. FLCY) THEN IF (.NOT. FSTOTALIMP .AND. .NOT. FSTOTALEXP) THEN - DO ISPEC=1,NSPEC - CALL PDLIB_W3XYPUG ( ISPEC, FACX, FACX, DTG, VGX, VGY, UGDTUPDATE ) - END DO + CALL PDLIB_W3XYPUG_DRIVER ( FACX, FACX, DTG, VGX, VGY, UGDTUPDATE ) END IF END IF #endif @@ -2158,6 +2165,7 @@ SUBROUTINE W3WAVE ( IMOD, ODAT, TEND, STAMP, NO_OUT & ! DO JSEA=1, NSEAL CALL INIT_GET_ISEA(ISEA, JSEA) + IX = MAPSF(ISEA,1) IY = MAPSF(ISEA,2) DELA=1. diff --git a/regtests/ww3_tp2.2/input/track_i.ww3 b/regtests/ww3_tp2.2/input/track_i.ww3 deleted file mode 100644 index e4e7fbf61..000000000 --- a/regtests/ww3_tp2.2/input/track_i.ww3 +++ /dev/null @@ -1,6 +0,0 @@ -WAVEWATCH III TRACK LOCATIONS DATA -20220606 000000 0 0 S1A -20220606 040000 1 0 S1B -20220606 060000 1 0 S1C -20220606 080000 2 0 S1D -20220606 120000 0.5 0 S1E diff --git a/regtests/ww3_tp2.22/info b/regtests/ww3_tp2.22/info new file mode 100644 index 000000000..08fedb1c1 --- /dev/null +++ b/regtests/ww3_tp2.22/info @@ -0,0 +1,29 @@ +############################################################################# +# # +# ww3_tp2.22 Test script for WW-III, unstructured grid. # +# Example of Limon harbour, Costa Rica # +# # +# Model should be compiled with the switches : # +# # +# NOGRB PDLIB METIS OMPG OMPH TRKNC DIST MPI PR3 UQ FLX1 LN1 ST1 STAB0 # +# NL1 BT0 DB0 TR0 BS0 SEC0 IC0 IS0 REF0 WNT2 WNX1 CRT1 CRX1 O0 O1 O2 O2a # +# O2b O2c O3 O4 O5 O6 O7 # +# # +# The choice of propagation schemes for unstructured grids is done via # +# namelists. This test is intendend to test the OMPH feature using # +# implicit and explicit schemes on unstructued grids # +# # +# Remarks : # +# # +# - No other optional switches should be used. # +# # +# Sample run_test commands : # +# ./bin/run_test -s ST4 ../model ww3_tp2.22 # +# # +# Domain Decomposition Implicit needs PDLIB and either of METIS or # +# SCOTCH switch # +# ./bin/run_test -s PDLIB ../model ww3_tp2.22 # +# # +# Aron Roland, Jan 2023 # +# # +############################################################################# diff --git a/regtests/ww3_tp2.22/input/CMakeCache.txt b/regtests/ww3_tp2.22/input/CMakeCache.txt new file mode 100644 index 000000000..6c38353e3 --- /dev/null +++ b/regtests/ww3_tp2.22/input/CMakeCache.txt @@ -0,0 +1,38 @@ +# This is the CMakeCache file. +# For build in directory: /home/aron/git/ww3.erdc/WW3/regtests/ww3_tp2.6/input +# It was generated by CMake: /snap/cmake/1361/bin/cmake +# You can edit this file to change values found and used by cmake. +# If you do not want to change any of the values, simply exit the editor. +# If you do want to change a value, simply edit, save, and exit the editor. +# The syntax for the file is as follows: +# KEY:TYPE=VALUE +# KEY is the name of a variable in the cache. +# TYPE is a hint to GUIs for the type of VALUE, DO NOT EDIT TYPE!. +# VALUE is the current value for the KEY. + +######################## +# EXTERNAL cache entries +######################## + + +######################## +# INTERNAL cache entries +######################## + +//This is the directory where this CMakeCache.txt was created +CMAKE_CACHEFILE_DIR:INTERNAL=/home/aron/git/ww3.erdc/WW3/regtests/ww3_tp2.6/input +//Major version of cmake used to create the current loaded cache +CMAKE_CACHE_MAJOR_VERSION:INTERNAL=3 +//Minor version of cmake used to create the current loaded cache +CMAKE_CACHE_MINOR_VERSION:INTERNAL=28 +//Patch version of cmake used to create the current loaded cache +CMAKE_CACHE_PATCH_VERSION:INTERNAL=1 +//Path to CMake executable. +CMAKE_COMMAND:INTERNAL=/snap/cmake/1361/bin/cmake +//Path to cpack program executable. +CMAKE_CPACK_COMMAND:INTERNAL=/snap/cmake/1361/bin/cpack +//Path to ctest program executable. +CMAKE_CTEST_COMMAND:INTERNAL=/snap/cmake/1361/bin/ctest +//Path to CMake installation. +CMAKE_ROOT:INTERNAL=/snap/cmake/1361/share/cmake-3.28 + diff --git a/regtests/ww3_tp2.22/input/CMakeFiles/cmake.check_cache b/regtests/ww3_tp2.22/input/CMakeFiles/cmake.check_cache new file mode 100644 index 000000000..3dccd7317 --- /dev/null +++ b/regtests/ww3_tp2.22/input/CMakeFiles/cmake.check_cache @@ -0,0 +1 @@ +# This file is generated by cmake for dependency checking of the CMakeCache.txt file diff --git a/regtests/ww3_tp2.22/input/bintoc.in b/regtests/ww3_tp2.22/input/bintoc.in new file mode 100644 index 000000000..3f2ff2d6c --- /dev/null +++ b/regtests/ww3_tp2.22/input/bintoc.in @@ -0,0 +1,5 @@ + + + + + diff --git a/regtests/ww3_tp2.22/input/limon_ll.msh b/regtests/ww3_tp2.22/input/limon_ll.msh new file mode 100644 index 000000000..9af7bfbf5 --- /dev/null +++ b/regtests/ww3_tp2.22/input/limon_ll.msh @@ -0,0 +1,5343 @@ +$MeshFormat +2 0 8 +$EndMeshFormat +$Nodes + 1778 + 1 -83.02999316 9.98002141 2.500 + 2 -83.02956556 9.98001773 3.450 + 3 -83.02913797 9.98001404 4.400 + 4 -83.02873845 9.98001547 4.800 + 5 -83.02833893 9.98001690 5.200 + 6 -83.02793941 9.98001833 5.600 + 7 -83.02753988 9.98001975 6.000 + 8 -83.02724198 9.98001859 6.250 + 9 -83.02694408 9.98001742 6.500 + 10 -83.02664617 9.98001626 6.750 + 11 -83.02634827 9.98001509 7.000 + 12 -83.02609945 9.98001709 7.375 + 13 -83.02585064 9.98001909 7.750 + 14 -83.02560182 9.98002109 8.125 + 15 -83.02535301 9.98002309 8.500 + 16 -83.02496050 9.98002446 8.750 + 17 -83.02456799 9.98002583 9.000 + 18 -83.02417548 9.98002720 9.250 + 19 -83.02378297 9.98002857 9.500 + 20 -83.02346231 9.98003115 9.750 + 21 -83.02314165 9.98003372 10.000 + 22 -83.02282100 9.98003630 10.250 + 23 -83.02250034 9.98003887 10.500 + 24 -83.02218666 9.98003605 10.750 + 25 -83.02187297 9.98003323 11.000 + 26 -83.02155928 9.98003041 11.250 + 27 -83.02124559 9.98002759 11.500 + 28 -83.02096872 9.98002804 11.750 + 29 -83.02069186 9.98002848 12.000 + 30 -83.02041500 9.98002892 12.250 + 31 -83.02013813 9.98002937 12.500 + 32 -83.01988757 9.98003138 13.000 + 33 -83.01963700 9.98003339 13.500 + 34 -83.01938643 9.98003541 14.000 + 35 -83.01913586 9.98003742 14.500 + 36 -83.01889402 9.98003402 14.750 + 37 -83.01865217 9.98003063 15.000 + 38 -83.01841032 9.98002723 15.250 + 39 -83.01816847 9.98002383 15.500 + 40 -83.01793455 9.98002571 15.875 + 41 -83.01770063 9.98002759 16.250 + 42 -83.01746671 9.98002947 16.625 + 43 -83.01723279 9.98003135 17.000 + 44 -83.01699887 9.98003323 17.375 + 45 -83.01676495 9.98003510 17.750 + 46 -83.01653103 9.98003698 18.125 + 47 -83.01629711 9.98003886 18.500 + 48 -83.01586423 9.98003166 17.575 + 49 -83.01543135 9.98002446 16.650 + 50 -83.01499846 9.98001726 15.725 + 51 -83.01456558 9.98001006 14.800 + 52 -83.01414682 9.98001521 15.100 + 53 -83.01372805 9.98002035 15.400 + 54 -83.01330929 9.98002549 15.700 + 55 -83.01289052 9.98003064 16.000 + 56 -83.01255234 9.98003335 16.500 + 57 -83.01221417 9.98003607 17.000 + 58 -83.01187599 9.98003878 17.500 + 59 -83.01153781 9.98004150 18.000 + 60 -83.01125567 9.98003932 18.250 + 61 -83.01097352 9.98003713 18.500 + 62 -83.01069138 9.98003495 18.750 + 63 -83.01040924 9.98003276 19.000 + 64 -83.01012710 9.98003058 19.250 + 65 -83.00984495 9.98002840 19.500 + 66 -83.00956281 9.98002621 19.750 + 67 -83.00940483 9.98021761 20.000 + 68 -83.00942837 9.98042676 20.000 + 69 -83.00957608 9.98082949 20.000 + 70 -83.00972378 9.98123222 20.000 + 71 -83.00987149 9.98163494 20.000 + 72 -83.01001919 9.98203767 20.000 + 73 -83.01016690 9.98244040 20.000 + 74 -83.01031460 9.98284313 20.000 + 75 -83.01046230 9.98324586 20.000 + 76 -83.01052376 9.98348736 20.025 + 77 -83.01058522 9.98372886 20.050 + 78 -83.01064668 9.98397036 20.075 + 79 -83.01070814 9.98421186 20.100 + 80 -83.01076960 9.98445335 20.125 + 81 -83.01083106 9.98469485 20.150 + 82 -83.01089252 9.98493635 20.175 + 83 -83.01095398 9.98517785 20.200 + 84 -83.01102826 9.98549042 20.300 + 85 -83.01110254 9.98580300 20.400 + 86 -83.01117681 9.98611557 20.500 + 87 -83.01125110 9.98642814 20.600 + 88 -83.01132538 9.98674071 20.700 + 89 -83.01139966 9.98705328 20.800 + 90 -83.01147394 9.98736585 20.900 + 91 -83.01154822 9.98767842 21.000 + 92 -83.01162420 9.98798475 21.000 + 93 -83.01170018 9.98829108 21.000 + 94 -83.01177617 9.98859741 21.000 + 95 -83.01185215 9.98890374 21.000 + 96 -83.01192813 9.98921007 21.000 + 97 -83.01200412 9.98951640 21.000 + 98 -83.01208010 9.98982273 21.000 + 99 -83.01237422 9.99001254 21.000 + 100 -83.01259235 9.98989602 21.000 + 101 -83.01302862 9.98966298 21.000 + 102 -83.01324675 9.98954646 21.000 + 103 -83.01346489 9.98942993 21.000 + 104 -83.01368302 9.98931341 21.000 + 105 -83.01390116 9.98919689 21.000 + 106 -83.01414027 9.98907398 20.938 + 107 -83.01437938 9.98895106 20.875 + 108 -83.01461849 9.98882814 20.812 + 109 -83.01485760 9.98870523 20.750 + 110 -83.01509671 9.98858231 20.688 + 111 -83.01533582 9.98845939 20.625 + 112 -83.01557493 9.98833648 20.562 + 113 -83.01581404 9.98821356 20.500 + 114 -83.01612122 9.98805451 20.375 + 115 -83.01642839 9.98789546 20.250 + 116 -83.01673556 9.98773641 20.125 + 117 -83.01704273 9.98757736 20.000 + 118 -83.01724336 9.98746365 19.375 + 119 -83.01744399 9.98734994 18.750 + 120 -83.01764463 9.98723623 18.125 + 121 -83.01784526 9.98712252 17.500 + 122 -83.01807220 9.98701215 16.750 + 123 -83.01829914 9.98690179 16.000 + 124 -83.01852608 9.98679143 15.250 + 125 -83.01875302 9.98668106 14.500 + 126 -83.01907939 9.98651118 14.000 + 127 -83.01940575 9.98634130 13.500 + 128 -83.01973212 9.98617142 13.000 + 129 -83.02005848 9.98600154 12.500 + 130 -83.02030457 9.98587501 11.950 + 131 -83.02055066 9.98574848 11.400 + 132 -83.02079676 9.98562195 10.850 + 133 -83.02104285 9.98549542 10.300 + 134 -83.02130104 9.98534744 7.550 + 135 -83.02155923 9.98519945 4.800 + 136 -83.02178257 9.98507666 4.800 + 137 -83.02200591 9.98495387 4.800 + 138 -83.02183516 9.98462785 4.800 + 139 -83.02191870 9.98455600 0.000 + 140 -83.02167457 9.98425903 0.000 + 141 -83.02143043 9.98396205 0.000 + 142 -83.02123220 9.98370741 0.000 + 143 -83.02100547 9.98339607 0.000 + 144 -83.02100960 9.98302593 0.000 + 145 -83.02100694 9.98268431 0.000 + 146 -83.02101123 9.98233553 0.000 + 147 -83.02101491 9.98190845 0.000 + 148 -83.02104810 9.98161100 0.000 + 149 -83.02111071 9.98160875 0.000 + 150 -83.02121650 9.98161100 0.000 + 151 -83.02121127 9.98187996 0.000 + 152 -83.02120603 9.98214891 0.000 + 153 -83.02118800 9.98253339 0.000 + 154 -83.02117742 9.98297476 0.000 + 155 -83.02117991 9.98329503 0.000 + 156 -83.02139963 9.98360643 0.000 + 157 -83.02157006 9.98388976 0.000 + 158 -83.02175412 9.98412315 0.000 + 159 -83.02195242 9.98438491 0.000 + 160 -83.02213343 9.98422687 8.500 + 161 -83.02246786 9.98396796 6.000 + 162 -83.02282376 9.98376582 3.900 + 163 -83.02305037 9.98406292 4.000 + 164 -83.02310140 9.98431518 3.900 + 165 -83.02315243 9.98456745 3.800 + 166 -83.02339765 9.98455302 3.800 + 167 -83.02364286 9.98453860 3.800 + 168 -83.02388807 9.98452417 3.800 + 169 -83.02413329 9.98450975 3.800 + 170 -83.02444510 9.98449657 3.875 + 171 -83.02475691 9.98448339 3.950 + 172 -83.02507228 9.98447729 3.875 + 173 -83.02538765 9.98447120 3.800 + 174 -83.02567655 9.98444041 3.600 + 175 -83.02596544 9.98440962 3.400 + 176 -83.02625433 9.98437883 3.200 + 177 -83.02654323 9.98434804 3.000 + 178 -83.02692835 9.98429869 2.800 + 179 -83.02731348 9.98424933 2.600 + 180 -83.02757086 9.98422235 2.325 + 181 -83.02782825 9.98419538 2.050 + 182 -83.02808563 9.98416840 1.775 + 183 -83.02834301 9.98414142 1.500 + 184 -83.02853203 9.98411143 1.500 + 185 -83.02875117 9.98389971 1.500 + 186 -83.02897032 9.98368798 1.500 + 187 -83.02927396 9.98352540 1.500 + 188 -83.02957759 9.98336282 1.500 + 189 -83.02965954 9.98308459 1.500 + 190 -83.02949618 9.98280832 1.500 + 191 -83.02956093 9.98257292 1.500 + 192 -83.02962569 9.98233753 1.500 + 193 -83.02971856 9.98211258 1.500 + 194 -83.02981143 9.98188763 1.500 + 195 -83.02992550 9.98168387 1.500 + 196 -83.03003957 9.98148011 1.500 + 197 -83.03011787 9.98118411 1.500 + 198 -83.03019617 9.98088810 1.500 + 199 -83.03009466 9.98045476 2.000 + 200 -83.02913644 9.98071868 4.100 + 201 -83.02913520 9.98145890 2.850 + 202 -83.02914897 9.98232712 1.950 + 203 -83.02915545 9.98315981 1.950 + 204 -83.02809304 9.98354556 2.500 + 205 -83.02826510 9.98313849 2.500 + 206 -83.02829405 9.98235534 3.500 + 207 -83.02828724 9.98147994 4.850 + 208 -83.02826740 9.98073277 5.100 + 209 -83.02751734 9.98072456 5.850 + 210 -83.02752327 9.98148608 5.250 + 211 -83.02753693 9.98234006 4.650 + 212 -83.02755042 9.98317270 3.600 + 213 -83.02755674 9.98398403 3.000 + 214 -83.02690492 9.98398927 3.000 + 215 -83.02721727 9.98359530 4.050 + 216 -83.02680826 9.98327830 4.500 + 217 -83.02692359 9.98278627 5.000 + 218 -83.02701434 9.98183892 5.500 + 219 -83.02699750 9.98147607 5.750 + 220 -83.02691006 9.98104972 6.100 + 221 -83.02668317 9.98071703 6.500 + 222 -83.02482188 9.98022664 9.010 + 223 -83.02611296 9.98040132 9.020 + 224 -83.02674856 9.98082998 9.030 + 225 -83.02688347 9.98123499 9.040 + 226 -83.02684041 9.98194145 9.050 + 227 -83.02681701 9.98260207 9.060 + 228 -83.02674412 9.98314358 9.070 + 229 -83.02629611 9.98321836 9.080 + 230 -83.02617447 9.98314620 9.050 + 231 -83.02576113 9.98320061 9.040 + 232 -83.02492043 9.98298030 9.060 + 233 -83.02450585 9.98284839 9.030 + 234 -83.02368278 9.98246354 9.020 + 235 -83.02313536 9.98237541 9.010 + 236 -83.02354572 9.98196642 9.020 + 237 -83.02370233 9.98137442 9.030 + 238 -83.02414884 9.98110749 9.040 + 239 -83.02456721 9.98082654 9.050 + 240 -83.02493602 9.98048195 9.060 + 241 -83.02492869 9.98404072 4.000 + 242 -83.02498037 9.98355037 5.400 + 243 -83.02628929 9.98418772 4.500 + 244 -83.02585298 9.98415663 4.500 + 245 -83.02576878 9.98350374 5.200 + 246 -83.02616682 9.98334829 6.000 + 247 -83.02589125 9.98332497 6.000 + 248 -83.02592953 9.98393900 6.000 + 249 -83.02626016 9.98400156 6.000 + 250 -83.02592187 9.98369805 6.050 + 251 -83.02333757 9.98403926 4.800 + 252 -83.02411941 9.98362730 6.100 + 253 -83.02359931 9.98344641 7.500 + 254 -83.02331005 9.98320674 8.000 + 255 -83.02410375 9.98071639 9.200 + 256 -83.02329767 9.98071574 9.750 + 257 -83.02330376 9.98149861 9.300 + 258 -83.02228149 9.98073813 10.400 + 259 -83.02230845 9.98149949 10.200 + 260 -83.02230792 9.98233223 9.900 + 261 -83.02230067 9.98320062 9.500 + 262 -83.02173301 9.98321230 10.500 + 263 -83.02177525 9.98233651 10.500 + 264 -83.02201408 9.98150185 10.500 + 265 -83.02097840 9.98081977 11.500 + 266 -83.02039594 9.98073192 11.950 + 267 -83.02042301 9.98150751 11.900 + 268 -83.02041542 9.98233320 11.950 + 269 -83.02042935 9.98322276 11.950 + 270 -83.02042900 9.98407686 11.950 + 271 -83.02046441 9.98502320 13.500 + 272 -83.01969848 9.98567703 14.900 + 273 -83.01966551 9.98504384 15.000 + 274 -83.01965803 9.98408305 13.000 + 275 -83.01965110 9.98319343 12.900 + 276 -83.01973911 9.98279414 12.900 + 277 -83.01964444 9.98233939 12.900 + 278 -83.01964513 9.98152799 12.600 + 279 -83.01962475 9.98070965 13.000 + 280 -83.01897992 9.98071483 14.500 + 281 -83.01870589 9.98152842 14.500 + 282 -83.01897148 9.98233056 16.000 + 283 -83.01899938 9.98321289 18.000 + 284 -83.01862179 9.98332980 19.500 + 285 -83.01900614 9.98408117 16.000 + 286 -83.01900656 9.98503490 15.200 + 287 -83.01901172 9.98569678 14.900 + 288 -83.01827321 9.98627211 16.500 + 289 -83.01826177 9.98570281 16.500 + 290 -83.01825634 9.98500534 15.500 + 291 -83.01823572 9.98415853 15.500 + 292 -83.01825213 9.98446444 14.500 + 293 -83.01822145 9.98322626 16.950 + 294 -83.01822209 9.98240774 15.500 + 295 -83.01820809 9.98151106 15.000 + 296 -83.01808980 9.98072198 15.500 + 297 -83.01745199 9.98072710 16.000 + 298 -83.01745825 9.98153131 15.900 + 299 -83.01745050 9.98233565 15.300 + 300 -83.01747140 9.98321805 15.000 + 301 -83.01751336 9.98410738 14.500 + 302 -83.01752797 9.98508236 17.150 + 303 -83.01753307 9.98573712 17.800 + 304 -83.01754734 9.98666940 18.000 + 305 -83.01681858 9.98669659 19.500 + 306 -83.01680404 9.98572874 18.900 + 307 -83.01680600 9.98508104 18.150 + 308 -83.01679123 9.98408472 14.800 + 309 -83.01679569 9.98375728 14.800 + 310 -83.01677056 9.98323079 16.000 + 311 -83.01661639 9.98233523 18.300 + 312 -83.01652029 9.98169544 18.300 + 313 -83.01645222 9.98105541 18.300 + 314 -83.01641279 9.98049345 18.300 + 315 -83.01614117 9.98071627 15.900 + 316 -83.01613330 9.98150638 15.200 + 317 -83.01611181 9.98234640 15.000 + 318 -83.01614672 9.98322869 14.500 + 319 -83.01614453 9.98384791 13.500 + 320 -83.01618927 9.98509311 18.000 + 321 -83.01618035 9.98574798 19.500 + 322 -83.01619496 9.98672296 20.200 + 323 -83.01538883 9.98671520 20.200 + 324 -83.01465517 9.98701290 20.200 + 325 -83.01378039 9.98719075 20.200 + 326 -83.01287112 9.98744004 20.200 + 327 -83.01343826 9.98826111 20.800 + 328 -83.01469035 9.98793077 20.800 + 329 -83.01561920 9.98749626 20.800 + 330 -83.01465258 9.98578161 1.000 + 331 -83.01499120 9.98515967 1.000 + 332 -83.01497303 9.98462601 1.000 + 333 -83.01481268 9.98383726 1.000 + 334 -83.01459047 9.98320559 1.000 + 335 -83.01424327 9.98272440 1.000 + 336 -83.01362704 9.98280052 1.000 + 337 -83.01319703 9.98338760 1.000 + 338 -83.01267874 9.98433839 1.000 + 339 -83.01246823 9.98520840 1.000 + 340 -83.01290132 9.98591666 1.000 + 341 -83.01376897 9.98572465 1.000 + 342 -83.01402979 9.98231330 10.000 + 343 -83.01402374 9.98153754 13.000 + 344 -83.01400335 9.98071921 15.500 + 345 -83.01280445 9.98067901 18.000 + 346 -83.01131270 9.98173725 18.000 + 347 -83.01096816 9.98339838 18.000 + 348 -83.01207440 9.98324004 12.500 + 349 -83.01355759 9.98198257 12.500 + 350 -83.01259549 9.98174830 15.000 + 351 -83.01461972 9.98156123 11.000 + 352 -83.01532039 9.98152714 11.500 + 353 -83.01530706 9.98071585 15.200 + 354 -83.01536875 9.98233814 11.500 + 355 -83.01552988 9.98322652 11.500 + 356 -83.01564200 9.98412241 11.000 + 357 -83.01549556 9.98512004 11.000 + 358 -83.01518637 9.98591967 11.000 + 359 -83.01549105 9.98544036 11.000 + 360 -83.01449587 9.98635938 11.000 + 361 -83.01367044 9.98657241 11.000 + 362 -83.01293450 9.98657832 11.000 + 363 -83.01230038 9.98615637 11.000 + 364 -83.01177873 9.98577622 11.000 + 365 -83.01186303 9.98490010 11.000 + 366 -83.01199639 9.98402358 11.000 + 367 -83.01252263 9.98319373 11.000 + 368 -83.01291064 9.98261410 11.000 + 369 -83.01248955 9.98254631 15.000 + 370 -83.01154641 9.98294534 15.000 + 371 -83.01138761 9.98415658 15.000 + 372 -83.01137997 9.98497515 15.000 + 373 -83.01290610 9.98563193 0.000 + 374 -83.01342354 9.98547119 0.000 + 375 -83.01389853 9.98526097 0.000 + 376 -83.01413745 9.98533734 0.000 + 377 -83.01421776 9.98574952 0.000 + 378 -83.01446307 9.98574754 0.000 + 379 -83.01463585 9.98543298 0.000 + 380 -83.01484446 9.98521779 0.000 + 381 -83.01471475 9.98476331 0.000 + 382 -83.01450188 9.98443050 0.000 + 383 -83.01445567 9.98389706 0.000 + 384 -83.01424207 9.98347173 0.000 + 385 -83.01413301 9.98296727 0.000 + 386 -83.01392141 9.98279815 0.000 + 387 -83.01371392 9.98315570 0.000 + 388 -83.01345102 9.98359908 0.000 + 389 -83.01305533 9.98409336 0.000 + 390 -83.01291297 9.98471372 0.000 + 391 -83.01269151 9.98507849 0.000 + 392 -83.01284815 9.98539041 0.000 + 393 -83.02173382 9.98452624 5.100 + 394 -83.02139766 9.98411882 9.000 + 395 -83.02126907 9.98394200 11.000 + 396 -83.02089522 9.98346549 11.500 + 397 -83.02086269 9.98306175 11.500 + 398 -83.02088076 9.98274243 11.500 + 399 -83.02085686 9.98231541 11.500 + 400 -83.02085366 9.98190263 11.500 + 401 -83.02085789 9.98154672 11.500 + 402 -83.02100366 9.98135134 11.500 + 403 -83.02124946 9.98136236 11.500 + 404 -83.02133477 9.98157848 11.200 + 405 -83.02132536 9.98194228 11.200 + 406 -83.02132536 9.98260662 11.000 + 407 -83.02130367 9.98327463 11.200 + 408 -83.02162538 9.98374444 10.000 + 409 -83.02183864 9.98402340 7.000 + 410 -83.02195793 9.98419270 6.000 + 411 -83.02595603 9.98185098 9.030 + 412 -83.02505243 9.98147923 9.035 + 413 -83.01205858 9.98120813 18.000 + 414 -83.01086097 9.98088501 18.500 + 415 -83.02956480 9.98037004 3.300 + 416 -83.02958738 9.98146951 2.175 + 417 -83.02451992 9.98330380 7.580 + 418 -83.02271802 9.98278801 9.255 + 419 -83.01179819 9.98062482 18.000 + 420 -83.01790314 9.98600462 17.150 + 421 -83.01056753 9.98291939 19.000 + 422 -83.02957609 9.98091978 2.737 + 423 -83.02938044 9.98189821 2.175 + 424 -83.02789533 9.98110943 5.175 + 425 -83.02853168 9.98361677 2.000 + 426 -83.02791208 9.98191000 4.750 + 427 -83.02723071 9.98037099 6.175 + 428 -83.02638652 9.98222653 9.045 + 429 -83.02587756 9.98257581 9.035 + 430 -83.02535976 9.98314047 9.050 + 431 -83.02429908 9.98172283 9.028 + 432 -83.02460064 9.98129336 9.038 + 433 -83.02388113 9.98408295 4.950 + 434 -83.01146701 9.98355096 15.000 + 435 -83.01661885 9.98715016 20.100 + 436 -83.01327078 9.98700623 15.600 + 437 -83.01332576 9.98731539 20.200 + 438 -83.01366971 9.98872900 20.900 + 439 -83.01453486 9.98844092 20.837 + 440 -83.01649947 9.98622229 19.500 + 441 -83.01618766 9.98623547 19.850 + 442 -83.01716600 9.98540555 18.025 + 443 -83.01752067 9.98459487 15.825 + 444 -83.02008144 9.98535011 14.200 + 445 -83.02101182 9.98511132 9.150 + 446 -83.02138101 9.98481654 7.125 + 447 -83.02790364 9.98037626 5.550 + 448 -83.02873768 9.98036779 4.650 + 449 -83.02871810 9.98190353 3.400 + 450 -83.02871028 9.98314915 2.225 + 451 -83.02892962 9.98273814 2.088 + 452 -83.02870130 9.98109584 3.975 + 453 -83.02790102 9.98273928 3.575 + 454 -83.02696896 9.98231260 5.250 + 455 -83.02643276 9.98186316 9.040 + 456 -83.02655468 9.98131859 9.035 + 457 -83.02634729 9.98258894 9.047 + 458 -83.02633382 9.98085996 9.028 + 459 -83.02660052 9.98360381 6.040 + 460 -83.02552449 9.98044163 9.040 + 461 -83.02569313 9.98116959 9.031 + 462 -83.02405258 9.98314740 8.265 + 463 -83.02289901 9.98037731 10.125 + 464 -83.02280306 9.98110762 9.975 + 465 -83.02372325 9.98091161 9.395 + 466 -83.02440247 9.98228561 9.029 + 467 -83.02397409 9.98212601 9.024 + 468 -83.02546500 9.98202752 9.035 + 469 -83.02493373 9.98215657 9.032 + 470 -83.02499423 9.98098059 9.047 + 471 -83.02537743 9.98405847 4.250 + 472 -83.02452405 9.98383401 5.050 + 473 -83.02541238 9.98258400 9.042 + 474 -83.02272190 9.98193745 9.605 + 475 -83.02142568 9.98042650 11.250 + 476 -83.02277089 9.98327691 6.577 + 477 -83.02210043 9.98359013 8.250 + 478 -83.02203796 9.98276856 10.000 + 479 -83.02003027 9.98193059 12.275 + 480 -83.01853486 9.98071840 15.000 + 481 -83.01966177 9.98456345 14.000 + 482 -83.02004369 9.98365291 12.475 + 483 -83.01842875 9.98374417 17.500 + 484 -83.01786741 9.98366682 15.725 + 485 -83.02006309 9.98479332 13.750 + 486 -83.01935529 9.98256235 14.450 + 487 -83.01930830 9.98192928 14.300 + 488 -83.01917551 9.98152820 13.550 + 489 -83.01940013 9.98111893 13.275 + 490 -83.02002053 9.98112996 12.275 + 491 -83.01932870 9.98364797 15.500 + 492 -83.01846399 9.98196808 15.000 + 493 -83.01842194 9.98286877 17.500 + 494 -83.01900635 9.98455803 15.600 + 495 -83.01888237 9.98618892 14.700 + 496 -83.01933861 9.98537031 14.950 + 497 -83.01863416 9.98536885 15.850 + 498 -83.01669348 9.98278301 17.150 + 499 -83.01784674 9.98281290 15.250 + 500 -83.01693239 9.98061028 17.150 + 501 -83.01777402 9.98112665 15.700 + 502 -83.01782930 9.98192336 15.150 + 503 -83.01719532 9.98107079 16.525 + 504 -83.01685780 9.98138312 17.413 + 505 -83.01789487 9.98539258 16.825 + 506 -83.01698927 9.98161338 17.100 + 507 -83.01493632 9.98036296 15.000 + 508 -83.01544932 9.98278233 11.500 + 509 -83.01713129 9.98702327 19.125 + 510 -83.01499424 9.98194968 11.250 + 511 -83.01754020 9.98620326 17.900 + 512 -83.01681131 9.98621267 19.200 + 513 -83.01575103 9.98192226 13.350 + 514 -83.01679861 9.98458288 16.475 + 515 -83.01708244 9.98300053 16.075 + 516 -83.01578626 9.98037037 16.275 + 517 -83.01572018 9.98111111 15.200 + 518 -83.01647157 9.98421540 14.988 + 519 -83.01611902 9.98732321 20.450 + 520 -83.01591563 9.98460776 14.500 + 521 -83.01323411 9.98229834 11.750 + 522 -83.01515478 9.98771352 20.800 + 523 -83.01394410 9.98616096 5.500 + 524 -83.01177574 9.98629225 15.800 + 525 -83.01360933 9.98772593 20.500 + 526 -83.01251637 9.98958969 21.000 + 527 -83.01264521 9.98858243 20.900 + 528 -83.01217269 9.98843675 20.950 + 529 -83.01275816 9.98801123 20.550 + 530 -83.01575393 9.98701920 20.325 + 531 -83.01527180 9.98721436 20.500 + 532 -83.01333514 9.98582066 1.000 + 533 -83.01477802 9.98096209 13.000 + 534 -83.01446983 9.98054108 15.250 + 535 -83.01278898 9.98364355 5.500 + 536 -83.01497961 9.98277186 6.250 + 537 -83.01506017 9.98321606 6.250 + 538 -83.01461875 9.98233704 6.125 + 539 -83.01238430 9.98568238 6.000 + 540 -83.01494235 9.98653729 15.600 + 541 -83.01432475 9.98193726 10.500 + 542 -83.01326625 9.98034968 16.700 + 543 -83.01230132 9.98065191 18.000 + 544 -83.01036623 9.98125998 19.250 + 545 -83.00996202 9.98102898 19.625 + 546 -83.01046104 9.98093572 19.062 + 547 -83.01094011 9.98232832 18.500 + 548 -83.01105697 9.98293237 17.000 + 549 -83.01318102 9.98133079 15.250 + 550 -83.01440088 9.98124982 13.000 + 551 -83.01269997 9.98121366 16.500 + 552 -83.01544433 9.98461688 7.750 + 553 -83.01558594 9.98367447 11.250 + 554 -83.01568336 9.98583383 15.250 + 555 -83.01553610 9.98627451 17.725 + 556 -83.01421778 9.98710182 20.200 + 557 -83.01445407 9.98751630 20.500 + 558 -83.01232343 9.98686615 18.000 + 559 -83.01186154 9.98695971 19.400 + 560 -83.01236633 9.98719988 19.800 + 561 -83.01195727 9.98743915 20.400 + 562 -83.01359218 9.98102500 15.375 + 563 -83.01275306 9.98218120 13.000 + 564 -83.01195409 9.98174278 16.500 + 565 -83.01175025 9.98234406 15.750 + 566 -83.01098642 9.98394272 17.525 + 567 -83.01191233 9.98279205 14.125 + 568 -83.01227089 9.98461924 6.000 + 569 -83.01212348 9.98549231 6.000 + 570 -83.02090501 9.98444670 9.538 + 571 -83.02185359 9.98058232 10.825 + 572 -83.02133022 9.98088190 11.375 + 573 -83.02167215 9.98119187 10.938 + 574 -83.00989773 9.98058133 19.562 + 575 -83.01235772 9.98772519 20.475 + 576 -83.01258079 9.98908606 20.950 + 577 -83.01398656 9.98835101 20.819 + 578 -83.01083946 9.98149861 18.625 + 579 -83.01035548 9.98156678 19.312 + 580 -83.01132958 9.98075491 18.250 + 581 -83.01168564 9.98147269 18.000 + 582 -83.01063510 9.98045889 18.750 + 583 -83.01064779 9.98194755 18.906 + 584 -83.01602380 9.98769586 20.525 + 585 -83.01312525 9.98890753 20.925 + 586 -83.01409894 9.98028072 15.325 + 587 -83.02409431 9.98265597 9.025 + 588 -83.01318375 9.98786858 20.525 + 589 -83.01422031 9.98793366 20.659 + 590 -83.02004538 9.98432015 12.975 + 591 -83.02048405 9.98462001 11.644 + 592 -83.01320757 9.98181457 13.500 + 593 -83.01222182 9.98214454 15.750 + 594 -83.01447877 9.98416378 0.000 + 595 -83.01325318 9.98384622 0.000 + 596 -83.01316482 9.98555156 0.000 + 597 -83.01366104 9.98536608 0.000 + 598 -83.01418754 9.98321950 0.000 + 599 -83.01434887 9.98368440 0.000 + 600 -83.01477960 9.98499055 0.000 + 601 -83.01358247 9.98337739 0.000 + 602 -83.01298415 9.98440354 0.000 + 603 -83.02935627 9.98081923 3.419 + 604 -83.02936129 9.98146420 2.513 + 605 -83.02738701 9.98378967 3.525 + 606 -83.02735024 9.98401950 3.062 + 607 -83.02714596 9.98388947 3.263 + 608 -83.02654570 9.98286626 9.059 + 609 -83.02632170 9.98290365 9.064 + 610 -83.02428625 9.98322560 7.923 + 611 -83.02408599 9.98338735 7.182 + 612 -83.02237799 9.98277829 9.627 + 613 -83.02216932 9.98298459 9.750 + 614 -83.02069930 9.98143412 11.700 + 615 -83.01787454 9.98413296 15.000 + 616 -83.01806333 9.98429870 14.750 + 617 -83.01769760 9.98436392 15.413 + 618 -83.01918318 9.98037512 14.250 + 619 -83.01790671 9.98623768 17.200 + 620 -83.01754377 9.98643633 17.950 + 621 -83.02940749 9.98312220 1.725 + 622 -83.02926471 9.98211267 2.062 + 623 -83.02904927 9.98190087 2.787 + 624 -83.02789949 9.98074284 5.363 + 625 -83.02771049 9.98055041 5.700 + 626 -83.02831236 9.98358116 2.250 + 627 -83.02839839 9.98337763 2.250 + 628 -83.02772451 9.98212503 4.700 + 629 -83.02771768 9.98169804 5.000 + 630 -83.02708739 9.98019421 6.338 + 631 -83.02613204 9.98240117 9.040 + 632 -83.02611242 9.98258238 9.041 + 633 -83.02557943 9.98322056 9.045 + 634 -83.02519470 9.98337938 7.225 + 635 -83.02539371 9.98330165 8.135 + 636 -83.02526167 9.98370709 5.738 + 637 -83.02444986 9.98150809 9.033 + 638 -83.02437474 9.98120042 9.039 + 639 -83.02400721 9.98429635 4.375 + 640 -83.02349021 9.98428893 4.300 + 641 -83.02202918 9.98389141 7.125 + 642 -83.02185205 9.98364728 9.125 + 643 -83.02246210 9.98367797 6.075 + 644 -83.02224564 9.98378469 6.600 + 645 -83.02342474 9.98173251 9.160 + 646 -83.02356354 9.98155346 9.095 + 647 -83.02130729 9.98296265 11.100 + 648 -83.02132536 9.98231666 11.500 + 649 -83.02167233 9.98172168 10.850 + 650 -83.02184311 9.98134686 10.719 + 651 -83.02097700 9.98109025 11.500 + 652 -83.02068717 9.98077585 11.725 + 653 -83.01683079 9.98736376 20.050 + 654 -83.01307095 9.98722313 17.900 + 655 -83.01378543 9.98896295 20.950 + 656 -83.01633991 9.98598514 19.500 + 657 -83.01698502 9.98556715 18.462 + 658 -83.01698600 9.98524330 18.087 + 659 -83.01715599 9.98434513 15.488 + 660 -83.01715964 9.98458888 16.150 + 661 -83.01988996 9.98551357 14.550 + 662 -83.01987348 9.98519698 14.600 + 663 -83.02065656 9.98314621 11.725 + 664 -83.02134103 9.98508199 7.338 + 665 -83.02180886 9.98485225 4.800 + 666 -83.02772176 9.98019801 5.775 + 667 -83.02853830 9.98019234 4.925 + 668 -83.02770633 9.98091699 5.512 + 669 -83.02938733 9.98233232 1.725 + 670 -83.02944175 9.98257032 1.612 + 671 -83.02918569 9.98265423 1.850 + 672 -83.02796064 9.98387047 2.275 + 673 -83.02843735 9.98387910 1.750 + 674 -83.02848769 9.98314382 2.362 + 675 -83.02809128 9.98129468 5.012 + 676 -83.02770930 9.98129775 5.213 + 677 -83.02862098 9.98338296 2.112 + 678 -83.02881995 9.98294364 2.156 + 679 -83.02861184 9.98254674 2.794 + 680 -83.02870970 9.98149968 3.688 + 681 -83.02849427 9.98128789 4.412 + 682 -83.02850267 9.98169174 4.125 + 683 -83.02891887 9.98090726 4.037 + 684 -83.02891825 9.98127737 3.412 + 685 -83.02819900 9.98387478 2.013 + 686 -83.02839836 9.98202354 3.812 + 687 -83.02834280 9.98175174 4.331 + 688 -83.02771898 9.98253967 4.113 + 689 -83.02809753 9.98254731 3.537 + 690 -83.02721370 9.98088714 5.975 + 691 -83.02737402 9.98054778 6.012 + 692 -83.02772572 9.98295599 3.588 + 693 -83.02736942 9.98198198 5.100 + 694 -83.02754355 9.98184001 5.050 + 695 -83.02790938 9.98325077 3.044 + 696 -83.02699165 9.98207576 5.375 + 697 -83.02716919 9.98214729 5.175 + 698 -83.02746871 9.98348118 3.562 + 699 -83.02751273 9.98373261 3.281 + 700 -83.02780289 9.98363908 2.891 + 701 -83.02703716 9.98409408 3.031 + 702 -83.02701276 9.98343680 4.275 + 703 -83.02680664 9.98352031 5.157 + 704 -83.02623062 9.98020821 8.010 + 705 -83.02643840 9.98011223 7.380 + 706 -83.02645689 9.98046262 7.255 + 707 -83.02696818 9.98311154 4.637 + 708 -83.02728159 9.98330475 3.938 + 709 -83.02619439 9.98185707 9.035 + 710 -83.02649372 9.98159088 9.038 + 711 -83.02685578 9.98375479 4.079 + 712 -83.02670160 9.98173311 9.044 + 713 -83.02732465 9.98287113 4.294 + 714 -83.02752181 9.98270540 4.203 + 715 -83.02726880 9.98166250 5.375 + 716 -83.02655153 9.98023944 7.003 + 717 -83.02661735 9.98047823 6.751 + 718 -83.02704858 9.98106107 7.508 + 719 -83.02722220 9.98062907 6.075 + 720 -83.02394336 9.98037248 9.350 + 721 -83.02376881 9.98183974 9.060 + 722 -83.02543875 9.98023236 8.770 + 723 -83.02609963 9.98273973 9.049 + 724 -83.02677609 9.98139733 7.392 + 725 -83.02673237 9.98118416 7.568 + 726 -83.02728592 9.98127357 6.379 + 727 -83.02653310 9.98102206 8.297 + 728 -83.02668908 9.98215114 7.210 + 729 -83.02658215 9.98259551 9.054 + 730 -83.02694627 9.98254944 5.125 + 731 -83.02644831 9.98341108 7.560 + 732 -83.02652012 9.98318097 9.075 + 733 -83.02581873 9.98042148 9.030 + 734 -83.02560881 9.98080561 9.036 + 735 -83.02611652 9.98423403 3.950 + 736 -83.02635424 9.98370632 6.780 + 737 -83.02569224 9.98379132 4.850 + 738 -83.02550270 9.98355035 5.469 + 739 -83.02519962 9.98012841 8.760 + 740 -83.02607627 9.98064072 9.029 + 741 -83.02584254 9.98072317 9.032 + 742 -83.02472598 9.98343737 6.490 + 743 -83.02452199 9.98356890 6.315 + 744 -83.02433587 9.98037111 9.100 + 745 -83.02318021 9.98363483 6.000 + 746 -83.02304047 9.98324183 7.289 + 747 -83.02384265 9.98341688 7.341 + 748 -83.02269967 9.98020809 10.312 + 749 -83.02305341 9.98130311 9.637 + 750 -83.02255575 9.98130355 10.087 + 751 -83.02280458 9.98130333 9.863 + 752 -83.02263883 9.98162050 9.846 + 753 -83.02322271 9.98279108 8.505 + 754 -83.02292669 9.98258171 9.132 + 755 -83.02386768 9.98280547 8.642 + 756 -83.02407345 9.98290169 8.645 + 757 -83.02393605 9.98100955 9.217 + 758 -83.02371279 9.98114302 9.212 + 759 -83.02418828 9.98220581 9.027 + 760 -83.02403420 9.98239099 9.025 + 761 -83.02383330 9.98064205 9.373 + 762 -83.02370283 9.98020182 9.550 + 763 -83.02376807 9.98042193 9.461 + 764 -83.02350025 9.98045878 9.650 + 765 -83.02567128 9.98230167 9.035 + 766 -83.02543869 9.98230576 9.039 + 767 -83.02457887 9.98029887 9.055 + 768 -83.02445154 9.98059883 9.075 + 769 -83.02519936 9.98209204 9.033 + 770 -83.02518621 9.98223116 9.035 + 771 -83.02502333 9.98122991 9.041 + 772 -83.02479743 9.98113698 9.042 + 773 -83.02522485 9.98426788 4.062 + 774 -83.02552699 9.98424944 3.925 + 775 -83.02432173 9.98373065 5.575 + 776 -83.02509518 9.98387391 4.869 + 777 -83.02672407 9.98416866 3.000 + 778 -83.02666229 9.98388623 4.520 + 779 -83.02649584 9.98411355 3.750 + 780 -83.02612089 9.98352706 6.025 + 781 -83.02606937 9.98386378 6.025 + 782 -83.02374022 9.98376468 6.225 + 783 -83.02400027 9.98385512 5.525 + 784 -83.02361425 9.98221498 9.020 + 785 -83.02464048 9.98415870 4.500 + 786 -83.02472637 9.98393736 4.525 + 787 -83.02373350 9.98312594 8.071 + 788 -83.02354519 9.98279827 8.574 + 789 -83.02360935 9.98406110 4.875 + 790 -83.02338976 9.98354062 6.750 + 791 -83.02336366 9.98378994 5.775 + 792 -83.02361175 9.98068520 9.523 + 793 -83.02435803 9.98096701 9.045 + 794 -83.02285103 9.98074246 10.050 + 795 -83.02305036 9.98091168 9.863 + 796 -83.02307332 9.98183498 9.382 + 797 -83.02350828 9.98132081 9.256 + 798 -83.02361577 9.98111621 9.326 + 799 -83.02241862 9.98102084 10.244 + 800 -83.02251517 9.98171847 9.903 + 801 -83.02282430 9.98225958 9.369 + 802 -83.02167224 9.98145678 10.894 + 803 -83.02297036 9.98278954 8.880 + 804 -83.02226463 9.98161016 10.201 + 805 -83.02169525 9.98286384 10.550 + 806 -83.02154277 9.98308571 10.800 + 807 -83.02274445 9.98303246 7.916 + 808 -83.02256122 9.98290537 8.772 + 809 -83.02196848 9.98166592 10.526 + 810 -83.02213087 9.98118385 10.481 + 811 -83.02220618 9.98096099 10.441 + 812 -83.02026703 9.98038065 12.225 + 813 -83.02069323 9.98110498 11.712 + 814 -83.02054459 9.98091845 11.831 + 815 -83.01903860 9.98020457 14.500 + 816 -83.01994589 9.98054515 12.613 + 817 -83.02007730 9.98020601 12.613 + 818 -83.02063833 9.98170507 11.700 + 819 -83.02063454 9.98211791 11.725 + 820 -83.01966929 9.98192993 13.288 + 821 -83.01947637 9.98213433 13.600 + 822 -83.01878673 9.98046149 14.750 + 823 -83.01933219 9.98432054 14.300 + 824 -83.01933406 9.98456074 14.800 + 825 -83.02023652 9.98343784 12.212 + 826 -83.02023634 9.98386488 12.212 + 827 -83.02106149 9.98371141 11.250 + 828 -83.02090429 9.98536664 10.000 + 829 -83.01987848 9.98583929 13.700 + 830 -83.01833224 9.98395135 16.500 + 831 -83.01814808 9.98370549 16.612 + 832 -83.01635495 9.98026616 18.400 + 833 -83.01818476 9.98346587 16.781 + 834 -83.01986243 9.98467838 13.875 + 835 -83.02005424 9.98455674 13.363 + 836 -83.02053599 9.98273970 11.837 + 837 -83.02075128 9.98293370 11.613 + 838 -83.01954720 9.98267824 13.675 + 839 -83.01917734 9.98288762 16.225 + 840 -83.01968620 9.98365044 13.988 + 841 -83.01949337 9.98386551 14.250 + 842 -83.01983736 9.98213499 12.587 + 843 -83.01998781 9.98311599 12.556 + 844 -83.02020858 9.98316938 12.253 + 845 -83.01900710 9.98172885 14.400 + 846 -83.02069643 9.98252756 11.669 + 847 -83.01907772 9.98112152 14.025 + 848 -83.01928782 9.98132357 13.413 + 849 -83.01825006 9.98037461 15.375 + 850 -83.01952263 9.98132346 12.938 + 851 -83.01983283 9.98132898 12.438 + 852 -83.01982264 9.98091980 12.637 + 853 -83.01809231 9.98020016 15.625 + 854 -83.01916404 9.98343043 16.750 + 855 -83.01948990 9.98342070 14.200 + 856 -83.01941422 9.98304052 14.562 + 857 -83.01920680 9.98312671 16.281 + 858 -83.01858494 9.98174825 14.750 + 859 -83.01871773 9.98214932 15.500 + 860 -83.01813434 9.98284083 16.375 + 861 -83.01803410 9.98301958 16.100 + 862 -83.01924975 9.98397334 15.125 + 863 -83.01908509 9.98375580 16.375 + 864 -83.01889291 9.98338012 18.125 + 865 -83.01856984 9.98250905 16.500 + 866 -83.01851691 9.98223856 15.750 + 867 -83.01949978 9.98480229 14.900 + 868 -83.01917031 9.98479782 15.000 + 869 -83.01965990 9.98432325 13.500 + 870 -83.01914406 9.98626511 14.100 + 871 -83.01917516 9.98553355 14.925 + 872 -83.01917259 9.98520261 15.075 + 873 -83.01961429 9.98544194 14.750 + 874 -83.01882036 9.98520187 15.525 + 875 -83.01882294 9.98553282 15.375 + 876 -83.01665493 9.98255912 17.725 + 877 -83.01688796 9.98289177 16.612 + 878 -83.01851312 9.98647658 15.500 + 879 -83.01788850 9.98480011 15.663 + 880 -83.01752432 9.98483862 16.487 + 881 -83.01869774 9.98633275 15.100 + 882 -83.01899776 9.98536771 15.225 + 883 -83.01775275 9.98311881 15.550 + 884 -83.01766940 9.98344244 15.363 + 885 -83.01792708 9.98345416 16.072 + 886 -83.01863134 9.98478169 15.550 + 887 -83.01862924 9.98451124 15.050 + 888 -83.01844173 9.98462306 15.025 + 889 -83.01801131 9.98391923 15.806 + 890 -83.01746459 9.98290671 15.663 + 891 -83.01727692 9.98310929 15.538 + 892 -83.02031605 9.98554930 12.800 + 893 -83.01719219 9.98066869 16.575 + 894 -83.01706386 9.98084054 16.837 + 895 -83.01879964 9.98287820 16.862 + 896 -83.01907441 9.98260909 16.112 + 897 -83.01793191 9.98092431 15.600 + 898 -83.01799106 9.98131886 15.350 + 899 -83.01814664 9.98194572 15.075 + 900 -83.01802569 9.98216555 15.325 + 901 -83.01684867 9.98032269 17.450 + 902 -83.01837148 9.98111473 15.000 + 903 -83.01831233 9.98072019 15.250 + 904 -83.01748467 9.98109872 16.112 + 905 -83.01732679 9.98130105 16.212 + 906 -83.01757631 9.98037735 16.125 + 907 -83.01783431 9.98028875 15.875 + 908 -83.01783305 9.98054966 15.812 + 909 -83.01773810 9.98225060 15.312 + 910 -83.01764378 9.98172734 15.525 + 911 -83.01801870 9.98171721 15.075 + 912 -83.01675804 9.98094797 17.569 + 913 -83.01843248 9.98433488 15.275 + 914 -83.01881769 9.98429620 15.525 + 915 -83.01697668 9.98100938 17.047 + 916 -83.01847976 9.98601778 15.800 + 917 -83.01771142 9.98523747 16.987 + 918 -83.01807560 9.98519896 16.163 + 919 -83.01779996 9.98501879 16.325 + 920 -83.01789900 9.98569860 16.987 + 921 -83.01771397 9.98556485 17.312 + 922 -83.01715803 9.98145722 16.656 + 923 -83.01475095 9.98018651 14.900 + 924 -83.01578056 9.98256436 13.250 + 925 -83.01548960 9.98300442 11.500 + 926 -83.01563508 9.98278439 12.375 + 927 -83.01558248 9.98300546 11.938 + 928 -83.01649665 9.98541093 18.450 + 929 -83.01674084 9.98548904 18.456 + 930 -83.01769630 9.98689596 17.750 + 931 -83.01698104 9.98719351 19.587 + 932 -83.01810292 9.98656974 16.600 + 933 -83.01782335 9.98650303 17.275 + 934 -83.01515731 9.98173841 11.375 + 935 -83.01518149 9.98214391 11.375 + 936 -83.01717754 9.98632450 18.575 + 937 -83.01596364 9.98289652 13.875 + 938 -83.01735530 9.98603081 18.188 + 939 -83.01593142 9.98213433 14.175 + 940 -83.01555989 9.98213020 12.425 + 941 -83.01723254 9.98359986 15.081 + 942 -83.01745097 9.98352115 15.222 + 943 -83.01737295 9.98385362 14.791 + 944 -83.01622585 9.98191488 16.237 + 945 -83.01707282 9.98491609 17.119 + 946 -83.01729857 9.98487735 16.803 + 947 -83.01714228 9.98506032 17.445 + 948 -83.01608620 9.98108326 16.750 + 949 -83.01592674 9.98130874 15.200 + 950 -83.01751701 9.98435113 15.163 + 951 -83.01632856 9.98283977 15.512 + 952 -83.01725473 9.98335457 15.309 + 953 -83.01629276 9.98128089 16.750 + 954 -83.01629669 9.98088584 17.100 + 955 -83.01708209 9.98396917 14.795 + 956 -83.01607060 9.98031826 17.337 + 957 -83.01731652 9.98167036 16.312 + 958 -83.01545417 9.98183033 12.363 + 959 -83.01654956 9.98303528 15.756 + 960 -83.01634814 9.98313198 15.128 + 961 -83.01615589 9.98301425 14.502 + 962 -83.01642112 9.98212506 17.269 + 963 -83.01560880 9.98019741 16.462 + 964 -83.01657191 9.98344463 14.964 + 965 -83.01635932 9.98333666 14.732 + 966 -83.01635822 9.98364627 14.232 + 967 -83.01649394 9.98483799 17.237 + 968 -83.01663509 9.98439914 15.731 + 969 -83.01656452 9.98461857 16.484 + 970 -83.01530751 9.98437421 6.000 + 971 -83.01520868 9.98462145 4.375 + 972 -83.01636894 9.98723668 20.275 + 973 -83.01627371 9.98760934 20.350 + 974 -83.01634721 9.98647262 19.850 + 975 -83.01620479 9.98472288 15.869 + 976 -83.01671871 9.98692338 19.800 + 977 -83.01584016 9.98526674 14.500 + 978 -83.01576176 9.98555028 14.875 + 979 -83.01307238 9.98245622 11.375 + 980 -83.01299359 9.98223977 12.375 + 981 -83.01264281 9.98579952 3.500 + 982 -83.01234234 9.98591938 8.500 + 983 -83.01492256 9.98782215 20.800 + 984 -83.01490497 9.98736321 20.500 + 985 -83.01491377 9.98759268 20.650 + 986 -83.01467952 9.98743975 20.500 + 987 -83.01380727 9.98636669 8.250 + 988 -83.01363962 9.98599081 3.250 + 989 -83.01369486 9.98745834 20.350 + 990 -83.01391482 9.98782979 20.580 + 991 -83.01325475 9.98759199 20.362 + 992 -83.01339654 9.98779725 20.513 + 993 -83.01352559 9.98709849 17.900 + 994 -83.01277249 9.98962633 21.000 + 995 -83.01548441 9.98796354 20.650 + 996 -83.01520349 9.98789284 20.725 + 997 -83.01246543 9.98822399 20.750 + 998 -83.01255794 9.98786821 20.513 + 999 -83.01593648 9.98717121 20.388 + 1000 -83.01568656 9.98725773 20.562 + 1001 -83.01521329 9.98746394 20.650 + 1002 -83.01355206 9.98577265 1.000 + 1003 -83.01524112 9.98530002 6.000 + 1004 -83.01462393 9.98075159 14.125 + 1005 -83.01423659 9.98063014 15.375 + 1006 -83.01479747 9.98615945 8.300 + 1007 -83.01506436 9.98622848 13.300 + 1008 -83.01535212 9.98487074 7.688 + 1009 -83.01516257 9.98474838 4.344 + 1010 -83.01493849 9.98536650 3.000 + 1011 -83.01506243 9.98564309 7.000 + 1012 -83.01484914 9.98553803 3.500 + 1013 -83.01472590 9.98439490 0.500 + 1014 -83.01322510 9.98361691 0.500 + 1015 -83.01501989 9.98299396 6.250 + 1016 -83.01527489 9.98311024 8.875 + 1017 -83.01508055 9.98245789 8.812 + 1018 -83.01503740 9.98220379 10.031 + 1019 -83.01413653 9.98251885 5.500 + 1020 -83.01443101 9.98253072 3.562 + 1021 -83.01326884 9.98270731 6.000 + 1022 -83.01343058 9.98254943 6.375 + 1023 -83.01491948 9.98585064 6.000 + 1024 -83.01395321 9.98553099 0.500 + 1025 -83.01399336 9.98573708 0.500 + 1026 -83.01302108 9.98374488 2.750 + 1027 -83.01261987 9.98555416 3.000 + 1028 -83.01479876 9.98677509 17.900 + 1029 -83.01471911 9.98644834 13.300 + 1030 -83.01457423 9.98607050 6.000 + 1031 -83.01439600 9.98591001 3.000 + 1032 -83.01447224 9.98174925 10.750 + 1033 -83.01447175 9.98213715 8.312 + 1034 -83.01397560 9.98255573 5.000 + 1035 -83.01394117 9.98195992 11.500 + 1036 -83.01417425 9.98173740 11.750 + 1037 -83.01250609 9.98287002 13.000 + 1038 -83.01307839 9.98019016 16.350 + 1039 -83.01363480 9.98053445 16.100 + 1040 -83.01342922 9.98068734 16.038 + 1041 -83.01336930 9.98165668 13.875 + 1042 -83.01319429 9.98157268 14.375 + 1043 -83.01239269 9.98383356 8.250 + 1044 -83.01265581 9.98341864 8.250 + 1045 -83.01252425 9.98362610 8.250 + 1046 -83.01451240 9.98100070 13.562 + 1047 -83.01437450 9.98081542 14.469 + 1048 -83.01237927 9.98121090 17.250 + 1049 -83.01275221 9.98094634 17.250 + 1050 -83.01256574 9.98107862 17.250 + 1051 -83.01252677 9.98079913 17.625 + 1052 -83.01229025 9.98305503 12.750 + 1053 -83.01567998 9.98461232 11.125 + 1054 -83.01504920 9.98124462 12.250 + 1055 -83.01469887 9.98126166 12.000 + 1056 -83.01641490 9.98393084 14.610 + 1057 -83.01420212 9.98098451 14.250 + 1058 -83.01593067 9.98091369 15.550 + 1059 -83.01649530 9.98512446 17.844 + 1060 -83.01586633 9.98345158 12.875 + 1061 -83.01586523 9.98376119 12.375 + 1062 -83.01601026 9.98550736 17.000 + 1063 -83.01589326 9.98398516 12.250 + 1064 -83.01618242 9.98410028 13.619 + 1065 -83.01590445 9.98429646 13.375 + 1066 -83.01523460 9.98288814 8.875 + 1067 -83.01533871 9.98568002 11.000 + 1068 -83.01430414 9.98232800 6.906 + 1069 -83.01560973 9.98605417 16.487 + 1070 -83.01586188 9.98625499 18.788 + 1071 -83.01602842 9.98648897 19.494 + 1072 -83.01578226 9.98638174 18.609 + 1073 -83.01532306 9.98344526 8.750 + 1074 -83.01555791 9.98345049 11.375 + 1075 -83.01303307 9.98573411 0.500 + 1076 -83.01418444 9.98767305 20.540 + 1077 -83.01401253 9.98673426 14.225 + 1078 -83.01328706 9.98628457 7.125 + 1079 -83.01346334 9.98613769 5.188 + 1080 -83.01347875 9.98642849 9.062 + 1081 -83.01398242 9.98743190 20.370 + 1082 -83.01421824 9.98747410 20.435 + 1083 -83.01261744 9.98636735 11.000 + 1084 -83.01231190 9.98651126 14.500 + 1085 -83.01248120 9.98484887 3.000 + 1086 -83.01373018 9.98243136 8.188 + 1087 -83.01348215 9.98236485 9.969 + 1088 -83.01364389 9.98220697 10.344 + 1089 -83.01348074 9.98134084 14.625 + 1090 -83.01369652 9.98159711 13.438 + 1091 -83.01389715 9.98100476 14.812 + 1092 -83.01285983 9.98329067 6.000 + 1093 -83.01227479 9.98174554 15.750 + 1094 -83.01232703 9.98147822 16.500 + 1095 -83.01229586 9.98535035 3.500 + 1096 -83.01458078 9.98376083 0.500 + 1097 -83.01544673 9.98402434 8.625 + 1098 -83.01458562 9.98348321 0.750 + 1099 -83.01441687 9.98296500 1.000 + 1100 -83.01478504 9.98298873 3.625 + 1101 -83.01349138 9.98293150 3.000 + 1102 -83.01323294 9.98304746 3.500 + 1103 -83.01353692 9.98315445 1.500 + 1104 -83.01286704 9.98421587 0.500 + 1105 -83.01257997 9.98459363 2.000 + 1106 -83.01269709 9.98478130 1.500 + 1107 -83.02156561 9.98466915 6.113 + 1108 -83.02116118 9.98426493 9.269 + 1109 -83.02114301 9.98463162 8.331 + 1110 -83.02136340 9.98446704 7.691 + 1111 -83.02107742 9.98487147 8.741 + 1112 -83.02099121 9.98465909 9.139 + 1113 -83.02054423 9.98346027 11.856 + 1114 -83.02039029 9.98366258 12.034 + 1115 -83.02072781 9.98484114 11.319 + 1116 -83.02026190 9.98292784 12.197 + 1117 -83.01978823 9.98246457 12.744 + 1118 -83.01993155 9.98162978 12.356 + 1119 -83.02033430 9.98181783 11.988 + 1120 -83.01961138 9.98101937 12.956 + 1121 -83.02082795 9.98040194 11.738 + 1122 -83.02159190 9.98073211 11.100 + 1123 -83.02150118 9.98103689 11.156 + 1124 -83.02145345 9.98126458 11.219 + 1125 -83.02193916 9.98107643 10.689 + 1126 -83.02202988 9.98077166 10.633 + 1127 -83.02152660 9.98235986 10.000 + 1128 -83.02195116 9.98309844 10.125 + 1129 -83.02147718 9.98354991 10.600 + 1130 -83.02525936 9.98071111 9.044 + 1131 -83.02514135 9.98097051 9.042 + 1132 -83.01740455 9.98020435 16.562 + 1133 -83.01261300 9.98883424 20.925 + 1134 -83.01285302 9.98899679 20.938 + 1135 -83.01437759 9.98818729 20.748 + 1136 -83.01410344 9.98814233 20.739 + 1137 -83.02422396 9.98141516 9.034 + 1138 -83.01242683 9.98034263 17.250 + 1139 -83.01622609 9.98779566 20.388 + 1140 -83.01281276 9.98931156 20.969 + 1141 -83.01418297 9.98865104 20.847 + 1142 -83.01382814 9.98854001 20.859 + 1143 -83.02859313 9.98082001 4.569 + 1144 -83.02882828 9.98063752 4.344 + 1145 -83.02694843 9.98080209 6.238 + 1146 -83.02598180 9.98021020 8.385 + 1147 -83.02332095 9.98024625 9.825 + 1148 -83.02186328 9.98030778 10.913 + 1149 -83.02054749 9.98039129 11.981 + 1150 -83.01979144 9.98028927 13.056 + 1151 -83.02039023 9.98528625 13.150 + 1152 -83.02047045 9.98551736 12.275 + 1153 -83.01942127 9.98597107 14.500 + 1154 -83.01663073 9.98040807 17.875 + 1155 -83.01845111 9.98020262 15.188 + 1156 -83.01849299 9.98046051 15.094 + 1157 -83.01561887 9.98081477 15.375 + 1158 -83.01585847 9.98064203 15.913 + 1159 -83.01715441 9.98667388 18.850 + 1160 -83.01699806 9.98651055 19.038 + 1161 -83.01229245 9.98930123 20.975 + 1162 -83.01515010 9.98823758 20.706 + 1163 -83.01503633 9.98802986 20.753 + 1164 -83.01428439 9.98041090 15.288 + 1165 -83.01241157 9.98797459 20.612 + 1166 -83.01229213 9.98820567 20.781 + 1167 -83.01232493 9.98796543 20.628 + 1168 -83.01804156 9.98046213 15.594 + 1169 -83.02935138 9.98019204 3.850 + 1170 -83.02924391 9.98045536 3.975 + 1171 -83.02919094 9.98023470 4.188 + 1172 -83.02935878 9.98114171 2.966 + 1173 -83.02472018 9.98314205 8.320 + 1174 -83.02238138 9.98343929 7.787 + 1175 -83.02261649 9.98347744 6.326 + 1176 -83.02277116 9.98252379 9.312 + 1177 -83.02256611 9.98229591 9.634 + 1178 -83.01234030 9.98093141 17.625 + 1179 -83.01819145 9.98601120 16.475 + 1180 -83.01771810 9.98587087 17.475 + 1181 -83.02887949 9.98170028 3.237 + 1182 -83.02749613 9.98109528 5.946 + 1183 -83.02790448 9.98149636 5.006 + 1184 -83.02875100 9.98365238 1.750 + 1185 -83.02888822 9.98327138 2.031 + 1186 -83.02754789 9.98037289 5.894 + 1187 -83.02675305 9.98237661 8.135 + 1188 -83.02571051 9.98193925 9.033 + 1189 -83.02615248 9.98300076 9.050 + 1190 -83.02583953 9.98298014 9.047 + 1191 -83.02493304 9.98324888 7.773 + 1192 -83.02388855 9.98255975 9.023 + 1193 -83.02416447 9.98401350 4.975 + 1194 -83.01728764 9.98718660 18.938 + 1195 -83.01589117 9.98675409 19.909 + 1196 -83.01337476 9.98671736 12.331 + 1197 -83.01300273 9.98690073 14.450 + 1198 -83.01297095 9.98793991 20.538 + 1199 -83.01302743 9.98765431 20.362 + 1200 -83.01328175 9.98858432 20.862 + 1201 -83.01339748 9.98881826 20.913 + 1202 -83.01481579 9.98851161 20.763 + 1203 -83.01428028 9.98841916 20.798 + 1204 -83.01665902 9.98645944 19.500 + 1205 -83.01641828 9.98569803 18.975 + 1206 -83.01625345 9.98545914 17.725 + 1207 -83.01602112 9.98600149 19.144 + 1208 -83.01743999 9.98548520 17.669 + 1209 -83.01797592 9.98454940 15.206 + 1210 -83.01811613 9.98477737 15.353 + 1211 -83.02007226 9.98507172 13.975 + 1212 -83.01986430 9.98491858 14.375 + 1213 -83.02064726 9.98532644 11.575 + 1214 -83.02158179 9.98494660 5.963 + 1215 -83.02822097 9.98028430 5.238 + 1216 -83.02899080 9.98041157 4.312 + 1217 -83.02815522 9.98196677 4.281 + 1218 -83.02850510 9.98228514 3.303 + 1219 -83.02917057 9.98290702 1.900 + 1220 -83.02854976 9.98284528 2.578 + 1221 -83.02835469 9.98254702 3.166 + 1222 -83.02882703 9.98230613 2.627 + 1223 -83.02913883 9.98102449 3.502 + 1224 -83.02838083 9.98101033 4.756 + 1225 -83.02830989 9.98284276 2.833 + 1226 -83.02791102 9.98233617 4.119 + 1227 -83.02713546 9.98271028 4.709 + 1228 -83.02609342 9.98138024 9.034 + 1229 -83.02629357 9.98148556 9.036 + 1230 -83.02614391 9.98161865 9.035 + 1231 -83.02596798 9.98105170 9.033 + 1232 -83.02621362 9.98112010 9.031 + 1233 -83.02534905 9.98047174 8.907 + 1234 -83.02537508 9.98088806 9.039 + 1235 -83.02541724 9.98107005 9.037 + 1236 -83.02538147 9.98170924 9.034 + 1237 -83.02566875 9.98178011 9.032 + 1238 -83.02430399 9.98347813 6.749 + 1239 -83.02430008 9.98275218 9.028 + 1240 -83.02429317 9.98298889 8.475 + 1241 -83.02277535 9.98047528 10.181 + 1242 -83.02330931 9.98048100 9.788 + 1243 -83.02308017 9.98061173 9.919 + 1244 -83.02284612 9.98146181 9.742 + 1245 -83.02285608 9.98172774 9.614 + 1246 -83.02333306 9.98101395 9.594 + 1247 -83.02392558 9.98124095 9.035 + 1248 -83.02471979 9.98250248 9.031 + 1249 -83.02466810 9.98222109 9.030 + 1250 -83.02448359 9.98197196 9.029 + 1251 -83.02470866 9.98206426 9.030 + 1252 -83.02373557 9.98160708 9.045 + 1253 -83.02403395 9.98178128 9.044 + 1254 -83.02457926 9.98178618 9.031 + 1255 -83.02488055 9.98177175 9.033 + 1256 -83.02506609 9.98254324 9.037 + 1257 -83.02482011 9.98274139 9.045 + 1258 -83.02435127 9.98251889 9.028 + 1259 -83.02516641 9.98278215 9.051 + 1260 -83.02496513 9.98073127 9.054 + 1261 -83.02458393 9.98105995 9.044 + 1262 -83.02544007 9.98380441 4.859 + 1263 -83.02500049 9.98425901 3.938 + 1264 -83.02559965 9.98306031 9.049 + 1265 -83.02562595 9.98278207 9.045 + 1266 -83.02564497 9.98257990 9.039 + 1267 -83.02330952 9.98190070 9.201 + 1268 -83.02310434 9.98210519 9.196 + 1269 -83.02307494 9.98148021 9.521 + 1270 -83.02103677 9.98021477 11.619 + 1271 -83.02112681 9.98041422 11.494 + 1272 -83.02297555 9.98345587 6.289 + 1273 -83.02300542 9.98301569 8.084 + 1274 -83.02202580 9.98334428 9.188 + 1275 -83.02179253 9.98342979 9.812 + 1276 -83.02217294 9.98255040 9.950 + 1277 -83.02161092 9.98261185 9.275 + 1278 -83.02012639 9.98223409 12.269 + 1279 -83.02037486 9.98207551 11.969 + 1280 -83.01815169 9.98101952 15.300 + 1281 -83.01872460 9.98111812 14.512 + 1282 -83.01853868 9.98132157 14.750 + 1283 -83.01994719 9.98397396 12.606 + 1284 -83.02074475 9.98389461 11.600 + 1285 -83.01875692 9.98374998 16.938 + 1286 -83.01840328 9.98339784 18.141 + 1287 -83.01787097 9.98389989 15.363 + 1288 -83.02069453 9.98453335 10.591 + 1289 -83.02026472 9.98447008 12.309 + 1290 -83.01882212 9.98255907 16.306 + 1291 -83.01947672 9.98172863 13.450 + 1292 -83.01922392 9.98223245 14.800 + 1293 -83.01894070 9.98152831 14.025 + 1294 -83.01951244 9.98091429 13.137 + 1295 -83.01929508 9.98101790 13.581 + 1296 -83.01924618 9.98081456 13.819 + 1297 -83.02048380 9.98121298 11.866 + 1298 -83.02028256 9.98102421 12.053 + 1299 -83.02011423 9.98078468 12.333 + 1300 -83.01832201 9.98263826 16.500 + 1301 -83.01886242 9.98193908 14.950 + 1302 -83.01852186 9.98309929 18.500 + 1303 -83.01876062 9.98315609 18.250 + 1304 -83.01857496 9.98412378 16.013 + 1305 -83.01933618 9.98500245 14.988 + 1306 -83.01874574 9.98585728 15.350 + 1307 -83.01835488 9.98528391 16.006 + 1308 -83.01812488 9.98533825 16.416 + 1309 -83.01850375 9.98578004 15.925 + 1310 -83.01700155 9.98341533 15.541 + 1311 -83.01705272 9.98244739 16.513 + 1312 -83.01687310 9.98261520 16.831 + 1313 -83.01683456 9.98239131 17.406 + 1314 -83.01798009 9.98232917 15.406 + 1315 -83.01779242 9.98253175 15.281 + 1316 -83.01652737 9.98091691 17.334 + 1317 -83.01657528 9.98133201 17.081 + 1318 -83.01640652 9.98148817 17.525 + 1319 -83.01781742 9.98152310 15.438 + 1320 -83.01818437 9.98217673 15.288 + 1321 -83.01761614 9.98132898 15.800 + 1322 -83.01668905 9.98153928 17.856 + 1323 -83.01844797 9.98553583 16.175 + 1324 -83.01675478 9.98165441 17.700 + 1325 -83.01679467 9.98202286 17.553 + 1326 -83.01391350 9.98015053 15.363 + 1327 -83.01527256 9.98028019 15.731 + 1328 -83.01526494 9.98262011 10.156 + 1329 -83.01749197 9.98704128 18.344 + 1330 -83.01473300 9.98204342 9.781 + 1331 -83.01789961 9.98673285 17.175 + 1332 -83.01708331 9.98612174 18.694 + 1333 -83.01717016 9.98579898 18.325 + 1334 -83.01680767 9.98597071 19.050 + 1335 -83.01734909 9.98655510 18.400 + 1336 -83.01583888 9.98161550 14.275 + 1337 -83.01577953 9.98136331 14.738 + 1338 -83.01567023 9.98234728 12.837 + 1339 -83.01706758 9.98272396 16.294 + 1340 -83.01538469 9.98117786 13.725 + 1341 -83.01557963 9.98157132 12.887 + 1342 -83.01605462 9.98450967 14.622 + 1343 -83.01630957 9.98456412 15.553 + 1344 -83.01586911 9.98740974 20.625 + 1345 -83.01650463 9.98767287 20.237 + 1346 -83.01576007 9.98493953 12.812 + 1347 -83.01289489 9.98166049 14.688 + 1348 -83.01294424 9.98195013 13.531 + 1349 -83.01544550 9.98735531 20.650 + 1350 -83.01468494 9.98768526 20.650 + 1351 -83.01444593 9.98613469 7.000 + 1352 -83.01417005 9.98603548 4.250 + 1353 -83.01367654 9.98804545 20.690 + 1354 -83.01343118 9.98912410 20.956 + 1355 -83.01341740 9.98802918 20.656 + 1356 -83.01312635 9.98826211 20.700 + 1357 -83.01261442 9.98758262 20.337 + 1358 -83.01551287 9.98711678 20.413 + 1359 -83.01509379 9.98674515 19.050 + 1360 -83.01485187 9.98706915 19.200 + 1361 -83.01506184 9.98714175 19.850 + 1362 -83.01309419 9.98610062 4.062 + 1363 -83.01483446 9.98140292 11.625 + 1364 -83.01504254 9.98083897 14.100 + 1365 -83.01461039 9.98036380 15.075 + 1366 -83.01229932 9.98343307 10.375 + 1367 -83.01282801 9.98392971 3.000 + 1368 -83.01484965 9.98239746 7.469 + 1369 -83.01460803 9.98275972 3.594 + 1370 -83.01482290 9.98334963 3.500 + 1371 -83.01481779 9.98359345 2.250 + 1372 -83.01467636 9.98180232 10.391 + 1373 -83.01263013 9.98608343 7.250 + 1374 -83.01285581 9.98623398 7.531 + 1375 -83.01522660 9.98647184 16.750 + 1376 -83.01464732 9.98656724 14.450 + 1377 -83.01294142 9.98043459 17.175 + 1378 -83.01330512 9.98100907 15.644 + 1379 -83.01311683 9.98068318 17.019 + 1380 -83.01274688 9.98023397 16.837 + 1381 -83.01302866 9.98097770 16.447 + 1382 -83.01428756 9.98149361 12.375 + 1383 -83.01279743 9.98143708 15.594 + 1384 -83.01517166 9.98501521 4.344 + 1385 -83.01600543 9.98364974 13.188 + 1386 -83.01530023 9.98625150 15.512 + 1387 -83.01584681 9.98567059 16.125 + 1388 -83.01558554 9.98654847 19.405 + 1389 -83.01432992 9.98665075 14.337 + 1390 -83.01389646 9.98696250 17.212 + 1391 -83.01378345 9.98676746 14.106 + 1392 -83.01455462 9.98726460 20.350 + 1393 -83.01268453 9.98705030 17.125 + 1394 -83.01280951 9.98681431 14.062 + 1395 -83.01271348 9.98659083 12.531 + 1396 -83.01376597 9.98076960 15.456 + 1397 -83.01248744 9.98216287 14.375 + 1398 -83.01235568 9.98234543 15.375 + 1399 -83.01262131 9.98236376 14.000 + 1400 -83.01247481 9.98447881 3.500 + 1401 -83.02095297 9.98407977 10.434 + 1402 -83.02069098 9.98407831 11.192 + 1403 -83.02023719 9.98419850 12.462 + 1404 -83.02223407 9.98038709 10.575 + 1405 -83.02164448 9.98036714 11.081 + 1406 -83.02122852 9.98064806 11.434 + 1407 -83.02176553 9.98090427 10.894 + 1408 -83.01268629 9.98779692 20.444 + 1409 -83.01236202 9.98746253 20.138 + 1410 -83.01333897 9.98933528 20.978 + 1411 -83.01323211 9.98912140 20.952 + 1412 -83.01363320 9.98840056 20.830 + 1413 -83.01398420 9.98880699 20.898 + 1414 -83.01575410 9.98782970 20.587 + 1415 -83.01274911 9.98878961 20.919 + 1416 -83.01377415 9.98034249 15.731 + 1417 -83.01347481 9.98752516 20.356 + 1418 -83.01445262 9.98780946 20.655 + 1419 -83.01399909 9.98714629 20.200 + 1420 -83.01985171 9.98420160 12.988 + 1421 -83.02027357 9.98470667 12.697 + 1422 -83.01322084 9.98205645 12.625 + 1423 -83.01238112 9.98195421 15.062 + 1424 -83.02376200 9.98431077 4.375 + 1425 -83.01643678 9.98745478 20.256 + 1426 -83.01666771 9.98751832 20.144 + 1427 -83.01440073 9.98873959 20.830 + 1428 -83.02908109 9.98339839 1.766 + 1429 -83.02681946 9.98021682 6.670 + 1430 -83.02571027 9.98022128 8.578 + 1431 -83.02430478 9.98425503 4.425 + 1432 -83.01958894 9.98016234 13.528 + 1433 -83.01964987 9.98590518 14.100 + 1434 -83.01871945 9.98024606 14.875 + 1435 -83.01831450 9.98668058 15.925 + 1436 -83.02009727 9.98569429 13.250 + 1437 -83.01704073 9.98017702 17.225 + 1438 -83.01732319 9.98685758 18.597 + 1439 -83.01464573 9.98400052 0.500 + 1440 -83.01354172 9.98018399 15.716 + 1441 -83.02560179 9.98406735 4.375 + 1442 -83.01492606 9.98827074 20.758 + 1443 -83.02738530 9.98019537 6.088 + 1444 -83.02886462 9.98021352 4.556 + 1445 -83.01302243 9.98921648 20.960 + 1446 -83.02925782 9.98167856 2.513 + 1447 -83.02451289 9.98307609 8.305 + 1448 -83.02257457 9.98265104 9.470 + 1449 -83.01774829 9.98457214 15.516 + 1450 -83.01960684 9.98043600 13.264 + 1451 -83.01938606 9.98026873 13.889 + 1452 -83.02893815 9.98210350 2.707 + 1453 -83.02808137 9.98092110 5.137 + 1454 -83.02808552 9.98055452 5.325 + 1455 -83.02812744 9.98183087 4.541 + 1456 -83.02616322 9.98212912 9.038 + 1457 -83.02591725 9.98221539 9.036 + 1458 -83.02597579 9.98315070 9.045 + 1459 -83.02539618 9.98278211 9.048 + 1460 -83.02514010 9.98306038 9.055 + 1461 -83.02466520 9.98163992 9.033 + 1462 -83.02218954 9.98400578 7.550 + 1463 -83.02155292 9.98213901 10.850 + 1464 -83.02213820 9.98199908 10.213 + 1465 -83.02190527 9.98186038 10.531 + 1466 -83.02128249 9.98110959 11.438 + 1467 -83.02025217 9.98117147 12.070 + 1468 -83.01657379 9.98597792 19.275 + 1469 -83.01665132 9.98524598 18.300 + 1470 -83.01729773 9.98403828 14.648 + 1471 -83.01697361 9.98421493 15.144 + 1472 -83.01680230 9.98483196 17.312 + 1473 -83.01950206 9.98520708 14.975 + 1474 -83.02840285 9.98046256 5.012 + 1475 -83.02903930 9.98253263 2.019 + 1476 -83.02768905 9.98336598 3.303 + 1477 -83.02861557 9.98055004 4.678 + 1478 -83.02733620 9.98252517 4.680 + 1479 -83.02808306 9.98293888 3.037 + 1480 -83.02678289 9.98064016 6.494 + 1481 -83.02700680 9.98050558 6.335 + 1482 -83.02411111 9.98199355 9.035 + 1483 -83.02397977 9.98151112 9.039 + 1484 -83.02469378 9.98054039 9.068 + 1485 -83.02246687 9.98029759 10.444 + 1486 -83.02237418 9.98051786 10.422 + 1487 -83.02328084 9.98131196 9.447 + 1488 -83.02263483 9.98088165 10.147 + 1489 -83.02342762 9.98300251 8.287 + 1490 -83.02334028 9.98258684 8.792 + 1491 -83.02347726 9.98240091 8.906 + 1492 -83.02503996 9.98193190 9.033 + 1493 -83.02539935 9.98138965 9.035 + 1494 -83.02553405 9.98158488 9.034 + 1495 -83.02478072 9.98090357 9.049 + 1496 -83.02482654 9.98138630 9.036 + 1497 -83.02441442 9.98404452 4.738 + 1498 -83.02335930 9.98216009 9.108 + 1499 -83.02235216 9.98214749 9.924 + 1500 -83.02243367 9.98193298 9.913 + 1501 -83.02182444 9.98269021 9.637 + 1502 -83.02252256 9.98311654 8.708 + 1503 -83.02172909 9.98199969 10.691 + 1504 -83.02195673 9.98216779 10.356 + 1505 -83.02017728 9.98156865 12.128 + 1506 -83.01908536 9.98193418 14.625 + 1507 -83.01875739 9.98071661 14.750 + 1508 -83.01900625 9.98431960 15.800 + 1509 -83.01900645 9.98479646 15.400 + 1510 -83.02001575 9.98338445 12.516 + 1511 -83.02064449 9.98367744 11.728 + 1512 -83.02053674 9.98387715 11.839 + 1513 -83.02068753 9.98508379 11.447 + 1514 -83.01852527 9.98353698 18.500 + 1515 -83.01985358 9.98444180 13.488 + 1516 -83.02019415 9.98258097 12.233 + 1517 -83.02045923 9.98303703 11.961 + 1518 -83.01966865 9.98342193 13.444 + 1519 -83.01885226 9.98091647 14.506 + 1520 -83.01883265 9.98132322 14.269 + 1521 -83.01839652 9.98162966 14.875 + 1522 -83.01800725 9.98246975 15.391 + 1523 -83.01907789 9.98598095 14.500 + 1524 -83.01929822 9.98575231 14.712 + 1525 -83.01872585 9.98499178 15.538 + 1526 -83.01849109 9.98499856 15.519 + 1527 -83.01636410 9.98234081 16.650 + 1528 -83.01622018 9.98259308 15.256 + 1529 -83.01745755 9.98262118 15.481 + 1530 -83.01738425 9.98052302 16.350 + 1531 -83.01721249 9.98035002 16.788 + 1532 -83.01672988 9.98076359 17.242 + 1533 -83.01769195 9.98082571 15.800 + 1534 -83.01769094 9.98198897 15.419 + 1535 -83.01750373 9.98182966 15.866 + 1536 -83.01702656 9.98122696 16.969 + 1537 -83.01734699 9.98524396 17.587 + 1538 -83.01442499 9.98021048 15.044 + 1539 -83.01555977 9.98256480 12.169 + 1540 -83.01572440 9.98322852 12.406 + 1541 -83.01609976 9.98530023 17.500 + 1542 -83.01697493 9.98685993 19.312 + 1543 -83.01510326 9.98149151 11.812 + 1544 -83.01488981 9.98164692 11.102 + 1545 -83.01598844 9.98191857 14.794 + 1546 -83.01762018 9.98376022 15.258 + 1547 -83.01701412 9.98367857 14.941 + 1548 -83.01631619 9.98170152 16.881 + 1549 -83.01705559 9.98184661 16.933 + 1550 -83.01692369 9.98223512 17.033 + 1551 -83.01747712 9.98208266 15.583 + 1552 -83.01727966 9.98183813 16.399 + 1553 -83.01618237 9.98349320 13.960 + 1554 -83.01545793 9.98045663 15.831 + 1555 -83.01657695 9.98370178 14.516 + 1556 -83.01624599 9.98433220 14.586 + 1557 -83.01561397 9.98389844 11.125 + 1558 -83.01501671 9.98438455 3.250 + 1559 -83.01497109 9.98486946 2.172 + 1560 -83.01640690 9.98693656 20.150 + 1561 -83.01617169 9.98705388 20.269 + 1562 -83.01637706 9.98670459 20.000 + 1563 -83.01598243 9.98483120 14.341 + 1564 -83.01591129 9.98504897 14.420 + 1565 -83.01461261 9.98818584 20.819 + 1566 -83.01406859 9.98650872 11.294 + 1567 -83.01428223 9.98643405 11.147 + 1568 -83.01385653 9.98594281 3.250 + 1569 -83.01555181 9.98772990 20.725 + 1570 -83.01240895 9.98850959 20.925 + 1571 -83.01270168 9.98829683 20.725 + 1572 -83.01478012 9.98055727 14.562 + 1573 -83.01483122 9.98419254 1.875 + 1574 -83.01523172 9.98420445 5.938 + 1575 -83.01299301 9.98351557 3.250 + 1576 -83.01307179 9.98283078 7.250 + 1577 -83.01518280 9.98697975 19.775 + 1578 -83.01417727 9.98212528 10.250 + 1579 -83.01268296 9.98308034 9.500 + 1580 -83.01296581 9.98306072 6.625 + 1581 -83.01270837 9.98274206 12.000 + 1582 -83.01368895 9.98117280 14.719 + 1583 -83.01294050 9.98127223 15.875 + 1584 -83.01243375 9.98415619 5.875 + 1585 -83.01263088 9.98404295 4.438 + 1586 -83.01251350 9.98134594 16.500 + 1587 -83.01247680 9.98057088 17.438 + 1588 -83.01566099 9.98436737 11.062 + 1589 -83.01521361 9.98100842 13.913 + 1590 -83.01411293 9.98126103 13.625 + 1591 -83.01547422 9.98586709 13.744 + 1592 -83.01566974 9.98678384 19.865 + 1593 -83.01493898 9.98340475 4.250 + 1594 -83.01507042 9.98351935 5.500 + 1595 -83.01525858 9.98377185 7.062 + 1596 -83.01503563 9.98380455 4.031 + 1597 -83.01449255 9.98683182 17.269 + 1598 -83.01427385 9.98687629 17.269 + 1599 -83.01315463 9.98664784 11.666 + 1600 -83.01311078 9.98643145 9.062 + 1601 -83.01251845 9.98672849 15.266 + 1602 -83.01385635 9.98135517 13.859 + 1603 -83.02000050 9.98286099 12.548 + 1604 -83.01989437 9.98266278 12.646 + 1605 -83.02009891 9.98134930 12.202 + 1606 -83.01254858 9.98933787 20.975 + 1607 -83.01301543 9.98868696 20.891 + 1608 -83.01541624 9.98091160 14.644 + 1609 -83.01285856 9.98849190 20.808 + 1610 -83.02581374 9.98148256 9.034 + 1611 -83.02589328 9.98127491 9.033 + 1612 -83.02504620 9.98170556 9.034 + 1613 -83.02197410 9.98244345 10.225 + 1614 -83.02069276 9.98430583 10.891 + 1615 -83.02047873 9.98438796 11.600 + 1616 -83.01942651 9.98062528 13.541 + 1617 -83.01710168 9.98203663 16.716 + 1618 -83.01727609 9.98218614 16.008 + 1619 -83.01512169 9.98053940 15.100 + 1620 -83.01267428 9.98196475 14.000 + 1621 -83.01294226 9.98813667 20.625 + 1622 -83.01264947 9.98731646 18.731 + 1623 -83.01443648 9.98705736 20.200 + 1624 -83.01235232 9.98438771 5.938 + 1625 -83.01166800 9.98033316 18.000 + 1626 -83.01071523 9.98332212 19.000 + 1627 -83.01122671 9.98374684 16.263 + 1628 -83.01118702 9.98404965 16.263 + 1629 -83.01163060 9.98700650 20.100 + 1630 -83.01169200 9.98409008 13.000 + 1631 -83.01173170 9.98378727 13.000 + 1632 -83.01138379 9.98456587 15.000 + 1633 -83.01128540 9.98430776 15.631 + 1634 -83.01220094 9.98266918 14.562 + 1635 -83.01190305 9.98351365 12.750 + 1636 -83.01194972 9.98376861 11.875 + 1637 -83.01206924 9.98077811 17.812 + 1638 -83.01021918 9.98102898 19.344 + 1639 -83.01009978 9.98073055 19.312 + 1640 -83.01099854 9.98263034 17.750 + 1641 -83.01130169 9.98293885 16.000 + 1642 -83.01116697 9.98507650 17.600 + 1643 -83.01172473 9.98322950 13.875 + 1644 -83.01208672 9.98673549 16.950 + 1645 -83.01204382 9.98640176 15.150 + 1646 -83.01216180 9.98731951 20.100 + 1647 -83.01193123 9.98651387 16.375 + 1648 -83.01157935 9.98537569 13.000 + 1649 -83.01137316 9.98522609 15.300 + 1650 -83.01206696 9.98475967 8.500 + 1651 -83.01212452 9.98360084 11.125 + 1652 -83.01217120 9.98380109 10.062 + 1653 -83.01185217 9.98204342 16.125 + 1654 -83.01198604 9.98224430 15.750 + 1655 -83.01105823 9.98450131 17.891 + 1656 -83.01112262 9.98427548 17.077 + 1657 -83.01183129 9.98256805 14.938 + 1658 -83.01134094 9.98558934 16.700 + 1659 -83.01226759 9.98498403 4.750 + 1660 -83.01206054 9.98584780 9.750 + 1661 -83.01179074 9.98771195 20.700 + 1662 -83.01197456 9.98797509 20.814 + 1663 -83.01059747 9.98153270 18.969 + 1664 -83.01050164 9.98175716 19.109 + 1665 -83.01151342 9.98636020 18.200 + 1666 -83.01149879 9.98054403 18.125 + 1667 -83.01151830 9.98029277 18.062 + 1668 -83.01200634 9.98147546 17.250 + 1669 -83.01174192 9.98104875 18.000 + 1670 -83.01187211 9.98134041 18.000 + 1671 -83.01052217 9.98024583 18.875 + 1672 -83.01026041 9.98189742 19.555 + 1673 -83.01221647 9.98899490 20.975 + 1674 -83.01033552 9.98045698 19.094 + 1675 -83.01032463 9.98013820 19.062 + 1676 -83.00966821 9.98048166 19.781 + 1677 -83.01097537 9.98471883 19.033 + 1678 -83.01077669 9.98356362 19.025 + 1679 -83.01098234 9.98060690 18.500 + 1680 -83.01074804 9.98067195 18.625 + 1681 -83.01111900 9.98032311 18.375 + 1682 -83.01122429 9.98053901 18.312 + 1683 -83.01113492 9.98316862 17.000 + 1684 -83.01137440 9.98248720 16.750 + 1685 -83.01133804 9.98271303 16.375 + 1686 -83.01147920 9.98376705 14.631 + 1687 -83.01142982 9.98319906 15.438 + 1688 -83.01130097 9.98335979 16.000 + 1689 -83.01191814 9.98607003 12.775 + 1690 -83.01125888 9.98585245 18.600 + 1691 -83.01201242 9.98867025 20.975 + 1692 -83.01231271 9.98875224 20.950 + 1693 -83.01225774 9.98034399 17.500 + 1694 -83.01040734 9.98219398 19.453 + 1695 -83.00989161 9.98028911 19.531 + 1696 -83.00992132 9.98133984 19.812 + 1697 -83.01014377 9.98129991 19.531 + 1698 -83.01062636 9.98101655 18.875 + 1699 -83.01098025 9.98184240 18.453 + 1700 -83.01079395 9.98213794 18.703 + 1701 -83.01048744 9.98255668 19.226 + 1702 -83.01088610 9.98312724 18.000 + 1703 -83.01168885 9.98275670 14.969 + 1704 -83.01162830 9.98662729 18.538 + 1705 -83.01163234 9.98753890 20.800 + 1706 -83.01224262 9.98709283 19.050 + 1707 -83.01171560 9.98740250 20.650 + 1708 -83.01193644 9.98836392 20.975 + 1709 -83.01134355 9.98211223 17.375 + 1710 -83.01154690 9.98222814 16.562 + 1711 -83.01208796 9.98194366 16.125 + 1712 -83.01181853 9.98301077 14.000 + 1713 -83.01209349 9.98245674 15.156 + 1714 -83.01100170 9.98365523 17.644 + 1715 -83.01203167 9.98439162 9.750 + 1716 -83.01185142 9.98543400 9.500 + 1717 -83.01195110 9.98563426 8.500 + 1718 -83.00976915 9.98088287 19.812 + 1719 -83.01126255 9.98148565 18.312 + 1720 -83.01150223 9.98126720 18.156 + 1721 -83.01072653 9.98128555 18.750 + 1722 -83.01099454 9.98138560 18.531 + 1723 -83.01124839 9.98132640 18.344 + 1724 -83.01176891 9.98175806 17.062 + 1725 -83.01010931 9.98039038 19.312 + 1726 -83.01109528 9.98081996 18.375 + 1727 -83.01116190 9.98197731 17.914 + 1728 -83.01074363 9.98172308 18.766 + 1729 -83.01229823 9.98970621 21.000 + 1730 -83.01205439 9.98303290 13.375 + 1731 -83.01207364 9.98539218 6.500 + 1732 -83.01207423 9.98771857 20.587 + 1733 -83.01216349 9.98056105 17.656 + 1734 -83.01196287 9.98033857 17.750 + 1735 -83.01223271 9.98427390 7.812 + 1736 -83.01117767 9.98484699 17.016 + 1737 -83.01078582 9.98383579 18.788 + 1738 -83.01138615 9.98610632 18.400 + 1739 -83.01080432 9.98024801 18.625 + 1740 -83.00964363 9.98022694 19.766 + 1741 -83.01178857 9.98718111 20.025 + 1742 -83.01006595 9.98176618 19.777 + 1743 -83.01189639 9.98673679 17.888 + 1744 -83.01153790 9.98432797 14.000 + 1745 -83.01162341 9.98473298 13.000 + 1746 -83.01182754 9.98456230 11.375 + 1747 -83.01162150 9.98493762 13.000 + 1748 -83.01221507 9.98408988 8.438 + 1749 -83.01039675 9.98071811 19.078 + 1750 -83.01074299 9.98259351 18.488 + 1751 -83.01089998 9.98276294 17.744 + 1752 -83.01201559 9.98713697 19.538 + 1753 -83.01173646 9.98518581 11.250 + 1754 -83.01196833 9.98514614 8.750 + 1755 -83.01155623 9.98193514 17.219 + 1756 -83.01154080 9.98174765 17.531 + 1757 -83.01160284 9.98252763 15.844 + 1758 -83.01155984 9.98568278 13.850 + 1759 -83.01165214 9.98608818 15.587 + 1760 -83.01010486 9.98153304 19.654 + 1761 -83.01156389 9.98068986 18.125 + 1762 -83.01104491 9.98110278 18.453 + 1763 -83.01115726 9.98240776 17.625 + 1764 -83.01147299 9.98589455 16.125 + 1765 -83.01064070 9.98234731 18.965 + 1766 -83.01112140 9.98166403 18.383 + 1767 -83.01186184 9.98424085 11.375 + 1768 -83.01153575 9.98090183 18.125 + 1769 -83.01129033 9.98100231 18.289 + 1770 -83.02957045 9.98064491 3.019 + 1771 -83.02977898 9.98019573 2.900 + 1772 -83.02985263 9.98132681 1.837 + 1773 -83.02984698 9.98105194 2.119 + 1774 -83.02997082 9.98075335 2.059 + 1775 -83.02969941 9.98167857 1.837 + 1776 -83.02960570 9.98123426 2.401 + 1777 -83.02949163 9.98211262 1.781 + 1778 -83.02983256 9.98054983 2.509 +$EndNodes +$Elements + 3556 + 1 15 2 0 0 149 + 2 15 2 0 0 150 + 3 15 2 0 0 151 + 4 15 2 0 0 152 + 5 15 2 0 0 153 + 6 15 2 0 0 154 + 7 15 2 0 0 155 + 8 15 2 0 0 156 + 9 15 2 0 0 157 + 10 15 2 0 0 158 + 11 15 2 0 0 159 + 12 15 2 0 0 160 + 13 15 2 0 0 161 + 14 15 2 0 0 162 + 15 15 2 0 0 163 + 16 15 2 0 0 164 + 17 15 2 0 0 165 + 18 15 2 0 0 166 + 19 15 2 0 0 167 + 20 15 2 0 0 168 + 21 15 2 0 0 169 + 22 15 2 0 0 170 + 23 15 2 0 0 171 + 24 15 2 0 0 172 + 25 15 2 0 0 173 + 26 15 2 0 0 174 + 27 15 2 0 0 175 + 28 15 2 0 0 176 + 29 15 2 0 0 177 + 30 15 2 0 0 178 + 31 15 2 0 0 179 + 32 15 2 0 0 180 + 33 15 2 0 0 181 + 34 15 2 0 0 182 + 35 15 2 0 0 183 + 36 15 2 0 0 184 + 37 15 2 0 0 185 + 38 15 2 0 0 186 + 39 15 2 0 0 187 + 40 15 2 0 0 188 + 41 15 2 0 0 189 + 42 15 2 0 0 190 + 43 15 2 0 0 191 + 44 15 2 0 0 192 + 45 15 2 0 0 193 + 46 15 2 0 0 194 + 47 15 2 0 0 195 + 48 15 2 0 0 196 + 49 15 2 0 0 197 + 50 15 2 0 0 198 + 51 15 2 0 0 199 + 52 15 2 0 0 1 + 53 15 2 0 0 2 + 54 15 2 0 0 3 + 55 15 2 0 0 4 + 56 15 2 0 0 5 + 57 15 2 0 0 6 + 58 15 2 0 0 7 + 59 15 2 0 0 8 + 60 15 2 0 0 9 + 61 15 2 0 0 10 + 62 15 2 0 0 11 + 63 15 2 0 0 12 + 64 15 2 0 0 13 + 65 15 2 0 0 14 + 66 15 2 0 0 15 + 67 15 2 0 0 16 + 68 15 2 0 0 17 + 69 15 2 0 0 18 + 70 15 2 0 0 19 + 71 15 2 0 0 20 + 72 15 2 0 0 21 + 73 15 2 0 0 22 + 74 15 2 0 0 23 + 75 15 2 0 0 24 + 76 15 2 0 0 25 + 77 15 2 0 0 26 + 78 15 2 0 0 27 + 79 15 2 0 0 28 + 80 15 2 0 0 29 + 81 15 2 0 0 30 + 82 15 2 0 0 31 + 83 15 2 0 0 32 + 84 15 2 0 0 33 + 85 15 2 0 0 34 + 86 15 2 0 0 35 + 87 15 2 0 0 36 + 88 15 2 0 0 37 + 89 15 2 0 0 38 + 90 15 2 0 0 39 + 91 15 2 0 0 40 + 92 15 2 0 0 41 + 93 15 2 0 0 42 + 94 15 2 0 0 43 + 95 15 2 0 0 44 + 96 15 2 0 0 45 + 97 15 2 0 0 46 + 98 15 2 0 0 47 + 99 15 2 0 0 48 + 100 15 2 0 0 49 + 101 15 2 0 0 50 + 102 15 2 0 0 51 + 103 15 2 0 0 52 + 104 15 2 0 0 53 + 105 15 2 0 0 54 + 106 15 2 0 0 55 + 107 15 2 0 0 56 + 108 15 2 0 0 57 + 109 15 2 0 0 58 + 110 15 2 0 0 59 + 111 15 2 0 0 60 + 112 15 2 0 0 61 + 113 15 2 0 0 62 + 114 15 2 0 0 63 + 115 15 2 0 0 64 + 116 15 2 0 0 65 + 117 15 2 0 0 66 + 118 15 2 0 0 67 + 119 15 2 0 0 68 + 120 15 2 0 0 69 + 121 15 2 0 0 70 + 122 15 2 0 0 71 + 123 15 2 0 0 72 + 124 15 2 0 0 73 + 125 15 2 0 0 74 + 126 15 2 0 0 75 + 127 15 2 0 0 76 + 128 15 2 0 0 77 + 129 15 2 0 0 78 + 130 15 2 0 0 79 + 131 15 2 0 0 80 + 132 15 2 0 0 81 + 133 15 2 0 0 82 + 134 15 2 0 0 83 + 135 15 2 0 0 84 + 136 15 2 0 0 85 + 137 15 2 0 0 86 + 138 15 2 0 0 87 + 139 15 2 0 0 88 + 140 15 2 0 0 89 + 141 15 2 0 0 90 + 142 15 2 0 0 91 + 143 15 2 0 0 92 + 144 15 2 0 0 93 + 145 15 2 0 0 94 + 146 15 2 0 0 95 + 147 15 2 0 0 96 + 148 15 2 0 0 97 + 149 15 2 0 0 98 + 150 15 2 0 0 99 + 151 15 2 0 0 100 + 152 15 2 0 0 101 + 153 15 2 0 0 102 + 154 15 2 0 0 103 + 155 15 2 0 0 104 + 156 15 2 0 0 105 + 157 15 2 0 0 106 + 158 15 2 0 0 107 + 159 15 2 0 0 108 + 160 15 2 0 0 109 + 161 15 2 0 0 110 + 162 15 2 0 0 111 + 163 15 2 0 0 112 + 164 15 2 0 0 113 + 165 15 2 0 0 114 + 166 15 2 0 0 115 + 167 15 2 0 0 116 + 168 15 2 0 0 117 + 169 15 2 0 0 118 + 170 15 2 0 0 119 + 171 15 2 0 0 120 + 172 15 2 0 0 121 + 173 15 2 0 0 122 + 174 15 2 0 0 123 + 175 15 2 0 0 124 + 176 15 2 0 0 125 + 177 15 2 0 0 126 + 178 15 2 0 0 127 + 179 15 2 0 0 128 + 180 15 2 0 0 129 + 181 15 2 0 0 130 + 182 15 2 0 0 131 + 183 15 2 0 0 132 + 184 15 2 0 0 133 + 185 15 2 0 0 134 + 186 15 2 0 0 135 + 187 15 2 0 0 136 + 188 15 2 0 0 137 + 189 15 2 0 0 138 + 190 15 2 0 0 139 + 191 15 2 0 0 140 + 192 15 2 0 0 141 + 193 15 2 0 0 142 + 194 15 2 0 0 143 + 195 15 2 0 0 144 + 196 15 2 0 0 145 + 197 15 2 0 0 146 + 198 15 2 0 0 147 + 199 15 2 0 0 148 + 200 15 2 0 1 594 + 201 15 2 0 1 382 + 202 15 2 0 1 381 + 203 15 2 0 1 600 + 204 15 2 0 1 380 + 205 15 2 0 1 379 + 206 15 2 0 1 378 + 207 15 2 0 1 377 + 208 15 2 0 1 376 + 209 15 2 0 1 375 + 210 15 2 0 1 597 + 211 15 2 0 1 374 + 212 15 2 0 1 596 + 213 15 2 0 1 373 + 214 15 2 0 1 392 + 215 15 2 0 1 391 + 216 15 2 0 1 390 + 217 15 2 0 1 602 + 218 15 2 0 1 389 + 219 15 2 0 1 595 + 220 15 2 0 1 388 + 221 15 2 0 1 601 + 222 15 2 0 1 387 + 223 15 2 0 1 386 + 224 15 2 0 1 385 + 225 15 2 0 1 598 + 226 15 2 0 1 384 + 227 15 2 0 1 599 + 228 15 2 0 1 383 + 229 2 3 0 1 5 1770 603 422 + 230 2 3 0 2 5 1446 416 604 + 231 2 3 0 3 5 607 606 605 + 232 2 3 0 4 5 609 608 457 + 233 2 3 0 5 5 611 610 462 + 234 2 3 0 6 5 613 612 478 + 235 2 3 0 7 5 150 404 403 + 236 2 3 0 8 5 403 149 150 + 237 2 3 0 9 5 818 614 267 + 238 2 3 0 10 5 617 616 615 + 239 2 3 0 11 5 1451 35 618 + 240 2 3 0 12 5 1625 58 59 + 241 2 3 0 13 5 620 619 511 + 242 2 3 0 14 5 74 75 421 + 243 2 3 0 15 5 1626 421 75 + 244 2 3 0 16 5 1771 199 1 + 245 2 3 0 17 5 1773 1772 197 + 246 2 3 0 18 5 1777 194 423 + 247 2 3 0 19 5 621 203 187 + 248 2 3 0 20 5 621 188 189 + 249 2 3 0 21 5 623 622 423 + 250 2 3 0 22 5 625 624 447 + 251 2 3 0 23 5 627 626 425 + 252 2 3 0 24 5 694 426 629 + 253 2 3 0 25 5 1443 630 427 + 254 2 3 0 26 5 632 631 429 + 255 2 3 0 27 5 738 634 636 + 256 2 3 0 28 5 738 633 635 + 257 2 3 0 29 5 638 637 432 + 258 2 3 0 30 5 639 168 169 + 259 2 3 0 31 5 640 166 167 + 260 2 3 0 32 5 158 159 410 + 261 2 3 0 33 5 642 641 477 + 262 2 3 0 34 5 1174 644 643 + 263 2 3 0 35 5 157 158 409 + 264 2 3 0 36 5 721 645 236 + 265 2 3 0 37 5 156 157 408 + 266 2 3 0 38 5 154 155 407 + 267 2 3 0 39 5 407 155 156 + 268 2 3 0 40 5 647 406 154 + 269 2 3 0 41 5 648 152 153 + 270 2 3 0 42 5 151 152 405 + 271 2 3 0 43 5 802 264 650 + 272 2 3 0 44 5 813 265 652 + 273 2 3 0 45 5 403 402 149 + 274 2 3 0 46 5 1628 1627 566 + 275 2 3 0 47 5 1426 117 653 + 276 2 3 0 48 5 654 437 436 + 277 2 3 0 49 5 655 104 105 + 278 2 3 0 50 5 1202 108 109 + 279 2 3 0 51 5 656 441 440 + 280 2 3 0 52 5 658 657 442 + 281 2 3 0 53 5 660 659 514 + 282 2 3 0 54 5 662 661 444 + 283 2 3 0 55 5 663 396 397 + 284 2 3 0 56 5 400 148 401 + 285 2 3 0 57 5 399 147 400 + 286 2 3 0 58 5 145 146 399 + 287 2 3 0 59 5 144 145 398 + 288 2 3 0 60 5 143 144 397 + 289 2 3 0 61 5 664 134 135 + 290 2 3 0 62 5 141 395 394 + 291 2 3 0 63 5 665 136 137 + 292 2 3 0 64 5 140 393 139 + 293 2 3 0 65 5 827 143 396 + 294 2 3 0 66 5 141 142 395 + 295 2 3 0 67 5 140 141 394 + 296 2 3 0 68 5 666 6 7 + 297 2 3 0 69 5 1444 667 448 + 298 2 3 0 70 5 1772 195 196 + 299 2 3 0 71 5 668 624 625 + 300 2 3 0 72 5 621 187 188 + 301 2 3 0 73 5 671 669 202 + 302 2 3 0 74 5 671 670 669 + 303 2 3 0 75 5 1452 622 623 + 304 2 3 0 76 5 672 181 182 + 305 2 3 0 77 5 673 425 626 + 306 2 3 0 78 5 627 204 626 + 307 2 3 0 79 5 677 674 627 + 308 2 3 0 80 5 1183 424 676 + 309 2 3 0 81 5 677 450 674 + 310 2 3 0 82 5 1220 451 679 + 311 2 3 0 83 5 681 680 452 + 312 2 3 0 84 5 682 680 681 + 313 2 3 0 85 5 684 683 452 + 314 2 3 0 86 5 685 673 626 + 315 2 3 0 87 5 687 686 682 + 316 2 3 0 88 5 689 688 453 + 317 2 3 0 89 5 719 209 691 + 318 2 3 0 90 5 714 453 688 + 319 2 3 0 91 5 694 693 628 + 320 2 3 0 92 5 695 692 212 + 321 2 3 0 93 5 697 696 454 + 322 2 3 0 94 5 699 698 605 + 323 2 3 0 95 5 700 699 213 + 324 2 3 0 96 5 701 607 214 + 325 2 3 0 97 5 703 702 216 + 326 2 3 0 98 5 716 704 706 + 327 2 3 0 99 5 708 707 702 + 328 2 3 0 100 5 707 228 216 + 329 2 3 0 101 5 701 606 607 + 330 2 3 0 102 5 1230 455 710 + 331 2 3 0 103 5 711 703 459 + 332 2 3 0 104 5 712 710 455 + 333 2 3 0 105 5 714 713 692 + 334 2 3 0 106 5 706 458 221 + 335 2 3 0 107 5 715 218 693 + 336 2 3 0 108 5 717 716 706 + 337 2 3 0 109 5 1145 718 690 + 338 2 3 0 110 5 1145 224 220 + 339 2 3 0 111 5 719 690 209 + 340 2 3 0 112 5 720 18 19 + 341 2 3 0 113 5 1252 645 721 + 342 2 3 0 114 5 722 14 15 + 343 2 3 0 115 5 723 609 457 + 344 2 3 0 116 5 724 456 710 + 345 2 3 0 117 5 725 456 724 + 346 2 3 0 118 5 726 718 225 + 347 2 3 0 119 5 727 725 220 + 348 2 3 0 120 5 728 696 226 + 349 2 3 0 121 5 712 218 219 + 350 2 3 0 122 5 729 608 227 + 351 2 3 0 123 5 1187 730 454 + 352 2 3 0 124 5 731 459 703 + 353 2 3 0 125 5 732 731 216 + 354 2 3 0 126 5 230 246 229 + 355 2 3 0 127 5 741 460 734 + 356 2 3 0 128 5 735 175 176 + 357 2 3 0 129 5 780 731 246 + 358 2 3 0 130 5 738 737 245 + 359 2 3 0 131 5 732 608 609 + 360 2 3 0 132 5 739 722 15 + 361 2 3 0 133 5 741 740 733 + 362 2 3 0 134 5 743 742 417 + 363 2 3 0 135 5 744 17 18 + 364 2 3 0 136 5 746 745 254 + 365 2 3 0 137 5 747 611 462 + 366 2 3 0 138 5 748 22 23 + 367 2 3 0 139 5 1244 750 752 + 368 2 3 0 140 5 1490 754 753 + 369 2 3 0 141 5 787 756 755 + 370 2 3 0 142 5 758 757 465 + 371 2 3 0 143 5 760 759 467 + 372 2 3 0 144 5 764 763 762 + 373 2 3 0 145 5 766 765 468 + 374 2 3 0 146 5 768 767 744 + 375 2 3 0 147 5 770 769 469 + 376 2 3 0 148 5 1484 222 767 + 377 2 3 0 149 5 772 771 470 + 378 2 3 0 150 5 773 172 173 + 379 2 3 0 151 5 774 174 244 + 380 2 3 0 152 5 775 472 743 + 381 2 3 0 153 5 776 636 242 + 382 2 3 0 154 5 777 177 178 + 383 2 3 0 155 5 737 250 245 + 384 2 3 0 156 5 779 176 177 + 385 2 3 0 157 5 778 777 214 + 386 2 3 0 158 5 738 635 634 + 387 2 3 0 159 5 770 473 766 + 388 2 3 0 160 5 1458 246 230 + 389 2 3 0 161 5 735 244 175 + 390 2 3 0 162 5 1458 247 780 + 391 2 3 0 163 5 231 245 247 + 392 2 3 0 164 5 779 778 249 + 393 2 3 0 165 5 780 245 250 + 394 2 3 0 166 5 1458 780 246 + 395 2 3 0 167 5 781 735 249 + 396 2 3 0 168 5 781 248 735 + 397 2 3 0 169 5 781 736 780 + 398 2 3 0 170 5 783 782 433 + 399 2 3 0 171 5 784 234 467 + 400 2 3 0 172 5 785 170 171 + 401 2 3 0 173 5 786 785 241 + 402 2 3 0 174 5 788 787 755 + 403 2 3 0 175 5 1424 789 640 + 404 2 3 0 176 5 745 162 163 + 405 2 3 0 177 5 791 790 745 + 406 2 3 0 178 5 792 764 256 + 407 2 3 0 179 5 793 238 638 + 408 2 3 0 180 5 795 794 464 + 409 2 3 0 181 5 796 645 257 + 410 2 3 0 182 5 798 797 237 + 411 2 3 0 183 5 799 750 464 + 412 2 3 0 184 5 800 474 752 + 413 2 3 0 185 5 26 27 475 + 414 2 3 0 186 5 801 754 235 + 415 2 3 0 187 5 809 802 649 + 416 2 3 0 188 5 803 753 754 + 417 2 3 0 189 5 804 800 259 + 418 2 3 0 190 5 806 805 647 + 419 2 3 0 191 5 1273 476 746 + 420 2 3 0 192 5 647 154 407 + 421 2 3 0 193 5 643 161 162 + 422 2 3 0 194 5 808 807 418 + 423 2 3 0 195 5 809 804 264 + 424 2 3 0 196 5 649 404 405 + 425 2 3 0 197 5 811 810 799 + 426 2 3 0 198 5 812 30 31 + 427 2 3 0 199 5 814 813 652 + 428 2 3 0 200 5 815 618 35 + 429 2 3 0 201 5 817 816 812 + 430 2 3 0 202 5 818 400 401 + 431 2 3 0 203 5 614 401 402 + 432 2 3 0 204 5 846 819 268 + 433 2 3 0 205 5 821 820 487 + 434 2 3 0 206 5 1434 815 36 + 435 2 3 0 207 5 824 823 494 + 436 2 3 0 208 5 143 397 396 + 437 2 3 0 209 5 1114 482 826 + 438 2 3 0 210 5 827 395 142 + 439 2 3 0 211 5 828 132 133 + 440 2 3 0 212 5 829 128 129 + 441 2 3 0 213 5 831 830 483 + 442 2 3 0 214 5 832 46 47 + 443 2 3 0 215 5 833 831 483 + 444 2 3 0 216 5 835 834 485 + 445 2 3 0 217 5 1517 837 836 + 446 2 3 0 218 5 839 838 486 + 447 2 3 0 219 5 841 840 491 + 448 2 3 0 220 5 842 820 821 + 449 2 3 0 221 5 1510 844 843 + 450 2 3 0 222 5 845 487 488 + 451 2 3 0 223 5 846 836 398 + 452 2 3 0 224 5 848 847 488 + 453 2 3 0 225 5 846 268 836 + 454 2 3 0 226 5 1155 39 853 + 455 2 3 0 227 5 1291 848 488 + 456 2 3 0 228 5 852 851 490 + 457 2 3 0 229 5 1155 853 849 + 458 2 3 0 230 5 855 854 491 + 459 2 3 0 231 5 857 856 839 + 460 2 3 0 232 5 856 276 838 + 461 2 3 0 233 5 1301 492 859 + 462 2 3 0 234 5 861 860 499 + 463 2 3 0 235 5 862 841 491 + 464 2 3 0 236 5 864 863 854 + 465 2 3 0 237 5 866 865 859 + 466 2 3 0 238 5 868 867 824 + 467 2 3 0 239 5 869 823 824 + 468 2 3 0 240 5 870 495 126 + 469 2 3 0 241 5 872 871 496 + 470 2 3 0 242 5 873 661 662 + 471 2 3 0 243 5 875 874 497 + 472 2 3 0 244 5 1313 1312 1311 + 473 2 3 0 245 5 878 124 125 + 474 2 3 0 246 5 1449 880 879 + 475 2 3 0 247 5 881 878 125 + 476 2 3 0 248 5 882 875 287 + 477 2 3 0 249 5 883 861 499 + 478 2 3 0 250 5 885 884 484 + 479 2 3 0 251 5 887 886 494 + 480 2 3 0 252 5 888 886 887 + 481 2 3 0 253 5 889 831 484 + 482 2 3 0 254 5 891 890 515 + 483 2 3 0 255 5 892 130 131 + 484 2 3 0 256 5 894 893 500 + 485 2 3 0 257 5 896 895 839 + 486 2 3 0 258 5 898 897 501 + 487 2 3 0 259 5 900 899 502 + 488 2 3 0 260 5 1437 45 901 + 489 2 3 0 261 5 903 902 480 + 490 2 3 0 262 5 905 904 503 + 491 2 3 0 263 5 908 907 906 + 492 2 3 0 264 5 909 900 502 + 493 2 3 0 265 5 911 910 502 + 494 2 3 0 266 5 1532 894 500 + 495 2 3 0 267 5 914 913 887 + 496 2 3 0 268 5 1536 912 504 + 497 2 3 0 269 5 916 881 495 + 498 2 3 0 270 5 918 917 505 + 499 2 3 0 271 5 919 918 879 + 500 2 3 0 272 5 921 920 505 + 501 2 3 0 273 5 1536 905 503 + 502 2 3 0 274 5 923 50 51 + 503 2 3 0 275 5 927 926 508 + 504 2 3 0 276 5 1205 929 928 + 505 2 3 0 277 5 930 120 121 + 506 2 3 0 278 5 931 653 117 + 507 2 3 0 279 5 933 932 619 + 508 2 3 0 280 5 935 934 510 + 509 2 3 0 281 5 936 620 511 + 510 2 3 0 282 5 937 924 926 + 511 2 3 0 283 5 938 936 511 + 512 2 3 0 284 5 940 939 513 + 513 2 3 0 285 5 943 942 941 + 514 2 3 0 286 5 944 939 317 + 515 2 3 0 287 5 947 946 945 + 516 2 3 0 288 5 949 948 517 + 517 2 3 0 289 5 950 659 660 + 518 2 3 0 290 5 961 960 951 + 519 2 3 0 291 5 952 941 942 + 520 2 3 0 292 5 953 313 948 + 521 2 3 0 293 5 877 310 515 + 522 2 3 0 294 5 954 314 315 + 523 2 3 0 295 5 955 943 941 + 524 2 3 0 296 5 956 832 47 + 525 2 3 0 297 5 1535 298 957 + 526 2 3 0 298 5 958 934 935 + 527 2 3 0 299 5 960 959 951 + 528 2 3 0 300 5 962 944 317 + 529 2 3 0 301 5 963 516 48 + 530 2 3 0 302 5 965 964 959 + 531 2 3 0 303 5 953 948 949 + 532 2 3 0 304 5 1469 658 307 + 533 2 3 0 305 5 966 964 965 + 534 2 3 0 306 5 1343 968 518 + 535 2 3 0 307 5 968 308 518 + 536 2 3 0 308 5 1558 971 970 + 537 2 3 0 309 5 1425 519 973 + 538 2 3 0 310 5 974 440 441 + 539 2 3 0 311 5 1343 967 969 + 540 2 3 0 312 5 976 435 931 + 541 2 3 0 313 5 978 977 359 + 542 2 3 0 314 5 980 979 521 + 543 2 3 0 315 5 982 981 539 + 544 2 3 0 316 5 986 985 984 + 545 2 3 0 317 5 988 987 523 + 546 2 3 0 318 5 1629 88 89 + 547 2 3 0 319 5 990 989 525 + 548 2 3 0 320 5 992 991 588 + 549 2 3 0 321 5 993 436 437 + 550 2 3 0 322 5 1569 996 995 + 551 2 3 0 323 5 995 112 113 + 552 2 3 0 324 5 1165 529 998 + 553 2 3 0 325 5 1000 999 530 + 554 2 3 0 326 5 1361 1001 531 + 555 2 3 0 327 5 1002 532 988 + 556 2 3 0 328 5 1010 331 380 + 557 2 3 0 329 5 1047 534 1005 + 558 2 3 0 330 5 1007 1006 540 + 559 2 3 0 331 5 1009 1008 971 + 560 2 3 0 332 5 1010 1003 331 + 561 2 3 0 333 5 1012 1011 1010 + 562 2 3 0 334 5 1013 594 382 + 563 2 3 0 335 5 1013 382 381 + 564 2 3 0 336 5 1014 595 388 + 565 2 3 0 337 5 1016 1015 537 + 566 2 3 0 338 5 1631 1630 366 + 567 2 3 0 339 5 1018 1017 935 + 568 2 3 0 340 5 1020 1019 335 + 569 2 3 0 341 5 1022 1021 336 + 570 2 3 0 342 5 1023 1011 1012 + 571 2 3 0 343 5 1025 1024 341 + 572 2 3 0 344 5 1575 1014 337 + 573 2 3 0 345 5 1027 981 373 + 574 2 3 0 346 5 1376 540 1029 + 575 2 3 0 347 5 1030 360 1006 + 576 2 3 0 348 5 1031 1030 330 + 577 2 3 0 349 5 1033 1032 541 + 578 2 3 0 350 5 1086 386 1034 + 579 2 3 0 351 5 1744 1633 1632 + 580 2 3 0 352 5 1036 1035 541 + 581 2 3 0 353 5 1634 1037 369 + 582 2 3 0 354 5 1038 54 55 + 583 2 3 0 355 5 1636 1635 1631 + 584 2 3 0 356 5 1040 1039 542 + 585 2 3 0 357 5 1637 1178 543 + 586 2 3 0 358 5 1749 1638 546 + 587 2 3 0 359 5 1685 548 1641 + 588 2 3 0 360 5 1642 82 83 + 589 2 3 0 361 5 1089 1042 1041 + 590 2 3 0 362 5 1643 1635 348 + 591 2 3 0 363 5 1366 1044 367 + 592 2 3 0 364 5 1047 1046 1004 + 593 2 3 0 365 5 1051 1050 1049 + 594 2 3 0 366 5 1634 1052 1037 + 595 2 3 0 367 5 1053 552 1008 + 596 2 3 0 368 5 1055 1054 533 + 597 2 3 0 369 5 1056 966 319 + 598 2 3 0 370 5 1057 550 1046 + 599 2 3 0 371 5 1058 517 948 + 600 2 3 0 372 5 1059 967 320 + 601 2 3 0 373 5 1061 1060 553 + 602 2 3 0 374 5 1062 977 978 + 603 2 3 0 375 5 1557 1063 1061 + 604 2 3 0 376 5 1065 1064 1063 + 605 2 3 0 377 5 1066 1016 925 + 606 2 3 0 378 5 1067 554 359 + 607 2 3 0 379 5 1578 1033 541 + 608 2 3 0 380 5 1070 1069 555 + 609 2 3 0 381 5 1067 1003 1011 + 610 2 3 0 382 5 1072 1071 1070 + 611 2 3 0 383 5 1074 1073 553 + 612 2 3 0 384 5 1023 1006 1007 + 613 2 3 0 385 5 1075 596 373 + 614 2 3 0 386 5 1076 990 589 + 615 2 3 0 387 5 1566 361 1077 + 616 2 3 0 388 5 1080 1079 1078 + 617 2 3 0 389 5 1082 1081 1076 + 618 2 3 0 390 5 1645 1644 1084 + 619 2 3 0 391 5 1084 1083 363 + 620 2 3 0 392 5 1732 1646 561 + 621 2 3 0 393 5 1647 1644 1645 + 622 2 3 0 394 5 1753 1649 1648 + 623 2 3 0 395 5 1659 568 1650 + 624 2 3 0 396 5 1086 1022 336 + 625 2 3 0 397 5 1088 1087 1086 + 626 2 3 0 398 5 1652 1651 1636 + 627 2 3 0 399 5 1090 1089 1041 + 628 2 3 0 400 5 1091 1057 344 + 629 2 3 0 401 5 1579 1044 1092 + 630 2 3 0 402 5 980 368 979 + 631 2 3 0 403 5 1094 1093 350 + 632 2 3 0 404 5 1654 1653 565 + 633 2 3 0 405 5 78 79 566 + 634 2 3 0 406 5 1656 1655 1633 + 635 2 3 0 407 5 1713 567 1634 + 636 2 3 0 408 5 1658 1648 1649 + 637 2 3 0 409 5 1754 1650 365 + 638 2 3 0 410 5 1660 982 539 + 639 2 3 0 411 5 1075 373 340 + 640 2 3 0 412 5 1002 597 374 + 641 2 3 0 413 5 1095 569 539 + 642 2 3 0 414 5 1085 339 391 + 643 2 3 0 415 5 598 384 334 + 644 2 3 0 416 5 1024 377 376 + 645 2 3 0 417 5 1002 988 341 + 646 2 3 0 418 5 330 379 378 + 647 2 3 0 419 5 1096 599 383 + 648 2 3 0 420 5 1559 381 600 + 649 2 3 0 421 5 600 380 331 + 650 2 3 0 422 5 1097 970 356 + 651 2 3 0 423 5 1371 1096 333 + 652 2 3 0 424 5 1013 381 332 + 653 2 3 0 425 5 1100 1099 334 + 654 2 3 0 426 5 1102 1101 1021 + 655 2 3 0 427 5 336 387 386 + 656 2 3 0 428 5 1103 1101 1102 + 657 2 3 0 429 5 385 335 386 + 658 2 3 0 430 5 1575 1044 535 + 659 2 3 0 431 5 1104 602 389 + 660 2 3 0 432 5 339 392 391 + 661 2 3 0 433 5 1106 1105 1085 + 662 2 3 0 434 5 1027 392 339 + 663 2 3 0 435 5 1095 1027 339 + 664 2 3 0 436 5 1107 665 138 + 665 2 3 0 437 5 138 139 393 + 666 2 3 0 438 5 1109 1108 570 + 667 2 3 0 439 5 1110 1109 446 + 668 2 3 0 440 5 827 142 143 + 669 2 3 0 441 5 1112 1111 1109 + 670 2 3 0 442 5 1114 1113 825 + 671 2 3 0 443 5 1288 1112 570 + 672 2 3 0 444 5 397 144 398 + 673 2 3 0 445 5 1116 843 844 + 674 2 3 0 446 5 398 145 399 + 675 2 3 0 447 5 1117 842 277 + 676 2 3 0 448 5 146 147 399 + 677 2 3 0 449 5 1118 851 278 + 678 2 3 0 450 5 147 148 400 + 679 2 3 0 451 5 1119 819 818 + 680 2 3 0 452 5 148 402 401 + 681 2 3 0 453 5 1120 852 279 + 682 2 3 0 454 5 148 149 402 + 683 2 3 0 455 5 1121 652 265 + 684 2 3 0 456 5 1123 1122 572 + 685 2 3 0 457 5 1466 1123 572 + 686 2 3 0 458 5 151 404 150 + 687 2 3 0 459 5 1126 1125 811 + 688 2 3 0 460 5 1463 648 1127 + 689 2 3 0 461 5 1127 648 406 + 690 2 3 0 462 5 153 154 406 + 691 2 3 0 463 5 1128 613 478 + 692 2 3 0 464 5 1129 262 407 + 693 2 3 0 465 5 1129 156 408 + 694 2 3 0 466 5 408 157 409 + 695 2 3 0 467 5 642 409 641 + 696 2 3 0 468 5 158 410 409 + 697 2 3 0 469 5 641 409 410 + 698 2 3 0 470 5 159 160 410 + 699 2 3 0 471 5 644 161 643 + 700 2 3 0 472 5 1639 545 1638 + 701 2 3 0 473 5 1260 1131 1130 + 702 2 3 0 474 5 1189 229 609 + 703 2 3 0 475 5 1662 1661 92 + 704 2 3 0 476 5 1132 906 41 + 705 2 3 0 477 5 1134 1133 576 + 706 2 3 0 478 5 1136 1135 589 + 707 2 3 0 479 5 1664 1663 579 + 708 2 3 0 480 5 1656 80 1655 + 709 2 3 0 481 5 1738 87 1665 + 710 2 3 0 482 5 1261 638 432 + 711 2 3 0 483 5 1137 431 637 + 712 2 3 0 484 5 1667 1666 1625 + 713 2 3 0 485 5 1724 1668 581 + 714 2 3 0 486 5 1720 1670 1669 + 715 2 3 0 487 5 1671 62 63 + 716 2 3 0 488 5 1138 56 57 + 717 2 3 0 489 5 1672 1664 579 + 718 2 3 0 490 5 640 165 166 + 719 2 3 0 491 5 1139 973 584 + 720 2 3 0 492 5 1140 1134 576 + 721 2 3 0 493 5 1142 1141 577 + 722 2 3 0 494 5 1144 1143 683 + 723 2 3 0 495 5 180 181 213 + 724 2 3 0 496 5 1145 690 719 + 725 2 3 0 497 5 16 17 222 + 726 2 3 0 498 5 1146 12 13 + 727 2 3 0 499 5 1147 764 762 + 728 2 3 0 500 5 174 175 244 + 729 2 3 0 501 5 1148 24 25 + 730 2 3 0 502 5 1149 1121 29 + 731 2 3 0 503 5 1150 816 817 + 732 2 3 0 504 5 1152 1151 892 + 733 2 3 0 505 5 1153 870 127 + 734 2 3 0 506 5 1154 901 45 + 735 2 3 0 507 5 1156 1155 849 + 736 2 3 0 508 5 1331 123 932 + 737 2 3 0 509 5 1158 1157 1058 + 738 2 3 0 510 5 1160 1159 936 + 739 2 3 0 511 5 1673 1161 576 + 740 2 3 0 512 5 1729 100 526 + 741 2 3 0 513 5 1163 1162 996 + 742 2 3 0 514 5 1167 1166 1165 + 743 2 3 0 515 5 1164 586 1005 + 744 2 3 0 516 5 1675 1674 1671 + 745 2 3 0 517 5 1676 68 69 + 746 2 3 0 518 5 1677 1655 81 + 747 2 3 0 519 5 1165 997 529 + 748 2 3 0 520 5 1168 908 296 + 749 2 3 0 521 5 1678 1626 76 + 750 2 3 0 522 5 1658 84 85 + 751 2 3 0 523 5 1680 1679 582 + 752 2 3 0 524 5 1169 2 3 + 753 2 3 0 525 5 1171 1170 1169 + 754 2 3 0 526 5 1774 1773 198 + 755 2 3 0 527 5 1776 604 416 + 756 2 3 0 528 5 1238 775 743 + 757 2 3 0 529 5 1173 417 742 + 758 2 3 0 530 5 1175 1174 643 + 759 2 3 0 531 5 1177 1176 801 + 760 2 3 0 532 5 1682 1681 1679 + 761 2 3 0 533 5 1178 1048 1050 + 762 2 3 0 534 5 1179 916 289 + 763 2 3 0 535 5 1180 511 420 + 764 2 3 0 536 5 1683 1641 548 + 765 2 3 0 537 5 1763 1685 1684 + 766 2 3 0 538 5 1774 1770 422 + 767 2 3 0 539 5 1770 1170 603 + 768 2 3 0 540 5 1775 423 194 + 769 2 3 0 541 5 1181 680 682 + 770 2 3 0 542 5 1182 726 210 + 771 2 3 0 543 5 1183 676 210 + 772 2 3 0 544 5 1184 185 186 + 773 2 3 0 545 5 1185 677 1184 + 774 2 3 0 546 5 1183 207 675 + 775 2 3 0 547 5 715 694 210 + 776 2 3 0 548 5 1186 691 625 + 777 2 3 0 549 5 630 8 9 + 778 2 3 0 550 5 1187 728 428 + 779 2 3 0 551 5 728 455 428 + 780 2 3 0 552 5 1188 468 765 + 781 2 3 0 553 5 1190 1189 723 + 782 2 3 0 554 5 1191 1173 742 + 783 2 3 0 555 5 633 245 231 + 784 2 3 0 556 5 1192 760 234 + 785 2 3 0 557 5 1258 759 760 + 786 2 3 0 558 5 1496 771 772 + 787 2 3 0 559 5 1137 637 638 + 788 2 3 0 560 5 1193 775 783 + 789 2 3 0 561 5 782 252 747 + 790 2 3 0 562 5 1686 1631 434 + 791 2 3 0 563 5 1688 1687 1683 + 792 2 3 0 564 5 1194 118 119 + 793 2 3 0 565 5 1195 1071 1072 + 794 2 3 0 566 5 1600 1080 1078 + 795 2 3 0 567 5 1197 654 436 + 796 2 3 0 568 5 1199 1198 588 + 797 2 3 0 569 5 993 437 989 + 798 2 3 0 570 5 1413 107 1141 + 799 2 3 0 571 5 1201 1200 585 + 800 2 3 0 572 5 1442 110 1162 + 801 2 3 0 573 5 1427 1203 1141 + 802 2 3 0 574 5 1204 512 440 + 803 2 3 0 575 5 1206 1205 928 + 804 2 3 0 576 5 1207 1070 441 + 805 2 3 0 577 5 1071 974 441 + 806 2 3 0 578 5 1208 921 917 + 807 2 3 0 579 5 946 302 880 + 808 2 3 0 580 5 919 302 917 + 809 2 3 0 581 5 1210 1209 879 + 810 2 3 0 582 5 1212 1211 485 + 811 2 3 0 583 5 1473 662 273 + 812 2 3 0 584 5 1213 1151 1152 + 813 2 3 0 585 5 1214 664 135 + 814 2 3 0 586 5 1214 136 665 + 815 2 3 0 587 5 1110 394 1108 + 816 2 3 0 588 5 1186 427 691 + 817 2 3 0 589 5 1215 667 5 + 818 2 3 0 590 5 1216 1170 1171 + 819 2 3 0 591 5 667 4 5 + 820 2 3 0 592 5 1217 686 687 + 821 2 3 0 593 5 1218 686 206 + 822 2 3 0 594 5 1219 671 451 + 823 2 3 0 595 5 1221 1220 679 + 824 2 3 0 596 5 1222 1218 679 + 825 2 3 0 597 5 1225 674 1220 + 826 2 3 0 598 5 1223 1172 603 + 827 2 3 0 599 5 1224 681 452 + 828 2 3 0 600 5 1225 1221 689 + 829 2 3 0 601 5 1226 689 206 + 830 2 3 0 602 5 1227 730 217 + 831 2 3 0 603 5 697 211 693 + 832 2 3 0 604 5 724 710 712 + 833 2 3 0 605 5 725 225 220 + 834 2 3 0 606 5 458 224 221 + 835 2 3 0 607 5 1230 1229 1228 + 836 2 3 0 608 5 729 428 457 + 837 2 3 0 609 5 631 457 428 + 838 2 3 0 610 5 1232 1231 1228 + 839 2 3 0 611 5 1231 458 740 + 840 2 3 0 612 5 711 215 702 + 841 2 3 0 613 5 732 216 228 + 842 2 3 0 614 5 1233 1130 734 + 843 2 3 0 615 5 1235 1234 1131 + 844 2 3 0 616 5 1237 1236 468 + 845 2 3 0 617 5 1230 710 1229 + 846 2 3 0 618 5 1238 743 417 + 847 2 3 0 619 5 1240 1239 756 + 848 2 3 0 620 5 1243 1241 794 + 849 2 3 0 621 5 1242 1147 463 + 850 2 3 0 622 5 1243 1242 463 + 851 2 3 0 623 5 1245 1244 752 + 852 2 3 0 624 5 1246 798 465 + 853 2 3 0 625 5 1247 757 758 + 854 2 3 0 626 5 1249 1248 469 + 855 2 3 0 627 5 1251 1250 1249 + 856 2 3 0 628 5 1253 1252 721 + 857 2 3 0 629 5 784 467 721 + 858 2 3 0 630 5 1255 1254 1251 + 859 2 3 0 631 5 1257 1256 1248 + 860 2 3 0 632 5 1258 1248 466 + 861 2 3 0 633 5 1259 473 1256 + 862 2 3 0 634 5 1260 470 1131 + 863 2 3 0 635 5 1495 1261 772 + 864 2 3 0 636 5 1262 738 636 + 865 2 3 0 637 5 1263 773 241 + 866 2 3 0 638 5 786 242 743 + 867 2 3 0 639 5 743 242 742 + 868 2 3 0 640 5 1265 1264 1190 + 869 2 3 0 641 5 1266 765 766 + 870 2 3 0 642 5 1268 1267 796 + 871 2 3 0 643 5 1269 1244 1245 + 872 2 3 0 644 5 1271 1270 1121 + 873 2 3 0 645 5 651 572 265 + 874 2 3 0 646 5 1272 745 746 + 875 2 3 0 647 5 1273 807 476 + 876 2 3 0 648 5 1274 1128 262 + 877 2 3 0 649 5 1275 1129 408 + 878 2 3 0 650 5 1276 478 612 + 879 2 3 0 651 5 1277 1127 406 + 880 2 3 0 652 5 1278 842 1117 + 881 2 3 0 653 5 1279 1119 479 + 882 2 3 0 654 5 1280 902 903 + 883 2 3 0 655 5 1282 1281 902 + 884 2 3 0 656 5 1212 662 1211 + 885 2 3 0 657 5 1515 834 835 + 886 2 3 0 658 5 1283 826 482 + 887 2 3 0 659 5 1512 1511 1114 + 888 2 3 0 660 5 1285 863 864 + 889 2 3 0 661 5 1286 833 483 + 890 2 3 0 662 5 885 293 861 + 891 2 3 0 663 5 1287 615 889 + 892 2 3 0 664 5 1288 591 1115 + 893 2 3 0 665 5 1421 835 485 + 894 2 3 0 666 5 821 486 277 + 895 2 3 0 667 5 1290 896 282 + 896 2 3 0 668 5 1291 488 487 + 897 2 3 0 669 5 1292 821 487 + 898 2 3 0 670 5 1293 845 488 + 899 2 3 0 671 5 1120 851 852 + 900 2 3 0 672 5 1294 489 1120 + 901 2 3 0 673 5 1296 1295 1294 + 902 2 3 0 674 5 1298 1297 814 + 903 2 3 0 675 5 1299 1298 266 + 904 2 3 0 676 5 1283 840 274 + 905 2 3 0 677 5 857 855 856 + 906 2 3 0 678 5 1300 865 294 + 907 2 3 0 679 5 1301 859 282 + 908 2 3 0 680 5 1302 493 293 + 909 2 3 0 681 5 1303 1302 284 + 910 2 3 0 682 5 1304 914 285 + 911 2 3 0 683 5 1473 872 496 + 912 2 3 0 684 5 1306 916 495 + 913 2 3 0 685 5 870 126 127 + 914 2 3 0 686 5 1305 273 867 + 915 2 3 0 687 5 882 874 875 + 916 2 3 0 688 5 1308 1307 918 + 917 2 3 0 689 5 1309 1306 875 + 918 2 3 0 690 5 1310 941 952 + 919 2 3 0 691 5 1312 876 498 + 920 2 3 0 692 5 860 293 493 + 921 2 3 0 693 5 1315 1314 909 + 922 2 3 0 694 5 1316 954 313 + 923 2 3 0 695 5 1318 1317 953 + 924 2 3 0 696 5 1319 910 911 + 925 2 3 0 697 5 1280 296 897 + 926 2 3 0 698 5 1320 899 900 + 927 2 3 0 699 5 1319 911 295 + 928 2 3 0 700 5 1321 904 905 + 929 2 3 0 701 5 893 503 297 + 930 2 3 0 702 5 1324 504 1322 + 931 2 3 0 703 5 922 504 506 + 932 2 3 0 704 5 1180 920 921 + 933 2 3 0 705 5 1323 1307 1308 + 934 2 3 0 706 5 1324 506 504 + 935 2 3 0 707 5 1325 1324 312 + 936 2 3 0 708 5 1326 52 53 + 937 2 3 0 709 5 1327 963 49 + 938 2 3 0 710 5 1328 1017 536 + 939 2 3 0 711 5 937 926 927 + 940 2 3 0 712 5 1329 1194 119 + 941 2 3 0 713 5 1542 931 509 + 942 2 3 0 714 5 1330 1033 538 + 943 2 3 0 715 5 958 935 940 + 944 2 3 0 716 5 1331 933 304 + 945 2 3 0 717 5 1333 1332 938 + 946 2 3 0 718 5 1334 512 1332 + 947 2 3 0 719 5 1438 1335 1159 + 948 2 3 0 720 5 1337 1336 949 + 949 2 3 0 721 5 1338 940 354 + 950 2 3 0 722 5 1555 308 309 + 951 2 3 0 723 5 947 307 658 + 952 2 3 0 724 5 890 300 883 + 953 2 3 0 725 5 1339 1312 877 + 954 2 3 0 726 5 956 314 832 + 955 2 3 0 727 5 963 48 49 + 956 2 3 0 728 5 1543 1340 1054 + 957 2 3 0 729 5 1341 1336 1337 + 958 2 3 0 730 5 1342 1065 520 + 959 2 3 0 731 5 1343 1342 975 + 960 2 3 0 732 5 1344 584 519 + 961 2 3 0 733 5 1345 973 1139 + 962 2 3 0 734 5 1588 552 1053 + 963 2 3 0 735 5 1346 1053 1008 + 964 2 3 0 736 5 1583 1042 549 + 965 2 3 0 737 5 1620 1347 350 + 966 2 3 0 738 5 1358 1349 1000 + 967 2 3 0 739 5 1350 986 557 + 968 2 3 0 740 5 1352 1351 1031 + 969 2 3 0 741 5 1568 1352 1025 + 970 2 3 0 742 5 1689 1660 364 + 971 2 3 0 743 5 1690 1658 85 + 972 2 3 0 744 5 1353 990 525 + 973 2 3 0 745 5 1353 1136 990 + 974 2 3 0 746 5 1411 1201 585 + 975 2 3 0 747 5 96 97 1161 + 976 2 3 0 748 5 1355 1353 525 + 977 2 3 0 749 5 1691 94 95 + 978 2 3 0 750 5 1692 1673 576 + 979 2 3 0 751 5 1356 1200 327 + 980 2 3 0 752 5 1357 575 998 + 981 2 3 0 753 5 1358 531 1349 + 982 2 3 0 754 5 1344 999 1000 + 983 2 3 0 755 5 1360 1359 1028 + 984 2 3 0 756 5 1361 1360 984 + 985 2 3 0 757 5 1362 1078 1079 + 986 2 3 0 758 5 1079 987 988 + 987 2 3 0 759 5 1363 1054 1055 + 988 2 3 0 760 5 1364 533 1054 + 989 2 3 0 761 5 1538 923 51 + 990 2 3 0 762 5 1057 1047 1005 + 991 2 3 0 763 5 1366 1045 1044 + 992 2 3 0 764 5 1367 1104 389 + 993 2 3 0 765 5 1368 1017 1018 + 994 2 3 0 766 5 1369 1100 536 + 995 2 3 0 767 5 1371 1370 1098 + 996 2 3 0 768 5 1016 355 925 + 997 2 3 0 769 5 1372 1330 510 + 998 2 3 0 770 5 1369 1368 538 + 999 2 3 0 771 5 1095 539 1027 + 1000 2 3 0 772 5 1374 1373 1083 + 1001 2 3 0 773 5 1375 1007 540 + 1002 2 3 0 774 5 1376 1028 540 + 1003 2 3 0 775 5 1090 1035 343 + 1004 2 3 0 776 5 1068 342 1019 + 1005 2 3 0 777 5 1380 1038 55 + 1006 2 3 0 778 5 1379 1378 1040 + 1007 2 3 0 779 5 1380 1377 1038 + 1008 2 3 0 780 5 1693 543 1587 + 1009 2 3 0 781 5 1694 583 1672 + 1010 2 3 0 782 5 1695 64 65 + 1011 2 3 0 783 5 1696 70 71 + 1012 2 3 0 784 5 1760 1696 71 + 1013 2 3 0 785 5 1698 546 544 + 1014 2 3 0 786 5 1698 1680 546 + 1015 2 3 0 787 5 1700 1699 583 + 1016 2 3 0 788 5 1701 1694 73 + 1017 2 3 0 789 5 1702 1626 347 + 1018 2 3 0 790 5 1703 1685 370 + 1019 2 3 0 791 5 1381 1378 1379 + 1020 2 3 0 792 5 1348 563 980 + 1021 2 3 0 793 5 1382 1036 1032 + 1022 2 3 0 794 5 1055 550 351 + 1023 2 3 0 795 5 1383 1347 1042 + 1024 2 3 0 796 5 1178 1050 1051 + 1025 2 3 0 797 5 1384 1008 1009 + 1026 2 3 0 798 5 1346 357 977 + 1027 2 3 0 799 5 1385 1060 1061 + 1028 2 3 0 800 5 1073 355 1016 + 1029 2 3 0 801 5 1386 1007 1375 + 1030 2 3 0 802 5 1387 1062 978 + 1031 2 3 0 803 5 1388 1195 1072 + 1032 2 3 0 804 5 1207 1069 1070 + 1033 2 3 0 805 5 1389 1376 360 + 1034 2 3 0 806 5 1391 1390 1077 + 1035 2 3 0 807 5 1350 983 985 + 1036 2 3 0 808 5 1392 557 986 + 1037 2 3 0 809 5 1394 1393 1197 + 1038 2 3 0 810 5 1395 1394 362 + 1039 2 3 0 811 5 1704 1665 88 + 1040 2 3 0 812 5 1707 1661 561 + 1041 2 3 0 813 5 1393 654 1197 + 1042 2 3 0 814 5 1706 1646 560 + 1043 2 3 0 815 5 1741 90 1707 + 1044 2 3 0 816 5 1708 1662 93 + 1045 2 3 0 817 5 1396 1091 344 + 1046 2 3 0 818 5 1381 1379 345 + 1047 2 3 0 819 5 1398 1397 593 + 1048 2 3 0 820 5 1399 563 1397 + 1049 2 3 0 821 5 1710 1709 1684 + 1050 2 3 0 822 5 1711 1653 1654 + 1051 2 3 0 823 5 1712 1643 348 + 1052 2 3 0 824 5 1713 1657 567 + 1053 2 3 0 825 5 1686 1630 1631 + 1054 2 3 0 826 5 1737 1714 1678 + 1055 2 3 0 827 5 1052 367 1037 + 1056 2 3 0 828 5 1713 593 1654 + 1057 2 3 0 829 5 1400 568 1105 + 1058 2 3 0 830 5 1715 1650 568 + 1059 2 3 0 831 5 1758 1716 1648 + 1060 2 3 0 832 5 1717 1660 569 + 1061 2 3 0 833 5 1402 1401 1284 + 1062 2 3 0 834 5 1615 1403 1289 + 1063 2 3 0 835 5 1404 24 1148 + 1064 2 3 0 836 5 1405 1148 26 + 1065 2 3 0 837 5 1406 1271 265 + 1066 2 3 0 838 5 1124 404 802 + 1067 2 3 0 839 5 1125 650 810 + 1068 2 3 0 840 5 1407 1125 1126 + 1069 2 3 0 841 5 1740 67 68 + 1070 2 3 0 842 5 1718 574 69 + 1071 2 3 0 843 5 1408 1357 998 + 1072 2 3 0 844 5 1409 575 1357 + 1073 2 3 0 845 5 1606 994 1140 + 1074 2 3 0 846 5 1411 1410 1354 + 1075 2 3 0 847 5 1412 1142 577 + 1076 2 3 0 848 5 1413 1142 438 + 1077 2 3 0 849 5 1720 1719 581 + 1078 2 3 0 850 5 1721 1698 544 + 1079 2 3 0 851 5 1697 579 544 + 1080 2 3 0 852 5 1694 1672 72 + 1081 2 3 0 853 5 1722 1721 578 + 1082 2 3 0 854 5 1723 1722 1719 + 1083 2 3 0 855 5 1669 413 1637 + 1084 2 3 0 856 5 1724 1653 564 + 1085 2 3 0 857 5 1725 1695 574 + 1086 2 3 0 858 5 1726 1679 414 + 1087 2 3 0 859 5 1727 1709 346 + 1088 2 3 0 860 5 1728 1663 1664 + 1089 2 3 0 861 5 1414 995 113 + 1090 2 3 0 862 5 1139 114 115 + 1091 2 3 0 863 5 1412 1200 438 + 1092 2 3 0 864 5 1607 1134 585 + 1093 2 3 0 865 5 1416 1326 53 + 1094 2 3 0 866 5 1005 586 344 + 1095 2 3 0 867 5 1192 755 587 + 1096 2 3 0 868 5 1258 587 1239 + 1097 2 3 0 869 5 1417 991 992 + 1098 2 3 0 870 5 1408 1198 1199 + 1099 2 3 0 871 5 1418 1350 557 + 1100 2 3 0 872 5 1419 1081 1082 + 1101 2 3 0 873 5 1403 826 1283 + 1102 2 3 0 874 5 1515 1420 869 + 1103 2 3 0 875 5 1421 591 1289 + 1104 2 3 0 876 5 1115 445 1111 + 1105 2 3 0 877 5 1422 592 1348 + 1106 2 3 0 878 5 1041 592 349 + 1107 2 3 0 879 5 1399 1397 1398 + 1108 2 3 0 880 5 1620 1423 1397 + 1109 2 3 0 881 5 1424 168 639 + 1110 2 3 0 882 5 164 251 163 + 1111 2 3 0 883 5 640 164 165 + 1112 2 3 0 884 5 151 405 404 + 1113 2 3 0 885 5 1426 1425 1345 + 1114 2 3 0 886 5 1354 655 1201 + 1115 2 3 0 887 5 1427 1141 107 + 1116 2 3 0 888 5 1214 665 1107 + 1117 2 3 0 889 5 393 140 394 + 1118 2 3 0 890 5 1215 6 447 + 1119 2 3 0 891 5 1428 1185 1184 + 1120 2 3 0 892 5 685 182 183 + 1121 2 3 0 893 5 777 178 214 + 1122 2 3 0 894 5 1429 716 717 + 1123 2 3 0 895 5 744 18 720 + 1124 2 3 0 896 5 1430 733 1146 + 1125 2 3 0 897 5 22 463 21 + 1126 2 3 0 898 5 1263 171 172 + 1127 2 3 0 899 5 735 176 243 + 1128 2 3 0 900 5 1431 1193 639 + 1129 2 3 0 901 5 1405 571 1148 + 1130 2 3 0 902 5 1149 30 812 + 1131 2 3 0 903 5 1432 1150 33 + 1132 2 3 0 904 5 1213 1152 132 + 1133 2 3 0 905 5 1433 1153 128 + 1134 2 3 0 906 5 1154 46 832 + 1135 2 3 0 907 5 1434 1155 1156 + 1136 2 3 0 908 5 1435 932 123 + 1137 2 3 0 909 5 1436 892 444 + 1138 2 3 0 910 5 1531 901 500 + 1139 2 3 0 911 5 1168 907 908 + 1140 2 3 0 912 5 1327 50 507 + 1141 2 3 0 913 5 1438 1329 304 + 1142 2 3 0 914 5 1331 122 123 + 1143 2 3 0 915 5 1162 112 995 + 1144 2 3 0 916 5 1573 594 1013 + 1145 2 3 0 917 5 1026 389 595 + 1146 2 3 0 918 5 1440 1416 53 + 1147 2 3 0 919 5 596 532 374 + 1148 2 3 0 920 5 1024 597 341 + 1149 2 3 0 921 5 1099 598 334 + 1150 2 3 0 922 5 1098 384 599 + 1151 2 3 0 923 5 1559 331 1384 + 1152 2 3 0 924 5 601 337 388 + 1153 2 3 0 925 5 602 338 390 + 1154 2 3 0 926 5 1271 27 1270 + 1155 2 3 0 927 5 1132 42 43 + 1156 2 3 0 928 5 1380 345 1377 + 1157 2 3 0 929 5 606 180 213 + 1158 2 3 0 930 5 739 222 240 + 1159 2 3 0 931 5 1146 704 12 + 1160 2 3 0 932 5 792 763 764 + 1161 2 3 0 933 5 1441 774 244 + 1162 2 3 0 934 5 1404 1148 571 + 1163 2 3 0 935 5 1150 32 33 + 1164 2 3 0 936 5 822 618 815 + 1165 2 3 0 937 5 1729 98 99 + 1166 2 3 0 938 5 1442 1202 110 + 1167 2 3 0 939 5 1771 2 415 + 1168 2 3 0 940 5 673 185 425 + 1169 2 3 0 941 5 1443 8 630 + 1170 2 3 0 942 5 1194 931 118 + 1171 2 3 0 943 5 1413 106 107 + 1172 2 3 0 944 5 134 445 133 + 1173 2 3 0 945 5 1444 1216 1171 + 1174 2 3 0 946 5 881 126 495 + 1175 2 3 0 947 5 1538 586 1164 + 1176 2 3 0 948 5 956 48 516 + 1177 2 3 0 949 5 1445 1411 585 + 1178 2 3 0 950 5 1414 114 584 + 1179 2 3 0 951 5 1223 200 683 + 1180 2 3 0 952 5 1172 201 604 + 1181 2 3 0 953 5 1776 1772 1773 + 1182 2 3 0 954 5 1446 604 201 + 1183 2 3 0 955 5 700 672 204 + 1184 2 3 0 956 5 711 702 703 + 1185 2 3 0 957 5 606 179 180 + 1186 2 3 0 958 5 606 213 605 + 1187 2 3 0 959 5 607 605 215 + 1188 2 3 0 960 5 701 214 178 + 1189 2 3 0 961 5 608 228 217 + 1190 2 3 0 962 5 608 217 227 + 1191 2 3 0 963 5 723 457 632 + 1192 2 3 0 964 5 732 609 229 + 1193 2 3 0 965 5 1447 1240 610 + 1194 2 3 0 966 5 1240 233 1239 + 1195 2 3 0 967 5 787 462 756 + 1196 2 3 0 968 5 1238 252 775 + 1197 2 3 0 969 5 1448 1176 1177 + 1198 2 3 0 970 5 1448 1276 612 + 1199 2 3 0 971 5 1128 478 805 + 1200 2 3 0 972 5 1502 613 261 + 1201 2 3 0 973 5 813 402 651 + 1202 2 3 0 974 5 1297 614 813 + 1203 2 3 0 975 5 889 830 831 + 1204 2 3 0 976 5 950 617 301 + 1205 2 3 0 977 5 616 292 291 + 1206 2 3 0 978 5 616 291 615 + 1207 2 3 0 979 5 617 615 301 + 1208 2 3 0 980 5 1449 1209 617 + 1209 2 3 0 981 5 1296 618 280 + 1210 2 3 0 982 5 1451 1450 1432 + 1211 2 3 0 983 5 1179 619 288 + 1212 2 3 0 984 5 619 420 511 + 1213 2 3 0 985 5 1180 938 511 + 1214 2 3 0 986 5 1331 304 930 + 1215 2 3 0 987 5 621 189 190 + 1216 2 3 0 988 5 1219 190 671 + 1217 2 3 0 989 5 669 622 202 + 1218 2 3 0 990 5 1777 193 194 + 1219 2 3 0 991 5 1446 623 423 + 1220 2 3 0 992 5 1452 1222 202 + 1221 2 3 0 993 5 1453 624 424 + 1222 2 3 0 994 5 1454 624 1453 + 1223 2 3 0 995 5 666 625 447 + 1224 2 3 0 996 5 668 625 209 + 1225 2 3 0 997 5 685 204 672 + 1226 2 3 0 998 5 685 626 204 + 1227 2 3 0 999 5 677 627 425 + 1228 2 3 0 1000 5 627 205 204 + 1229 2 3 0 1001 5 1226 211 688 + 1230 2 3 0 1002 5 1226 1217 426 + 1231 2 3 0 1003 5 1455 1183 426 + 1232 2 3 0 1004 5 715 693 694 + 1233 2 3 0 1005 5 1429 10 716 + 1234 2 3 0 1006 5 1481 630 1429 + 1235 2 3 0 1007 5 1456 709 411 + 1236 2 3 0 1008 5 1457 1456 411 + 1237 2 3 0 1009 5 723 632 429 + 1238 2 3 0 1010 5 632 457 631 + 1239 2 3 0 1011 5 1458 1190 231 + 1240 2 3 0 1012 5 1459 1265 473 + 1241 2 3 0 1013 5 1460 1191 634 + 1242 2 3 0 1014 5 786 776 242 + 1243 2 3 0 1015 5 635 633 430 + 1244 2 3 0 1016 5 635 430 634 + 1245 2 3 0 1017 5 636 634 242 + 1246 2 3 0 1018 5 1441 737 1262 + 1247 2 3 0 1019 5 1254 431 1250 + 1248 2 3 0 1020 5 1496 1255 412 + 1249 2 3 0 1021 5 1261 793 638 + 1250 2 3 0 1022 5 1137 638 238 + 1251 2 3 0 1023 5 1431 169 170 + 1252 2 3 0 1024 5 1424 639 433 + 1253 2 3 0 1025 5 1424 640 167 + 1254 2 3 0 1026 5 640 251 164 + 1255 2 3 0 1027 5 1462 410 160 + 1256 2 3 0 1028 5 1462 644 641 + 1257 2 3 0 1029 5 1274 642 477 + 1258 2 3 0 1030 5 409 642 408 + 1259 2 3 0 1031 5 1272 1175 162 + 1260 2 3 0 1032 5 1502 1174 1175 + 1261 2 3 0 1033 5 644 477 641 + 1262 2 3 0 1034 5 1462 641 410 + 1263 2 3 0 1035 5 1269 749 1244 + 1264 2 3 0 1036 5 784 721 236 + 1265 2 3 0 1037 5 797 646 237 + 1266 2 3 0 1038 5 646 257 645 + 1267 2 3 0 1039 5 806 407 262 + 1268 2 3 0 1040 5 1128 805 262 + 1269 2 3 0 1041 5 648 153 406 + 1270 2 3 0 1042 5 1277 406 647 + 1271 2 3 0 1043 5 1503 405 1463 + 1272 2 3 0 1044 5 1465 1464 809 + 1273 2 3 0 1045 5 810 259 750 + 1274 2 3 0 1046 5 802 650 573 + 1275 2 3 0 1047 5 651 402 403 + 1276 2 3 0 1048 5 1466 651 403 + 1277 2 3 0 1049 5 1406 265 572 + 1278 2 3 0 1050 5 1467 1297 1298 + 1279 2 3 0 1051 5 931 117 118 + 1280 2 3 0 1052 5 1425 435 972 + 1281 2 3 0 1053 5 1599 436 1196 + 1282 2 3 0 1054 5 1199 654 326 + 1283 2 3 0 1055 5 655 105 106 + 1284 2 3 0 1056 5 1201 655 438 + 1285 2 3 0 1057 5 1468 1334 306 + 1286 2 3 0 1058 5 1207 656 321 + 1287 2 3 0 1059 5 1334 1332 1333 + 1288 2 3 0 1060 5 1333 1208 442 + 1289 2 3 0 1061 5 1537 946 947 + 1290 2 3 0 1062 5 1469 929 658 + 1291 2 3 0 1063 5 1471 1470 955 + 1292 2 3 0 1064 5 1471 659 1470 + 1293 2 3 0 1065 5 1472 945 660 + 1294 2 3 0 1066 5 950 660 443 + 1295 2 3 0 1067 5 829 661 272 + 1296 2 3 0 1068 5 1436 130 892 + 1297 2 3 0 1069 5 1211 662 444 + 1298 2 3 0 1070 5 1473 873 662 + 1299 2 3 0 1071 5 837 397 398 + 1300 2 3 0 1072 5 1113 663 269 + 1301 2 3 0 1073 5 1111 664 446 + 1302 2 3 0 1074 5 664 445 134 + 1303 2 3 0 1075 5 665 137 138 + 1304 2 3 0 1076 5 1107 138 393 + 1305 2 3 0 1077 5 1443 1186 666 + 1306 2 3 0 1078 5 666 447 6 + 1307 2 3 0 1079 5 1215 5 6 + 1308 2 3 0 1080 5 1474 667 1215 + 1309 2 3 0 1081 5 1182 209 690 + 1310 2 3 0 1082 5 668 424 624 + 1311 2 3 0 1083 5 1777 192 193 + 1312 2 3 0 1084 5 1475 671 202 + 1313 2 3 0 1085 5 191 192 669 + 1314 2 3 0 1086 5 191 669 670 + 1315 2 3 0 1087 5 1219 451 678 + 1316 2 3 0 1088 5 671 190 670 + 1317 2 3 0 1089 5 1476 700 695 + 1318 2 3 0 1090 5 672 213 181 + 1319 2 3 0 1091 5 673 183 184 + 1320 2 3 0 1092 5 673 184 185 + 1321 2 3 0 1093 5 1220 450 678 + 1322 2 3 0 1094 5 674 205 627 + 1323 2 3 0 1095 5 681 675 207 + 1324 2 3 0 1096 5 1453 675 1224 + 1325 2 3 0 1097 5 676 424 668 + 1326 2 3 0 1098 5 1183 210 629 + 1327 2 3 0 1099 5 1184 677 425 + 1328 2 3 0 1100 5 1428 186 187 + 1329 2 3 0 1101 5 1185 678 450 + 1330 2 3 0 1102 5 1219 678 203 + 1331 2 3 0 1103 5 1475 1222 679 + 1332 2 3 0 1104 5 1221 206 689 + 1333 2 3 0 1105 5 1181 449 623 + 1334 2 3 0 1106 5 1181 684 680 + 1335 2 3 0 1107 5 1224 452 1143 + 1336 2 3 0 1108 5 682 681 207 + 1337 2 3 0 1109 5 1455 1217 687 + 1338 2 3 0 1110 5 1181 682 449 + 1339 2 3 0 1111 5 1216 200 1170 + 1340 2 3 0 1112 5 1477 1474 208 + 1341 2 3 0 1113 5 684 452 680 + 1342 2 3 0 1114 5 1223 201 1172 + 1343 2 3 0 1115 5 685 672 182 + 1344 2 3 0 1116 5 685 183 673 + 1345 2 3 0 1117 5 1221 1218 206 + 1346 2 3 0 1118 5 686 449 682 + 1347 2 3 0 1119 5 687 682 207 + 1348 2 3 0 1120 5 1455 207 1183 + 1349 2 3 0 1121 5 1478 1227 713 + 1350 2 3 0 1122 5 1478 730 1227 + 1351 2 3 0 1123 5 1479 1225 689 + 1352 2 3 0 1124 5 1226 206 1217 + 1353 2 3 0 1125 5 718 220 225 + 1354 2 3 0 1126 5 1182 676 668 + 1355 2 3 0 1127 5 691 209 625 + 1356 2 3 0 1128 5 719 691 427 + 1357 2 3 0 1129 5 1476 212 698 + 1358 2 3 0 1130 5 1479 692 695 + 1359 2 3 0 1131 5 697 218 696 + 1360 2 3 0 1132 5 693 211 628 + 1361 2 3 0 1133 5 694 628 426 + 1362 2 3 0 1134 5 694 629 210 + 1363 2 3 0 1135 5 695 204 205 + 1364 2 3 0 1136 5 1479 695 205 + 1365 2 3 0 1137 5 696 218 226 + 1366 2 3 0 1138 5 728 226 712 + 1367 2 3 0 1139 5 1478 454 730 + 1368 2 3 0 1140 5 697 693 218 + 1369 2 3 0 1141 5 708 698 212 + 1370 2 3 0 1142 5 698 215 605 + 1371 2 3 0 1143 5 699 605 213 + 1372 2 3 0 1144 5 700 213 672 + 1373 2 3 0 1145 5 700 204 695 + 1374 2 3 0 1146 5 700 698 699 + 1375 2 3 0 1147 5 701 178 179 + 1376 2 3 0 1148 5 701 179 606 + 1377 2 3 0 1149 5 708 215 698 + 1378 2 3 0 1150 5 713 707 708 + 1379 2 3 0 1151 5 731 703 216 + 1380 2 3 0 1152 5 778 736 249 + 1381 2 3 0 1153 5 704 11 12 + 1382 2 3 0 1154 5 740 706 223 + 1383 2 3 0 1155 5 705 10 11 + 1384 2 3 0 1156 5 705 11 704 + 1385 2 3 0 1157 5 706 704 223 + 1386 2 3 0 1158 5 1481 717 1480 + 1387 2 3 0 1159 5 707 217 228 + 1388 2 3 0 1160 5 707 216 702 + 1389 2 3 0 1161 5 708 702 215 + 1390 2 3 0 1162 5 713 708 212 + 1391 2 3 0 1163 5 1457 411 1188 + 1392 2 3 0 1164 5 1456 455 709 + 1393 2 3 0 1165 5 728 712 455 + 1394 2 3 0 1166 5 1232 456 727 + 1395 2 3 0 1167 5 711 214 607 + 1396 2 3 0 1168 5 711 607 215 + 1397 2 3 0 1169 5 712 226 218 + 1398 2 3 0 1170 5 724 712 219 + 1399 2 3 0 1171 5 1227 707 713 + 1400 2 3 0 1172 5 713 212 692 + 1401 2 3 0 1173 5 714 692 453 + 1402 2 3 0 1174 5 714 688 211 + 1403 2 3 0 1175 5 726 715 210 + 1404 2 3 0 1176 5 715 219 218 + 1405 2 3 0 1177 5 716 10 705 + 1406 2 3 0 1178 5 716 705 704 + 1407 2 3 0 1179 5 717 706 221 + 1408 2 3 0 1180 5 1480 221 224 + 1409 2 3 0 1181 5 726 225 219 + 1410 2 3 0 1182 5 726 219 715 + 1411 2 3 0 1183 5 1481 1480 1145 + 1412 2 3 0 1184 5 1481 1429 717 + 1413 2 3 0 1185 5 762 19 20 + 1414 2 3 0 1186 5 744 720 255 + 1415 2 3 0 1187 5 1482 1253 467 + 1416 2 3 0 1188 5 1483 1253 431 + 1417 2 3 0 1189 5 739 15 16 + 1418 2 3 0 1190 5 1430 460 733 + 1419 2 3 0 1191 5 1266 1265 429 + 1420 2 3 0 1192 5 1458 230 1189 + 1421 2 3 0 1193 5 724 219 225 + 1422 2 3 0 1194 5 725 724 225 + 1423 2 3 0 1195 5 727 220 224 + 1424 2 3 0 1196 5 727 224 458 + 1425 2 3 0 1197 5 1182 210 676 + 1426 2 3 0 1198 5 726 690 718 + 1427 2 3 0 1199 5 1232 727 458 + 1428 2 3 0 1200 5 727 456 725 + 1429 2 3 0 1201 5 1187 428 729 + 1430 2 3 0 1202 5 728 454 696 + 1431 2 3 0 1203 5 1187 729 227 + 1432 2 3 0 1204 5 729 457 608 + 1433 2 3 0 1205 5 730 227 217 + 1434 2 3 0 1206 5 1227 217 707 + 1435 2 3 0 1207 5 731 229 246 + 1436 2 3 0 1208 5 780 736 731 + 1437 2 3 0 1209 5 732 228 608 + 1438 2 3 0 1210 5 732 229 731 + 1439 2 3 0 1211 5 1146 733 223 + 1440 2 3 0 1212 5 1430 13 14 + 1441 2 3 0 1213 5 1233 734 460 + 1442 2 3 0 1214 5 1231 740 741 + 1443 2 3 0 1215 5 735 243 249 + 1444 2 3 0 1216 5 735 248 244 + 1445 2 3 0 1217 5 779 249 243 + 1446 2 3 0 1218 5 736 459 731 + 1447 2 3 0 1219 5 737 244 248 + 1448 2 3 0 1220 5 737 248 250 + 1449 2 3 0 1221 5 738 245 633 + 1450 2 3 0 1222 5 1262 636 776 + 1451 2 3 0 1223 5 739 16 222 + 1452 2 3 0 1224 5 1233 739 240 + 1453 2 3 0 1225 5 740 458 706 + 1454 2 3 0 1226 5 740 223 733 + 1455 2 3 0 1227 5 741 733 460 + 1456 2 3 0 1228 5 1231 734 461 + 1457 2 3 0 1229 5 1191 242 634 + 1458 2 3 0 1230 5 1191 742 242 + 1459 2 3 0 1231 5 1238 417 610 + 1460 2 3 0 1232 5 786 743 472 + 1461 2 3 0 1233 5 793 768 255 + 1462 2 3 0 1234 5 1484 768 239 + 1463 2 3 0 1235 5 791 163 251 + 1464 2 3 0 1236 5 791 782 790 + 1465 2 3 0 1237 5 1489 1273 254 + 1466 2 3 0 1238 5 1272 746 476 + 1467 2 3 0 1239 5 782 747 253 + 1468 2 3 0 1240 5 747 252 611 + 1469 2 3 0 1241 5 1486 1485 1404 + 1470 2 3 0 1242 5 748 463 22 + 1471 2 3 0 1243 5 1487 797 1246 + 1472 2 3 0 1244 5 1487 1246 749 + 1473 2 3 0 1245 5 1488 799 464 + 1474 2 3 0 1246 5 800 752 259 + 1475 2 3 0 1247 5 751 749 464 + 1476 2 3 0 1248 5 751 464 750 + 1477 2 3 0 1249 5 752 750 259 + 1478 2 3 0 1250 5 1245 474 796 + 1479 2 3 0 1251 5 1489 788 753 + 1480 2 3 0 1252 5 1490 788 234 + 1481 2 3 0 1253 5 1268 801 235 + 1482 2 3 0 1254 5 803 754 418 + 1483 2 3 0 1255 5 1491 1490 234 + 1484 2 3 0 1256 5 787 254 253 + 1485 2 3 0 1257 5 1240 462 610 + 1486 2 3 0 1258 5 756 587 755 + 1487 2 3 0 1259 5 757 238 255 + 1488 2 3 0 1260 5 761 757 255 + 1489 2 3 0 1261 5 1246 256 795 + 1490 2 3 0 1262 5 1247 758 237 + 1491 2 3 0 1263 5 1250 759 466 + 1492 2 3 0 1264 5 1482 431 1253 + 1493 2 3 0 1265 5 760 467 234 + 1494 2 3 0 1266 5 1258 760 587 + 1495 2 3 0 1267 5 761 465 757 + 1496 2 3 0 1268 5 761 255 720 + 1497 2 3 0 1269 5 762 720 19 + 1498 2 3 0 1270 5 1147 20 21 + 1499 2 3 0 1271 5 763 761 720 + 1500 2 3 0 1272 5 763 720 762 + 1501 2 3 0 1273 5 1147 762 20 + 1502 2 3 0 1274 5 1246 792 256 + 1503 2 3 0 1275 5 1457 429 631 + 1504 2 3 0 1276 5 1457 1188 765 + 1505 2 3 0 1277 5 769 766 468 + 1506 2 3 0 1278 5 1266 766 473 + 1507 2 3 0 1279 5 767 222 17 + 1508 2 3 0 1280 5 767 17 744 + 1509 2 3 0 1281 5 768 744 255 + 1510 2 3 0 1282 5 1495 1484 239 + 1511 2 3 0 1283 5 1236 769 468 + 1512 2 3 0 1284 5 1492 1255 1251 + 1513 2 3 0 1285 5 1256 469 1248 + 1514 2 3 0 1286 5 770 766 769 + 1515 2 3 0 1287 5 1494 1493 1236 + 1516 2 3 0 1288 5 1235 734 1234 + 1517 2 3 0 1289 5 1495 772 470 + 1518 2 3 0 1290 5 1496 772 432 + 1519 2 3 0 1291 5 774 773 173 + 1520 2 3 0 1292 5 776 773 471 + 1521 2 3 0 1293 5 774 471 773 + 1522 2 3 0 1294 5 774 173 174 + 1523 2 3 0 1295 5 783 775 252 + 1524 2 3 0 1296 5 1193 783 433 + 1525 2 3 0 1297 5 776 241 773 + 1526 2 3 0 1298 5 1262 776 471 + 1527 2 3 0 1299 5 778 214 711 + 1528 2 3 0 1300 5 779 177 777 + 1529 2 3 0 1301 5 778 711 459 + 1530 2 3 0 1302 5 778 459 736 + 1531 2 3 0 1303 5 779 243 176 + 1532 2 3 0 1304 5 779 777 778 + 1533 2 3 0 1305 5 780 247 245 + 1534 2 3 0 1306 5 781 780 250 + 1535 2 3 0 1307 5 781 249 736 + 1536 2 3 0 1308 5 781 250 248 + 1537 2 3 0 1309 5 790 782 253 + 1538 2 3 0 1310 5 791 789 782 + 1539 2 3 0 1311 5 1193 433 639 + 1540 2 3 0 1312 5 783 252 782 + 1541 2 3 0 1313 5 1498 236 1267 + 1542 2 3 0 1314 5 1491 235 1490 + 1543 2 3 0 1315 5 1263 785 171 + 1544 2 3 0 1316 5 1497 1431 785 + 1545 2 3 0 1317 5 786 241 776 + 1546 2 3 0 1318 5 1497 786 472 + 1547 2 3 0 1319 5 787 253 747 + 1548 2 3 0 1320 5 787 747 462 + 1549 2 3 0 1321 5 788 755 234 + 1550 2 3 0 1322 5 1489 753 1273 + 1551 2 3 0 1323 5 789 433 782 + 1552 2 3 0 1324 5 789 251 640 + 1553 2 3 0 1325 5 790 253 254 + 1554 2 3 0 1326 5 790 254 745 + 1555 2 3 0 1327 5 791 745 163 + 1556 2 3 0 1328 5 791 251 789 + 1557 2 3 0 1329 5 792 465 761 + 1558 2 3 0 1330 5 792 761 763 + 1559 2 3 0 1331 5 793 239 768 + 1560 2 3 0 1332 5 793 255 238 + 1561 2 3 0 1333 5 1241 463 748 + 1562 2 3 0 1334 5 1488 258 799 + 1563 2 3 0 1335 5 795 464 749 + 1564 2 3 0 1336 5 1243 795 256 + 1565 2 3 0 1337 5 1268 474 801 + 1566 2 3 0 1338 5 1498 1268 235 + 1567 2 3 0 1339 5 797 257 646 + 1568 2 3 0 1340 5 798 237 758 + 1569 2 3 0 1341 5 798 758 465 + 1570 2 3 0 1342 5 1246 465 792 + 1571 2 3 0 1343 5 1407 1126 571 + 1572 2 3 0 1344 5 810 750 799 + 1573 2 3 0 1345 5 804 259 264 + 1574 2 3 0 1346 5 1499 1464 260 + 1575 2 3 0 1347 5 1500 1499 1177 + 1576 2 3 0 1348 5 1448 1177 260 + 1577 2 3 0 1349 5 1124 802 573 + 1578 2 3 0 1350 5 802 404 649 + 1579 2 3 0 1351 5 807 803 418 + 1580 2 3 0 1352 5 1273 753 803 + 1581 2 3 0 1353 5 809 264 802 + 1582 2 3 0 1354 5 1500 804 1464 + 1583 2 3 0 1355 5 1501 1277 805 + 1584 2 3 0 1356 5 1277 647 805 + 1585 2 3 0 1357 5 806 647 407 + 1586 2 3 0 1358 5 806 262 805 + 1587 2 3 0 1359 5 1448 808 418 + 1588 2 3 0 1360 5 1502 807 808 + 1589 2 3 0 1361 5 1502 612 613 + 1590 2 3 0 1362 5 1502 808 612 + 1591 2 3 0 1363 5 1503 1465 649 + 1592 2 3 0 1364 5 1504 1464 1465 + 1593 2 3 0 1365 5 810 650 264 + 1594 2 3 0 1366 5 810 264 259 + 1595 2 3 0 1367 5 811 799 258 + 1596 2 3 0 1368 5 1404 1126 258 + 1597 2 3 0 1369 5 817 31 32 + 1598 2 3 0 1370 5 1149 652 1121 + 1599 2 3 0 1371 5 813 614 402 + 1600 2 3 0 1372 5 813 651 265 + 1601 2 3 0 1373 5 814 652 266 + 1602 2 3 0 1374 5 1299 266 812 + 1603 2 3 0 1375 5 815 35 36 + 1604 2 3 0 1376 5 1434 36 37 + 1605 2 3 0 1377 5 852 816 279 + 1606 2 3 0 1378 5 1299 812 816 + 1607 2 3 0 1379 5 817 812 31 + 1608 2 3 0 1380 5 1150 817 32 + 1609 2 3 0 1381 5 818 401 614 + 1610 2 3 0 1382 5 1505 1119 267 + 1611 2 3 0 1383 5 819 399 400 + 1612 2 3 0 1384 5 819 400 818 + 1613 2 3 0 1385 5 1118 820 479 + 1614 2 3 0 1386 5 1291 820 278 + 1615 2 3 0 1387 5 1506 1301 282 + 1616 2 3 0 1388 5 842 821 277 + 1617 2 3 0 1389 5 1507 822 480 + 1618 2 3 0 1390 5 822 280 618 + 1619 2 3 0 1391 5 862 274 841 + 1620 2 3 0 1392 5 1508 823 285 + 1621 2 3 0 1393 5 1509 868 494 + 1622 2 3 0 1394 5 869 824 481 + 1623 2 3 0 1395 5 1517 844 269 + 1624 2 3 0 1396 5 1510 843 275 + 1625 2 3 0 1397 5 1283 482 840 + 1626 2 3 0 1398 5 1511 1284 827 + 1627 2 3 0 1399 5 1511 396 1113 + 1628 2 3 0 1400 5 1401 570 1108 + 1629 2 3 0 1401 5 828 133 445 + 1630 2 3 0 1402 5 1513 1213 828 + 1631 2 3 0 1403 5 1436 129 130 + 1632 2 3 0 1404 5 1524 1433 272 + 1633 2 3 0 1405 5 1304 291 913 + 1634 2 3 0 1406 5 1304 1285 483 + 1635 2 3 0 1407 5 1514 1286 483 + 1636 2 3 0 1408 5 1287 889 484 + 1637 2 3 0 1409 5 956 47 48 + 1638 2 3 0 1410 5 1154 832 314 + 1639 2 3 0 1411 5 885 861 883 + 1640 2 3 0 1412 5 885 831 833 + 1641 2 3 0 1413 5 867 834 481 + 1642 2 3 0 1414 5 1212 834 867 + 1643 2 3 0 1415 5 1421 1289 835 + 1644 2 3 0 1416 5 1515 835 590 + 1645 2 3 0 1417 5 1516 1278 1117 + 1646 2 3 0 1418 5 1517 1116 844 + 1647 2 3 0 1419 5 837 663 397 + 1648 2 3 0 1420 5 837 398 836 + 1649 2 3 0 1421 5 1117 838 276 + 1650 2 3 0 1422 5 838 277 486 + 1651 2 3 0 1423 5 1292 896 486 + 1652 2 3 0 1424 5 857 854 855 + 1653 2 3 0 1425 5 1510 840 482 + 1654 2 3 0 1426 5 1518 855 840 + 1655 2 3 0 1427 5 863 862 491 + 1656 2 3 0 1428 5 841 274 840 + 1657 2 3 0 1429 5 1117 277 838 + 1658 2 3 0 1430 5 842 479 820 + 1659 2 3 0 1431 5 843 276 275 + 1660 2 3 0 1432 5 1518 1510 275 + 1661 2 3 0 1433 5 844 825 269 + 1662 2 3 0 1434 5 1517 269 663 + 1663 2 3 0 1435 5 858 845 281 + 1664 2 3 0 1436 5 1506 1292 487 + 1665 2 3 0 1437 5 399 846 398 + 1666 2 3 0 1438 5 846 399 819 + 1667 2 3 0 1439 5 1519 1507 480 + 1668 2 3 0 1440 5 1520 1293 847 + 1669 2 3 0 1441 5 1291 850 848 + 1670 2 3 0 1442 5 1295 848 489 + 1671 2 3 0 1443 5 1168 903 849 + 1672 2 3 0 1444 5 1434 1156 822 + 1673 2 3 0 1445 5 851 850 278 + 1674 2 3 0 1446 5 850 489 848 + 1675 2 3 0 1447 5 1118 278 820 + 1676 2 3 0 1448 5 1605 1118 1505 + 1677 2 3 0 1449 5 1299 490 1298 + 1678 2 3 0 1450 5 1294 1120 279 + 1679 2 3 0 1451 5 853 39 40 + 1680 2 3 0 1452 5 907 41 906 + 1681 2 3 0 1453 5 1303 864 283 + 1682 2 3 0 1454 5 1514 864 284 + 1683 2 3 0 1455 5 855 491 840 + 1684 2 3 0 1456 5 856 855 275 + 1685 2 3 0 1457 5 856 275 276 + 1686 2 3 0 1458 5 856 838 839 + 1687 2 3 0 1459 5 857 839 283 + 1688 2 3 0 1460 5 857 283 854 + 1689 2 3 0 1461 5 1521 281 1282 + 1690 2 3 0 1462 5 1521 858 281 + 1691 2 3 0 1463 5 866 294 865 + 1692 2 3 0 1464 5 1506 282 1292 + 1693 2 3 0 1465 5 1300 860 493 + 1694 2 3 0 1466 5 1522 1315 499 + 1695 2 3 0 1467 5 890 883 499 + 1696 2 3 0 1468 5 861 293 860 + 1697 2 3 0 1469 5 862 285 823 + 1698 2 3 0 1470 5 862 823 274 + 1699 2 3 0 1471 5 863 285 862 + 1700 2 3 0 1472 5 863 491 854 + 1701 2 3 0 1473 5 864 854 283 + 1702 2 3 0 1474 5 1514 1285 864 + 1703 2 3 0 1475 5 895 865 493 + 1704 2 3 0 1476 5 1290 859 865 + 1705 2 3 0 1477 5 866 859 492 + 1706 2 3 0 1478 5 1320 492 899 + 1707 2 3 0 1479 5 1212 867 273 + 1708 2 3 0 1480 5 867 481 824 + 1709 2 3 0 1481 5 868 824 494 + 1710 2 3 0 1482 5 1305 286 872 + 1711 2 3 0 1483 5 1515 869 481 + 1712 2 3 0 1484 5 869 274 823 + 1713 2 3 0 1485 5 1153 127 128 + 1714 2 3 0 1486 5 1523 870 1153 + 1715 2 3 0 1487 5 1524 1153 1433 + 1716 2 3 0 1488 5 1524 873 496 + 1717 2 3 0 1489 5 1473 1305 872 + 1718 2 3 0 1490 5 882 286 874 + 1719 2 3 0 1491 5 1524 496 871 + 1720 2 3 0 1492 5 873 272 661 + 1721 2 3 0 1493 5 1526 1525 886 + 1722 2 3 0 1494 5 1526 497 1525 + 1723 2 3 0 1495 5 1323 1309 875 + 1724 2 3 0 1496 5 882 287 871 + 1725 2 3 0 1497 5 1527 876 311 + 1726 2 3 0 1498 5 1528 951 876 + 1727 2 3 0 1499 5 959 877 498 + 1728 2 3 0 1500 5 1529 1339 890 + 1729 2 3 0 1501 5 881 125 126 + 1730 2 3 0 1502 5 1435 288 932 + 1731 2 3 0 1503 5 1210 292 1209 + 1732 2 3 0 1504 5 1209 292 616 + 1733 2 3 0 1505 5 946 443 660 + 1734 2 3 0 1506 5 919 880 302 + 1735 2 3 0 1507 5 1523 1306 495 + 1736 2 3 0 1508 5 881 288 878 + 1737 2 3 0 1509 5 882 871 872 + 1738 2 3 0 1510 5 882 872 286 + 1739 2 3 0 1511 5 884 883 300 + 1740 2 3 0 1512 5 885 883 884 + 1741 2 3 0 1513 5 952 300 891 + 1742 2 3 0 1514 5 1546 884 942 + 1743 2 3 0 1515 5 885 484 831 + 1744 2 3 0 1516 5 885 833 293 + 1745 2 3 0 1517 5 1526 1307 497 + 1746 2 3 0 1518 5 1525 1509 886 + 1747 2 3 0 1519 5 1508 914 494 + 1748 2 3 0 1520 5 913 888 887 + 1749 2 3 0 1521 5 1210 888 292 + 1750 2 3 0 1522 5 1526 888 290 + 1751 2 3 0 1523 5 889 615 291 + 1752 2 3 0 1524 5 889 291 830 + 1753 2 3 0 1525 5 1529 499 1315 + 1754 2 3 0 1526 5 1529 1311 1339 + 1755 2 3 0 1527 5 1310 515 310 + 1756 2 3 0 1528 5 891 300 890 + 1757 2 3 0 1529 5 1213 132 828 + 1758 2 3 0 1530 5 1436 444 661 + 1759 2 3 0 1531 5 1530 906 1132 + 1760 2 3 0 1532 5 1531 1530 1132 + 1761 2 3 0 1533 5 1532 1316 912 + 1762 2 3 0 1534 5 894 503 893 + 1763 2 3 0 1535 5 1302 895 493 + 1764 2 3 0 1536 5 895 283 839 + 1765 2 3 0 1537 5 896 839 486 + 1766 2 3 0 1538 5 1290 282 859 + 1767 2 3 0 1539 5 908 897 296 + 1768 2 3 0 1540 5 1533 897 908 + 1769 2 3 0 1541 5 1321 1319 898 + 1770 2 3 0 1542 5 902 898 295 + 1771 2 3 0 1543 5 1521 899 492 + 1772 2 3 0 1544 5 1521 911 899 + 1773 2 3 0 1545 5 1535 1534 910 + 1774 2 3 0 1546 5 1320 900 1314 + 1775 2 3 0 1547 5 1154 45 46 + 1776 2 3 0 1548 5 1531 500 893 + 1777 2 3 0 1549 5 1521 1282 295 + 1778 2 3 0 1550 5 1520 281 1293 + 1779 2 3 0 1551 5 1156 903 480 + 1780 2 3 0 1552 5 1280 903 296 + 1781 2 3 0 1553 5 1533 904 501 + 1782 2 3 0 1554 5 904 297 503 + 1783 2 3 0 1555 5 1536 922 905 + 1784 2 3 0 1556 5 1321 905 298 + 1785 2 3 0 1557 5 1132 41 42 + 1786 2 3 0 1558 5 1533 908 297 + 1787 2 3 0 1559 5 907 853 40 + 1788 2 3 0 1560 5 907 40 41 + 1789 2 3 0 1561 5 908 906 297 + 1790 2 3 0 1562 5 1168 296 903 + 1791 2 3 0 1563 5 1529 1315 299 + 1792 2 3 0 1564 5 1522 860 1300 + 1793 2 3 0 1565 5 957 298 922 + 1794 2 3 0 1566 5 1551 909 1534 + 1795 2 3 0 1567 5 911 502 899 + 1796 2 3 0 1568 5 1319 295 898 + 1797 2 3 0 1569 5 1317 912 313 + 1798 2 3 0 1570 5 1536 915 912 + 1799 2 3 0 1571 5 913 291 292 + 1800 2 3 0 1572 5 913 292 888 + 1801 2 3 0 1573 5 914 887 494 + 1802 2 3 0 1574 5 1304 285 1285 + 1803 2 3 0 1575 5 915 503 894 + 1804 2 3 0 1576 5 915 894 912 + 1805 2 3 0 1577 5 1179 289 920 + 1806 2 3 0 1578 5 916 288 881 + 1807 2 3 0 1579 5 1537 1208 917 + 1808 2 3 0 1580 5 1537 917 302 + 1809 2 3 0 1581 5 1323 1308 289 + 1810 2 3 0 1582 5 1210 918 290 + 1811 2 3 0 1583 5 919 879 880 + 1812 2 3 0 1584 5 919 917 918 + 1813 2 3 0 1585 5 1179 920 420 + 1814 2 3 0 1586 5 1308 920 289 + 1815 2 3 0 1587 5 921 505 917 + 1816 2 3 0 1588 5 1180 921 303 + 1817 2 3 0 1589 5 957 922 506 + 1818 2 3 0 1590 5 922 298 905 + 1819 2 3 0 1591 5 1538 1365 923 + 1820 2 3 0 1592 5 923 507 50 + 1821 2 3 0 1593 5 1338 317 939 + 1822 2 3 0 1594 5 1539 1338 354 + 1823 2 3 0 1595 5 1066 536 1015 + 1824 2 3 0 1596 5 1540 1060 318 + 1825 2 3 0 1597 5 1539 926 924 + 1826 2 3 0 1598 5 927 508 925 + 1827 2 3 0 1599 5 927 925 355 + 1828 2 3 0 1600 5 1540 937 927 + 1829 2 3 0 1601 5 1541 1206 320 + 1830 2 3 0 1602 5 1205 321 656 + 1831 2 3 0 1603 5 929 306 657 + 1832 2 3 0 1604 5 929 657 658 + 1833 2 3 0 1605 5 1331 121 122 + 1834 2 3 0 1606 5 1438 1194 1329 + 1835 2 3 0 1607 5 1542 976 931 + 1836 2 3 0 1608 5 931 435 653 + 1837 2 3 0 1609 5 1435 123 124 + 1838 2 3 0 1610 5 932 288 619 + 1839 2 3 0 1611 5 933 619 620 + 1840 2 3 0 1612 5 933 620 304 + 1841 2 3 0 1613 5 1543 1054 1363 + 1842 2 3 0 1614 5 1544 1543 1363 + 1843 2 3 0 1615 5 1368 1018 1330 + 1844 2 3 0 1616 5 940 935 354 + 1845 2 3 0 1617 5 1204 1160 512 + 1846 2 3 0 1618 5 1542 1159 305 + 1847 2 3 0 1619 5 965 959 960 + 1848 2 3 0 1620 5 1528 924 937 + 1849 2 3 0 1621 5 1333 303 1208 + 1850 2 3 0 1622 5 1334 1333 306 + 1851 2 3 0 1623 5 1527 962 317 + 1852 2 3 0 1624 5 1548 1545 944 + 1853 2 3 0 1625 5 958 940 513 + 1854 2 3 0 1626 5 1539 354 1328 + 1855 2 3 0 1627 5 955 309 308 + 1856 2 3 0 1628 5 1546 943 301 + 1857 2 3 0 1629 5 942 884 300 + 1858 2 3 0 1630 5 952 942 300 + 1859 2 3 0 1631 5 1547 955 941 + 1860 2 3 0 1632 5 1546 301 1287 + 1861 2 3 0 1633 5 1548 1318 316 + 1862 2 3 0 1634 5 1545 316 1336 + 1863 2 3 0 1635 5 1472 660 514 + 1864 2 3 0 1636 5 1537 947 442 + 1865 2 3 0 1637 5 946 880 443 + 1866 2 3 0 1638 5 946 660 945 + 1867 2 3 0 1639 5 947 945 307 + 1868 2 3 0 1640 5 947 658 442 + 1869 2 3 0 1641 5 954 948 313 + 1870 2 3 0 1642 5 1058 948 315 + 1871 2 3 0 1643 5 1341 1337 1340 + 1872 2 3 0 1644 5 953 949 316 + 1873 2 3 0 1645 5 950 443 617 + 1874 2 3 0 1646 5 1470 950 301 + 1875 2 3 0 1647 5 951 498 876 + 1876 2 3 0 1648 5 1528 876 1527 + 1877 2 3 0 1649 5 952 891 515 + 1878 2 3 0 1650 5 1310 952 515 + 1879 2 3 0 1651 5 1548 316 1545 + 1880 2 3 0 1652 5 1322 1317 1318 + 1881 2 3 0 1653 5 954 315 948 + 1882 2 3 0 1654 5 1316 313 912 + 1883 2 3 0 1655 5 1471 955 308 + 1884 2 3 0 1656 5 1470 659 950 + 1885 2 3 0 1657 5 1158 956 516 + 1886 2 3 0 1658 5 956 315 314 + 1887 2 3 0 1659 5 1617 1325 1550 + 1888 2 3 0 1660 5 1552 1551 1535 + 1889 2 3 0 1661 5 1341 513 1336 + 1890 2 3 0 1662 5 958 352 934 + 1891 2 3 0 1663 5 959 310 877 + 1892 2 3 0 1664 5 959 498 951 + 1893 2 3 0 1665 5 961 951 937 + 1894 2 3 0 1666 5 1553 1385 319 + 1895 2 3 0 1667 5 961 937 318 + 1896 2 3 0 1668 5 961 318 960 + 1897 2 3 0 1669 5 1325 962 311 + 1898 2 3 0 1670 5 962 312 944 + 1899 2 3 0 1671 5 1327 49 50 + 1900 2 3 0 1672 5 1554 963 1327 + 1901 2 3 0 1673 5 1310 964 309 + 1902 2 3 0 1674 5 964 310 959 + 1903 2 3 0 1675 5 965 960 318 + 1904 2 3 0 1676 5 1553 1060 1385 + 1905 2 3 0 1677 5 1064 1056 319 + 1906 2 3 0 1678 5 1555 966 1056 + 1907 2 3 0 1679 5 1206 1059 320 + 1908 2 3 0 1680 5 1472 967 307 + 1909 2 3 0 1681 5 1471 968 514 + 1910 2 3 0 1682 5 1556 1343 518 + 1911 2 3 0 1683 5 1472 969 967 + 1912 2 3 0 1684 5 969 514 968 + 1913 2 3 0 1685 5 1557 1097 356 + 1914 2 3 0 1686 5 1558 1013 332 + 1915 2 3 0 1687 5 1559 1384 1009 + 1916 2 3 0 1688 5 971 552 970 + 1917 2 3 0 1689 5 1560 972 435 + 1918 2 3 0 1690 5 1561 1560 322 + 1919 2 3 0 1691 5 973 519 584 + 1920 2 3 0 1692 5 1345 115 116 + 1921 2 3 0 1693 5 1562 1560 976 + 1922 2 3 0 1694 5 1562 1204 974 + 1923 2 3 0 1695 5 1564 1563 1346 + 1924 2 3 0 1696 5 975 320 967 + 1925 2 3 0 1697 5 1562 305 1204 + 1926 2 3 0 1698 5 1562 976 305 + 1927 2 3 0 1699 5 1563 320 975 + 1928 2 3 0 1700 5 977 357 359 + 1929 2 3 0 1701 5 978 359 554 + 1930 2 3 0 1702 5 1387 321 1062 + 1931 2 3 0 1703 5 1021 979 368 + 1932 2 3 0 1704 5 1022 979 1021 + 1933 2 3 0 1705 5 1422 1348 980 + 1934 2 3 0 1706 5 1399 980 563 + 1935 2 3 0 1707 5 981 340 373 + 1936 2 3 0 1708 5 1660 539 569 + 1937 2 3 0 1709 5 1373 363 1083 + 1938 2 3 0 1710 5 1565 1442 328 + 1939 2 3 0 1711 5 1162 995 996 + 1940 2 3 0 1712 5 1001 984 985 + 1941 2 3 0 1713 5 1392 986 984 + 1942 2 3 0 1714 5 985 983 522 + 1943 2 3 0 1715 5 1001 985 522 + 1944 2 3 0 1716 5 1392 984 1360 + 1945 2 3 0 1717 5 1418 557 1076 + 1946 2 3 0 1718 5 1391 993 1390 + 1947 2 3 0 1719 5 1567 1566 1389 + 1948 2 3 0 1720 5 1568 988 523 + 1949 2 3 0 1721 5 1362 532 1075 + 1950 2 3 0 1722 5 993 989 325 + 1951 2 3 0 1723 5 1417 437 991 + 1952 2 3 0 1724 5 1355 525 992 + 1953 2 3 0 1725 5 1418 1076 589 + 1954 2 3 0 1726 5 991 437 654 + 1955 2 3 0 1727 5 1199 991 654 + 1956 2 3 0 1728 5 1356 588 1198 + 1957 2 3 0 1729 5 1417 992 525 + 1958 2 3 0 1730 5 1390 993 325 + 1959 2 3 0 1731 5 1391 1196 993 + 1960 2 3 0 1732 5 1445 102 1410 + 1961 2 3 0 1733 5 994 526 100 + 1962 2 3 0 1734 5 1414 113 114 + 1963 2 3 0 1735 5 1569 995 1414 + 1964 2 3 0 1736 5 996 522 983 + 1965 2 3 0 1737 5 1565 1202 1442 + 1966 2 3 0 1738 5 1570 997 1166 + 1967 2 3 0 1739 5 1571 997 1570 + 1968 2 3 0 1740 5 1408 1199 326 + 1969 2 3 0 1741 5 1165 998 575 + 1970 2 3 0 1742 5 1561 519 972 + 1971 2 3 0 1743 5 1561 1195 999 + 1972 2 3 0 1744 5 1358 1000 530 + 1973 2 3 0 1745 5 1344 1000 329 + 1974 2 3 0 1746 5 1569 1001 522 + 1975 2 3 0 1747 5 1569 1349 1001 + 1976 2 3 0 1748 5 1002 341 597 + 1977 2 3 0 1749 5 1002 374 532 + 1978 2 3 0 1750 5 1003 359 357 + 1979 2 3 0 1751 5 1384 357 1008 + 1980 2 3 0 1752 5 1572 533 1364 + 1981 2 3 0 1753 5 1572 1365 534 + 1982 2 3 0 1754 5 1164 1005 534 + 1983 2 3 0 1755 5 1057 1046 1047 + 1984 2 3 0 1756 5 1030 1006 330 + 1985 2 3 0 1757 5 1029 1006 360 + 1986 2 3 0 1758 5 1375 540 1359 + 1987 2 3 0 1759 5 1023 1007 358 + 1988 2 3 0 1760 5 1346 1008 357 + 1989 2 3 0 1761 5 1008 552 971 + 1990 2 3 0 1762 5 1009 971 332 + 1991 2 3 0 1763 5 1559 332 381 + 1992 2 3 0 1764 5 1010 380 379 + 1993 2 3 0 1765 5 1023 1012 330 + 1994 2 3 0 1766 5 1067 1011 358 + 1995 2 3 0 1767 5 1011 1003 1010 + 1996 2 3 0 1768 5 1012 1010 379 + 1997 2 3 0 1769 5 1012 379 330 + 1998 2 3 0 1770 5 1558 332 971 + 1999 2 3 0 1771 5 1574 1573 1558 + 2000 2 3 0 1772 5 1014 388 337 + 2001 2 3 0 1773 5 1575 1026 1014 + 2002 2 3 0 1774 5 1100 1015 536 + 2003 2 3 0 1775 5 1100 537 1015 + 2004 2 3 0 1776 5 1073 1016 537 + 2005 2 3 0 1777 5 1066 925 508 + 2006 2 3 0 1778 5 1328 536 1066 + 2007 2 3 0 1779 5 1017 354 935 + 2008 2 3 0 1780 5 1018 935 510 + 2009 2 3 0 1781 5 1330 1018 510 + 2010 2 3 0 1782 5 1034 1019 342 + 2011 2 3 0 1783 5 1034 335 1019 + 2012 2 3 0 1784 5 1369 335 1099 + 2013 2 3 0 1785 5 1068 538 1033 + 2014 2 3 0 1786 5 1576 1102 1021 + 2015 2 3 0 1787 5 1103 1102 337 + 2016 2 3 0 1788 5 1086 336 386 + 2017 2 3 0 1789 5 1022 521 979 + 2018 2 3 0 1790 5 1023 330 1006 + 2019 2 3 0 1791 5 1023 358 1011 + 2020 2 3 0 1792 5 1024 376 375 + 2021 2 3 0 1793 5 1024 375 597 + 2022 2 3 0 1794 5 1568 1025 341 + 2023 2 3 0 1795 5 1025 377 1024 + 2024 2 3 0 1796 5 1367 1026 535 + 2025 2 3 0 1797 5 1026 595 1014 + 2026 2 3 0 1798 5 1027 539 981 + 2027 2 3 0 1799 5 1392 1360 324 + 2028 2 3 0 1800 5 1577 1359 1360 + 2029 2 3 0 1801 5 1029 540 1006 + 2030 2 3 0 1802 5 1376 1029 360 + 2031 2 3 0 1803 5 1031 330 378 + 2032 2 3 0 1804 5 1031 378 377 + 2033 2 3 0 1805 5 1352 377 1025 + 2034 2 3 0 1806 5 1567 1352 523 + 2035 2 3 0 1807 5 1382 351 550 + 2036 2 3 0 1808 5 1382 1032 351 + 2037 2 3 0 1809 5 1578 1068 1033 + 2038 2 3 0 1810 5 1368 1330 538 + 2039 2 3 0 1811 5 1034 386 335 + 2040 2 3 0 1812 5 1086 1034 342 + 2041 2 3 0 1813 5 1088 1035 349 + 2042 2 3 0 1814 5 1578 1035 342 + 2043 2 3 0 1815 5 1036 541 1032 + 2044 2 3 0 1816 5 1036 343 1035 + 2045 2 3 0 1817 5 1580 1579 1092 + 2046 2 3 0 1818 5 1581 1037 1579 + 2047 2 3 0 1819 5 1380 55 56 + 2048 2 3 0 1820 5 1038 542 54 + 2049 2 3 0 1821 5 1416 344 586 + 2050 2 3 0 1822 5 1440 1039 1416 + 2051 2 3 0 1823 5 1379 542 1377 + 2052 2 3 0 1824 5 1396 1040 562 + 2053 2 3 0 1825 5 1090 349 1035 + 2054 2 3 0 1826 5 1582 1091 562 + 2055 2 3 0 1827 5 1583 1383 1042 + 2056 2 3 0 1828 5 1042 592 1041 + 2057 2 3 0 1829 5 1584 1400 338 + 2058 2 3 0 1830 5 1585 1584 338 + 2059 2 3 0 1831 5 1575 1092 1044 + 2060 2 3 0 1832 5 1366 367 1052 + 2061 2 3 0 1833 5 1585 1045 1043 + 2062 2 3 0 1834 5 1045 535 1044 + 2063 2 3 0 1835 5 1055 1046 550 + 2064 2 3 0 1836 5 1046 533 1004 + 2065 2 3 0 1837 5 1047 1004 534 + 2066 2 3 0 1838 5 1057 1005 344 + 2067 2 3 0 1839 5 1668 1093 1094 + 2068 2 3 0 1840 5 1586 1094 350 + 2069 2 3 0 1841 5 1583 1381 1049 + 2070 2 3 0 1842 5 1693 1587 1138 + 2071 2 3 0 1843 5 1586 1050 1048 + 2072 2 3 0 1844 5 1050 551 1049 + 2073 2 3 0 1845 5 1051 1049 345 + 2074 2 3 0 1846 5 1178 1051 543 + 2075 2 3 0 1847 5 1730 1712 348 + 2076 2 3 0 1848 5 1366 1052 348 + 2077 2 3 0 1849 5 1588 520 1065 + 2078 2 3 0 1850 5 1588 1053 520 + 2079 2 3 0 1851 5 1341 1340 352 + 2080 2 3 0 1852 5 1589 1364 1054 + 2081 2 3 0 1853 5 1055 533 1046 + 2082 2 3 0 1854 5 1363 1055 351 + 2083 2 3 0 1855 5 1056 518 308 + 2084 2 3 0 1856 5 1555 1056 308 + 2085 2 3 0 1857 5 1396 344 1039 + 2086 2 3 0 1858 5 1590 1057 1091 + 2087 2 3 0 1859 5 1158 315 956 + 2088 2 3 0 1860 5 1554 1157 1158 + 2089 2 3 0 1861 5 1469 1059 928 + 2090 2 3 0 1862 5 1059 307 967 + 2091 2 3 0 1863 5 1540 318 937 + 2092 2 3 0 1864 5 1540 1074 1060 + 2093 2 3 0 1865 5 1557 1061 553 + 2094 2 3 0 1866 5 1385 1061 319 + 2095 2 3 0 1867 5 1206 321 1205 + 2096 2 3 0 1868 5 1541 977 1062 + 2097 2 3 0 1869 5 1588 1065 356 + 2098 2 3 0 1870 5 1063 319 1061 + 2099 2 3 0 1871 5 1064 518 1056 + 2100 2 3 0 1872 5 1064 319 1063 + 2101 2 3 0 1873 5 1065 1063 356 + 2102 2 3 0 1874 5 1342 520 975 + 2103 2 3 0 1875 5 1328 1066 508 + 2104 2 3 0 1876 5 1066 1015 1016 + 2105 2 3 0 1877 5 1067 359 1003 + 2106 2 3 0 1878 5 1591 1069 554 + 2107 2 3 0 1879 5 1068 1019 1020 + 2108 2 3 0 1880 5 1068 1020 538 + 2109 2 3 0 1881 5 1591 554 1067 + 2110 2 3 0 1882 5 1591 1386 1069 + 2111 2 3 0 1883 5 1592 1388 323 + 2112 2 3 0 1884 5 1207 441 656 + 2113 2 3 0 1885 5 1071 322 974 + 2114 2 3 0 1886 5 1071 441 1070 + 2115 2 3 0 1887 5 1072 1070 555 + 2116 2 3 0 1888 5 1388 555 1375 + 2117 2 3 0 1889 5 1594 1593 1371 + 2118 2 3 0 1890 5 1596 1595 1594 + 2119 2 3 0 1891 5 1074 553 1060 + 2120 2 3 0 1892 5 1074 355 1073 + 2121 2 3 0 1893 5 1362 1075 340 + 2122 2 3 0 1894 5 1075 532 596 + 2123 2 3 0 1895 5 1419 1082 556 + 2124 2 3 0 1896 5 1081 990 1076 + 2125 2 3 0 1897 5 1598 1597 1389 + 2126 2 3 0 1898 5 1566 523 987 + 2127 2 3 0 1899 5 1599 1197 436 + 2128 2 3 0 1900 5 1080 987 1079 + 2129 2 3 0 1901 5 1079 988 532 + 2130 2 3 0 1902 5 1362 1079 532 + 2131 2 3 0 1903 5 1600 1599 1080 + 2132 2 3 0 1904 5 1080 361 987 + 2133 2 3 0 1905 5 1081 325 989 + 2134 2 3 0 1906 5 1081 989 990 + 2135 2 3 0 1907 5 1082 1076 557 + 2136 2 3 0 1908 5 1392 1082 557 + 2137 2 3 0 1909 5 1600 1374 362 + 2138 2 3 0 1910 5 1373 340 981 + 2139 2 3 0 1911 5 1689 363 1660 + 2140 2 3 0 1912 5 1601 1395 1083 + 2141 2 3 0 1913 5 1106 391 390 + 2142 2 3 0 1914 5 1105 390 338 + 2143 2 3 0 1915 5 1088 342 1035 + 2144 2 3 0 1916 5 1422 1087 349 + 2145 2 3 0 1917 5 1087 521 1022 + 2146 2 3 0 1918 5 1087 1022 1086 + 2147 2 3 0 1919 5 1088 1086 342 + 2148 2 3 0 1920 5 1088 349 1087 + 2149 2 3 0 1921 5 1378 1089 562 + 2150 2 3 0 1922 5 1089 549 1042 + 2151 2 3 0 1923 5 1090 1041 349 + 2152 2 3 0 1924 5 1602 1590 1091 + 2153 2 3 0 1925 5 1582 562 1089 + 2154 2 3 0 1926 5 1602 1091 1582 + 2155 2 3 0 1927 5 1580 337 1102 + 2156 2 3 0 1928 5 1581 1580 1576 + 2157 2 3 0 1929 5 1711 1093 564 + 2158 2 3 0 1930 5 1586 350 1383 + 2159 2 3 0 1931 5 1094 1048 413 + 2160 2 3 0 1932 5 1668 1094 413 + 2161 2 3 0 1933 5 1659 1095 339 + 2162 2 3 0 1934 5 1731 1716 1717 + 2163 2 3 0 1935 5 1439 1096 383 + 2164 2 3 0 1936 5 1594 537 1593 + 2165 2 3 0 1937 5 1595 553 1073 + 2166 2 3 0 1938 5 1596 1573 1574 + 2167 2 3 0 1939 5 1098 334 384 + 2168 2 3 0 1940 5 1098 599 1096 + 2169 2 3 0 1941 5 1099 335 385 + 2170 2 3 0 1942 5 1099 385 598 + 2171 2 3 0 1943 5 1370 1100 334 + 2172 2 3 0 1944 5 1369 536 1368 + 2173 2 3 0 1945 5 1101 387 336 + 2174 2 3 0 1946 5 1101 336 1021 + 2175 2 3 0 1947 5 1576 1021 368 + 2176 2 3 0 1948 5 1103 337 601 + 2177 2 3 0 1949 5 1103 601 387 + 2178 2 3 0 1950 5 1103 387 1101 + 2179 2 3 0 1951 5 1367 389 1026 + 2180 2 3 0 1952 5 1104 338 602 + 2181 2 3 0 1953 5 1400 1105 338 + 2182 2 3 0 1954 5 1105 568 1085 + 2183 2 3 0 1955 5 1106 1085 391 + 2184 2 3 0 1956 5 1106 390 1105 + 2185 2 3 0 1957 5 394 1110 393 + 2186 2 3 0 1958 5 1214 1107 446 + 2187 2 3 0 1959 5 1108 394 395 + 2188 2 3 0 1960 5 1401 827 1284 + 2189 2 3 0 1961 5 1115 591 271 + 2190 2 3 0 1962 5 1110 446 1107 + 2191 2 3 0 1963 5 1110 1107 393 + 2192 2 3 0 1964 5 1110 1108 1109 + 2193 2 3 0 1965 5 1111 445 664 + 2194 2 3 0 1966 5 1111 446 1109 + 2195 2 3 0 1967 5 1112 1109 570 + 2196 2 3 0 1968 5 1288 1115 1112 + 2197 2 3 0 1969 5 1113 396 663 + 2198 2 3 0 1970 5 1113 269 825 + 2199 2 3 0 1971 5 1114 825 482 + 2200 2 3 0 1972 5 1512 826 270 + 2201 2 3 0 1973 5 1513 271 1213 + 2202 2 3 0 1974 5 1115 1111 1112 + 2203 2 3 0 1975 5 1516 836 268 + 2204 2 3 0 1976 5 1603 1116 1516 + 2205 2 3 0 1977 5 1604 1603 1516 + 2206 2 3 0 1978 5 1604 276 1603 + 2207 2 3 0 1979 5 1505 479 1119 + 2208 2 3 0 1980 5 1605 1505 267 + 2209 2 3 0 1981 5 1119 818 267 + 2210 2 3 0 1982 5 1279 479 1278 + 2211 2 3 0 1983 5 1120 489 850 + 2212 2 3 0 1984 5 1120 850 851 + 2213 2 3 0 1985 5 1270 29 1121 + 2214 2 3 0 1986 5 1149 29 30 + 2215 2 3 0 1987 5 1405 1122 571 + 2216 2 3 0 1988 5 1406 1122 475 + 2217 2 3 0 1989 5 1466 1124 1123 + 2218 2 3 0 1990 5 1407 573 1125 + 2219 2 3 0 1991 5 1124 403 404 + 2220 2 3 0 1992 5 1124 573 1123 + 2221 2 3 0 1993 5 1125 573 650 + 2222 2 3 0 1994 5 1125 810 811 + 2223 2 3 0 1995 5 1126 811 258 + 2224 2 3 0 1996 5 1407 571 1122 + 2225 2 3 0 1997 5 1463 1127 263 + 2226 2 3 0 1998 5 405 152 648 + 2227 2 3 0 1999 5 1275 1274 262 + 2228 2 3 0 2000 5 1128 261 613 + 2229 2 3 0 2001 5 1129 407 156 + 2230 2 3 0 2002 5 1275 408 642 + 2231 2 3 0 2003 5 1233 460 722 + 2232 2 3 0 2004 5 1260 1130 240 + 2233 2 3 0 2005 5 1131 470 771 + 2234 2 3 0 2006 5 1493 771 412 + 2235 2 3 0 2007 5 1531 43 1437 + 2236 2 3 0 2008 5 1531 1132 43 + 2237 2 3 0 2009 5 1692 527 1570 + 2238 2 3 0 2010 5 1692 528 1691 + 2239 2 3 0 2011 5 1606 1140 576 + 2240 2 3 0 2012 5 1607 1415 1134 + 2241 2 3 0 2013 5 1565 1135 439 + 2242 2 3 0 2014 5 1565 1418 1135 + 2243 2 3 0 2015 5 1136 589 990 + 2244 2 3 0 2016 5 1203 1136 577 + 2245 2 3 0 2017 5 1247 1137 238 + 2246 2 3 0 2018 5 1483 1247 237 + 2247 2 3 0 2019 5 1693 1138 57 + 2248 2 3 0 2020 5 1587 543 1051 + 2249 2 3 0 2021 5 1139 584 114 + 2250 2 3 0 2022 5 1345 1139 115 + 2251 2 3 0 2023 5 1140 994 101 + 2252 2 3 0 2024 5 1445 101 102 + 2253 2 3 0 2025 5 1427 107 108 + 2254 2 3 0 2026 5 1203 439 1135 + 2255 2 3 0 2027 5 1412 577 1353 + 2256 2 3 0 2028 5 1413 438 655 + 2257 2 3 0 2029 5 1224 1143 208 + 2258 2 3 0 2030 5 1143 452 683 + 2259 2 3 0 2031 5 1144 683 200 + 2260 2 3 0 2032 5 1477 448 1474 + 2261 2 3 0 2033 5 1480 224 1145 + 2262 2 3 0 2034 5 1145 220 718 + 2263 2 3 0 2035 5 1430 1146 13 + 2264 2 3 0 2036 5 1146 223 704 + 2265 2 3 0 2037 5 1147 21 463 + 2266 2 3 0 2038 5 1243 463 1241 + 2267 2 3 0 2039 5 1148 25 26 + 2268 2 3 0 2040 5 1404 571 1126 + 2269 2 3 0 2041 5 1149 812 266 + 2270 2 3 0 2042 5 1149 266 652 + 2271 2 3 0 2043 5 1432 33 34 + 2272 2 3 0 2044 5 1450 816 1150 + 2273 2 3 0 2045 5 1211 1151 271 + 2274 2 3 0 2046 5 1151 444 892 + 2275 2 3 0 2047 5 1152 892 131 + 2276 2 3 0 2048 5 1152 131 132 + 2277 2 3 0 2049 5 1524 272 873 + 2278 2 3 0 2050 5 1524 1523 1153 + 2279 2 3 0 2051 5 1532 314 1316 + 2280 2 3 0 2052 5 1154 500 901 + 2281 2 3 0 2053 5 1155 37 38 + 2282 2 3 0 2054 5 1155 38 39 + 2283 2 3 0 2055 5 1156 849 903 + 2284 2 3 0 2056 5 1156 480 822 + 2285 2 3 0 2057 5 1608 1589 1340 + 2286 2 3 0 2058 5 1157 517 1058 + 2287 2 3 0 2059 5 1158 1058 315 + 2288 2 3 0 2060 5 1554 1158 516 + 2289 2 3 0 2061 5 1438 509 1194 + 2290 2 3 0 2062 5 1335 304 620 + 2291 2 3 0 2063 5 1160 936 512 + 2292 2 3 0 2064 5 1160 305 1159 + 2293 2 3 0 2065 5 1729 1161 97 + 2294 2 3 0 2066 5 1606 1161 526 + 2295 2 3 0 2067 5 1162 110 111 + 2296 2 3 0 2068 5 1162 111 112 + 2297 2 3 0 2069 5 1163 996 983 + 2298 2 3 0 2070 5 1163 983 328 + 2299 2 3 0 2071 5 1538 534 1365 + 2300 2 3 0 2072 5 1538 52 586 + 2301 2 3 0 2073 5 1662 1166 1167 + 2302 2 3 0 2074 5 1166 997 1165 + 2303 2 3 0 2075 5 1708 1166 1662 + 2304 2 3 0 2076 5 1570 1166 528 + 2305 2 3 0 2077 5 1167 1165 575 + 2306 2 3 0 2078 5 1732 1661 1662 + 2307 2 3 0 2079 5 1168 849 853 + 2308 2 3 0 2080 5 1168 853 907 + 2309 2 3 0 2081 5 1444 1171 3 + 2310 2 3 0 2082 5 1169 415 2 + 2311 2 3 0 2083 5 1170 200 603 + 2312 2 3 0 2084 5 1170 415 1169 + 2313 2 3 0 2085 5 1171 1169 3 + 2314 2 3 0 2086 5 1444 3 4 + 2315 2 3 0 2087 5 1172 422 603 + 2316 2 3 0 2088 5 1223 603 200 + 2317 2 3 0 2089 5 1257 1173 232 + 2318 2 3 0 2090 5 1447 1173 233 + 2319 2 3 0 2091 5 1274 1174 261 + 2320 2 3 0 2092 5 1174 477 644 + 2321 2 3 0 2093 5 1175 643 162 + 2322 2 3 0 2094 5 1502 1175 476 + 2323 2 3 0 2095 5 1176 418 754 + 2324 2 3 0 2096 5 1176 754 801 + 2325 2 3 0 2097 5 1177 801 474 + 2326 2 3 0 2098 5 1448 260 1276 + 2327 2 3 0 2099 5 1734 1733 1693 + 2328 2 3 0 2100 5 1178 413 1048 + 2329 2 3 0 2101 5 1179 420 619 + 2330 2 3 0 2102 5 1179 288 916 + 2331 2 3 0 2103 5 1180 420 920 + 2332 2 3 0 2104 5 1180 303 938 + 2333 2 3 0 2105 5 1446 1181 623 + 2334 2 3 0 2106 5 1181 201 684 + 2335 2 3 0 2107 5 1182 668 209 + 2336 2 3 0 2108 5 1182 690 726 + 2337 2 3 0 2109 5 1183 629 426 + 2338 2 3 0 2110 5 1183 675 424 + 2339 2 3 0 2111 5 1428 1184 186 + 2340 2 3 0 2112 5 1184 425 185 + 2341 2 3 0 2113 5 1185 203 678 + 2342 2 3 0 2114 5 1185 450 677 + 2343 2 3 0 2115 5 1186 625 666 + 2344 2 3 0 2116 5 1443 666 7 + 2345 2 3 0 2117 5 1187 227 730 + 2346 2 3 0 2118 5 1187 454 728 + 2347 2 3 0 2119 5 1494 461 1493 + 2348 2 3 0 2120 5 1493 461 1235 + 2349 2 3 0 2121 5 1189 230 229 + 2350 2 3 0 2122 5 1189 609 723 + 2351 2 3 0 2123 5 1190 723 429 + 2352 2 3 0 2124 5 1264 231 1190 + 2353 2 3 0 2125 5 1460 634 430 + 2354 2 3 0 2126 5 1191 232 1173 + 2355 2 3 0 2127 5 1192 234 755 + 2356 2 3 0 2128 5 1192 587 760 + 2357 2 3 0 2129 5 1431 639 169 + 2358 2 3 0 2130 5 1497 775 1193 + 2359 2 3 0 2131 5 1329 119 120 + 2360 2 3 0 2132 5 1194 509 931 + 2361 2 3 0 2133 5 1195 530 999 + 2362 2 3 0 2134 5 1195 322 1071 + 2363 2 3 0 2135 5 1196 436 993 + 2364 2 3 0 2136 5 1196 361 1080 + 2365 2 3 0 2137 5 1601 1393 1394 + 2366 2 3 0 2138 5 1393 558 560 + 2367 2 3 0 2139 5 1609 1607 1356 + 2368 2 3 0 2140 5 1356 1355 588 + 2369 2 3 0 2141 5 1199 588 991 + 2370 2 3 0 2142 5 1408 326 1357 + 2371 2 3 0 2143 5 1356 327 1355 + 2372 2 3 0 2144 5 1609 1415 1607 + 2373 2 3 0 2145 5 1445 1410 1411 + 2374 2 3 0 2146 5 1201 438 1200 + 2375 2 3 0 2147 5 1202 439 108 + 2376 2 3 0 2148 5 1202 109 110 + 2377 2 3 0 2149 5 1203 1135 1136 + 2378 2 3 0 2150 5 1203 577 1141 + 2379 2 3 0 2151 5 1204 440 974 + 2380 2 3 0 2152 5 1204 305 1160 + 2381 2 3 0 2153 5 1468 1205 656 + 2382 2 3 0 2154 5 1205 306 929 + 2383 2 3 0 2155 5 1206 928 1059 + 2384 2 3 0 2156 5 1206 1062 321 + 2385 2 3 0 2157 5 1387 1207 321 + 2386 2 3 0 2158 5 1207 554 1069 + 2387 2 3 0 2159 5 1333 442 657 + 2388 2 3 0 2160 5 1208 303 921 + 2389 2 3 0 2161 5 1209 616 617 + 2390 2 3 0 2162 5 1449 617 443 + 2391 2 3 0 2163 5 1210 879 918 + 2392 2 3 0 2164 5 1210 290 888 + 2393 2 3 0 2165 5 1211 444 1151 + 2394 2 3 0 2166 5 1421 1211 271 + 2395 2 3 0 2167 5 1212 485 834 + 2396 2 3 0 2168 5 1212 273 662 + 2397 2 3 0 2169 5 1513 828 445 + 2398 2 3 0 2170 5 1213 271 1151 + 2399 2 3 0 2171 5 1214 446 664 + 2400 2 3 0 2172 5 1214 135 136 + 2401 2 3 0 2173 5 1454 1215 447 + 2402 2 3 0 2174 5 1474 1215 1454 + 2403 2 3 0 2175 5 1216 448 1144 + 2404 2 3 0 2176 5 1216 1144 200 + 2405 2 3 0 2177 5 1226 426 628 + 2406 2 3 0 2178 5 1217 206 686 + 2407 2 3 0 2179 5 1475 679 451 + 2408 2 3 0 2180 5 1218 449 686 + 2409 2 3 0 2181 5 1219 203 621 + 2410 2 3 0 2182 5 1219 621 190 + 2411 2 3 0 2183 5 1220 674 450 + 2412 2 3 0 2184 5 1220 678 451 + 2413 2 3 0 2185 5 1221 679 1218 + 2414 2 3 0 2186 5 1479 689 453 + 2415 2 3 0 2187 5 1452 202 622 + 2416 2 3 0 2188 5 1222 449 1218 + 2417 2 3 0 2189 5 1223 683 684 + 2418 2 3 0 2190 5 1223 684 201 + 2419 2 3 0 2191 5 1453 1224 208 + 2420 2 3 0 2192 5 1224 675 681 + 2421 2 3 0 2193 5 1225 205 674 + 2422 2 3 0 2194 5 1225 1220 1221 + 2423 2 3 0 2195 5 1226 628 211 + 2424 2 3 0 2196 5 1226 688 689 + 2425 2 3 0 2197 5 1478 713 714 + 2426 2 3 0 2198 5 1478 714 211 + 2427 2 3 0 2199 5 1610 1494 1237 + 2428 2 3 0 2200 5 1230 411 709 + 2429 2 3 0 2201 5 1229 710 456 + 2430 2 3 0 2202 5 1232 1229 456 + 2431 2 3 0 2203 5 1610 1230 1228 + 2432 2 3 0 2204 5 1230 709 455 + 2433 2 3 0 2205 5 1231 741 734 + 2434 2 3 0 2206 5 1611 1231 461 + 2435 2 3 0 2207 5 1232 1228 1229 + 2436 2 3 0 2208 5 1232 458 1231 + 2437 2 3 0 2209 5 1233 722 739 + 2438 2 3 0 2210 5 1233 240 1130 + 2439 2 3 0 2211 5 1234 734 1130 + 2440 2 3 0 2212 5 1234 1130 1131 + 2441 2 3 0 2213 5 1235 1131 771 + 2442 2 3 0 2214 5 1235 461 734 + 2443 2 3 0 2215 5 1612 1492 1236 + 2444 2 3 0 2216 5 1237 468 1188 + 2445 2 3 0 2217 5 1237 1188 411 + 2446 2 3 0 2218 5 1610 411 1230 + 2447 2 3 0 2219 5 1238 610 611 + 2448 2 3 0 2220 5 1238 611 252 + 2449 2 3 0 2221 5 1258 233 1248 + 2450 2 3 0 2222 5 1239 587 756 + 2451 2 3 0 2223 5 1240 756 462 + 2452 2 3 0 2224 5 1447 610 417 + 2453 2 3 0 2225 5 1485 1241 748 + 2454 2 3 0 2226 5 1488 1241 1486 + 2455 2 3 0 2227 5 1242 256 764 + 2456 2 3 0 2228 5 1242 764 1147 + 2457 2 3 0 2229 5 1243 794 795 + 2458 2 3 0 2230 5 1243 256 1242 + 2459 2 3 0 2231 5 1244 749 751 + 2460 2 3 0 2232 5 1244 751 750 + 2461 2 3 0 2233 5 1245 752 474 + 2462 2 3 0 2234 5 1269 1245 796 + 2463 2 3 0 2235 5 1246 795 749 + 2464 2 3 0 2236 5 1246 797 798 + 2465 2 3 0 2237 5 1483 237 1252 + 2466 2 3 0 2238 5 1247 238 757 + 2467 2 3 0 2239 5 1257 233 1173 + 2468 2 3 0 2240 5 1259 1256 1257 + 2469 2 3 0 2241 5 1461 432 637 + 2470 2 3 0 2242 5 1249 466 1248 + 2471 2 3 0 2243 5 1482 1250 431 + 2472 2 3 0 2244 5 1250 466 1249 + 2473 2 3 0 2245 5 1251 1249 469 + 2474 2 3 0 2246 5 1492 469 769 + 2475 2 3 0 2247 5 1252 237 646 + 2476 2 3 0 2248 5 1252 646 645 + 2477 2 3 0 2249 5 1253 721 467 + 2478 2 3 0 2250 5 1483 431 1137 + 2479 2 3 0 2251 5 1254 637 431 + 2480 2 3 0 2252 5 1254 1250 1251 + 2481 2 3 0 2253 5 1492 1251 469 + 2482 2 3 0 2254 5 1496 1461 1255 + 2483 2 3 0 2255 5 1256 473 770 + 2484 2 3 0 2256 5 1256 770 469 + 2485 2 3 0 2257 5 1257 1248 233 + 2486 2 3 0 2258 5 1259 1257 232 + 2487 2 3 0 2259 5 1258 466 759 + 2488 2 3 0 2260 5 1258 1239 233 + 2489 2 3 0 2261 5 1460 1259 232 + 2490 2 3 0 2262 5 1459 1264 1265 + 2491 2 3 0 2263 5 1484 1260 240 + 2492 2 3 0 2264 5 1495 1260 1484 + 2493 2 3 0 2265 5 1261 239 793 + 2494 2 3 0 2266 5 1261 432 772 + 2495 2 3 0 2267 5 1441 1262 471 + 2496 2 3 0 2268 5 1262 737 738 + 2497 2 3 0 2269 5 1263 241 785 + 2498 2 3 0 2270 5 1263 172 773 + 2499 2 3 0 2271 5 1264 430 633 + 2500 2 3 0 2272 5 1264 633 231 + 2501 2 3 0 2273 5 1265 1190 429 + 2502 2 3 0 2274 5 1459 473 1259 + 2503 2 3 0 2275 5 1266 473 1265 + 2504 2 3 0 2276 5 1266 429 765 + 2505 2 3 0 2277 5 1267 236 645 + 2506 2 3 0 2278 5 1267 645 796 + 2507 2 3 0 2279 5 1268 796 474 + 2508 2 3 0 2280 5 1498 235 1491 + 2509 2 3 0 2281 5 1269 796 257 + 2510 2 3 0 2282 5 1487 1269 257 + 2511 2 3 0 2283 5 1270 27 28 + 2512 2 3 0 2284 5 1270 28 29 + 2513 2 3 0 2285 5 1271 1121 265 + 2514 2 3 0 2286 5 1271 475 27 + 2515 2 3 0 2287 5 1272 476 1175 + 2516 2 3 0 2288 5 1272 162 745 + 2517 2 3 0 2289 5 1273 746 254 + 2518 2 3 0 2290 5 1273 803 807 + 2519 2 3 0 2291 5 1274 477 1174 + 2520 2 3 0 2292 5 1274 261 1128 + 2521 2 3 0 2293 5 1275 642 1274 + 2522 2 3 0 2294 5 1275 262 1129 + 2523 2 3 0 2295 5 1613 260 1504 + 2524 2 3 0 2296 5 1613 1501 478 + 2525 2 3 0 2297 5 1501 805 478 + 2526 2 3 0 2298 5 1277 263 1127 + 2527 2 3 0 2299 5 1279 1278 268 + 2528 2 3 0 2300 5 1278 479 842 + 2529 2 3 0 2301 5 1279 268 819 + 2530 2 3 0 2302 5 1279 819 1119 + 2531 2 3 0 2303 5 1280 897 898 + 2532 2 3 0 2304 5 1280 898 902 + 2533 2 3 0 2305 5 1519 847 1296 + 2534 2 3 0 2306 5 1281 480 902 + 2535 2 3 0 2307 5 1282 902 295 + 2536 2 3 0 2308 5 1520 1282 281 + 2537 2 3 0 2309 5 1420 1283 274 + 2538 2 3 0 2310 5 1403 1283 590 + 2539 2 3 0 2311 5 1614 1402 270 + 2540 2 3 0 2312 5 1511 827 396 + 2541 2 3 0 2313 5 1304 483 830 + 2542 2 3 0 2314 5 1285 285 863 + 2543 2 3 0 2315 5 1302 1286 284 + 2544 2 3 0 2316 5 1286 293 833 + 2545 2 3 0 2317 5 1546 1287 484 + 2546 2 3 0 2318 5 1287 301 615 + 2547 2 3 0 2319 5 1614 1401 1402 + 2548 2 3 0 2320 5 1615 1614 270 + 2549 2 3 0 2321 5 1615 1288 1614 + 2550 2 3 0 2322 5 1289 590 835 + 2551 2 3 0 2323 5 1290 865 895 + 2552 2 3 0 2324 5 1290 895 896 + 2553 2 3 0 2325 5 1291 487 820 + 2554 2 3 0 2326 5 1291 278 850 + 2555 2 3 0 2327 5 1292 282 896 + 2556 2 3 0 2328 5 1292 486 821 + 2557 2 3 0 2329 5 1293 488 847 + 2558 2 3 0 2330 5 1293 281 845 + 2559 2 3 0 2331 5 1616 1450 1451 + 2560 2 3 0 2332 5 1296 847 1295 + 2561 2 3 0 2333 5 1295 847 848 + 2562 2 3 0 2334 5 1295 489 1294 + 2563 2 3 0 2335 5 1616 1294 279 + 2564 2 3 0 2336 5 1519 1296 280 + 2565 2 3 0 2337 5 1297 267 614 + 2566 2 3 0 2338 5 1297 813 814 + 2567 2 3 0 2339 5 1298 814 266 + 2568 2 3 0 2340 5 1467 1298 490 + 2569 2 3 0 2341 5 1299 816 852 + 2570 2 3 0 2342 5 1299 852 490 + 2571 2 3 0 2343 5 1522 1300 294 + 2572 2 3 0 2344 5 1300 493 865 + 2573 2 3 0 2345 5 1301 845 858 + 2574 2 3 0 2346 5 1301 858 492 + 2575 2 3 0 2347 5 1302 293 1286 + 2576 2 3 0 2348 5 1303 284 864 + 2577 2 3 0 2349 5 1303 283 895 + 2578 2 3 0 2350 5 1303 895 1302 + 2579 2 3 0 2351 5 1304 830 291 + 2580 2 3 0 2352 5 1304 913 914 + 2581 2 3 0 2353 5 1305 867 868 + 2582 2 3 0 2354 5 1305 868 286 + 2583 2 3 0 2355 5 1306 287 875 + 2584 2 3 0 2356 5 1323 875 497 + 2585 2 3 0 2357 5 1525 497 874 + 2586 2 3 0 2358 5 1307 290 918 + 2587 2 3 0 2359 5 1308 918 505 + 2588 2 3 0 2360 5 1308 505 920 + 2589 2 3 0 2361 5 1309 289 916 + 2590 2 3 0 2362 5 1309 916 1306 + 2591 2 3 0 2363 5 1310 310 964 + 2592 2 3 0 2364 5 1547 1310 309 + 2593 2 3 0 2365 5 1617 1552 1549 + 2594 2 3 0 2366 5 1313 876 1312 + 2595 2 3 0 2367 5 1312 498 877 + 2596 2 3 0 2368 5 1339 877 515 + 2597 2 3 0 2369 5 1618 1617 1550 + 2598 2 3 0 2370 5 1313 311 876 + 2599 2 3 0 2371 5 1320 1314 294 + 2600 2 3 0 2372 5 1314 900 909 + 2601 2 3 0 2373 5 1315 909 299 + 2602 2 3 0 2374 5 1522 499 860 + 2603 2 3 0 2375 5 1532 912 894 + 2604 2 3 0 2376 5 1316 314 954 + 2605 2 3 0 2377 5 1317 504 912 + 2606 2 3 0 2378 5 1317 313 953 + 2607 2 3 0 2379 5 1318 953 316 + 2608 2 3 0 2380 5 1322 1318 312 + 2609 2 3 0 2381 5 1321 898 501 + 2610 2 3 0 2382 5 1319 298 910 + 2611 2 3 0 2383 5 1320 294 866 + 2612 2 3 0 2384 5 1320 866 492 + 2613 2 3 0 2385 5 1321 298 1319 + 2614 2 3 0 2386 5 1321 501 904 + 2615 2 3 0 2387 5 1322 504 1317 + 2616 2 3 0 2388 5 1324 1322 312 + 2617 2 3 0 2389 5 1323 289 1309 + 2618 2 3 0 2390 5 1323 497 1307 + 2619 2 3 0 2391 5 1325 312 962 + 2620 2 3 0 2392 5 1550 311 1313 + 2621 2 3 0 2393 5 1550 1313 1311 + 2622 2 3 0 2394 5 1549 1324 1325 + 2623 2 3 0 2395 5 1440 53 54 + 2624 2 3 0 2396 5 1326 586 52 + 2625 2 3 0 2397 5 1619 1327 507 + 2626 2 3 0 2398 5 1619 1554 1327 + 2627 2 3 0 2399 5 1539 1328 508 + 2628 2 3 0 2400 5 1328 354 1017 + 2629 2 3 0 2401 5 1329 120 930 + 2630 2 3 0 2402 5 1329 930 304 + 2631 2 3 0 2403 5 1544 510 934 + 2632 2 3 0 2404 5 1372 1033 1330 + 2633 2 3 0 2405 5 1331 930 121 + 2634 2 3 0 2406 5 1331 932 933 + 2635 2 3 0 2407 5 1332 512 936 + 2636 2 3 0 2408 5 1332 936 938 + 2637 2 3 0 2409 5 1333 938 303 + 2638 2 3 0 2410 5 1333 657 306 + 2639 2 3 0 2411 5 1468 306 1205 + 2640 2 3 0 2412 5 1468 512 1334 + 2641 2 3 0 2413 5 1335 620 936 + 2642 2 3 0 2414 5 1335 936 1159 + 2643 2 3 0 2415 5 1545 1336 513 + 2644 2 3 0 2416 5 1336 316 949 + 2645 2 3 0 2417 5 1337 949 517 + 2646 2 3 0 2418 5 1340 1337 517 + 2647 2 3 0 2419 5 1338 924 317 + 2648 2 3 0 2420 5 1338 939 940 + 2649 2 3 0 2421 5 1339 515 890 + 2650 2 3 0 2422 5 1339 1311 1312 + 2651 2 3 0 2423 5 1608 517 1157 + 2652 2 3 0 2424 5 1589 353 1364 + 2653 2 3 0 2425 5 1341 352 958 + 2654 2 3 0 2426 5 1341 958 513 + 2655 2 3 0 2427 5 1343 975 967 + 2656 2 3 0 2428 5 1556 1065 1342 + 2657 2 3 0 2429 5 1343 969 968 + 2658 2 3 0 2430 5 1556 518 1064 + 2659 2 3 0 2431 5 1344 519 999 + 2660 2 3 0 2432 5 1414 1344 329 + 2661 2 3 0 2433 5 1426 116 117 + 2662 2 3 0 2434 5 1426 435 1425 + 2663 2 3 0 2435 5 1564 320 1563 + 2664 2 3 0 2436 5 1346 520 1053 + 2665 2 3 0 2437 5 1620 1348 1347 + 2666 2 3 0 2438 5 1347 592 1042 + 2667 2 3 0 2439 5 1422 980 521 + 2668 2 3 0 2440 5 1348 592 1347 + 2669 2 3 0 2441 5 1349 531 1001 + 2670 2 3 0 2442 5 1349 329 1000 + 2671 2 3 0 2443 5 1350 328 983 + 2672 2 3 0 2444 5 1350 985 986 + 2673 2 3 0 2445 5 1351 360 1030 + 2674 2 3 0 2446 5 1351 1030 1031 + 2675 2 3 0 2447 5 1352 1031 377 + 2676 2 3 0 2448 5 1567 523 1566 + 2677 2 3 0 2449 5 1412 1353 327 + 2678 2 3 0 2450 5 1353 577 1136 + 2679 2 3 0 2451 5 1354 103 104 + 2680 2 3 0 2452 5 1354 104 655 + 2681 2 3 0 2453 5 1355 992 588 + 2682 2 3 0 2454 5 1355 327 1353 + 2683 2 3 0 2455 5 1621 1356 1198 + 2684 2 3 0 2456 5 1621 1571 1609 + 2685 2 3 0 2457 5 1622 1393 560 + 2686 2 3 0 2458 5 1622 1409 1357 + 2687 2 3 0 2459 5 1592 1358 530 + 2688 2 3 0 2460 5 1577 1358 323 + 2689 2 3 0 2461 5 1375 1359 323 + 2690 2 3 0 2462 5 1359 540 1028 + 2691 2 3 0 2463 5 1360 1028 324 + 2692 2 3 0 2464 5 1361 984 1001 + 2693 2 3 0 2465 5 1577 1361 531 + 2694 2 3 0 2466 5 1577 1360 1361 + 2695 2 3 0 2467 5 1374 340 1373 + 2696 2 3 0 2468 5 1600 1362 1374 + 2697 2 3 0 2469 5 1544 351 1372 + 2698 2 3 0 2470 5 1544 1363 351 + 2699 2 3 0 2471 5 1619 1364 353 + 2700 2 3 0 2472 5 1619 1572 1364 + 2701 2 3 0 2473 5 1572 534 1004 + 2702 2 3 0 2474 5 1365 507 923 + 2703 2 3 0 2475 5 1651 348 1635 + 2704 2 3 0 2476 5 1651 1045 1366 + 2705 2 3 0 2477 5 1367 535 1045 + 2706 2 3 0 2478 5 1585 1043 1584 + 2707 2 3 0 2479 5 1369 538 1020 + 2708 2 3 0 2480 5 1368 536 1017 + 2709 2 3 0 2481 5 1369 1020 335 + 2710 2 3 0 2482 5 1369 1099 1100 + 2711 2 3 0 2483 5 1370 537 1100 + 2712 2 3 0 2484 5 1370 334 1098 + 2713 2 3 0 2485 5 1371 1098 1096 + 2714 2 3 0 2486 5 1596 1574 1595 + 2715 2 3 0 2487 5 1372 351 1032 + 2716 2 3 0 2488 5 1372 1032 1033 + 2717 2 3 0 2489 5 1373 981 982 + 2718 2 3 0 2490 5 1373 982 363 + 2719 2 3 0 2491 5 1395 1374 1083 + 2720 2 3 0 2492 5 1374 1362 340 + 2721 2 3 0 2493 5 1388 1375 323 + 2722 2 3 0 2494 5 1386 1375 555 + 2723 2 3 0 2495 5 1567 1351 1352 + 2724 2 3 0 2496 5 1597 1028 1376 + 2725 2 3 0 2497 5 1379 1377 345 + 2726 2 3 0 2498 5 1377 542 1038 + 2727 2 3 0 2499 5 1378 549 1089 + 2728 2 3 0 2500 5 1378 562 1040 + 2729 2 3 0 2501 5 1379 1040 542 + 2730 2 3 0 2502 5 1381 345 1049 + 2731 2 3 0 2503 5 1380 56 1138 + 2732 2 3 0 2504 5 1587 1380 1138 + 2733 2 3 0 2505 5 1583 1049 551 + 2734 2 3 0 2506 5 1381 549 1378 + 2735 2 3 0 2507 5 1590 1382 550 + 2736 2 3 0 2508 5 1382 343 1036 + 2737 2 3 0 2509 5 1586 1383 551 + 2738 2 3 0 2510 5 1383 350 1347 + 2739 2 3 0 2511 5 1384 331 1003 + 2740 2 3 0 2512 5 1384 1003 357 + 2741 2 3 0 2513 5 1553 319 966 + 2742 2 3 0 2514 5 1553 966 965 + 2743 2 3 0 2515 5 1386 555 1069 + 2744 2 3 0 2516 5 1386 358 1007 + 2745 2 3 0 2517 5 1387 978 554 + 2746 2 3 0 2518 5 1387 554 1207 + 2747 2 3 0 2519 5 1388 1072 555 + 2748 2 3 0 2520 5 1592 323 1358 + 2749 2 3 0 2521 5 1598 1077 1390 + 2750 2 3 0 2522 5 1623 1597 1598 + 2751 2 3 0 2523 5 1419 1390 325 + 2752 2 3 0 2524 5 1598 1390 556 + 2753 2 3 0 2525 5 1391 1077 361 + 2754 2 3 0 2526 5 1391 361 1196 + 2755 2 3 0 2527 5 1623 1392 324 + 2756 2 3 0 2528 5 1392 556 1082 + 2757 2 3 0 2529 5 1622 560 1409 + 2758 2 3 0 2530 5 1622 654 1393 + 2759 2 3 0 2531 5 1394 1197 362 + 2760 2 3 0 2532 5 1395 362 1374 + 2761 2 3 0 2533 5 1601 1083 1084 + 2762 2 3 0 2534 5 1601 1084 558 + 2763 2 3 0 2535 5 1396 1039 1040 + 2764 2 3 0 2536 5 1396 562 1091 + 2765 2 3 0 2537 5 1620 1397 563 + 2766 2 3 0 2538 5 1423 350 1093 + 2767 2 3 0 2539 5 1713 1398 593 + 2768 2 3 0 2540 5 1399 1398 369 + 2769 2 3 0 2541 5 1581 1399 369 + 2770 2 3 0 2542 5 1399 368 980 + 2771 2 3 0 2543 5 1585 338 1104 + 2772 2 3 0 2544 5 1735 1715 1624 + 2773 2 3 0 2545 5 1401 1108 395 + 2774 2 3 0 2546 5 1401 395 827 + 2775 2 3 0 2547 5 1512 1402 1284 + 2776 2 3 0 2548 5 1615 270 1403 + 2777 2 3 0 2549 5 1403 270 826 + 2778 2 3 0 2550 5 1403 590 1289 + 2779 2 3 0 2551 5 1486 1241 1485 + 2780 2 3 0 2552 5 1485 24 1404 + 2781 2 3 0 2553 5 1405 26 475 + 2782 2 3 0 2554 5 1405 475 1122 + 2783 2 3 0 2555 5 1406 572 1122 + 2784 2 3 0 2556 5 1406 475 1271 + 2785 2 3 0 2557 5 1407 1122 1123 + 2786 2 3 0 2558 5 1407 1123 573 + 2787 2 3 0 2559 5 1408 998 529 + 2788 2 3 0 2560 5 1408 529 1198 + 2789 2 3 0 2561 5 1646 1409 560 + 2790 2 3 0 2562 5 1732 1409 1646 + 2791 2 3 0 2563 5 1410 102 103 + 2792 2 3 0 2564 5 1410 103 1354 + 2793 2 3 0 2565 5 1411 1354 1201 + 2794 2 3 0 2566 5 1445 585 1134 + 2795 2 3 0 2567 5 1412 327 1200 + 2796 2 3 0 2568 5 1412 438 1142 + 2797 2 3 0 2569 5 1413 655 106 + 2798 2 3 0 2570 5 1413 1141 1142 + 2799 2 3 0 2571 5 1414 584 1344 + 2800 2 3 0 2572 5 1569 1414 329 + 2801 2 3 0 2573 5 1415 527 1133 + 2802 2 3 0 2574 5 1415 1133 1134 + 2803 2 3 0 2575 5 1416 1039 344 + 2804 2 3 0 2576 5 1416 586 1326 + 2805 2 3 0 2577 5 1417 525 989 + 2806 2 3 0 2578 5 1417 989 437 + 2807 2 3 0 2579 5 1418 589 1135 + 2808 2 3 0 2580 5 1418 328 1350 + 2809 2 3 0 2581 5 1419 556 1390 + 2810 2 3 0 2582 5 1419 325 1081 + 2811 2 3 0 2583 5 1420 590 1283 + 2812 2 3 0 2584 5 1420 274 869 + 2813 2 3 0 2585 5 1421 485 1211 + 2814 2 3 0 2586 5 1421 271 591 + 2815 2 3 0 2587 5 1422 521 1087 + 2816 2 3 0 2588 5 1422 349 592 + 2817 2 3 0 2589 5 1711 1423 1093 + 2818 2 3 0 2590 5 1423 593 1397 + 2819 2 3 0 2591 5 1424 433 789 + 2820 2 3 0 2592 5 1424 167 168 + 2821 2 3 0 2593 5 1425 972 519 + 2822 2 3 0 2594 5 1425 973 1345 + 2823 2 3 0 2595 5 1426 1345 116 + 2824 2 3 0 2596 5 1426 653 435 + 2825 2 3 0 2597 5 1427 108 439 + 2826 2 3 0 2598 5 1427 439 1203 + 2827 2 3 0 2599 5 1428 187 203 + 2828 2 3 0 2600 5 1428 203 1185 + 2829 2 3 0 2601 5 1429 630 9 + 2830 2 3 0 2602 5 1429 9 10 + 2831 2 3 0 2603 5 1430 14 722 + 2832 2 3 0 2604 5 1430 722 460 + 2833 2 3 0 2605 5 1431 170 785 + 2834 2 3 0 2606 5 1497 785 786 + 2835 2 3 0 2607 5 1451 34 35 + 2836 2 3 0 2608 5 1616 618 1296 + 2837 2 3 0 2609 5 1433 128 829 + 2838 2 3 0 2610 5 1433 829 272 + 2839 2 3 0 2611 5 1434 822 815 + 2840 2 3 0 2612 5 1434 37 1155 + 2841 2 3 0 2613 5 1435 124 878 + 2842 2 3 0 2614 5 1435 878 288 + 2843 2 3 0 2615 5 1436 661 829 + 2844 2 3 0 2616 5 1436 829 129 + 2845 2 3 0 2617 5 1437 43 44 + 2846 2 3 0 2618 5 1437 44 45 + 2847 2 3 0 2619 5 1438 304 1335 + 2848 2 3 0 2620 5 1438 1159 509 + 2849 2 3 0 2621 5 1439 333 1096 + 2850 2 3 0 2622 5 1439 383 594 + 2851 2 3 0 2623 5 1440 54 542 + 2852 2 3 0 2624 5 1440 542 1039 + 2853 2 3 0 2625 5 1441 244 737 + 2854 2 3 0 2626 5 1441 471 774 + 2855 2 3 0 2627 5 1442 1162 1163 + 2856 2 3 0 2628 5 1442 1163 328 + 2857 2 3 0 2629 5 1443 427 1186 + 2858 2 3 0 2630 5 1443 7 8 + 2859 2 3 0 2631 5 1444 4 667 + 2860 2 3 0 2632 5 1444 448 1216 + 2861 2 3 0 2633 5 1445 1134 1140 + 2862 2 3 0 2634 5 1445 1140 101 + 2863 2 3 0 2635 5 1446 201 1181 + 2864 2 3 0 2636 5 1775 1446 423 + 2865 2 3 0 2637 5 1447 417 1173 + 2866 2 3 0 2638 5 1447 233 1240 + 2867 2 3 0 2639 5 1448 612 808 + 2868 2 3 0 2640 5 1448 418 1176 + 2869 2 3 0 2641 5 1449 443 880 + 2870 2 3 0 2642 5 1449 879 1209 + 2871 2 3 0 2643 5 1450 279 816 + 2872 2 3 0 2644 5 1450 1150 1432 + 2873 2 3 0 2645 5 1451 1432 34 + 2874 2 3 0 2646 5 1616 1451 618 + 2875 2 3 0 2647 5 1452 623 449 + 2876 2 3 0 2648 5 1452 449 1222 + 2877 2 3 0 2649 5 1453 424 675 + 2878 2 3 0 2650 5 1454 1453 208 + 2879 2 3 0 2651 5 1474 1454 208 + 2880 2 3 0 2652 5 1454 447 624 + 2881 2 3 0 2653 5 1455 426 1217 + 2882 2 3 0 2654 5 1455 687 207 + 2883 2 3 0 2655 5 1456 631 428 + 2884 2 3 0 2656 5 1456 428 455 + 2885 2 3 0 2657 5 1457 765 429 + 2886 2 3 0 2658 5 1457 631 1456 + 2887 2 3 0 2659 5 1458 231 247 + 2888 2 3 0 2660 5 1458 1189 1190 + 2889 2 3 0 2661 5 1460 1459 1259 + 2890 2 3 0 2662 5 1459 430 1264 + 2891 2 3 0 2663 5 1460 430 1459 + 2892 2 3 0 2664 5 1460 232 1191 + 2893 2 3 0 2665 5 1461 637 1254 + 2894 2 3 0 2666 5 1461 1254 1255 + 2895 2 3 0 2667 5 1462 160 161 + 2896 2 3 0 2668 5 1462 161 644 + 2897 2 3 0 2669 5 648 1463 405 + 2898 2 3 0 2670 5 1504 1465 1503 + 2899 2 3 0 2671 5 1499 260 1177 + 2900 2 3 0 2672 5 1464 804 809 + 2901 2 3 0 2673 5 1465 809 649 + 2902 2 3 0 2674 5 1503 649 405 + 2903 2 3 0 2675 5 1466 403 1124 + 2904 2 3 0 2676 5 1466 572 651 + 2905 2 3 0 2677 5 1605 851 1118 + 2906 2 3 0 2678 5 1467 267 1297 + 2907 2 3 0 2679 5 1468 656 440 + 2908 2 3 0 2680 5 1468 440 512 + 2909 2 3 0 2681 5 1469 307 1059 + 2910 2 3 0 2682 5 1469 928 929 + 2911 2 3 0 2683 5 1470 301 943 + 2912 2 3 0 2684 5 1470 943 955 + 2913 2 3 0 2685 5 1471 308 968 + 2914 2 3 0 2686 5 1471 514 659 + 2915 2 3 0 2687 5 1472 514 969 + 2916 2 3 0 2688 5 1472 307 945 + 2917 2 3 0 2689 5 1473 273 1305 + 2918 2 3 0 2690 5 1473 496 873 + 2919 2 3 0 2691 5 1477 208 1143 + 2920 2 3 0 2692 5 1474 448 667 + 2921 2 3 0 2693 5 1475 202 1222 + 2922 2 3 0 2694 5 1475 451 671 + 2923 2 3 0 2695 5 1476 695 212 + 2924 2 3 0 2696 5 1476 698 700 + 2925 2 3 0 2697 5 1477 1143 1144 + 2926 2 3 0 2698 5 1477 1144 448 + 2927 2 3 0 2699 5 1478 211 697 + 2928 2 3 0 2700 5 1478 697 454 + 2929 2 3 0 2701 5 1479 453 692 + 2930 2 3 0 2702 5 1479 205 1225 + 2931 2 3 0 2703 5 1480 717 221 + 2932 2 3 0 2704 5 1481 1145 719 + 2933 2 3 0 2705 5 1481 719 427 + 2934 2 3 0 2706 5 1481 427 630 + 2935 2 3 0 2707 5 1482 467 759 + 2936 2 3 0 2708 5 1482 759 1250 + 2937 2 3 0 2709 5 1483 1137 1247 + 2938 2 3 0 2710 5 1483 1252 1253 + 2939 2 3 0 2711 5 1484 240 222 + 2940 2 3 0 2712 5 1484 767 768 + 2941 2 3 0 2713 5 1485 748 23 + 2942 2 3 0 2714 5 1485 23 24 + 2943 2 3 0 2715 5 1486 1404 258 + 2944 2 3 0 2716 5 1488 1486 258 + 2945 2 3 0 2717 5 1487 749 1269 + 2946 2 3 0 2718 5 1487 257 797 + 2947 2 3 0 2719 5 1488 464 794 + 2948 2 3 0 2720 5 1488 794 1241 + 2949 2 3 0 2721 5 1489 254 787 + 2950 2 3 0 2722 5 1489 787 788 + 2951 2 3 0 2723 5 1490 235 754 + 2952 2 3 0 2724 5 1490 753 788 + 2953 2 3 0 2725 5 1491 234 784 + 2954 2 3 0 2726 5 1498 1491 784 + 2955 2 3 0 2727 5 1492 769 1236 + 2956 2 3 0 2728 5 1612 1236 412 + 2957 2 3 0 2729 5 1493 1235 771 + 2958 2 3 0 2730 5 1493 412 1236 + 2959 2 3 0 2731 5 1494 1236 1237 + 2960 2 3 0 2732 5 1610 1237 411 + 2961 2 3 0 2733 5 1495 470 1260 + 2962 2 3 0 2734 5 1495 239 1261 + 2963 2 3 0 2735 5 1496 432 1461 + 2964 2 3 0 2736 5 1496 412 771 + 2965 2 3 0 2737 5 1497 472 775 + 2966 2 3 0 2738 5 1497 1193 1431 + 2967 2 3 0 2739 5 1498 784 236 + 2968 2 3 0 2740 5 1498 1267 1268 + 2969 2 3 0 2741 5 1500 1177 474 + 2970 2 3 0 2742 5 1500 474 800 + 2971 2 3 0 2743 5 1500 800 804 + 2972 2 3 0 2744 5 1500 1464 1499 + 2973 2 3 0 2745 5 1613 478 1276 + 2974 2 3 0 2746 5 1501 263 1277 + 2975 2 3 0 2747 5 1502 261 1174 + 2976 2 3 0 2748 5 1502 476 807 + 2977 2 3 0 2749 5 1503 1463 263 + 2978 2 3 0 2750 5 1504 1503 263 + 2979 2 3 0 2751 5 1613 1504 263 + 2980 2 3 0 2752 5 1504 260 1464 + 2981 2 3 0 2753 5 1605 267 1467 + 2982 2 3 0 2754 5 1505 1118 479 + 2983 2 3 0 2755 5 1506 487 845 + 2984 2 3 0 2756 5 1506 845 1301 + 2985 2 3 0 2757 5 1519 480 1281 + 2986 2 3 0 2758 5 1507 280 822 + 2987 2 3 0 2759 5 1508 285 914 + 2988 2 3 0 2760 5 1508 494 823 + 2989 2 3 0 2761 5 1509 494 886 + 2990 2 3 0 2762 5 1509 286 868 + 2991 2 3 0 2763 5 1510 482 825 + 2992 2 3 0 2764 5 1510 825 844 + 2993 2 3 0 2765 5 1511 1113 1114 + 2994 2 3 0 2766 5 1512 1114 826 + 2995 2 3 0 2767 5 1512 270 1402 + 2996 2 3 0 2768 5 1512 1284 1511 + 2997 2 3 0 2769 5 1513 445 1115 + 2998 2 3 0 2770 5 1513 1115 271 + 2999 2 3 0 2771 5 1514 483 1285 + 3000 2 3 0 2772 5 1514 284 1286 + 3001 2 3 0 2773 5 1515 590 1420 + 3002 2 3 0 2774 5 1515 481 834 + 3003 2 3 0 2775 5 1516 1116 836 + 3004 2 3 0 2776 5 1516 268 1278 + 3005 2 3 0 2777 5 1517 663 837 + 3006 2 3 0 2778 5 1517 836 1116 + 3007 2 3 0 2779 5 1518 840 1510 + 3008 2 3 0 2780 5 1518 275 855 + 3009 2 3 0 2781 5 1519 1281 847 + 3010 2 3 0 2782 5 1519 280 1507 + 3011 2 3 0 2783 5 1520 847 1281 + 3012 2 3 0 2784 5 1520 1281 1282 + 3013 2 3 0 2785 5 1521 295 911 + 3014 2 3 0 2786 5 1521 492 858 + 3015 2 3 0 2787 5 1522 294 1314 + 3016 2 3 0 2788 5 1522 1314 1315 + 3017 2 3 0 2789 5 1523 287 1306 + 3018 2 3 0 2790 5 1523 495 870 + 3019 2 3 0 2791 5 1524 871 287 + 3020 2 3 0 2792 5 1524 287 1523 + 3021 2 3 0 2793 5 1525 874 286 + 3022 2 3 0 2794 5 1525 286 1509 + 3023 2 3 0 2795 5 1526 886 888 + 3024 2 3 0 2796 5 1526 290 1307 + 3025 2 3 0 2797 5 1527 311 962 + 3026 2 3 0 2798 5 1528 1527 317 + 3027 2 3 0 2799 5 1528 317 924 + 3028 2 3 0 2800 5 1528 937 951 + 3029 2 3 0 2801 5 1529 890 499 + 3030 2 3 0 2802 5 1529 299 1311 + 3031 2 3 0 2803 5 1530 893 297 + 3032 2 3 0 2804 5 1530 297 906 + 3033 2 3 0 2805 5 1531 1437 901 + 3034 2 3 0 2806 5 1531 893 1530 + 3035 2 3 0 2807 5 1532 500 1154 + 3036 2 3 0 2808 5 1532 1154 314 + 3037 2 3 0 2809 5 1533 297 904 + 3038 2 3 0 2810 5 1533 501 897 + 3039 2 3 0 2811 5 1534 909 502 + 3040 2 3 0 2812 5 1534 502 910 + 3041 2 3 0 2813 5 1535 910 298 + 3042 2 3 0 2814 5 1552 957 1549 + 3043 2 3 0 2815 5 1536 503 915 + 3044 2 3 0 2816 5 1536 504 922 + 3045 2 3 0 2817 5 1537 302 946 + 3046 2 3 0 2818 5 1537 442 1208 + 3047 2 3 0 2819 5 1538 51 52 + 3048 2 3 0 2820 5 1538 1164 534 + 3049 2 3 0 2821 5 1539 508 926 + 3050 2 3 0 2822 5 1539 924 1338 + 3051 2 3 0 2823 5 1540 927 355 + 3052 2 3 0 2824 5 1540 355 1074 + 3053 2 3 0 2825 5 1564 1541 320 + 3054 2 3 0 2826 5 1541 1062 1206 + 3055 2 3 0 2827 5 1542 509 1159 + 3056 2 3 0 2828 5 1542 305 976 + 3057 2 3 0 2829 5 1543 934 352 + 3058 2 3 0 2830 5 1543 352 1340 + 3059 2 3 0 2831 5 1544 1372 510 + 3060 2 3 0 2832 5 1544 934 1543 + 3061 2 3 0 2833 5 1545 513 939 + 3062 2 3 0 2834 5 1545 939 944 + 3063 2 3 0 2835 5 1546 484 884 + 3064 2 3 0 2836 5 1546 942 943 + 3065 2 3 0 2837 5 1547 941 1310 + 3066 2 3 0 2838 5 1547 309 955 + 3067 2 3 0 2839 5 1548 944 312 + 3068 2 3 0 2840 5 1548 312 1318 + 3069 2 3 0 2841 5 1549 957 506 + 3070 2 3 0 2842 5 1549 506 1324 + 3071 2 3 0 2843 5 1550 1325 311 + 3072 2 3 0 2844 5 1618 1311 299 + 3073 2 3 0 2845 5 1551 299 909 + 3074 2 3 0 2846 5 1551 1534 1535 + 3075 2 3 0 2847 5 1552 1535 957 + 3076 2 3 0 2848 5 1617 1549 1325 + 3077 2 3 0 2849 5 1553 965 318 + 3078 2 3 0 2850 5 1553 318 1060 + 3079 2 3 0 2851 5 1554 353 1157 + 3080 2 3 0 2852 5 1554 516 963 + 3081 2 3 0 2853 5 1555 309 964 + 3082 2 3 0 2854 5 1555 964 966 + 3083 2 3 0 2855 5 1556 1064 1065 + 3084 2 3 0 2856 5 1556 1342 1343 + 3085 2 3 0 2857 5 1557 356 1063 + 3086 2 3 0 2858 5 1595 1557 553 + 3087 2 3 0 2859 5 1574 970 1097 + 3088 2 3 0 2860 5 1573 333 1439 + 3089 2 3 0 2861 5 1559 1009 332 + 3090 2 3 0 2862 5 1559 600 331 + 3091 2 3 0 2863 5 1560 435 976 + 3092 2 3 0 2864 5 1561 322 1195 + 3093 2 3 0 2865 5 1561 999 519 + 3094 2 3 0 2866 5 1561 972 1560 + 3095 2 3 0 2867 5 1562 974 322 + 3096 2 3 0 2868 5 1562 322 1560 + 3097 2 3 0 2869 5 1563 975 520 + 3098 2 3 0 2870 5 1563 520 1346 + 3099 2 3 0 2871 5 1564 1346 977 + 3100 2 3 0 2872 5 1564 977 1541 + 3101 2 3 0 2873 5 1565 328 1418 + 3102 2 3 0 2874 5 1565 439 1202 + 3103 2 3 0 2875 5 1566 987 361 + 3104 2 3 0 2876 5 1566 1077 1389 + 3105 2 3 0 2877 5 1567 1389 360 + 3106 2 3 0 2878 5 1567 360 1351 + 3107 2 3 0 2879 5 1568 523 1352 + 3108 2 3 0 2880 5 1568 341 988 + 3109 2 3 0 2881 5 1569 329 1349 + 3110 2 3 0 2882 5 1569 522 996 + 3111 2 3 0 2883 5 1692 1691 1673 + 3112 2 3 0 2884 5 1571 1570 527 + 3113 2 3 0 2885 5 1609 527 1415 + 3114 2 3 0 2886 5 1571 529 997 + 3115 2 3 0 2887 5 1572 1004 533 + 3116 2 3 0 2888 5 1572 507 1365 + 3117 2 3 0 2889 5 1573 1439 594 + 3118 2 3 0 2890 5 1573 1013 1558 + 3119 2 3 0 2891 5 1574 1558 970 + 3120 2 3 0 2892 5 1595 1574 1097 + 3121 2 3 0 2893 5 1575 337 1092 + 3122 2 3 0 2894 5 1575 535 1026 + 3123 2 3 0 2895 5 1581 1579 1580 + 3124 2 3 0 2896 5 1580 1102 1576 + 3125 2 3 0 2897 5 1577 531 1358 + 3126 2 3 0 2898 5 1577 323 1359 + 3127 2 3 0 2899 5 1578 541 1035 + 3128 2 3 0 2900 5 1578 342 1068 + 3129 2 3 0 2901 5 1579 1037 367 + 3130 2 3 0 2902 5 1579 367 1044 + 3131 2 3 0 2903 5 1580 1092 337 + 3132 2 3 0 2904 5 1581 1576 368 + 3133 2 3 0 2905 5 1581 368 1399 + 3134 2 3 0 2906 5 1581 369 1037 + 3135 2 3 0 2907 5 1602 1089 1090 + 3136 2 3 0 2908 5 1602 1090 343 + 3137 2 3 0 2909 5 1583 549 1381 + 3138 2 3 0 2910 5 1583 551 1383 + 3139 2 3 0 2911 5 1748 1043 1652 + 3140 2 3 0 2912 5 1735 1624 1584 + 3141 2 3 0 2913 5 1585 1104 1367 + 3142 2 3 0 2914 5 1585 1367 1045 + 3143 2 3 0 2915 5 1586 551 1050 + 3144 2 3 0 2916 5 1586 1048 1094 + 3145 2 3 0 2917 5 1587 1051 345 + 3146 2 3 0 2918 5 1587 345 1380 + 3147 2 3 0 2919 5 1588 356 970 + 3148 2 3 0 2920 5 1588 970 552 + 3149 2 3 0 2921 5 1589 1054 1340 + 3150 2 3 0 2922 5 1608 1340 517 + 3151 2 3 0 2923 5 1590 343 1382 + 3152 2 3 0 2924 5 1590 550 1057 + 3153 2 3 0 2925 5 1591 1067 358 + 3154 2 3 0 2926 5 1591 358 1386 + 3155 2 3 0 2927 5 1592 530 1195 + 3156 2 3 0 2928 5 1592 1195 1388 + 3157 2 3 0 2929 5 1593 537 1370 + 3158 2 3 0 2930 5 1593 1370 1371 + 3159 2 3 0 2931 5 1596 1371 333 + 3160 2 3 0 2932 5 1594 1073 537 + 3161 2 3 0 2933 5 1595 1097 1557 + 3162 2 3 0 2934 5 1595 1073 1594 + 3163 2 3 0 2935 5 1596 1594 1371 + 3164 2 3 0 2936 5 1596 333 1573 + 3165 2 3 0 2937 5 1597 324 1028 + 3166 2 3 0 2938 5 1597 1376 1389 + 3167 2 3 0 2939 5 1598 1389 1077 + 3168 2 3 0 2940 5 1623 1598 556 + 3169 2 3 0 2941 5 1599 1196 1080 + 3170 2 3 0 2942 5 1599 362 1197 + 3171 2 3 0 2943 5 1600 1078 1362 + 3172 2 3 0 2944 5 1600 362 1599 + 3173 2 3 0 2945 5 1601 558 1393 + 3174 2 3 0 2946 5 1601 1394 1395 + 3175 2 3 0 2947 5 1602 1582 1089 + 3176 2 3 0 2948 5 1602 343 1590 + 3177 2 3 0 2949 5 1603 276 843 + 3178 2 3 0 2950 5 1603 843 1116 + 3179 2 3 0 2951 5 1604 1516 1117 + 3180 2 3 0 2952 5 1604 1117 276 + 3181 2 3 0 2953 5 1605 1467 490 + 3182 2 3 0 2954 5 1605 490 851 + 3183 2 3 0 2955 5 1606 576 1161 + 3184 2 3 0 2956 5 1606 526 994 + 3185 2 3 0 2957 5 1607 585 1200 + 3186 2 3 0 2958 5 1607 1200 1356 + 3187 2 3 0 2959 5 1608 1157 353 + 3188 2 3 0 2960 5 1608 353 1589 + 3189 2 3 0 2961 5 1621 1609 1356 + 3190 2 3 0 2962 5 1609 1571 527 + 3191 2 3 0 2963 5 1611 1610 1228 + 3192 2 3 0 2964 5 1610 461 1494 + 3193 2 3 0 2965 5 1611 461 1610 + 3194 2 3 0 2966 5 1611 1228 1231 + 3195 2 3 0 2967 5 1612 412 1255 + 3196 2 3 0 2968 5 1612 1255 1492 + 3197 2 3 0 2969 5 1613 1276 260 + 3198 2 3 0 2970 5 1613 263 1501 + 3199 2 3 0 2971 5 1614 1288 570 + 3200 2 3 0 2972 5 1614 570 1401 + 3201 2 3 0 2973 5 1615 1289 591 + 3202 2 3 0 2974 5 1615 591 1288 + 3203 2 3 0 2975 5 1616 1296 1294 + 3204 2 3 0 2976 5 1616 279 1450 + 3205 2 3 0 2977 5 1618 1550 1311 + 3206 2 3 0 2978 5 1618 1552 1617 + 3207 2 3 0 2979 5 1618 299 1551 + 3208 2 3 0 2980 5 1618 1551 1552 + 3209 2 3 0 2981 5 1619 507 1572 + 3210 2 3 0 2982 5 1619 353 1554 + 3211 2 3 0 2983 5 1620 350 1423 + 3212 2 3 0 2984 5 1620 563 1348 + 3213 2 3 0 2985 5 1621 1198 529 + 3214 2 3 0 2986 5 1621 529 1571 + 3215 2 3 0 2987 5 1622 1357 326 + 3216 2 3 0 2988 5 1622 326 654 + 3217 2 3 0 2989 5 1623 556 1392 + 3218 2 3 0 2990 5 1623 324 1597 + 3219 2 3 0 2991 5 1624 568 1400 + 3220 2 3 0 2992 5 1624 1400 1584 + 3221 2 3 0 2993 5 1734 58 1625 + 3222 2 3 0 2994 5 1701 74 421 + 3223 2 3 0 2995 5 1743 1629 559 + 3224 2 3 0 2996 5 1736 1677 82 + 3225 2 3 0 2997 5 1737 78 566 + 3226 2 3 0 2998 5 1655 80 81 + 3227 2 3 0 2999 5 1658 1649 84 + 3228 2 3 0 3000 5 1738 1690 86 + 3229 2 3 0 3001 5 1739 62 1671 + 3230 2 3 0 3002 5 1740 1695 65 + 3231 2 3 0 3003 5 1678 76 77 + 3232 2 3 0 3004 5 1682 1667 1681 + 3233 2 3 0 3005 5 1729 99 100 + 3234 2 3 0 3006 5 1673 96 1161 + 3235 2 3 0 3007 5 1708 94 1691 + 3236 2 3 0 3008 5 1725 1639 1674 + 3237 2 3 0 3009 5 1718 70 545 + 3238 2 3 0 3010 5 1741 1707 561 + 3239 2 3 0 3011 5 1732 1662 1167 + 3240 2 3 0 3012 5 1740 68 1676 + 3241 2 3 0 3013 5 1742 1672 579 + 3242 2 3 0 3014 5 1681 1667 60 + 3243 2 3 0 3015 5 1734 419 1733 + 3244 2 3 0 3016 5 1626 75 76 + 3245 2 3 0 3017 5 1702 347 1683 + 3246 2 3 0 3018 5 1688 1627 434 + 3247 2 3 0 3019 5 1714 347 1678 + 3248 2 3 0 3020 5 1656 566 79 + 3249 2 3 0 3021 5 1686 1628 371 + 3250 2 3 0 3022 5 1629 89 90 + 3251 2 3 0 3023 5 1743 1704 1629 + 3252 2 3 0 3024 5 1745 1744 1632 + 3253 2 3 0 3025 5 1746 1745 365 + 3254 2 3 0 3026 5 1651 1043 1045 + 3255 2 3 0 3027 5 1686 434 1627 + 3256 2 3 0 3028 5 1747 1745 372 + 3257 2 3 0 3029 5 1746 1650 1715 + 3258 2 3 0 3030 5 1633 371 1628 + 3259 2 3 0 3031 5 1656 79 80 + 3260 2 3 0 3032 5 1634 369 1398 + 3261 2 3 0 3033 5 1730 1634 567 + 3262 2 3 0 3034 5 1730 348 1052 + 3263 2 3 0 3035 5 1635 434 1631 + 3264 2 3 0 3036 5 1636 1631 366 + 3265 2 3 0 3037 5 1748 1652 366 + 3266 2 3 0 3038 5 1669 1637 419 + 3267 2 3 0 3039 5 1637 413 1178 + 3268 2 3 0 3040 5 1697 545 1696 + 3269 2 3 0 3041 5 1638 544 546 + 3270 2 3 0 3042 5 1749 1680 582 + 3271 2 3 0 3043 5 1718 1639 574 + 3272 2 3 0 3044 5 1750 1701 421 + 3273 2 3 0 3045 5 1751 1750 421 + 3274 2 3 0 3046 5 1702 1683 548 + 3275 2 3 0 3047 5 1757 1685 1703 + 3276 2 3 0 3048 5 1642 83 84 + 3277 2 3 0 3049 5 1736 1655 1677 + 3278 2 3 0 3050 5 1687 1641 1683 + 3279 2 3 0 3051 5 1643 434 1635 + 3280 2 3 0 3052 5 1752 1644 559 + 3281 2 3 0 3053 5 1644 558 1084 + 3282 2 3 0 3054 5 1645 1084 363 + 3283 2 3 0 3055 5 1647 1645 524 + 3284 2 3 0 3056 5 1706 560 558 + 3285 2 3 0 3057 5 1752 1741 561 + 3286 2 3 0 3058 5 1704 524 1665 + 3287 2 3 0 3059 5 1743 1644 1647 + 3288 2 3 0 3060 5 1717 1716 364 + 3289 2 3 0 3061 5 1753 1747 1649 + 3290 2 3 0 3062 5 1649 372 1642 + 3291 2 3 0 3063 5 1649 1642 84 + 3292 2 3 0 3064 5 1715 568 1624 + 3293 2 3 0 3065 5 1754 1753 1716 + 3294 2 3 0 3066 5 1651 1366 348 + 3295 2 3 0 3067 5 1651 1635 1636 + 3296 2 3 0 3068 5 1652 1636 366 + 3297 2 3 0 3069 5 1652 1043 1651 + 3298 2 3 0 3070 5 1724 564 1668 + 3299 2 3 0 3071 5 1756 1755 1724 + 3300 2 3 0 3072 5 1657 1654 565 + 3301 2 3 0 3073 5 1711 1654 593 + 3302 2 3 0 3074 5 1677 81 82 + 3303 2 3 0 3075 5 1655 1632 1633 + 3304 2 3 0 3076 5 1656 1633 1628 + 3305 2 3 0 3077 5 1656 1628 566 + 3306 2 3 0 3078 5 1757 1684 1685 + 3307 2 3 0 3079 5 1703 567 1657 + 3308 2 3 0 3080 5 1690 85 86 + 3309 2 3 0 3081 5 1764 1658 1690 + 3310 2 3 0 3082 5 1659 339 1085 + 3311 2 3 0 3083 5 1659 1085 568 + 3312 2 3 0 3084 5 1759 1738 1665 + 3313 2 3 0 3085 5 1660 363 982 + 3314 2 3 0 3086 5 1707 1705 1661 + 3315 2 3 0 3087 5 1661 91 92 + 3316 2 3 0 3088 5 1662 92 93 + 3317 2 3 0 3089 5 1732 1167 575 + 3318 2 3 0 3090 5 1721 1663 578 + 3319 2 3 0 3091 5 1663 544 579 + 3320 2 3 0 3092 5 1760 1742 579 + 3321 2 3 0 3093 5 1728 1664 583 + 3322 2 3 0 3094 5 1665 87 88 + 3323 2 3 0 3095 5 1759 524 1689 + 3324 2 3 0 3096 5 1761 1666 580 + 3325 2 3 0 3097 5 1666 419 1625 + 3326 2 3 0 3098 5 1667 1625 59 + 3327 2 3 0 3099 5 1667 59 60 + 3328 2 3 0 3100 5 1668 564 1093 + 3329 2 3 0 3101 5 1670 1668 413 + 3330 2 3 0 3102 5 1768 419 1761 + 3331 2 3 0 3103 5 1762 1726 414 + 3332 2 3 0 3104 5 1670 581 1668 + 3333 2 3 0 3105 5 1670 413 1669 + 3334 2 3 0 3106 5 1675 63 64 + 3335 2 3 0 3107 5 1739 1671 582 + 3336 2 3 0 3108 5 1694 72 73 + 3337 2 3 0 3109 5 1672 583 1664 + 3338 2 3 0 3110 5 1692 576 1133 + 3339 2 3 0 3111 5 1673 95 96 + 3340 2 3 0 3112 5 1749 1639 1638 + 3341 2 3 0 3113 5 1674 582 1671 + 3342 2 3 0 3114 5 1675 1671 63 + 3343 2 3 0 3115 5 1725 64 1695 + 3344 2 3 0 3116 5 1676 69 574 + 3345 2 3 0 3117 5 1695 1676 574 + 3346 2 3 0 3118 5 1736 82 1642 + 3347 2 3 0 3119 5 1736 1642 372 + 3348 2 3 0 3120 5 1737 1678 77 + 3349 2 3 0 3121 5 1678 347 1626 + 3350 2 3 0 3122 5 1682 1666 1667 + 3351 2 3 0 3123 5 1739 1679 1681 + 3352 2 3 0 3124 5 1749 582 1674 + 3353 2 3 0 3125 5 1680 414 1679 + 3354 2 3 0 3126 5 1681 60 61 + 3355 2 3 0 3127 5 1739 1681 61 + 3356 2 3 0 3128 5 1726 1682 1679 + 3357 2 3 0 3129 5 1682 580 1666 + 3358 2 3 0 3130 5 1714 1688 347 + 3359 2 3 0 3131 5 1687 434 1643 + 3360 2 3 0 3132 5 1755 1653 1724 + 3361 2 3 0 3133 5 1763 1684 1709 + 3362 2 3 0 3134 5 1685 1640 548 + 3363 2 3 0 3135 5 1685 1641 370 + 3364 2 3 0 3136 5 1686 1627 1628 + 3365 2 3 0 3137 5 1686 371 1630 + 3366 2 3 0 3138 5 1687 1643 370 + 3367 2 3 0 3139 5 1687 370 1641 + 3368 2 3 0 3140 5 1688 1683 347 + 3369 2 3 0 3141 5 1688 434 1687 + 3370 2 3 0 3142 5 1689 524 1645 + 3371 2 3 0 3143 5 1689 1645 363 + 3372 2 3 0 3144 5 1738 86 87 + 3373 2 3 0 3145 5 1764 1758 1658 + 3374 2 3 0 3146 5 1691 95 1673 + 3375 2 3 0 3147 5 1708 1691 528 + 3376 2 3 0 3148 5 1692 1133 527 + 3377 2 3 0 3149 5 1692 1570 528 + 3378 2 3 0 3150 5 1734 57 58 + 3379 2 3 0 3151 5 1733 419 1637 + 3380 2 3 0 3152 5 1701 73 74 + 3381 2 3 0 3153 5 1765 1701 1750 + 3382 2 3 0 3154 5 1740 65 66 + 3383 2 3 0 3155 5 1725 574 1639 + 3384 2 3 0 3156 5 1760 71 1742 + 3385 2 3 0 3157 5 1696 545 70 + 3386 2 3 0 3158 5 1697 544 1638 + 3387 2 3 0 3159 5 1697 1638 545 + 3388 2 3 0 3160 5 1721 544 1663 + 3389 2 3 0 3161 5 1698 414 1680 + 3390 2 3 0 3162 5 1766 1719 1722 + 3391 2 3 0 3163 5 1728 1699 578 + 3392 2 3 0 3164 5 1700 583 1694 + 3393 2 3 0 3165 5 1727 1700 547 + 3394 2 3 0 3166 5 1751 421 1702 + 3395 2 3 0 3167 5 1765 1750 547 + 3396 2 3 0 3168 5 1751 1702 548 + 3397 2 3 0 3169 5 1702 421 1626 + 3398 2 3 0 3170 5 1712 1703 370 + 3399 2 3 0 3171 5 1757 1703 1657 + 3400 2 3 0 3172 5 1704 88 1629 + 3401 2 3 0 3173 5 1704 1647 524 + 3402 2 3 0 3174 5 1705 90 91 + 3403 2 3 0 3175 5 1705 91 1661 + 3404 2 3 0 3176 5 1706 558 1644 + 3405 2 3 0 3177 5 1752 559 1741 + 3406 2 3 0 3178 5 1707 90 1705 + 3407 2 3 0 3179 5 1752 561 1646 + 3408 2 3 0 3180 5 1708 93 94 + 3409 2 3 0 3181 5 1708 528 1166 + 3410 2 3 0 3182 5 1766 1727 346 + 3411 2 3 0 3183 5 1763 1709 1727 + 3412 2 3 0 3184 5 1757 1710 1684 + 3413 2 3 0 3185 5 1710 565 1653 + 3414 2 3 0 3186 5 1711 593 1423 + 3415 2 3 0 3187 5 1711 564 1653 + 3416 2 3 0 3188 5 1712 567 1703 + 3417 2 3 0 3189 5 1712 370 1643 + 3418 2 3 0 3190 5 1713 1634 1398 + 3419 2 3 0 3191 5 1713 1654 1657 + 3420 2 3 0 3192 5 1714 566 1627 + 3421 2 3 0 3193 5 1714 1627 1688 + 3422 2 3 0 3194 5 1767 1715 366 + 3423 2 3 0 3195 5 1767 1744 1746 + 3424 2 3 0 3196 5 1731 569 1095 + 3425 2 3 0 3197 5 1753 365 1747 + 3426 2 3 0 3198 5 1731 1717 569 + 3427 2 3 0 3199 5 1717 364 1660 + 3428 2 3 0 3200 5 1718 69 70 + 3429 2 3 0 3201 5 1718 545 1639 + 3430 2 3 0 3202 5 1766 1722 578 + 3431 2 3 0 3203 5 1756 1719 346 + 3432 2 3 0 3204 5 1720 581 1670 + 3433 2 3 0 3205 5 1768 1720 1669 + 3434 2 3 0 3206 5 1766 578 1699 + 3435 2 3 0 3207 5 1721 414 1698 + 3436 2 3 0 3208 5 1723 1719 1720 + 3437 2 3 0 3209 5 1762 1721 1722 + 3438 2 3 0 3210 5 1769 1768 580 + 3439 2 3 0 3211 5 1769 1726 1762 + 3440 2 3 0 3212 5 1756 581 1719 + 3441 2 3 0 3213 5 1755 346 1709 + 3442 2 3 0 3214 5 1725 1674 1675 + 3443 2 3 0 3215 5 1725 1675 64 + 3444 2 3 0 3216 5 1762 414 1721 + 3445 2 3 0 3217 5 1726 580 1682 + 3446 2 3 0 3218 5 1727 1699 1700 + 3447 2 3 0 3219 5 1763 1727 547 + 3448 2 3 0 3220 5 1728 583 1699 + 3449 2 3 0 3221 5 1728 578 1663 + 3450 2 3 0 3222 5 1729 526 1161 + 3451 2 3 0 3223 5 1729 97 98 + 3452 2 3 0 3224 5 1730 1052 1634 + 3453 2 3 0 3225 5 1730 567 1712 + 3454 2 3 0 3226 5 1754 1095 1659 + 3455 2 3 0 3227 5 1754 1659 1650 + 3456 2 3 0 3228 5 1732 575 1409 + 3457 2 3 0 3229 5 1732 561 1661 + 3458 2 3 0 3230 5 1733 1637 543 + 3459 2 3 0 3231 5 1733 543 1693 + 3460 2 3 0 3232 5 1734 1693 57 + 3461 2 3 0 3233 5 1734 1625 419 + 3462 2 3 0 3234 5 1748 1735 1584 + 3463 2 3 0 3235 5 1735 366 1715 + 3464 2 3 0 3236 5 1736 372 1632 + 3465 2 3 0 3237 5 1736 1632 1655 + 3466 2 3 0 3238 5 1737 566 1714 + 3467 2 3 0 3239 5 1737 77 78 + 3468 2 3 0 3240 5 1759 1665 524 + 3469 2 3 0 3241 5 1764 1759 364 + 3470 2 3 0 3242 5 1739 582 1679 + 3471 2 3 0 3243 5 1739 61 62 + 3472 2 3 0 3244 5 1740 66 67 + 3473 2 3 0 3245 5 1740 1676 1695 + 3474 2 3 0 3246 5 1741 559 1629 + 3475 2 3 0 3247 5 1741 1629 90 + 3476 2 3 0 3248 5 1742 71 72 + 3477 2 3 0 3249 5 1742 72 1672 + 3478 2 3 0 3250 5 1743 559 1644 + 3479 2 3 0 3251 5 1743 1647 1704 + 3480 2 3 0 3252 5 1744 1630 371 + 3481 2 3 0 3253 5 1744 371 1633 + 3482 2 3 0 3254 5 1745 1632 372 + 3483 2 3 0 3255 5 1746 365 1650 + 3484 2 3 0 3256 5 1767 1746 1715 + 3485 2 3 0 3257 5 1746 1744 1745 + 3486 2 3 0 3258 5 1747 372 1649 + 3487 2 3 0 3259 5 1747 365 1745 + 3488 2 3 0 3260 5 1748 366 1735 + 3489 2 3 0 3261 5 1748 1584 1043 + 3490 2 3 0 3262 5 1749 1674 1639 + 3491 2 3 0 3263 5 1749 546 1680 + 3492 2 3 0 3264 5 1750 1640 547 + 3493 2 3 0 3265 5 1765 547 1700 + 3494 2 3 0 3266 5 1751 548 1640 + 3495 2 3 0 3267 5 1751 1640 1750 + 3496 2 3 0 3268 5 1752 1646 1706 + 3497 2 3 0 3269 5 1752 1706 1644 + 3498 2 3 0 3270 5 1753 1648 1716 + 3499 2 3 0 3271 5 1754 1716 1731 + 3500 2 3 0 3272 5 1754 1731 1095 + 3501 2 3 0 3273 5 1754 365 1753 + 3502 2 3 0 3274 5 1755 1709 1710 + 3503 2 3 0 3275 5 1755 1710 1653 + 3504 2 3 0 3276 5 1756 1724 581 + 3505 2 3 0 3277 5 1756 346 1755 + 3506 2 3 0 3278 5 1757 1657 565 + 3507 2 3 0 3279 5 1757 565 1710 + 3508 2 3 0 3280 5 1758 364 1716 + 3509 2 3 0 3281 5 1758 1648 1658 + 3510 2 3 0 3282 5 1759 1689 364 + 3511 2 3 0 3283 5 1764 364 1758 + 3512 2 3 0 3284 5 1760 579 1697 + 3513 2 3 0 3285 5 1760 1697 1696 + 3514 2 3 0 3286 5 1768 1761 580 + 3515 2 3 0 3287 5 1761 419 1666 + 3516 2 3 0 3288 5 1762 1722 1723 + 3517 2 3 0 3289 5 1769 1720 1768 + 3518 2 3 0 3290 5 1763 547 1640 + 3519 2 3 0 3291 5 1763 1640 1685 + 3520 2 3 0 3292 5 1764 1690 1738 + 3521 2 3 0 3293 5 1764 1738 1759 + 3522 2 3 0 3294 5 1765 1700 1694 + 3523 2 3 0 3295 5 1765 1694 1701 + 3524 2 3 0 3296 5 1766 1699 1727 + 3525 2 3 0 3297 5 1766 346 1719 + 3526 2 3 0 3298 5 1767 366 1630 + 3527 2 3 0 3299 5 1767 1630 1744 + 3528 2 3 0 3300 5 1768 1669 419 + 3529 2 3 0 3301 5 1769 580 1726 + 3530 2 3 0 3302 5 1769 1762 1723 + 3531 2 3 0 3303 5 1769 1723 1720 + 3532 2 3 0 3304 5 1778 1770 1774 + 3533 2 3 0 3305 5 1777 423 622 + 3534 2 3 0 3306 5 1775 195 1772 + 3535 2 3 0 3307 5 1776 1773 422 + 3536 2 3 0 3308 5 191 670 190 + 3537 2 3 0 3309 5 1774 422 1773 + 3538 2 3 0 3310 5 1770 415 1170 + 3539 2 3 0 3311 5 1771 1 2 + 3540 2 3 0 3312 5 1778 1771 415 + 3541 2 3 0 3313 5 1775 1772 416 + 3542 2 3 0 3314 5 1772 196 197 + 3543 2 3 0 3315 5 1773 197 198 + 3544 2 3 0 3316 5 1776 422 1172 + 3545 2 3 0 3317 5 1774 198 199 + 3546 2 3 0 3318 5 1778 1774 199 + 3547 2 3 0 3319 5 1775 194 195 + 3548 2 3 0 3320 5 1775 416 1446 + 3549 2 3 0 3321 5 1776 1172 604 + 3550 2 3 0 3322 5 1776 416 1772 + 3551 2 3 0 3323 5 1777 622 669 + 3552 2 3 0 3324 5 1777 669 192 + 3553 2 3 0 3325 5 1778 199 1771 + 3554 2 3 0 3326 5 1778 415 1770 + 3555 2 3 0 3327 5 101 994 100 + 3556 2 3 0 3328 5 392 1027 373 +$EndElements diff --git a/regtests/ww3_tp2.22/input/namelists_explicit.nml b/regtests/ww3_tp2.22/input/namelists_explicit.nml new file mode 100644 index 000000000..9ec36af80 --- /dev/null +++ b/regtests/ww3_tp2.22/input/namelists_explicit.nml @@ -0,0 +1,26 @@ +&UNST +UGOBCAUTO = F, +UGOBCDEPTH= -10., +EXPFSN = T, +EXPFSPSI = F, +EXPFSFCT = F, +IMPFSN = F, +EXPTOTAL = F, +IMPTOTAL = F, +IMPREFRACTION = F, +IMPFREQSHIFT = F, +IMPSOURCE = F, +SETUP_APPLY_WLV = F, +SOLVERTHR_SETUP=1E-14, +CRIT_DEP_SETUP=0.1, +JGS_USE_JACOBI = T, +JGS_BLOCK_GAUSS_SEIDEL = T, +JGS_TERMINATE_MAXITER = T, +JGS_MAXITER = 1000, +JGS_TERMINATE_NORM = F, +JGS_TERMINATE_DIFFERENCE = T, +JGS_DIFF_THR = 1.E-8, +JGS_PMIN = 3.0, +JGS_LIMITER = F, +JGS_NORM_THR = 1.E-20 / +END OF NAMELISTS diff --git a/regtests/ww3_tp2.22/input/namelists_implicit.nml b/regtests/ww3_tp2.22/input/namelists_implicit.nml new file mode 100644 index 000000000..d7ea8672e --- /dev/null +++ b/regtests/ww3_tp2.22/input/namelists_implicit.nml @@ -0,0 +1,26 @@ +&UNST +UGOBCAUTO = F, +UGOBCDEPTH= -10., +EXPFSN = F, +EXPFSPSI = F, +EXPFSFCT = F, +IMPFSN = F, +EXPTOTAL = F, +IMPTOTAL = T, +IMPREFRACTION = T, +IMPFREQSHIFT = T, +IMPSOURCE = T, +SETUP_APPLY_WLV = F, +SOLVERTHR_SETUP=1E-14, +CRIT_DEP_SETUP=0.1, +JGS_USE_JACOBI = T, +JGS_BLOCK_GAUSS_SEIDEL = T, +JGS_TERMINATE_MAXITER = T, +JGS_MAXITER = 1000, +JGS_TERMINATE_NORM = F, +JGS_TERMINATE_DIFFERENCE = T, +JGS_DIFF_THR = 1.E-8, +JGS_PMIN = 3.0, +JGS_LIMITER = F, +JGS_NORM_THR = 1.E-20 / +END OF NAMELISTS diff --git a/regtests/ww3_tp2.22/input/points.list b/regtests/ww3_tp2.22/input/points.list new file mode 100644 index 000000000..9ff9a3b23 --- /dev/null +++ b/regtests/ww3_tp2.22/input/points.list @@ -0,0 +1,2 @@ +-83.02097840 9.98081977 'POINT1' +-83.01589326 9.98398516 'POINT2' diff --git a/regtests/ww3_tp2.22/input/run_post.sh b/regtests/ww3_tp2.22/input/run_post.sh new file mode 100755 index 000000000..e9acc03a9 --- /dev/null +++ b/regtests/ww3_tp2.22/input/run_post.sh @@ -0,0 +1,4 @@ +ww3_ounf +ww32xfn < ww32xfn.in +bintoc < bintoc.in +xfn diff --git a/regtests/ww3_tp2.22/input/ww32xfn.in b/regtests/ww3_tp2.22/input/ww32xfn.in new file mode 100644 index 000000000..6dc185f5a --- /dev/null +++ b/regtests/ww3_tp2.22/input/ww32xfn.in @@ -0,0 +1,4 @@ +ww3.201008_hs.nc +hs +1 + diff --git a/regtests/ww3_tp2.22/input/ww3_grid.inp b/regtests/ww3_tp2.22/input/ww3_grid.inp new file mode 100644 index 000000000..23753fb19 --- /dev/null +++ b/regtests/ww3_tp2.22/input/ww3_grid.inp @@ -0,0 +1,298 @@ +$ -------------------------------------------------------------------- $ +$ WAVEWATCH III Grid preprocessor input file $ +$ -------------------------------------------------------------------- $ +$ Grid name (C*30, in quotes) +$ + 'LIMON' +$ +$ Frequency increment factor and first frequency (Hz) ---------------- $ +$ number of frequencies (wavenumbers) and directions, relative offset +$ of first direction in terms of the directional increment [-0.5,0.5]. +$ In versions 1.18 and 2.22 of the model this value was by definiton 0, +$ it is added to mitigate the GSE for a first order scheme. Note that +$ this factor is IGNORED in the print plots in ww3_outp. +$ +1.1 0.05 36 36 0. +$ +$ Set model flags ---------------------------------------------------- $ +$ - FLDRY Dry run (input/output only, no calculation). +$ - FLCX, FLCY Activate X and Y component of propagation. +$ - FLCTH, FLCK Activate direction and wavenumber shifts. +$ - FLSOU Activate source terms. +$ + F T T T T T +$ +$ Set time steps ----------------------------------------------------- $ +$ - Time step information (this information is always read) +$ maximum global time step, maximum CFL time step for x-y and +$ k-theta, minimum source term time step (all in seconds). +$ +$ + 10 10 10 10 +$ +$ Start of namelist input section ------------------------------------ $ +$ Starting with WAVEWATCH III version 2.00, the tunable parameters +$ for source terms, propagation schemes, and numerics are read using +$ namelists. Any namelist found in the folowing sections up to the +$ end-of-section identifier string (see below) is temporarily written +$ to ww3_grid.scratch, and read from there if necessary. Namelists +$ not needed for the given switch settings will be skipped +$ automatically, and the order of the namelists is immaterial. +$ As an example, namelist input to change SWELLF and ZWND in the +$ Tolman and Chalikov input would be +$ +$ &SIN2 SWELLF = 0.1, ZWND = 15. / +$ +$ Define constants in source terms ----------------------------------- $ +$ +$ Input - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - +$ WAM-3 : Namelist SIN1 +$ CINP : Proportionality constant. +$ &SIN1 CINP= 0.25 / +$ +$ Tolman and Chalikov : Namelist SIN2 +$ ZWND : Height of wind (m). +$ SWELLF : swell factor in (2.48). +$ STABSH, STABOF, CNEG, CPOS, FNEG : +$ c0, ST0, c1, c2 and f1 in . (2.63) +$ through (2.65) for definition of +$ effective wind speed (!/STAB2). +$ +$ Nonlinear interactions - - - - - - - - - - - - - - - - - - - - - - - +$ Discrete I.A. : Namelist SNL1 +$ LAMBDA : Lambda in source term. +$ NLPROP : C in sourc term. NOTE : default +$ value depends on other source +$ terms selected. +$ KDCONV : Factor before kd in Eq. (2.24). +$ KDMIN, SNLCS1, SNLCS2, SNLCS3 : +$ Minimum kd, and constants c1-3 +$ in depth scaling function. +$ Exact interactions : Namelist SNL2 +$ IQTYPE : Type of depth treatment +$ 1 : Deep water +$ 2 : Deep water / WAM scaling +$ 3 : Shallow water +$ TAILNL : Parametric tail power. +$ NDEPTH : Number of depths in for which +$ integration space is established. +$ Used for IQTYPE = 3 only +$ Namelist ANL2 +$ DEPTHS : Array with depths for NDEPTH = 3 +$ +$ Dissipation - - - - - - - - - - - - - - - - - - - - - - - - - - - - +$ WAM-3 : Namelist SDS1 +$ CDIS, APM : As in source term. +$ +$ Tolman and Chalikov : Namelist SDS2 +$ SDSA0, SDSA1, SDSA2, SDSB0, SDSB1, PHIMIN : +$ Constants a0, a1, a2, b0, b1 and +$ PHImin. +$ +$ BAJ (adjusted) +$ +&SIN4 BETAMAX = 1.52, Z0MAX = 1.002 / +$&SDS4 SDSC1 = 1.0, SDSC2 = 0.0 , SDSBCK = 0.100, SDSHCK = 1.0, SDSDTH = 0 / +$&SDB1 BJGAM = 1.0, BJALFA = 0.001 / +&SNL1 NLPROP = 3.1E7 / +$ +$ TEST451 +$ +$ &SNL1 NLPROP=2.5E7 / +$ +$ +&UNST +UGOBCAUTO = F +UGOBCDEPTH= -10. +EXPFSN = F, +EXPFSPSI = F, +EXPFSFCT = F, +IMPFSN = F, +IMPTOTAL = T, +EXPTOTAL = F, +IMPREFRACTION = T, +IMPFREQSHIFT = T, +IMPSOURCE = T, +SETUP_APPLY_WLV = F +SOLVERTHR_SETUP=1E-14 +CRIT_DEP_SETUP=0.1 +JGS_USE_JACOBI = T, +JGS_NLEVEL = 0 +JGS_SOURCE_NONLINEAR = F, +JGS_BLOCK_GAUSS_SEIDEL = T, +JGS_TERMINATE_MAXITER = T, +JGS_MAXITER = 100000, +JGS_TERMINATE_NORM = F, +JGS_TERMINATE_DIFFERENCE = T, +JGS_DIFF_THR = 1.E-4, +JGS_PMIN = 3.0 +JGS_LIMITER = F, +JGS_BLOCK_GAUSS_SEIDEL = T +JGS_NORM_THR = 1.E-6 +/ +$ +$ Bottom friction - - - - - - - - - - - - - - - - - - - - - - - - - - +$ JONSWAP : Namelist SBT1 +$ GAMMA : As it says. +$ &SBT1 GAMMA = 0.15 / +$ +$ Propagation schemes ------------------------------------------------ $ +$ First order : Namelist PRO1 +$ CFLTM : Maximum CFL number for refraction. +$ +$ UQ with diffusion : Namelist PRO2 +$ CFLTM : Maximum CFL number for refraction. +$ FLSOFT : Flag for 'soft' land boundaries. +$ DTIME : Swell age (s) in garden sprinkler +$ correction. If 0., all diffusion +$ switched off. If small non-zero +$ (DEFAULT !!!) only wave growth +$ diffusion. +$ LATMIN : Maximum latitude used in calc. of +$ strength of diffusion for prop. +$ +$ UQ with averaging : Namelist PRO3 +$ CFLTM : Maximum CFL number for refraction. +$ FLSOFT : Flag for 'soft' land boundaries. +$ WDTHCG : Tuning factor propag. direction. +$ WDTHTH : Tuning factor normal direction. +$ +$ UQ with divergence : Namelist PRO4 +$ CFLTM : Maximum CFL number for refraction. +$ FLSOFT : Flag for 'soft' land boundaries. +$ QTFAC : Tuning factor Eq. (3.41). +$ RSFAC : Tuning factor Eq. (3.42). +$ RNFAC : Tuning factor Eq. (3.43). +$ +$ Miscellaneous ------------------------------------------------------ $ +$ Misc. parameters : Namelist MISC +$ CICE0 : Ice concentration cut-off. +$ CICEN : Ice concentration cut-off. +$ XSEED : Xseed in seeding alg. (!/SEED). +$ FLAGTR : Indicating presence and type of +$ subgrid information : +$ 0 : No subgrid information. +$ 1 : Transparancies at cell boun- +$ daries between grid points. +$ 2 : Transp. at cell centers. +$ 3 : Like 1 with cont. ice. +$ 4 : Like 2 with cont. ice. +$ XP, XR, XFILT +$ Xp, Xr and Xf for the dynamic +$ integration scheme. +$ +$ In the 'Out of the box' test setup we run with sub-grid obstacles +$ and with continuous ice treatment. +$ +$ &MISC CICE0 = 0.25, CICEN = 0.75, FLAGTR = 4 / +$ +$ Mandatory string to identify end of namelist input section. +$ +END OF NAMELISTS +$ +$ Define grid -------------------------------------------------------- $ +$ + 'UNST' T 'NONE' +$ + 1.0 0.10 20 -1. 4 1 '(20f10.2)' 'NAME' 'limon_ll.2dm' +$ +$ If the above unit number equals 10, the bottom data is read from +$ this file and follows below (no intermediate comment lines allowed). +$ +$ 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 +$ +$ If sub-grid information is avalaible as indicated by FLAGTR above, +$ additional input to define this is needed below. In such cases a +$ field of fractional obstructions at or between grid points needs to +$ be supplied. First the location and format of the data is defined +$ by (as above) : +$ - Unit number of file (can be 10, and/or identical to bottem depth +$ unit), scale factor for fractional obstruction, IDLA, IDFM, +$ format for formatted read, FROM and filename +$ +$ 10 0.2 3 1 '(....)' 'NAME' 'obstr.inp' +$ +$ *** NOTE if this unit number is the same as the previous bottom +$ depth unit number, it is assumed that this is the same file +$ without further checks. *** +$ +$ If the above unit number equals 10, the bottom data is read from +$ this file and follows below (no intermediate comment lines allowed, +$ except between the two fields). +$ +$ 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 +$ 0 0 0 0 0 0 0 0 0 0 0 0 +$ 0 0 0 0 0 0 5 0 0 0 0 0 +$ 0 0 0 0 0 0 5 0 0 0 0 0 +$ 0 0 0 0 0 0 4 0 0 0 0 0 +$ 0 0 0 0 0 0 4 0 0 0 0 0 +$ 0 0 0 0 0 0 5 0 0 0 0 0 +$ 0 0 0 0 0 0 5 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 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 5 5 5 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 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 +$ +$ *** NOTE size of fields is always NX * NY *** +$ + 10 3 1 '(....)' 'PART' 'mapsta.inp' +$ Input boundary points ---------------------------------------------- $ +$ An unlimited number of lines identifying points at which input +$ boundary conditions are to be defined. If the actual input data is +$ not defined in the actual wave model run, the initial conditions +$ will be applied as constant boundary conditions. Each line contains: +$ Discrete grid counters (IX,IY) of the active point and a +$ connect flag. If this flag is true, and the present and previous +$ point are on a grid line or diagonal, all intermediate points +$ are also defined as boundary points. +$ + 66 1 F + 99 1 T +$ +$ Close list by defining point (0,0) (mandatory) +$ + 0 0 F +$ +$ +$ +$ Excluded grid points from segment data ( FROM != PART ) +$ First defined as lines, identical to the definition of the input +$ boundary points, and closed the same way. +$ + 0 0 F +$ +$ Second, define a point in a closed body of sea points to remove +$ the entire body os sea points. Also close by point (0,0) +$ + 0 0 +$ +$ Output boundary points --------------------------------------------- $ +$ Output boundary points are defined as a number of straight lines, +$ defined by its starting point (X0,Y0), increments (DX,DY) and number +$ of points. A negative number of points starts a new output file. +$ Note that this data is only generated if requested by the actual +$ program. Example again for spherical grid in degrees. +$ +$ -2.5312 48.5 0.00 0.008738 102 +$ -2.5312 49.3850 0.013554 0.00 51 +$ +$ Close list by defining line with 0 points (mandatory) +$ + 0. 0. 0. 0. 0 +$ +$ -------------------------------------------------------------------- $ +$ End of input file $ +$ -------------------------------------------------------------------- $ diff --git a/regtests/ww3_tp2.22/input/ww3_grid.nml b/regtests/ww3_tp2.22/input/ww3_grid.nml new file mode 100644 index 000000000..87506bbd8 --- /dev/null +++ b/regtests/ww3_tp2.22/input/ww3_grid.nml @@ -0,0 +1,74 @@ +! -------------------------------------------------------------------- ! +! WAVEWATCH III - ww3_grid.nml - Grid pre-processing ! +! -------------------------------------------------------------------- ! + +! -------------------------------------------------------------------- ! +! Define the spectrum parameterization via SPECTRUM_NML namelist +! -------------------------------------------------------------------- ! +&SPECTRUM_NML + SPECTRUM%XFR = 1.1 + SPECTRUM%FREQ1 = 0.05 + SPECTRUM%NK = 36 + SPECTRUM%NTH = 36 +/ + +! -------------------------------------------------------------------- ! +! Define the run parameterization via RUN_NML namelist +! -------------------------------------------------------------------- ! +&RUN_NML + RUN%FLCX = T + RUN%FLCY = T + RUN%FLCK = T + RUN%FLCTH = T + RUN%FLSOU = T +/ + +! -------------------------------------------------------------------- ! +! Define the timesteps parameterization via TIMESTEPS_NML namelist +! -------------------------------------------------------------------- ! +&TIMESTEPS_NML + TIMESTEPS%DTMAX = 10 + TIMESTEPS%DTXY = 10 + TIMESTEPS%DTKTH = 10 + TIMESTEPS%DTMIN = 10 +/ + +! -------------------------------------------------------------------- ! +! Define the grid to preprocess via GRID_NML namelist +! -------------------------------------------------------------------- ! +&GRID_NML + GRID%NAME = 'LIMON' + GRID%NML = 'namelists.nml' + GRID%TYPE = 'UNST' + GRID%COORD = 'SPHE' + GRID%CLOS = 'NONE' + GRID%ZLIM = 1.0 + GRID%DMIN = 0.10 +/ + +! -------------------------------------------------------------------- ! +! Define the unstructured grid type via UNST_NML namelist +! -------------------------------------------------------------------- ! +&UNST_NML + UNST%SF = -1. + UNST%FILENAME = 'limon_ll.msh' + UNST%IDLA = 4 + UNST%FORMAT = '(20f10.2)' +/ + +! -------------------------------------------------------------------- ! +! Define the input boundary points via INBND_COUNT_NML and +! INBND_POINT_NML namelist +! -------------------------------------------------------------------- ! +&INBND_COUNT_NML + INBND_COUNT%N_POINT = 2 +/ + +&INBND_POINT_NML + INBND_POINT(1) = 66 1 F + INBND_POINT(2) = 99 1 T +/ + +! -------------------------------------------------------------------- ! +! WAVEWATCH III - end of namelist ! +! -------------------------------------------------------------------- ! diff --git a/regtests/ww3_tp2.22/input/ww3_grid_pdlib.inp b/regtests/ww3_tp2.22/input/ww3_grid_pdlib.inp new file mode 100644 index 000000000..c72f5e229 --- /dev/null +++ b/regtests/ww3_tp2.22/input/ww3_grid_pdlib.inp @@ -0,0 +1,235 @@ +$ -------------------------------------------------------------------- $ +$ WAVEWATCH III Grid preprocessor input file $ +$ -------------------------------------------------------------------- $ +$ Grid name (C*30, in quotes) +$ + 'LIMON' +$ +$ Frequency increment factor and first frequency (Hz) ---------------- $ +$ number of frequencies (wavenumbers) and directions, relative offset +$ of first direction in terms of the directional increment [-0.5,0.5]. +$ In versions 1.18 and 2.22 of the model this value was by definiton 0, +$ it is added to mitigate the GSE for a first order scheme. Note that +$ this factor is IGNORED in the print plots in ww3_outp. +$ +1.1 0.05 25 24 0. +$ +$ Set model flags ---------------------------------------------------- $ +$ - FLDRY Dry run (input/output only, no calculation). +$ - FLCX, FLCY Activate X and Y component of propagation. +$ - FLCTH, FLCK Activate direction and wavenumber shifts. +$ - FLSOU Activate source terms. +$ + F T T T T T +$ +$ Set time steps ----------------------------------------------------- $ +$ - Time step information (this information is always read) +$ maximum global time step, maximum CFL time step for x-y and +$ k-theta, minimum source term time step (all in seconds). +$ +$ + 10. 10. 10. 10. +$ +$ Start of namelist input section ------------------------------------ $ +$ Starting with WAVEWATCH III version 2.00, the tunable parameters +$ for source terms, propagation schemes, and numerics are read using +$ namelists. Any namelist found in the folowing sections up to the +$ end-of-section identifier string (see below) is temporarily written +$ to ww3_grid.scratch, and read from there if necessary. Namelists +$ not needed for the given switch settings will be skipped +$ automatically, and the order of the namelists is immaterial. +$ As an example, namelist input to change SWELLF and ZWND in the +$ Tolman and Chalikov input would be +$ +&SLN1 CLIN = 80.0, RFPM = 1.00, RFHF = 0.50 / +$ +&UNST UGOBCAUTO = F, + UGOBCDEPTH= -10., + EXPFSN = F, + EXPFSPSI = F, + EXPFSFCT = F, + IMPFSN = F, + EXPTOTAL = F, + IMPTOTAL = T, + IMPREFRACTION = T, + IMPFREQSHIFT = T, + IMPSOURCE = T, + SETUP_APPLY_WLV = F, + SOLVERTHR_SETUP=1E-14, + CRIT_DEP_SETUP=0.1, + JGS_USE_JACOBI = T, + JGS_BLOCK_GAUSS_SEIDEL = T, + JGS_TERMINATE_MAXITER = T, + JGS_MAXITER = 1000, + JGS_TERMINATE_NORM = F, + JGS_TERMINATE_DIFFERENCE = T, + JGS_DIFF_THR = 1.E-8, + JGS_PMIN = 3.0, + JGS_LIMITER = F, + JGS_NORM_THR = 1.E-20 / +$ +$ Bottom friction - - - - - - - - - - - - - - - - - - - - - - - - - - +$ JONSWAP : Namelist SBT1 +$ GAMMA : As it says. +$ &SBT1 GAMMA = 0.15 / +$ +$ Propagation schemes ------------------------------------------------ $ +$ First order : Namelist PRO1 +$ CFLTM : Maximum CFL number for refraction. +$ +$ UQ with diffusion : Namelist PRO2 +$ CFLTM : Maximum CFL number for refraction. +$ FLSOFT : Flag for 'soft' land boundaries. +$ DTIME : Swell age (s) in garden sprinkler +$ correction. If 0., all diffusion +$ switched off. If small non-zero +$ (DEFAULT !!!) only wave growth +$ diffusion. +$ LATMIN : Maximum latitude used in calc. of +$ strength of diffusion for prop. +$ +$ UQ with averaging : Namelist PRO3 +$ CFLTM : Maximum CFL number for refraction. +$ FLSOFT : Flag for 'soft' land boundaries. +$ WDTHCG : Tuning factor propag. direction. +$ WDTHTH : Tuning factor normal direction. +$ +$ UQ with divergence : Namelist PRO4 +$ CFLTM : Maximum CFL number for refraction. +$ FLSOFT : Flag for 'soft' land boundaries. +$ QTFAC : Tuning factor Eq. (3.41). +$ RSFAC : Tuning factor Eq. (3.42). +$ RNFAC : Tuning factor Eq. (3.43). +$ +$ Miscellaneous ------------------------------------------------------ $ +$ Misc. parameters : Namelist MISC +$ CICE0 : Ice concentration cut-off. +$ CICEN : Ice concentration cut-off. +$ XSEED : Xseed in seeding alg. (!/SEED). +$ FLAGTR : Indicating presence and type of +$ subgrid information : +$ 0 : No subgrid information. +$ 1 : Transparancies at cell boun- +$ daries between grid points. +$ 2 : Transp. at cell centers. +$ 3 : Like 1 with cont. ice. +$ 4 : Like 2 with cont. ice. +$ XP, XR, XFILT +$ Xp, Xr and Xf for the dynamic +$ integration scheme. +$ +$ In the 'Out of the box' test setup we run with sub-grid obstacles +$ and with continuous ice treatment. +$ +$ &MISC CICE0 = 0.25, CICEN = 0.75, FLAGTR = 4 / +$ +$ Mandatory string to identify end of namelist input section. +$ +END OF NAMELISTS +$ +$ Define grid -------------------------------------------------------- $ +$ + 'UNST' T 'NONE' +$ + 5.0 0.30 20 -1. 4 1 '(20f10.2)' 'NAME' './../input/limon_ll.msh' +$ +$ If the above unit number equals 10, the bottom data is read from +$ this file and follows below (no intermediate comment lines allowed). +$ +$ 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 +$ +$ If sub-grid information is avalaible as indicated by FLAGTR above, +$ additional input to define this is needed below. In such cases a +$ field of fractional obstructions at or between grid points needs to +$ be supplied. First the location and format of the data is defined +$ by (as above) : +$ - Unit number of file (can be 10, and/or identical to bottem depth +$ unit), scale factor for fractional obstruction, IDLA, IDFM, +$ format for formatted read, FROM and filename +$ +$ 10 0.2 3 1 '(....)' 'NAME' 'obstr.inp' +$ +$ *** NOTE if this unit number is the same as the previous bottom +$ depth unit number, it is assumed that this is the same file +$ without further checks. *** +$ +$ If the above unit number equals 10, the bottom data is read from +$ this file and follows below (no intermediate comment lines allowed, +$ except between the two fields). +$ +$ 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 +$ 0 0 0 0 0 0 0 0 0 0 0 0 +$ 0 0 0 0 0 0 5 0 0 0 0 0 +$ 0 0 0 0 0 0 5 0 0 0 0 0 +$ 0 0 0 0 0 0 4 0 0 0 0 0 +$ 0 0 0 0 0 0 4 0 0 0 0 0 +$ 0 0 0 0 0 0 5 0 0 0 0 0 +$ 0 0 0 0 0 0 5 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 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 5 5 5 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 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 +$ +$ *** NOTE size of fields is always NX * NY *** +$ + 10 3 1 '(....)' 'PART' 'mapsta.inp' +$ Input boundary points ---------------------------------------------- $ +$ An unlimited number of lines identifying points at which input +$ boundary conditions are to be defined. If the actual input data is +$ not defined in the actual wave model run, the initial conditions +$ will be applied as constant boundary conditions. Each line contains: +$ Discrete grid counters (IX,IY) of the active point and a +$ connect flag. If this flag is true, and the present and previous +$ point are on a grid line or diagonal, all intermediate points +$ are also defined as boundary points. +$ + 66 1 F + 99 1 T +$ +$ Close list by defining point (0,0) (mandatory) +$ + 0 0 F +$ +$ +$ +$ Excluded grid points from segment data ( FROM != PART ) +$ First defined as lines, identical to the definition of the input +$ boundary points, and closed the same way. +$ + 0 0 F +$ +$ Second, define a point in a closed body of sea points to remove +$ the entire body os sea points. Also close by point (0,0) +$ + 0 0 +$ +$ Output boundary points --------------------------------------------- $ +$ Output boundary points are defined as a number of straight lines, +$ defined by its starting point (X0,Y0), increments (DX,DY) and number +$ of points. A negative number of points starts a new output file. +$ Note that this data is only generated if requested by the actual +$ program. Example again for spherical grid in degrees. +$ +$ -2.5312 48.5 0.00 0.008738 102 +$ -2.5312 49.3850 0.013554 0.00 51 +$ +$ Close list by defining line with 0 points (mandatory) +$ + 0. 0. 0. 0. 0 +$ +$ -------------------------------------------------------------------- $ +$ End of input file $ +$ -------------------------------------------------------------------- $ diff --git a/regtests/ww3_tp2.22/input/ww3_grid_pdlib.nml b/regtests/ww3_tp2.22/input/ww3_grid_pdlib.nml new file mode 100644 index 000000000..3232907ef --- /dev/null +++ b/regtests/ww3_tp2.22/input/ww3_grid_pdlib.nml @@ -0,0 +1,74 @@ +! -------------------------------------------------------------------- ! +! WAVEWATCH III - ww3_grid.nml - Grid pre-processing ! +! -------------------------------------------------------------------- ! + +! -------------------------------------------------------------------- ! +! Define the spectrum parameterization via SPECTRUM_NML namelist +! -------------------------------------------------------------------- ! +&SPECTRUM_NML + SPECTRUM%XFR = 1.1 + SPECTRUM%FREQ1 = 0.05 + SPECTRUM%NK = 25 + SPECTRUM%NTH = 24 +/ + +! -------------------------------------------------------------------- ! +! Define the run parameterization via RUN_NML namelist +! -------------------------------------------------------------------- ! +&RUN_NML + RUN%FLCX = T + RUN%FLCY = T + RUN%FLCTH = T + RUN%FLCK = T + RUN%FLSOU = T +/ + +! -------------------------------------------------------------------- ! +! Define the timesteps parameterization via TIMESTEPS_NML namelist +! -------------------------------------------------------------------- ! +&TIMESTEPS_NML + TIMESTEPS%DTMAX = 10. + TIMESTEPS%DTXY = 10. + TIMESTEPS%DTKTH = 10. + TIMESTEPS%DTMIN = 10. +/ + +! -------------------------------------------------------------------- ! +! Define the grid to preprocess via GRID_NML namelist +! -------------------------------------------------------------------- ! +&GRID_NML + GRID%NAME = 'LIMON' + GRID%NML = '../input/namelists_pdlib.nml' + GRID%TYPE = 'UNST' + GRID%COORD = 'SPHE' + GRID%CLOS = 'NONE' + GRID%ZLIM = 5.0 + GRID%DMIN = 0.30 +/ + +! -------------------------------------------------------------------- ! +! Define the unstructured grid type via UNST_NML namelist +! -------------------------------------------------------------------- ! +&UNST_NML + UNST%SF = -1. + UNST%FILENAME = './../input/limon_ll.msh' + UNST%IDLA = 4 + UNST%FORMAT = '(20f10.2)' +/ + +! -------------------------------------------------------------------- ! +! Define the input boundary points via INBND_COUNT_NML and +! INBND_POINT_NML namelist +! -------------------------------------------------------------------- ! +&INBND_COUNT_NML + INBND_COUNT%N_POINT = 2 +/ + +&INBND_POINT_NML + INBND_POINT(1) = 66 1 F + INBND_POINT(2) = 99 1 T +/ + +! -------------------------------------------------------------------- ! +! WAVEWATCH III - end of namelist ! +! -------------------------------------------------------------------- ! diff --git a/regtests/ww3_tp2.22/input/ww3_ounf.inp b/regtests/ww3_tp2.22/input/ww3_ounf.inp new file mode 100644 index 000000000..d2bde30b6 --- /dev/null +++ b/regtests/ww3_tp2.22/input/ww3_ounf.inp @@ -0,0 +1,43 @@ +$ -------------------------------------------------------------------- $ +$ WAVEWATCH III Grid output post-processing $ +$--------------------------------------------------------------------- $ +$ First output time (yyyymmdd hhmmss), increment of output (s), +$ and number of output times. +$ + 20100801 000000 10 3600 +$ +$ Fields requested --------------------------------------------------- $ +$ +$ Output request flags identifying fields as in ww3_shel.inp. See that +$ file for a full documentation of field output options. Namelist type +$ selection is used here (for alternative F/T flags, see ww3_shel.inp). +$ + N + HS LM T02 T01 T0M1 UST CHA CGE DTD FC CFX CFD QP QKK +$ +$--------------------------------------------------------------------- $ +$ netCDF version [3,4] +$ and variable type 4 [2 = SHORT, 3 = it depends , 4 = REAL] +$ swell partitions [0 1 2 3 4 5] +$ variables in same file [T] or not [F] +$ + 3 4 + 0 1 2 + F +$ +$ -------------------------------------------------------------------- $ +$ File prefix +$ number of characters in date +$ IX, IY range +$ + ww3. + 6 + 1 1778 1 1 +$ +$ For each field and time a new file is generated with the file name +$ ww3.date_xxx.nc , where date is a conventional time indicator with S3 +$ characters, and xxx is a field identifier. +$ +$ -------------------------------------------------------------------- $ +$ End of input file $ +$ -------------------------------------------------------------------- $ diff --git a/regtests/ww3_tp2.22/input/ww3_ounf.nml b/regtests/ww3_tp2.22/input/ww3_ounf.nml new file mode 100644 index 000000000..7b344cc1c --- /dev/null +++ b/regtests/ww3_tp2.22/input/ww3_ounf.nml @@ -0,0 +1,28 @@ +! -------------------------------------------------------------------- ! +! WAVEWATCH III ww3_ounf.nml - Grid output post-processing ! +! -------------------------------------------------------------------- ! + +! -------------------------------------------------------------------- ! +! Define the output fields to postprocess via FIELD_NML namelist +! -------------------------------------------------------------------- ! +&FIELD_NML + FIELD%TIMESTART = '20100801 000000' + FIELD%TIMESTRIDE = '10' + FIELD%TIMECOUNT = '3600' + FIELD%LIST = 'HS LM T02 T01 T0M1 UST CHA CGE DTD FC CFX CFD QP QKK' + FIELD%PARTITION = '0 1 2' + FIELD%SAMEFILE = F + FIELD%TYPE = 4 +/ + +! -------------------------------------------------------------------- ! +! Define the content of the output file via FILE_NML namelist +! -------------------------------------------------------------------- ! +&FILE_NML + FILE%IXN = 1778 + FILE%IYN = 1 +/ + +! -------------------------------------------------------------------- ! +! WAVEWATCH III - end of namelist ! +! -------------------------------------------------------------------- ! diff --git a/regtests/ww3_tp2.22/input/ww3_ounp.inp b/regtests/ww3_tp2.22/input/ww3_ounp.inp new file mode 100644 index 000000000..dd99c642f --- /dev/null +++ b/regtests/ww3_tp2.22/input/ww3_ounp.inp @@ -0,0 +1,117 @@ +$ -------------------------------------------------------------------- $ +$ WAVEWATCH III NETCDF Point output post-processing $ +$--------------------------------------------------------------------- $ +$ First output time (yyyymmdd hhmmss), increment of output (s), +$ and number of output times. +$ + 19850101 000000 3600. 1000 +$ +$ Points requested --------------------------------------------------- $ +$ +$ Define points index for which output is to be generated. +$ If no one defined, all points are selected +$ One index number per line, negative number identifies end of list. + 1 +$ mandatory end of list + -1 +$ +$--------------------------------------------------------------------- $ +$ file prefix +$ number of characters in date [4(yearly),6(monthly),8(daily),10(hourly)] +$ netCDF version [3,4] +$ points in same file [T] or not [F] +$ and max number of points to be processed in one pass +$ output type ITYPE [0,1,2,3] +$ flag for global attributes WW3 [0] or variable version [1-2-3-4] +$ flag for dimensions order time,station [T] or station,time [F] +$ + ww3. + 8 + 3 + F 100 + 1 + 0 + T +$ +$ -------------------------------------------------------------------- $ +$ ITYPE = 0, inventory of file. +$ No additional input, the above time range is ignored. +$ +$ -------------------------------------------------------------------- $ +$ ITYPE = 1, netCDF Spectra. +$ - Sub-type OTYPE : 1 : Print plots. +$ 2 : Table of 1-D spectra +$ 3 : Transfer file. +$ 4 : Spectral partitioning. +$ - Scaling factors for 1-D and 2-D spectra Negative factor +$ disables, output, factor = 0. gives normalized spectrum. +$ - Netcdf variable type [2=SHORT, 3=it depends, 4=REAL] +$ + 3 1 0 4 +$ +$ The transfer file contains records with the following contents. +$ +$ - File ID in quotes, number of frequencies, directions and points. +$ grid name in quotes (for unformatted file C*21,3I,C*30). +$ - Bin frequencies in Hz for all bins. +$ - Bin directions in radians for all bins (Oceanographic conv.). +$ -+ +$ - Time in yyyymmdd hhmmss format | loop +$ -+ | +$ - Point name (C*40), lat, lon, d, U10 and | loop | over +$ direction, current speed and direction | over | +$ - E(f,theta) | points | times +$ -+ -+ +$ +$ -------------------------------------------------------------------- $ +$ ITYPE = 2, netCDF Tables of (mean) parameter +$ - Sub-type OTYPE : 1 : Depth, current, wind +$ 2 : Mean wave pars. +$ 3 : Nondimensional pars. (U*) +$ 4 : Nondimensional pars. (U10) +$ 5 : 'Validation table' +$ 6 : WMO standard output +$ 4 +$ +$ -------------------------------------------------------------------- $ +$ ITYPE = 3, netCDF Source terms +$ - Sub-type OTYPE : 1 : Print plots. +$ 2 : Table of 1-D S(f). +$ 3 : Table of 1-D inverse time scales +$ (1/T = S/F). +$ 4 : Transfer file +$ - Scaling factors for 1-D and 2-D source terms. Negative +$ factor disables print plots, factor = 0. gives normalized +$ print plots. +$ - Flags for spectrum, input, interactions, dissipation, +$ bottom and total source term. +$ - scale ISCALE for OTYPE=2,3 +$ 0 : Dimensional. +$ 1 : Nondimensional in terms of U10 +$ 2 : Nondimensional in terms of U* +$ 3-5: like 0-2 with f normalized with fp. +$ +$ 4 0 0 T T T T T T 0 +$ +$ The transfer file contains records with the following contents. +$ +$ - File ID in quotes, nubmer of frequencies, directions and points, +$ flags for spectrum and source terms (C*21, 3I, 6L) +$ - Bin frequencies in Hz for all bins. +$ - Bin directions in radians for all bins (Oceanographic conv.). +$ -+ +$ - Time in yyyymmdd hhmmss format | loop +$ -+ | +$ - Point name (C*40), depth, wind speed and | loop | over +$ direction, current speed and direction | over | +$ - E(f,theta) if requested | points | times +$ - Sin(f,theta) if requested | | +$ - Snl(f,theta) if requested | | +$ - Sds(f,theta) if requested | | +$ - Sbt(f,theta) if requested | | +$ - Stot(f,theta) if requested | | +$ -+ -+ +$ +$ -------------------------------------------------------------------- $ +$ End of input file $ +$ -------------------------------------------------------------------- $ diff --git a/regtests/ww3_tp2.22/input/ww3_ounp.nml b/regtests/ww3_tp2.22/input/ww3_ounp.nml new file mode 100644 index 000000000..b5088c9cc --- /dev/null +++ b/regtests/ww3_tp2.22/input/ww3_ounp.nml @@ -0,0 +1,49 @@ +! -------------------------------------------------------------------- ! +! WAVEWATCH III ww3_ounp.nml - Point output post-processing ! +! -------------------------------------------------------------------- ! + +! -------------------------------------------------------------------- ! +! Define the output fields to postprocess via POINT_NML namelist +! -------------------------------------------------------------------- ! +&POINT_NML + POINT%TIMESTART = '19850101 000000' + POINT%TIMESTRIDE = '3600.' + POINT%TIMECOUNT = '1000' + POINT%TIMESPLIT = 8 + POINT%LIST = '1' + POINT%SAMEFILE = F + POINT%BUFFER = 100 +/ + +! -------------------------------------------------------------------- ! +! Define the content of the output file via FILE_NML namelist +! -------------------------------------------------------------------- ! +&FILE_NML +/ + +! -------------------------------------------------------------------- ! +! Define the type 0, inventory of file +! -------------------------------------------------------------------- ! + + +! -------------------------------------------------------------------- ! +! Define the type 1, spectra via SPECTRA_NML namelist +! -------------------------------------------------------------------- ! +&SPECTRA_NML +/ + +! -------------------------------------------------------------------- ! +! Define the type 2, mean parameter via PARAM_NML namelist +! -------------------------------------------------------------------- ! +&PARAM_NML +/ + +! -------------------------------------------------------------------- ! +! Define the type 3, source terms via SOURCE_NML namelist +! -------------------------------------------------------------------- ! +&SOURCE_NML +/ + +! -------------------------------------------------------------------- ! +! WAVEWATCH III - end of namelist ! +! -------------------------------------------------------------------- ! diff --git a/regtests/ww3_tp2.22/input/ww3_outf.inp b/regtests/ww3_tp2.22/input/ww3_outf.inp new file mode 100644 index 000000000..86c1115ff --- /dev/null +++ b/regtests/ww3_tp2.22/input/ww3_outf.inp @@ -0,0 +1,66 @@ +$ -------------------------------------------------------------------- $ +$ WAVEWATCH III Grid output post-processing $ +$--------------------------------------------------------------------- $ +$ Time, time increment and number of outputs +$ + 20020101 120000 3600 10000 +$ +$ Request flags identifying fields as in ww3_shel input and section 2.4 fo the manual. +N +HS LM T02 T01 T0M1 UST CHA CGE DTD FC CFX CFD QP QKK +$ +$ Output type ITYPE [0,1,2,3] +$ + 3 0 +$ -------------------------------------------------------------------- $ +$ ITYPE = 0, inventory of file. +$ No additional input, the above time range is ignored. +$ +$ -------------------------------------------------------------------- $ +$ ITYPE = 1, print plots. +$ IX,IY range and stride, flag for automatic scaling to +$ maximum value (otherwise fixed scaling), +$ vector component flag (dummy for scalar quantities). +$ +$ 1 12 1 1 12 1 F T +$ +$ -------------------------------------------------------------------- $ +$ ITYPE = 2, field statistics. +$ IX,IY range. +$ +$ 1 12 1 12 +$ +$ -------------------------------------------------------------------- $ +$ ITYPE = 3, transfer files. +$ IX, IY range, IDLA and IDFM as in ww3_grid.inp. +$ The additional option IDLA=5 gives ia longitude, lattitude +$ and parameter value(s) per record (defined points only). +$ +$1 1778 1 1 3 2 +$ +$ For each field and time a new file is generated with the file name +$ ww3.yymmddhh.xxx, where yymmddhh is a conventional time idicator, +$ and xxx is a field identifier. The first record of the file contains +$ a file ID (C*13), the time in yyyymmdd hhmmss format, the lowest, +$ highest and number of longitudes (2R,I), id. latitudes, the file +$ extension name (C*$), a scale factor (R), a unit identifier (C*10), +$ IDLA, IDFM, a format (C*11) and a number identifying undefined or +$ missing values (land, ice, etc.). The field follows as defined by +$ IDFM and IDLA, defined as in the grid proprocessor. IDLA=5 is added +$ and gives a set of records containing the longitude, latitude and +$ parameter value. Note that the actual data is written as an integers. +$ -------------------------------------------------------------------- $ +$ ITYPE = 4, Netcdf Files +$ S3: number of characters in date +$ IX, IY range +$ + 1 1778 1 1 3 2 +$ For each field and time a new file is generated with the file name +$ ww3.date_xxx.nc , where date is a conventional time idicator with S3 +$ characters, +$ and xxx is a field identifier. +$ +$ +$ -------------------------------------------------------------------- $ +$ End of input file $ +$ -------------------------------------------------------------------- $ diff --git a/regtests/ww3_tp2.22/input/ww3_outp.inp b/regtests/ww3_tp2.22/input/ww3_outp.inp new file mode 100644 index 000000000..888ca870c --- /dev/null +++ b/regtests/ww3_tp2.22/input/ww3_outp.inp @@ -0,0 +1,113 @@ +$ -------------------------------------------------------------------- $ +$ WAVEWATCH III Point output post-processing $ +$--------------------------------------------------------------------- $ +$ First output time (yyyymmdd hhmmss), increment of output (s), +$ and number of output times. +$ + 19680606 000000 3600. 9999 +$ +$ Points requested --------------------------------------------------- $ +$ Define points for which output is to be generated. +$ +1 +$ mandatory end of list + -1 +$ +$ Output type ITYPE [0,1,2,3] +$ + 1 +$ -------------------------------------------------------------------- $ +$ ITYPE = 0, inventory of file. +$ No additional input, the above time range is ignored. +$ +$ -------------------------------------------------------------------- $ +$ ITYPE = 1, Spectra. +$ - Sub-type OTYPE : 1 : Print plots. +$ 2 : Table of 1-D spectra +$ 3 : Transfer file. +$ 4 : Spectral partitioning. +$ - Scaling factors for 1-D and 2-D spectra Negative factor +$ disables, output, factor = 0. gives normalized spectrum. +$ - Unit number for transfer file, also used in table file +$ name. +$ - Flag for unformatted transfer file. +$ + 3 1. 0. 33 F +$ +$ The transfer file contains records with the following contents. +$ +$ - File ID in quotes, number of frequencies, directions and points. +$ grid name in quotes (for unformatted file C*21,3I,C*30). +$ - Bin frequenies in Hz for all bins. +$ - Bin directions in radians for all bins (Oceanographic conv.). +$ -+ +$ - Time in yyyymmdd hhmmss format | loop +$ -+ | +$ - Point name (C*40), lat, lon, d, U10 and | loop | over +$ direction, current speed and direction | over | +$ - E(f,theta) | points | times +$ -+ -+ +$ +$ The formatted file is readable usign free format throughout. +$ This datat set can be used as input for the bulletin generator +$ w3split. +$ +$ -------------------------------------------------------------------- $ +$ ITYPE = 2, Tables of (mean) parameter +$ - Sub-type OTYPE : 1 : Depth, current, wind +$ 2 : Mean wave pars. +$ 3 : Nondimensional pars. (U*) +$ 4 : Nondimensional pars. (U10) +$ 5 : 'Validation table' +$ - Unit number for file, also used in file name. +$ +$ 2 33 +$ +$ If output for one point is requested, a time series table is made, +$ otherwise the file contains a separate tables for each output time. +$ +$ -------------------------------------------------------------------- $ +$ ITYPE = 3, Source terms +$ - Sub-type OTYPE : 1 : Print plots. +$ 2 : Table of 1-D S(f). +$ 3 : Table of 1-D inverse time scales +$ (1/T = S/F). +$ 4 : Transfer file +$ - Scaling factors for 1-D and 2-D source terms. Negative +$ factor disables print plots, factor = 0. gives normalized +$ print plots. +$ - Unit number for transfer file, also used in table file +$ name. +$ - Flags for spectrum, input, interactions, dissipation, +$ bottom and total source term. +$ - scale ISCALE for OTYPE=2,3 +$ 0 : Dimensional. +$ 1 : Nondimensional in terms of U10 +$ 2 : Nondimensional in terms of U* +$ 3-5: like 0-2 with f normalized with fp. +$ - Flag for unformatted transfer file. +$ +$ 1 0. 0. 50 T T T T T T 0 F +$ +$ The transfer file contains records with the following contents. +$ +$ - File ID in quotes, nubmer of frequencies, directions and points, +$ flags for spectrum and source terms (C*21, 3I, 6L) +$ - Bin frequenies in Hz for all bins. +$ - Bin directions in radians for all bins (Oceanographic conv.). +$ -+ +$ - Time in yyyymmdd hhmmss format | loop +$ -+ | +$ - Point name (C*40), depth, wind speed and | loop | over +$ direction, current speed and direction | over | +$ - E(f,theta) if requested | points | times +$ - Sin(f,theta) if requested | | +$ - Snl(f,theta) if requested | | +$ - Sds(f,theta) if requested | | +$ - Sbt(f,theta) if requested | | +$ - Stot(f,theta) if requested | | +$ -+ -+ +$ +$ -------------------------------------------------------------------- $ +$ End of input file $ +$ -------------------------------------------------------------------- $ diff --git a/regtests/ww3_tp2.22/input/ww3_shel.inp b/regtests/ww3_tp2.22/input/ww3_shel.inp new file mode 100644 index 000000000..2bd59dc2c --- /dev/null +++ b/regtests/ww3_tp2.22/input/ww3_shel.inp @@ -0,0 +1,136 @@ +$ -------------------------------------------------------------------- $ +$ WAVEWATCH III shell input file $ +$ -------------------------------------------------------------------- $ +$ Define input to be used with flag for use and flag for definition +$ as a homogeneous field (first three only); seven input lines. +$ + F F Water levels + F F Currents + T T Winds + F F Ice concentrations + F F Atmospheric momentum + F F Air density + F Assimilation data : Mean parameters + F Assimilation data : 1-D spectra + F Assimilation data : 2-D spectra. +$ +$ Time frame of calculations ----------------------------------------- $ +$ - Starting time in yyyymmdd hhmmss format. +$ - Ending time in yyyymmdd hhmmss format. +$ + 20100801 000000 + 20100801 001000 +$ +$ Define output data ------------------------------------------------- $ +$ +$ Define output server mode. This is used only in the parallel version +$ of the model. To keep the input file consistent, it is always needed. +$ IOSTYP = 1 is generally recommended. IOSTYP > 2 may be more efficient +$ for massively parallel computations. Only IOSTYP = 0 requires a true +$ parallel file system like GPFS. +$ +$ IOSTYP = 0 : No data server processes, direct access output from +$ each process (requirese true parallel file system). +$ 1 : No data server process. All output for each type +$ performed by process that performes computations too. +$ 2 : Last process is reserved for all output, and does no +$ computing. +$ 3 : Multiple dedicated output processes. +$ + 1 +$ +$ Five output types are available (see below). All output types share +$ a similar format for the first input line: +$ - first time in yyyymmdd hhmmss format, output interval (s), and +$ last time in yyyymmdd hhmmss format (all integers). +$ Output is disabled by setting the output interval to 0. +$ +$ Type 1 : Fields of mean wave parameters +$ Standard line and line with flags to activate output fields +$ as defined in section 2.4 of the manual. The second line is +$ not supplied if no output is requested. +$ The raw data file is out_grd.ww3, +$ see w3iogo.ftn for additional doc. +$ +$ +$ + 20071101 000000 10 20121231 233000 +$---------------------------------------------------------------- +$ Output request flags identifying fields as in ww3_shel input and +$ section 2.4 of the manual. +$ +N +HS LM T02 T01 T0M1 UST CHA CGE DTD FC CFX CFD QP QKK +$ +$---------------------------------------------------------------- +$ +$ Type 2 : Point output +$ Standard line and a number of lines identifying the +$ longitude, latitude and name (C*40) of output points. +$ The list is closed by defining a point with the name +$ 'STOPSTRING'. No point info read if no point output is +$ requested (i.e., no 'STOPSTRING' needed). +$ Example for spherical grid. +$ The raw data file is out_pnt.ww3, +$ see w3iogo.ftn for additional doc. +$ +$ NOTE : Spaces may be included in the name, but this is not +$ advised, because it will break the GrADS utility to +$ plots spectra and source terms, and will make it more +$ difficult to use point names in data files. +$ + 20071101 000000 60 20121231 233000 +$output points for cartesian grid +$output points for IROISE +$ + -83.02097840 9.98081977 'POINT1' + -83.01589326 9.98398516 'POINT2' +$ + 0.0 0.0 'STOPSTRING' +$ +$ Type 3 : Output along track. +$ Flag for formatted input file. +$ The data files are track_i.ww3 and +$ track_o.ww3, see w3iotr.ftn for ad. doc. +$ + 20040101 000000 1 20040101 000000 + T +$ +$ Type 4 : Restart files (no additional data required). +$ The data file is restartN.ww3, see +$ w3iors.ftn for additional doc. +$ + 20100101 000000 1728000 20120603 000000 +$ +$ Type 5 : Boundary data (no additional data required). +$ The data file is nestN.ww3, see +$ w3iobp.ftn for additional doc. +$ + 20040601 000000 0 20040103 000000 +$ +$ Type 6 : Separated wave field data (dummy for now). +$ First, last step IX and IY, flag for formatted file +$ + 20040101 000000 0 20040603 000000 +$ +$ Testing of output through parameter list (C/TPAR) ------------------ $ +$ Time for output and field flags as in above output type 1. +$ +$ 19680606 014500 +$ T T T T T T T T T T T T T T T T +$ +$ Homogeneous field data --------------------------------------------- $ +$ Homogeneous fields can be defined by a list of lines containing an ID +$ string 'LEV' 'CUR' 'WND', date and time information (yyyymmdd +$ hhmmss), value (S.I. units), direction (current and wind, oceanographic +$ convention degrees)) and air-sea temparature difference (degrees C). +$ 'STP' is mandatory stop string. +$ +$ 'LEV' 19680606 010000 1.0 +$ 'CUR' 19680606 073125 2.0 25. + 'WND' 20020905 000000 30. 180. 0.0 + 'STP' +$ +$ -------------------------------------------------------------------- $ +$ End of input file $ +$ -------------------------------------------------------------------- $ diff --git a/regtests/ww3_tp2.22/input/ww3_shel.nml b/regtests/ww3_tp2.22/input/ww3_shel.nml new file mode 100644 index 000000000..3cb7ceb0c --- /dev/null +++ b/regtests/ww3_tp2.22/input/ww3_shel.nml @@ -0,0 +1,56 @@ +! -------------------------------------------------------------------- ! +! WAVEWATCH III ww3_shel.nml - single-grid model ! +! -------------------------------------------------------------------- ! + + +! -------------------------------------------------------------------- ! +! Define top-level model parameters via DOMAIN_NML namelist +! -------------------------------------------------------------------- ! +&DOMAIN_NML + DOMAIN%START = '20100801 000000' + DOMAIN%STOP = '20100801 006000' +/ + +! -------------------------------------------------------------------- ! +! Define each forcing via the INPUT_NML namelist +! -------------------------------------------------------------------- ! +&INPUT_NML + INPUT%FORCING%WINDS = 'H' +/ + +! -------------------------------------------------------------------- ! +! Define the output types point parameters via OUTPUT_TYPE_NML namelist +! -------------------------------------------------------------------- ! +&OUTPUT_TYPE_NML + TYPE%FIELD%LIST = 'HS LM T02 T01 T0M1 UST CHA CGE DTD FC CFX CFD QP QKK' + TYPE%POINT%FILE = '../input/points.list' +/ + +! -------------------------------------------------------------------- ! +! Define output dates via OUTPUT_DATE_NML namelist +! -------------------------------------------------------------------- ! +&OUTPUT_DATE_NML + DATE%FIELD = '20100801 000000' '10' '20100801 006000' + !DATE%POINT = '20100801 000000' '60' '20121231 233000' + !DATE%TRACK = '20040101 000000' '1' '20040101 000000' + !DATE%RESTART = '20100101 000000' '1728000' '20120603 000000' +/ + +! -------------------------------------------------------------------- ! +! Define homogeneous input via HOMOG_COUNT_NML and HOMOG_INPUT_NML namelist +! -------------------------------------------------------------------- ! +&HOMOG_COUNT_NML + HOMOG_COUNT%N_WND = 1 +/ + +&HOMOG_INPUT_NML + HOMOG_INPUT(1)%NAME = 'WND' + HOMOG_INPUT(1)%DATE = '20020905 000000' + HOMOG_INPUT(1)%VALUE1 = 30. + HOMOG_INPUT(1)%VALUE2 = 180. + HOMOG_INPUT(1)%VALUE3 = 0.0 +/ + +! -------------------------------------------------------------------- ! +! WAVEWATCH III - end of namelist ! +! -------------------------------------------------------------------- ! diff --git a/regtests/ww3_tp2.22/input/ww3_strt.inp b/regtests/ww3_tp2.22/input/ww3_strt.inp new file mode 100644 index 000000000..9f4ee18cb --- /dev/null +++ b/regtests/ww3_tp2.22/input/ww3_strt.inp @@ -0,0 +1,11 @@ +$ WAVEWATCH III Initial conditions input file +$ ------------------------------------------- +$ ITYPE: 1= GAUSSIAN + 1 +$ fp sip thm ncos xm six ym siy hmax + 0.125 0.0001 90. 10 -83.01 -0.01 9.99 2.8 4. +$ +$ Other possibility: non-zero values only near boundary +$ 0.125 0.0001 80. 200 -83.012 0.005 9.99 2.8 4. +EOF +