From 43613bc8c89f9b16dcd5886df34479f9f459a733 Mon Sep 17 00:00:00 2001 From: jesse meng Date: Thu, 12 Dec 2024 23:06:12 +0000 Subject: [PATCH 1/6] 20241212 Jesse Meng add Utah SLR 2024 algorithm --- sorc/ncep_post.fd/MDL2P.f | 11 +- sorc/ncep_post.fd/UPP_PHYSICS.f | 231 +++++++++++++++++++++++++++++++- 2 files changed, 230 insertions(+), 12 deletions(-) diff --git a/sorc/ncep_post.fd/MDL2P.f b/sorc/ncep_post.fd/MDL2P.f index 7f4f62f7b..915275db0 100644 --- a/sorc/ncep_post.fd/MDL2P.f +++ b/sorc/ncep_post.fd/MDL2P.f @@ -75,7 +75,8 @@ SUBROUTINE MDL2P(iostatusD3D) IEND_2U, slrutah_on, gtg_on use rqstfld_mod, only: IGET, LVLS, ID, IAVBLFLD, LVLSXML use gridspec_mod, only: GRIDTYPE, MAPTYPE, DXVAL - use upp_physics, only: FPVSNEW, CALRH, CALVOR, CALSLR_ROEBBER, CALSLR_UUTAH + use upp_physics, only: FPVSNEW, CALRH, CALVOR, CALSLR_ROEBBER, CALSLR_UUTAH, & + CALSLR_UUTAH2 !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ! @@ -4287,11 +4288,9 @@ SUBROUTINE MDL2P(iostatusD3D) ! SNOW DESITY SOLID-LIQUID-RATION SLR IF ( IGET(1006)>0 ) THEN egrid1=spval - if(slrutah_on) then - call calslr_uutah(EGRID1) - else - call calslr_roebber(TPRS,RHPRS,EGRID1) - endif + call calslr_uutah2(EGRID1) +! call calslr_uutah(EGRID1) +! call calslr_roebber(TPRS,RHPRS,EGRID1) !$omp parallel do private(i,j) do j=jsta,jend do i=ista,iend diff --git a/sorc/ncep_post.fd/UPP_PHYSICS.f b/sorc/ncep_post.fd/UPP_PHYSICS.f index b2d3f95d5..d00cc8623 100644 --- a/sorc/ncep_post.fd/UPP_PHYSICS.f +++ b/sorc/ncep_post.fd/UPP_PHYSICS.f @@ -19,6 +19,8 @@ !> calslr_roebber() computes snow solid-liquid-ratio slr using the Roebber algorithm. !> !> calslr_uutah() computes snow solid-liquid-ratio slr using the UUtah Steenburgh algorithm. +!> +!> calslr_uutah2() computes snow solid-liquid-ratio slr using the UUtah Steenburgh 2024 algorithm. !> !> calvor() computes absolute vorticity. !> @@ -33,6 +35,7 @@ !> 2022-07-11 | Jesse Meng | CALSLR_ROEBBER !> 2023-02-14 | Jesse Meng | CALSLR_UUTAH !> 2023-03-22 | Sam Trahan | Fix out-of-bounds access by not calling BOUND +!> 2024-12-12 | Jesse Meng | CALSLR_UUTAH2 !> !> @author Jesse Meng @date 2020-05-20 module upp_physics @@ -48,7 +51,7 @@ module upp_physics public :: CALRH public :: CALRH_GFS, CALRH_GSD, CALRH_NAM public :: CALRH_PW - public :: CALSLR_ROEBBER, CALSLR_UUTAH + public :: CALSLR_ROEBBER, CALSLR_UUTAH, CALSLR_UUTAH2 public :: CALVOR public :: FPVSNEW @@ -2809,7 +2812,7 @@ SUBROUTINE CALSLR_ROEBBER(tprs,rhprs,slr) DO J=JSTA,JEND DO I=ISTA,IEND PSFC(I,J)=PINT(I,J,NINT(LMH(I,J))+1) - PRES(I,J)=SLP(I,J) + PRES(I,J)=PSFC(I,J) QPF(I,J)=AVGPREC_CONT(I,J)*3600.*3. SWND(I,J)=SPVAL IF(U10(I,J)/=SPVAL .AND. V10(I,J)/=SPVAL) & @@ -3043,10 +3046,10 @@ SUBROUTINE CALSLR_ROEBBER(tprs,rhprs,slr) if(lprob(i,j) < .67) then slrgrid2(i,j) = hprob(i,j)*8.0+mprob(i,j)*13.0+lprob(i,j)*18.0 - slrgrid2(i,j) = slrgrid2(i,j)*p/(hprob(i,j)+mprob(i,j)+lprob(i,j)) + slrgrid2(i,j) = slrgrid2(i,j)/(hprob(i,j)+mprob(i,j)+lprob(i,j)) else slrgrid2(i,j) = hprob(i,j)*8.0+mprob(i,j)*13.0+lprob(i,j)*27.0 - slrgrid2(i,j) = slrgrid2(i,j)*p/(hprob(i,j)+mprob(i,j)+lprob(i,j)) + slrgrid2(i,j) = slrgrid2(i,j)/(hprob(i,j)+mprob(i,j)+lprob(i,j)) endif ! slr(i,j) = climosub(i,j) @@ -4466,12 +4469,12 @@ SUBROUTINE CALSLR_UUTAH(SLR) ENDDO ENDDO - DO L=LM,1,-1 + DO L=1,LM !$omp parallel do private(i,j) DO J=JSTA,JEND DO I=ISTA,IEND IF(TWET05(I,J) < 0) THEN - IF(TWET(I,J,L) <= 273.15+0.5) THEN + IF(TWET(I,J,L) >= 273.15+0.5) THEN ZWET(I,J)=ZMID(I,J,L) TWET05(I,J)=1 ENDIF @@ -4497,6 +4500,222 @@ SUBROUTINE CALSLR_UUTAH(SLR) END SUBROUTINE CALSLR_UUTAH ! !------------------------------------------------------------------------------------- +! +!> Computes snow solid-liquid-ratio slr using the Steenburgh 2024 algorithm. +!> +!> Obtained the code and data from U of Utah Jim Steenburgh, +!> Peter Veals, and Michael Pletcher. +!> +!> @param[out] SLR real Solid snow to liquid ratio +!> +!> ### Program history log: +!> Date | Programmer | Comments +!> -----|------------|--------- +!> 2024-11-15 | Jesse Meng | Initial +!> +!> @author Jesse Meng @date 2024-11-15 + + SUBROUTINE CALSLR_UUTAH2(SLR) + + use vrbls3d, only: ZINT,ZMID,PMID,T,Q,UH,VH + use masks, only: LMH,HTM,GDLAT,GDLON + use ctlblk_mod, only: ME,ISTA,IEND,JSTA,JEND,ista_2l,iend_2u,jsta_2l,jend_2u,& + LM,SPVAL + + implicit none + + real,dimension(ista_2l:iend_2u,jsta_2l:jend_2u),intent(out) :: slr !slr=snod/weasd=1000./sndens + + integer, parameter :: NFL=8 + real, parameter :: HTFL(NFL)=(/ 300., 600., 900., 1200., & + 1500.,1800.,2100., 2400. /) + real,dimension(ISTA:IEND,JSTA:JEND,NFL) :: TFD,UFD,VFD,PFD,QFD,RHFD + real,dimension(ISTA:IEND,JSTA:JEND) :: ZSFC + + real LHL(NFL),DZABH(NFL),SWND(NFL) + real HTSFC,HTABH,DZ,RDZ,DELT,DELU,DELV,DELP,DELQ + + real, parameter :: s03 = 0.2113589753880838 + real, parameter :: s06 =-0.3113780353218734 + real, parameter :: s09 = 0.030295727788329747 + real, parameter :: s12 = 0.14200126274780872 + real, parameter :: s15 =-0.3036948150474089 + real, parameter :: s18 = 0.36742135429588796 + real, parameter :: s21 =-0.45316009735021756 + real, parameter :: s24 = 0.2732018488504477 + real, parameter :: t03 = 0.08908223593334653 + real, parameter :: t06 =-0.24948847161912707 + real, parameter :: t09 = 0.14521457107694088 + real, parameter :: t12 = 0.17265963006356744 + real, parameter :: t15 =-0.3741056734263027 + real, parameter :: t18 = 0.39704205782424823 + real, parameter :: t21 =-0.36577798019766355 + real, parameter :: t24 =-0.12603742209070648 + real, parameter :: r03 =-0.08523012915185951 + real, parameter :: r06 = 0.0879493556495648 + real, parameter :: r09 =-0.04508491900731953 + real, parameter :: r12 = 0.0347032913014311 + real, parameter :: r15 =-0.031872141634061976 + real, parameter :: r18 = 0.05199814866971972 + real, parameter :: r21 =-0.02739515218481534 + real, parameter :: r24 =-0.0338838765912164 + real, parameter :: b = 97.96209163 + + integer,dimension(ISTA:IEND,JSTA:JEND) :: KARR + integer,dimension(ISTA:IEND,JSTA:JEND) :: TWET05 + real,dimension(ISTA:IEND,JSTA:JEND) :: ZWET + + REAL, ALLOCATABLE :: TWET(:,:,:) + + integer I,J,L,LLMH,LMHK,IFD +! +!*************************************************************************** +! + ALLOCATE(TWET(ISTA_2L:IEND_2U,JSTA_2L:JEND_2U,LM)) + + DO IFD = 1,NFL +!$omp parallel do private(i,j) + DO J=JSTA,JEND + DO I=ISTA,IEND + ZSFC(I,J) = SPVAL + TFD(I,J,IFD) = SPVAL + UFD(I,J,IFD) = SPVAL + VFD(I,J,IFD) = SPVAL + PFD(I,J,IFD) = SPVAL + QFD(I,J,IFD) = SPVAL + RHFD(I,J,IFD) = SPVAL + ENDDO + ENDDO + ENDDO + +! LOCATE VERTICAL INDICES OF T,U,V, LEVEL JUST +! ABOVE EACH FD LEVEL. + + DO J=JSTA,JEND + DO I=ISTA,IEND + IF(ZINT(I,J,LM+1)HTFL(IFD)) THEN + LHL(IFD) = L + DZABH(IFD) = HTABH-HTFL(IFD) + IFD = IFD + 1 + ENDIF + IF(IFD > NFL) exit + ENDDO + +! COMPUTE T, U, V AT FD LEVELS. + + DO IFD = 1,NFL + L = LHL(IFD) + IF (L 0.5C + + KARR = 1 + CALL WETBULB(T,Q,PMID,HTM,KARR,TWET) + +!$omp parallel do private(i,j) + DO J=JSTA,JEND + DO I=ISTA,IEND + ZWET(I,J)=ZMID(I,J,LM) + TWET05(I,J)=-1 + ENDDO + ENDDO + + DO L=1,LM +!$omp parallel do private(i,j) + DO J=JSTA,JEND + DO I=ISTA,IEND + IF(TWET05(I,J) < 0) THEN + IF(TWET(I,J,L) >= 273.15+0.5) THEN + ZWET(I,J)=ZMID(I,J,L) + TWET05(I,J)=1 + ENDIF + ENDIF + ENDDO + ENDDO + ENDDO + +!$omp parallel do private(i,j,HTABH) + DO J=JSTA,JEND + DO I=ISTA,IEND + IF(TWET05(I,J) > 0 .AND. SLR(I,J) Date: Mon, 16 Dec 2024 15:11:40 +0000 Subject: [PATCH 2/6] 20241216 Jesse Meng convert new SUBROUTINE CALSLR_UUTAH2(SLR) in UPP_PHYSICS.f to all lowercase. --- sorc/ncep_post.fd/UPP_PHYSICS.f | 278 ++++++++++++++++---------------- 1 file changed, 139 insertions(+), 139 deletions(-) diff --git a/sorc/ncep_post.fd/UPP_PHYSICS.f b/sorc/ncep_post.fd/UPP_PHYSICS.f index d00cc8623..6cdeaea7f 100644 --- a/sorc/ncep_post.fd/UPP_PHYSICS.f +++ b/sorc/ncep_post.fd/UPP_PHYSICS.f @@ -4515,25 +4515,25 @@ END SUBROUTINE CALSLR_UUTAH !> !> @author Jesse Meng @date 2024-11-15 - SUBROUTINE CALSLR_UUTAH2(SLR) + subroutine calslr_uutah2(slr) - use vrbls3d, only: ZINT,ZMID,PMID,T,Q,UH,VH - use masks, only: LMH,HTM,GDLAT,GDLON - use ctlblk_mod, only: ME,ISTA,IEND,JSTA,JEND,ista_2l,iend_2u,jsta_2l,jend_2u,& - LM,SPVAL + use vrbls3d, only: zint,zmid,pmid,t,q,uh,vh + use masks, only: lmh,htm,gdlat,gdlon + use ctlblk_mod, only: me,ista,iend,jsta,jend,ista_2l,iend_2u,jsta_2l,jend_2u,& + lm,spval implicit none real,dimension(ista_2l:iend_2u,jsta_2l:jend_2u),intent(out) :: slr !slr=snod/weasd=1000./sndens - integer, parameter :: NFL=8 - real, parameter :: HTFL(NFL)=(/ 300., 600., 900., 1200., & + integer, parameter :: nfl=8 + real, parameter :: htfl(nfl)=(/ 300., 600., 900., 1200., & 1500.,1800.,2100., 2400. /) - real,dimension(ISTA:IEND,JSTA:JEND,NFL) :: TFD,UFD,VFD,PFD,QFD,RHFD - real,dimension(ISTA:IEND,JSTA:JEND) :: ZSFC + real,dimension(ista:iend,jsta:jend,nfl) :: tfd,ufd,vfd,pfd,qfd,rhfd + real,dimension(ista:iend,jsta:jend) :: zsfc - real LHL(NFL),DZABH(NFL),SWND(NFL) - real HTSFC,HTABH,DZ,RDZ,DELT,DELU,DELV,DELP,DELQ + real lhl(nfl),dzabh(nfl),swnd(nfl) + real htsfc,htabh,dz,rdz,delt,delu,delv,delp,delq real, parameter :: s03 = 0.2113589753880838 real, parameter :: s06 =-0.3113780353218734 @@ -4561,159 +4561,159 @@ SUBROUTINE CALSLR_UUTAH2(SLR) real, parameter :: r24 =-0.0338838765912164 real, parameter :: b = 97.96209163 - integer,dimension(ISTA:IEND,JSTA:JEND) :: KARR - integer,dimension(ISTA:IEND,JSTA:JEND) :: TWET05 - real,dimension(ISTA:IEND,JSTA:JEND) :: ZWET + integer,dimension(ista:iend,jsta:jend) :: karr + integer,dimension(ista:iend,jsta:jend) :: twet05 + real,dimension(ista:iend,jsta:jend) :: zwet - REAL, ALLOCATABLE :: TWET(:,:,:) + real, allocatable :: twet(:,:,:) - integer I,J,L,LLMH,LMHK,IFD + integer i,j,l,llmh,lmhk,ifd ! !*************************************************************************** ! - ALLOCATE(TWET(ISTA_2L:IEND_2U,JSTA_2L:JEND_2U,LM)) + allocate(twet(ista_2l:iend_2u,jsta_2l:jend_2u,lm)) - DO IFD = 1,NFL + do ifd = 1,nfl !$omp parallel do private(i,j) - DO J=JSTA,JEND - DO I=ISTA,IEND - ZSFC(I,J) = SPVAL - TFD(I,J,IFD) = SPVAL - UFD(I,J,IFD) = SPVAL - VFD(I,J,IFD) = SPVAL - PFD(I,J,IFD) = SPVAL - QFD(I,J,IFD) = SPVAL - RHFD(I,J,IFD) = SPVAL - ENDDO - ENDDO - ENDDO - -! LOCATE VERTICAL INDICES OF T,U,V, LEVEL JUST -! ABOVE EACH FD LEVEL. + do j=jsta,jend + do i=ista,iend + zsfc(i,j) = spval + tfd(i,j,ifd) = spval + ufd(i,j,ifd) = spval + vfd(i,j,ifd) = spval + pfd(i,j,ifd) = spval + qfd(i,j,ifd) = spval + rhfd(i,j,ifd) = spval + enddo + enddo + enddo - DO J=JSTA,JEND - DO I=ISTA,IEND - IF(ZINT(I,J,LM+1)HTFL(IFD)) THEN - LHL(IFD) = L - DZABH(IFD) = HTABH-HTFL(IFD) - IFD = IFD + 1 - ENDIF - IF(IFD > NFL) exit - ENDDO +! locate vertical indices of t,u,v, level just +! above each fd level. -! COMPUTE T, U, V AT FD LEVELS. + do j=jsta,jend + do i=ista,iend + if(zint(i,j,lm+1)htfl(ifd)) then + lhl(ifd) = l + dzabh(ifd) = htabh-htfl(ifd) + ifd = ifd + 1 + endif + if(ifd > nfl) exit + enddo - DO IFD = 1,NFL - L = LHL(IFD) - IF (L 0.5C +! compute wetbulb temperature and search for twet > 0.5c - KARR = 1 - CALL WETBULB(T,Q,PMID,HTM,KARR,TWET) + karr = 1 + call wetbulb(t,q,pmid,htm,karr,twet) !$omp parallel do private(i,j) - DO J=JSTA,JEND - DO I=ISTA,IEND - ZWET(I,J)=ZMID(I,J,LM) - TWET05(I,J)=-1 - ENDDO - ENDDO + do j=jsta,jend + do i=ista,iend + zwet(i,j)=zmid(i,j,lm) + twet05(i,j)=-1 + enddo + enddo - DO L=1,LM + do l=1,lm !$omp parallel do private(i,j) - DO J=JSTA,JEND - DO I=ISTA,IEND - IF(TWET05(I,J) < 0) THEN - IF(TWET(I,J,L) >= 273.15+0.5) THEN - ZWET(I,J)=ZMID(I,J,L) - TWET05(I,J)=1 - ENDIF - ENDIF - ENDDO - ENDDO - ENDDO + do j=jsta,jend + do i=ista,iend + if(twet05(i,j) < 0) then + if(twet(i,j,l) >= 273.15+0.5) then + zwet(i,j)=zmid(i,j,l) + twet05(i,j)=1 + endif + endif + enddo + enddo + enddo -!$omp parallel do private(i,j,HTABH) - DO J=JSTA,JEND - DO I=ISTA,IEND - IF(TWET05(I,J) > 0 .AND. SLR(I,J) 0 .and. slr(i,j) Date: Tue, 17 Dec 2024 15:40:23 -0500 Subject: [PATCH 3/6] 20241217 Jesse Meng Adding UUtah 2024 SLR algorithm --- sorc/ncep_post.fd/MDL2P.f | 1 + 1 file changed, 1 insertion(+) diff --git a/sorc/ncep_post.fd/MDL2P.f b/sorc/ncep_post.fd/MDL2P.f index 915275db0..ef228bf79 100644 --- a/sorc/ncep_post.fd/MDL2P.f +++ b/sorc/ncep_post.fd/MDL2P.f @@ -39,6 +39,7 @@ !> 2023-08-24 | Y Mao | Add gtg_on option for GTG interpolation !> 2023-09-12 | J Kenyon | Prevent spurious supercooled rain and cloud water !> 2024-04-23 | E James | Adding smoke emissions (ebb) from RRFS +!> 2024-12-12 | J Meng | Adding UUtah 2024 SLR algorithm !> !> @author T Black W/NP2 @date 1999-09-23 !-------------------------------------------------------------------------------------- From acf0bac02ba84d6a0a5df4a154e0afce9a1d0b94 Mon Sep 17 00:00:00 2001 From: gspetro-NOAA Date: Mon, 23 Dec 2024 16:53:20 +0000 Subject: [PATCH 4/6] add hera rt log --- tests/logs/rt.log.HERA | 120 +++++++++++++++++++++-------------------- 1 file changed, 63 insertions(+), 57 deletions(-) diff --git a/tests/logs/rt.log.HERA b/tests/logs/rt.log.HERA index 6dfd23849..46861970f 100644 --- a/tests/logs/rt.log.HERA +++ b/tests/logs/rt.log.HERA @@ -1,69 +1,75 @@ ===== Start of UPP Regression Testing Log ===== UPP Hash Tested: -5a4bb70bb4050d0b94c4c66e9569551620dfe249 +6f373c84a5e96eb5596c816cf00f0771cd43d8af Submodule hashes: -179cae1dd84401cf25d250bd9102e66560a9d328 sorc/libIFI.fd -529f870d33b65c3b6c1aa3c3236b94efc3bd336d sorc/ncep_post.fd/post_gtg.fd -Run directory: /scratch2/NAGAPE/epic/Gillian.Petro/RTs/upp-rts/1088/ci/rundir/upp-HERA +Run directory: /scratch2/NAGAPE/epic/Gillian.Petro/RTs/upp-rts/1104/ci/rundir/upp-HERA Baseline directory: /scratch2/NAGAPE/epic/UPP/test_suite -Total runtime: 00h:11m:26s -Test Date: 20241122 18:22:20 +Total runtime: 00h:13m:56s +Test Date: 20241223 15:19:18 Summary Results: -11/22 18:14:30Z -fv3hafs test: your new post executable generates bit-identical HURPRS09.tm00 as the trunk -11/22 18:14:59Z -fv3gefs pe test: your new post executable generates bit-identical geaer.t00z.master.grb2f060 as the trunk -11/22 18:15:27Z -fv3gefs test: your new post executable generates bit-identical geaer.t00z.master.grb2f060 as the trunk -11/22 18:15:28Z -rtma pe test: your new post executable generates bit-identical NATLEV00.tm00 as the trunk -11/22 18:15:31Z -rtma pe test: your new post executable generates bit-identical PRSLEV00.tm00 as the trunk -11/22 18:15:31Z -rtma pe test: your new post executable generates bit-identical IFIFIP00.tm00 as the trunk -11/22 18:15:34Z -fv3hafs pe test: your new post executable generates bit-identical HURPRS09.tm00 as the trunk -11/22 18:15:48Z -hrrr pe test: your new post executable generates bit-identical WRFTWO.GrbF04 as the trunk -11/22 18:15:50Z -hrrr pe test: your new post executable generates bit-identical WRFPRS.GrbF04 as the trunk -11/22 18:15:52Z -hrrr pe test: your new post executable generates bit-identical WRFNAT.GrbF04 as the trunk -11/22 18:15:57Z -rap test: your new post executable generates bit-identical WRFPRS.GrbF16 as the trunk -11/22 18:15:58Z -rap test: your new post executable generates bit-identical WRFNAT.GrbF16 as the trunk -11/22 18:16:12Z -nmmb pe test: your new post executable generates bit-identical BGDAWP03.tm00.Grib2 as the trunk -11/22 18:16:14Z -nmmb pe test: your new post executable generates bit-identical BGRD3D03.tm00.Grib2 as the trunk -11/22 18:16:14Z -hrrr test: your new post executable generates bit-identical WRFTWO.GrbF04 as the trunk -11/22 18:16:14Z -nmmb pe test: your new post executable generates bit-identical BGRDSF03.tm00.Grib2 as the trunk -11/22 18:16:15Z -hrrr test: your new post executable generates bit-identical WRFPRS.GrbF04 as the trunk -11/22 18:16:17Z -hrrr test: your new post executable generates bit-identical WRFNAT.GrbF04 as the trunk -11/22 18:16:18Z -nmmb test: your new post executable generates bit-identical BGDAWP03.tm00.Grib2 as the trunk -11/22 18:16:20Z -nmmb test: your new post executable generates bit-identical BGRD3D03.tm00.Grib2 as the trunk -11/22 18:16:20Z -nmmb test: your new post executable generates bit-identical BGRDSF03.tm00.Grib2 as the trunk -11/22 18:16:21Z -rap pe test: your new post executable did generate changed results in WRFPRS.GrbF16 -11/22 18:16:22Z -rap pe test: your new post executable generates bit-identical WRFNAT.GrbF16 as the trunk -11/22 18:16:26Z -rtma test: your new post executable generates bit-identical NATLEV00.tm00 as the trunk -11/22 18:16:28Z -fv3r test: your new post executable generates bit-identical PRSLEV10.tm00 as the trunk -11/22 18:16:29Z -rtma test: your new post executable generates bit-identical PRSLEV00.tm00 as the trunk -11/22 18:16:29Z -rtma test: your new post executable generates bit-identical IFIFIP00.tm00 as the trunk -11/22 18:16:33Z -fv3r test: your new post executable generates bit-identical NATLEV10.tm00 as the trunk -11/22 18:16:37Z -fv3r pe test: your new post executable generates bit-identical PRSLEV10.tm00 as the trunk -11/22 18:16:42Z -fv3r pe test: your new post executable generates bit-identical NATLEV10.tm00 as the trunk -11/22 18:21:18Z -fv3gfs test: your new post executable generates bit-identical gfs.t00z.master.grb2f006 as the trunk -11/22 18:21:22Z -fv3gfs test: your new post executable generates bit-identical gfs.t00z.sfluxgrbf006.grib2 as the trunk -11/22 18:21:22Z -fv3gfs test: your new post executable generates bit-identical gfs.t00z.special.grb2f006 as the trunk -11/22 18:22:04Z -fv3gfs pe test: your new post executable generates bit-identical gfs.t00z.master.grb2f006 as the trunk -11/22 18:22:08Z -fv3gfs pe test: your new post executable generates bit-identical gfs.t00z.sfluxgrbf006.grib2 as the trunk -11/22 18:22:08Z -fv3gfs pe test: your new post executable generates bit-identical gfs.t00z.special.grb2f006 as the trunk -11/22 18:16:27Z -Runtime: nmmb_test 00:01:27 -- baseline 00:01:00 -11/22 18:16:27Z -Runtime: nmmb_pe_test 00:01:21 -- baseline 00:01:00 -11/22 18:16:27Z -Runtime: fv3gefs_test 00:00:34 -- baseline 00:40:00 -11/22 18:16:28Z -Runtime: fv3gefs_pe_test 00:00:35 -- baseline 00:40:00 -11/22 18:16:28Z -Runtime: rap_test 00:01:17 -- baseline 00:02:00 -11/22 18:16:28Z -Runtime: rap_pe_test 00:01:29 -- baseline 00:02:00 -11/22 18:16:29Z -Runtime: hrrr_test 00:02:34 -- baseline 00:02:00 -11/22 18:16:29Z -Runtime: hrrr_pe_test 00:01:58 -- baseline 00:02:00 -11/22 18:21:32Z -Runtime: fv3gfs_test 00:07:02 -- baseline 00:15:00 -11/22 18:22:18Z -Runtime: fv3gfs_pe_test 00:07:19 -- baseline 00:15:00 -11/22 18:22:18Z -Runtime: fv3r_test 00:02:02 -- baseline 00:03:00 -11/22 18:22:18Z -Runtime: fv3r_pe_test 00:01:49 -- baseline 00:03:00 -11/22 18:22:19Z -Runtime: fv3hafs_test 00:00:32 -- baseline 00:03:00 -11/22 18:22:19Z -Runtime: fv3hafs_pe_test 00:00:45 -- baseline 00:03:00 -11/22 18:22:19Z -Runtime: rtma_test 00:01:57 -- baseline 00:03:00 -11/22 18:22:19Z -Runtime: rtma_test_pe_test 00:01:41 -- baseline -No changes in test results detected. +12/23 15:08:58Z -fv3gefs pe test: your new post executable generates bit-identical geaer.t00z.master.grb2f060 as the trunk +12/23 15:09:17Z -fv3hafs test: your new post executable generates bit-identical HURPRS09.tm00 as the trunk +12/23 15:09:34Z -fv3hafs pe test: your new post executable generates bit-identical HURPRS09.tm00 as the trunk +12/23 15:09:37Z -rap test: your new post executable generates bit-identical WRFPRS.GrbF16 as the trunk +12/23 15:09:38Z -rap test: your new post executable generates bit-identical WRFNAT.GrbF16 as the trunk +12/23 15:09:53Z -fv3gefs test: your new post executable generates bit-identical geaer.t00z.master.grb2f060 as the trunk +12/23 15:10:09Z -hrrr pe test: your new post executable generates bit-identical WRFTWO.GrbF04 as the trunk +12/23 15:10:11Z -hrrr pe test: your new post executable generates bit-identical WRFPRS.GrbF04 as the trunk +12/23 15:10:12Z -hrrr pe test: your new post executable generates bit-identical WRFNAT.GrbF04 as the trunk +12/23 15:10:17Z -hrrr test: your new post executable generates bit-identical WRFTWO.GrbF04 as the trunk +12/23 15:10:18Z -hrrr test: your new post executable generates bit-identical WRFPRS.GrbF04 as the trunk +12/23 15:10:19Z -hrrr test: your new post executable generates bit-identical WRFNAT.GrbF04 as the trunk +12/23 15:10:31Z -rap pe test: your new post executable did generate changed results in WRFPRS.GrbF16 +12/23 15:10:32Z -rap pe test: your new post executable generates bit-identical WRFNAT.GrbF16 as the trunk +12/23 15:10:47Z -nmmb pe test: your new post executable generates bit-identical BGDAWP03.tm00.Grib2 as the trunk +12/23 15:10:49Z -nmmb pe test: your new post executable generates bit-identical BGRD3D03.tm00.Grib2 as the trunk +12/23 15:10:49Z -nmmb pe test: your new post executable generates bit-identical BGRDSF03.tm00.Grib2 as the trunk +12/23 15:10:50Z -nmmb test: your new post executable generates bit-identical BGDAWP03.tm00.Grib2 as the trunk +12/23 15:10:51Z -nmmb test: your new post executable generates bit-identical BGRD3D03.tm00.Grib2 as the trunk +12/23 15:10:52Z -nmmb test: your new post executable generates bit-identical BGRDSF03.tm00.Grib2 as the trunk +12/23 15:10:55Z -fv3r test: your new post executable generates bit-identical PRSLEV10.tm00 as the trunk +12/23 15:11:09Z -fv3r pe test: your new post executable generates bit-identical PRSLEV10.tm00 as the trunk +12/23 15:12:27Z -rtma pe test: your new post executable did not generate bit-identical NATLEV00.tm00 as the trunk +12/23 15:12:30Z -rtma pe test: your new post executable generates bit-identical PRSLEV00.tm00 as the trunk +12/23 15:12:30Z -rtma pe test: your new post executable generates bit-identical IFIFIP00.tm00 as the trunk +12/23 15:13:23Z -fv3r test: your new post executable did not generate bit-identical NATLEV10.tm00 as the trunk +12/23 15:13:28Z -rtma test: your new post executable did not generate bit-identical NATLEV00.tm00 as the trunk +12/23 15:13:32Z -rtma test: your new post executable generates bit-identical PRSLEV00.tm00 as the trunk +12/23 15:13:32Z -rtma test: your new post executable generates bit-identical IFIFIP00.tm00 as the trunk +12/23 15:13:39Z -fv3r pe test: your new post executable did not generate bit-identical NATLEV10.tm00 as the trunk +12/23 15:18:20Z -fv3gfs test: your new post executable did not generate bit-identical gfs.t00z.master.grb2f006 as the trunk +12/23 15:18:23Z -fv3gfs test: your new post executable generates bit-identical gfs.t00z.sfluxgrbf006.grib2 as the trunk +12/23 15:18:24Z -fv3gfs test: your new post executable generates bit-identical gfs.t00z.special.grb2f006 as the trunk +12/23 15:19:05Z -fv3gfs pe test: your new post executable did not generate bit-identical gfs.t00z.master.grb2f006 as the trunk +12/23 15:19:08Z -fv3gfs pe test: your new post executable generates bit-identical gfs.t00z.sfluxgrbf006.grib2 as the trunk +12/23 15:19:08Z -fv3gfs pe test: your new post executable generates bit-identical gfs.t00z.special.grb2f006 as the trunk +12/23 15:10:53Z -Runtime: nmmb_test 00:00:59 -- baseline 00:01:00 +12/23 15:10:54Z -Runtime: nmmb_pe_test 00:01:07 -- baseline 00:01:00 +12/23 15:10:54Z -Runtime: fv3gefs_test 00:00:26 -- baseline 00:40:00 +12/23 15:10:54Z -Runtime: fv3gefs_pe_test 00:00:30 -- baseline 00:40:00 +12/23 15:10:54Z -Runtime: rap_test 00:01:02 -- baseline 00:02:00 +12/23 15:10:55Z -Runtime: rap_pe_test 00:01:13 -- baseline 00:02:00 +12/23 15:10:55Z -Runtime: hrrr_test 00:02:26 -- baseline 00:02:00 +12/23 15:10:56Z -Runtime: hrrr_pe_test 00:01:57 -- baseline 00:02:00 +12/23 15:18:31Z -Runtime: fv3gfs_test 00:09:01 -- baseline 00:15:00 +12/23 15:19:16Z -Runtime: fv3gfs_pe_test 00:09:45 -- baseline 00:15:00 +12/23 15:19:17Z -Runtime: fv3r_test 00:04:00 -- baseline 00:03:00 +12/23 15:19:17Z -Runtime: fv3r_pe_test 00:04:00 -- baseline 00:03:00 +12/23 15:19:17Z -Runtime: fv3hafs_test 00:00:34 -- baseline 00:03:00 +12/23 15:19:18Z -Runtime: fv3hafs_pe_test 00:00:32 -- baseline 00:03:00 +12/23 15:19:18Z -Runtime: rtma_test 00:04:09 -- baseline 00:03:00 +12/23 15:19:18Z -Runtime: rtma_test_pe_test 00:04:06 -- baseline +There are changes in results for case fv3r_pe_test in NATLEV10.tm00 +There are changes in results for case fv3r in NATLEV10.tm00 +There are changes in results for case gfs_pe_test in gfs.t00z.master.grb2f006 +There are changes in results for case gfs in gfs.t00z.master.grb2f006 +There are changes in results for case rtma_pe_test in NATLEV00.tm00 +There are changes in results for case rtma in NATLEV00.tm00 +Refer to .diff files in rundir: /scratch2/NAGAPE/epic/Gillian.Petro/RTs/upp-rts/1104/ci/rundir/upp-HERA for details on differences in results for each case. ===== End of UPP Regression Testing Log ===== From 1a7c45d6d11eb335b7cf502ef3390f7860ec6d13 Mon Sep 17 00:00:00 2001 From: gspetro-NOAA Date: Mon, 23 Dec 2024 10:54:15 -0600 Subject: [PATCH 5/6] add hercules rt log --- tests/logs/rt.log.HERCULES | 120 +++++++++++++++++++------------------ 1 file changed, 63 insertions(+), 57 deletions(-) diff --git a/tests/logs/rt.log.HERCULES b/tests/logs/rt.log.HERCULES index 451015f20..6bb869605 100644 --- a/tests/logs/rt.log.HERCULES +++ b/tests/logs/rt.log.HERCULES @@ -1,69 +1,75 @@ ===== Start of UPP Regression Testing Log ===== UPP Hash Tested: -37b7153aa49291e898b19768475ace063640ae13 +6f373c84a5e96eb5596c816cf00f0771cd43d8af Submodule hashes: -179cae1dd84401cf25d250bd9102e66560a9d328 sorc/libIFI.fd -529f870d33b65c3b6c1aa3c3236b94efc3bd336d sorc/ncep_post.fd/post_gtg.fd -Run directory: /work/noaa/epic/gpetro/hercules/RTs/upp-rts/1088/ci/rundir/upp-HERCULES +Run directory: /work/noaa/epic/gpetro/hercules/RTs/upp-rts/1104/ci/rundir/upp-HERCULES Baseline directory: /work/noaa/epic/UPP -Total runtime: 00h:11m:52s -Test Date: 20241121 09:39:43 +Total runtime: 00h:14m:52s +Test Date: 20241223 09:20:17 Summary Results: -11/21 15:30:55Z -nmmb pe test: your new post executable generates bit-identical BGDAWP03.tm00.Grib2 as the trunk -11/21 15:30:56Z -nmmb pe test: your new post executable generates bit-identical BGRD3D03.tm00.Grib2 as the trunk -11/21 15:30:56Z -nmmb pe test: your new post executable generates bit-identical BGRDSF03.tm00.Grib2 as the trunk -11/21 15:31:02Z -nmmb test: your new post executable generates bit-identical BGDAWP03.tm00.Grib2 as the trunk -11/21 15:31:03Z -nmmb test: your new post executable generates bit-identical BGRD3D03.tm00.Grib2 as the trunk -11/21 15:31:03Z -nmmb test: your new post executable generates bit-identical BGRDSF03.tm00.Grib2 as the trunk -11/21 15:31:07Z -fv3hafs test: your new post executable generates bit-identical HURPRS09.tm00 as the trunk -11/21 15:31:25Z -fv3gefs test: your new post executable generates bit-identical geaer.t00z.master.grb2f060 as the trunk -11/21 15:31:27Z -fv3gefs pe test: your new post executable generates bit-identical geaer.t00z.master.grb2f060 as the trunk -11/21 15:31:37Z -rap pe test: your new post executable did generate changed results in WRFPRS.GrbF16 -11/21 15:31:38Z -rap pe test: your new post executable generates bit-identical WRFNAT.GrbF16 as the trunk -11/21 15:31:38Z -fv3hafs pe test: your new post executable generates bit-identical HURPRS09.tm00 as the trunk -11/21 15:31:58Z -rap test: your new post executable generates bit-identical WRFPRS.GrbF16 as the trunk -11/21 15:31:58Z -rap test: your new post executable generates bit-identical WRFNAT.GrbF16 as the trunk -11/21 15:32:19Z -hrrr pe test: your new post executable generates bit-identical WRFTWO.GrbF04 as the trunk -11/21 15:32:20Z -hrrr pe test: your new post executable generates bit-identical WRFPRS.GrbF04 as the trunk -11/21 15:32:21Z -hrrr pe test: your new post executable generates bit-identical WRFNAT.GrbF04 as the trunk -11/21 15:32:26Z -fv3r test: your new post executable generates bit-identical PRSLEV10.tm00 as the trunk -11/21 15:32:29Z -fv3r test: your new post executable generates bit-identical NATLEV10.tm00 as the trunk -11/21 15:32:39Z -fv3r pe test: your new post executable generates bit-identical PRSLEV10.tm00 as the trunk -11/21 15:32:42Z -fv3r pe test: your new post executable generates bit-identical NATLEV10.tm00 as the trunk -11/21 15:33:20Z -rtma pe test: your new post executable generates bit-identical NATLEV00.tm00 as the trunk -11/21 15:33:22Z -rtma test: your new post executable generates bit-identical NATLEV00.tm00 as the trunk -11/21 15:33:22Z -rtma pe test: your new post executable generates bit-identical PRSLEV00.tm00 as the trunk -11/21 15:33:22Z -rtma pe test: your new post executable generates bit-identical IFIFIP00.tm00 as the trunk -11/21 15:33:23Z -rtma test: your new post executable generates bit-identical PRSLEV00.tm00 as the trunk -11/21 15:33:23Z -rtma test: your new post executable generates bit-identical IFIFIP00.tm00 as the trunk -11/21 15:35:32Z -hrrr test: your new post executable generates bit-identical WRFTWO.GrbF04 as the trunk -11/21 15:35:33Z -hrrr test: your new post executable generates bit-identical WRFPRS.GrbF04 as the trunk -11/21 15:35:34Z -hrrr test: your new post executable generates bit-identical WRFNAT.GrbF04 as the trunk -11/21 15:36:56Z -fv3gfs pe test: your new post executable generates bit-identical gfs.t00z.master.grb2f006 as the trunk -11/21 15:36:57Z -fv3gfs pe test: your new post executable generates bit-identical gfs.t00z.sfluxgrbf006.grib2 as the trunk -11/21 15:36:57Z -fv3gfs pe test: your new post executable generates bit-identical gfs.t00z.special.grb2f006 as the trunk -11/21 15:39:35Z -fv3gfs test: your new post executable generates bit-identical gfs.t00z.master.grb2f006 as the trunk -11/21 15:39:35Z -fv3gfs test: your new post executable generates bit-identical gfs.t00z.sfluxgrbf006.grib2 as the trunk -11/21 15:39:35Z -fv3gfs test: your new post executable generates bit-identical gfs.t00z.special.grb2f006 as the trunk -11/21 15:31:12Z -Runtime: nmmb_test 00:01:04 -- baseline 00:03:00 -11/21 15:31:12Z -Runtime: nmmb_pe_test 00:00:58 -- baseline 00:03:00 -11/21 15:31:27Z -Runtime: fv3gefs_test 00:00:15 -- baseline 01:20:00 -11/21 15:31:42Z -Runtime: fv3gefs_pe_test 00:00:17 -- baseline 01:20:00 -11/21 15:32:12Z -Runtime: rap_test 00:00:48 -- baseline 00:02:00 -11/21 15:32:12Z -Runtime: rap_pe_test 00:00:57 -- baseline 00:02:00 -11/21 15:35:42Z -Runtime: hrrr_test 00:04:24 -- baseline 00:02:00 -11/21 15:35:42Z -Runtime: hrrr_pe_test 00:01:40 -- baseline 00:02:00 -11/21 15:39:43Z -Runtime: fv3gfs_test 00:08:54 -- baseline 00:18:00 -11/21 15:39:43Z -Runtime: fv3gfs_pe_test 00:06:16 -- baseline 00:18:00 -11/21 15:39:43Z -Runtime: fv3r_test 00:01:48 -- baseline 00:03:00 -11/21 15:39:43Z -Runtime: fv3r_pe_test 00:02:01 -- baseline 00:03:00 -11/21 15:39:43Z -Runtime: fv3hafs_test 00:00:26 -- baseline 00:00:40 -11/21 15:39:43Z -Runtime: fv3hafs_pe_test 00:00:28 -- baseline 00:00:40 -11/21 15:39:43Z -Runtime: rtma_test 00:02:13 -- baseline 00:04:00 -11/21 15:39:43Z -Runtime: rtma_pe_test 00:02:12 -- baseline 00:04:00 -No changes in test results detected. +12/23 15:08:36Z -nmmb pe test: your new post executable generates bit-identical BGDAWP03.tm00.Grib2 as the trunk +12/23 15:08:37Z -nmmb pe test: your new post executable generates bit-identical BGRD3D03.tm00.Grib2 as the trunk +12/23 15:08:37Z -nmmb pe test: your new post executable generates bit-identical BGRDSF03.tm00.Grib2 as the trunk +12/23 15:08:42Z -rap pe test: your new post executable did generate changed results in WRFPRS.GrbF16 +12/23 15:08:42Z -rap pe test: your new post executable generates bit-identical WRFNAT.GrbF16 as the trunk +12/23 15:08:49Z -nmmb test: your new post executable generates bit-identical BGDAWP03.tm00.Grib2 as the trunk +12/23 15:08:50Z -nmmb test: your new post executable generates bit-identical BGRD3D03.tm00.Grib2 as the trunk +12/23 15:08:50Z -nmmb test: your new post executable generates bit-identical BGRDSF03.tm00.Grib2 as the trunk +12/23 15:08:59Z -fv3gefs test: your new post executable generates bit-identical geaer.t00z.master.grb2f060 as the trunk +12/23 15:09:02Z -fv3gefs pe test: your new post executable generates bit-identical geaer.t00z.master.grb2f060 as the trunk +12/23 15:09:08Z -fv3hafs pe test: your new post executable generates bit-identical HURPRS09.tm00 as the trunk +12/23 15:09:08Z -fv3hafs test: your new post executable generates bit-identical HURPRS09.tm00 as the trunk +12/23 15:09:12Z -hrrr pe test: your new post executable generates bit-identical WRFTWO.GrbF04 as the trunk +12/23 15:09:13Z -hrrr pe test: your new post executable generates bit-identical WRFPRS.GrbF04 as the trunk +12/23 15:09:14Z -hrrr pe test: your new post executable generates bit-identical WRFNAT.GrbF04 as the trunk +12/23 15:09:32Z -rap test: your new post executable generates bit-identical WRFPRS.GrbF16 as the trunk +12/23 15:09:32Z -rap test: your new post executable generates bit-identical WRFNAT.GrbF16 as the trunk +12/23 15:09:34Z -fv3r pe test: your new post executable generates bit-identical PRSLEV10.tm00 as the trunk +12/23 15:10:20Z -fv3r test: your new post executable generates bit-identical PRSLEV10.tm00 as the trunk +12/23 15:11:40Z -fv3r pe test: your new post executable did not generate bit-identical NATLEV10.tm00 as the trunk +12/23 15:12:37Z -fv3r test: your new post executable did not generate bit-identical NATLEV10.tm00 as the trunk +12/23 15:13:00Z -rtma test: your new post executable did not generate bit-identical NATLEV00.tm00 as the trunk +12/23 15:13:02Z -rtma test: your new post executable generates bit-identical PRSLEV00.tm00 as the trunk +12/23 15:13:02Z -rtma test: your new post executable generates bit-identical IFIFIP00.tm00 as the trunk +12/23 15:13:02Z -rtma pe test: your new post executable did not generate bit-identical NATLEV00.tm00 as the trunk +12/23 15:13:04Z -rtma pe test: your new post executable generates bit-identical PRSLEV00.tm00 as the trunk +12/23 15:13:04Z -rtma pe test: your new post executable generates bit-identical IFIFIP00.tm00 as the trunk +12/23 15:13:28Z -fv3gfs pe test: your new post executable did not generate bit-identical gfs.t00z.master.grb2f006 as the trunk +12/23 15:13:29Z -fv3gfs pe test: your new post executable generates bit-identical gfs.t00z.sfluxgrbf006.grib2 as the trunk +12/23 15:13:29Z -fv3gfs pe test: your new post executable generates bit-identical gfs.t00z.special.grb2f006 as the trunk +12/23 15:16:56Z -hrrr test: your new post executable generates bit-identical WRFTWO.GrbF04 as the trunk +12/23 15:16:56Z -hrrr test: your new post executable generates bit-identical WRFPRS.GrbF04 as the trunk +12/23 15:16:58Z -hrrr test: your new post executable generates bit-identical WRFNAT.GrbF04 as the trunk +12/23 15:20:06Z -fv3gfs test: your new post executable did not generate bit-identical gfs.t00z.master.grb2f006 as the trunk +12/23 15:20:07Z -fv3gfs test: your new post executable generates bit-identical gfs.t00z.sfluxgrbf006.grib2 as the trunk +12/23 15:20:07Z -fv3gfs test: your new post executable generates bit-identical gfs.t00z.special.grb2f006 as the trunk +12/23 15:09:01Z -Runtime: nmmb_test 00:01:18 -- baseline 00:03:00 +12/23 15:09:01Z -Runtime: nmmb_pe_test 00:01:05 -- baseline 00:03:00 +12/23 15:09:01Z -Runtime: fv3gefs_test 00:00:18 -- baseline 01:20:00 +12/23 15:09:16Z -Runtime: fv3gefs_pe_test 00:00:21 -- baseline 01:20:00 +12/23 15:09:46Z -Runtime: rap_test 00:00:51 -- baseline 00:02:00 +12/23 15:09:46Z -Runtime: rap_pe_test 00:01:09 -- baseline 00:02:00 +12/23 15:17:01Z -Runtime: hrrr_test 00:08:17 -- baseline 00:02:00 +12/23 15:17:01Z -Runtime: hrrr_pe_test 00:01:41 -- baseline 00:02:00 +12/23 15:20:17Z -Runtime: fv3gfs_test 00:12:34 -- baseline 00:18:00 +12/23 15:20:17Z -Runtime: fv3gfs_pe_test 00:05:56 -- baseline 00:18:00 +12/23 15:20:17Z -Runtime: fv3r_test 00:05:04 -- baseline 00:03:00 +12/23 15:20:17Z -Runtime: fv3r_pe_test 00:04:07 -- baseline 00:03:00 +12/23 15:20:17Z -Runtime: fv3hafs_test 00:00:27 -- baseline 00:00:40 +12/23 15:20:17Z -Runtime: fv3hafs_pe_test 00:00:27 -- baseline 00:00:40 +12/23 15:20:17Z -Runtime: rtma_test 00:04:21 -- baseline 00:04:00 +12/23 15:20:17Z -Runtime: rtma_pe_test 00:04:23 -- baseline 00:04:00 +There are changes in results for case rtma_pe_test in NATLEV00.tm00 +There are changes in results for case gfs in gfs.t00z.master.grb2f006 +There are changes in results for case fv3r in NATLEV10.tm00 +There are changes in results for case rtma in NATLEV00.tm00 +There are changes in results for case fv3r_pe_test in NATLEV10.tm00 +There are changes in results for case gfs_pe_test in gfs.t00z.master.grb2f006 +Refer to .diff files in rundir: /work/noaa/epic/gpetro/hercules/RTs/upp-rts/1104/ci/rundir/upp-HERCULES for details on differences in results for each case. ===== End of UPP Regression Testing Log ===== From 43b66d9028ab2f15feeaf8ec23e361cb1c7a6ff7 Mon Sep 17 00:00:00 2001 From: gspetro-NOAA Date: Mon, 23 Dec 2024 10:55:08 -0600 Subject: [PATCH 6/6] add orion rt log --- tests/logs/rt.log.ORION | 120 +++++++++++++++++++++------------------- 1 file changed, 63 insertions(+), 57 deletions(-) diff --git a/tests/logs/rt.log.ORION b/tests/logs/rt.log.ORION index cb3a82e28..e1d2d6038 100644 --- a/tests/logs/rt.log.ORION +++ b/tests/logs/rt.log.ORION @@ -1,69 +1,75 @@ ===== Start of UPP Regression Testing Log ===== UPP Hash Tested: -37b7153aa49291e898b19768475ace063640ae13 +6f373c84a5e96eb5596c816cf00f0771cd43d8af Submodule hashes: -179cae1dd84401cf25d250bd9102e66560a9d328 sorc/libIFI.fd -529f870d33b65c3b6c1aa3c3236b94efc3bd336d sorc/ncep_post.fd/post_gtg.fd -Run directory: /work/noaa/epic/gpetro/orion/RTs/upp-rts/1088/ci/rundir/upp-ORION +Run directory: /work/noaa/epic/gpetro/orion/RTs/upp-rts/1104/ci/rundir/upp-ORION Baseline directory: /work/noaa/epic/UPP -Total runtime: 00h:14m:12s -Test Date: 20241121 09:43:42 +Total runtime: 00h:13m:00s +Test Date: 20241223 09:18:28 Summary Results: -11/21 15:33:53Z -nmmb pe test: your new post executable generates bit-identical BGDAWP03.tm00.Grib2 as the trunk -11/21 15:33:57Z -nmmb pe test: your new post executable generates bit-identical BGRD3D03.tm00.Grib2 as the trunk -11/21 15:33:57Z -nmmb pe test: your new post executable generates bit-identical BGRDSF03.tm00.Grib2 as the trunk -11/21 15:34:04Z -nmmb test: your new post executable generates bit-identical BGDAWP03.tm00.Grib2 as the trunk -11/21 15:34:05Z -nmmb test: your new post executable generates bit-identical BGRD3D03.tm00.Grib2 as the trunk -11/21 15:34:06Z -nmmb test: your new post executable generates bit-identical BGRDSF03.tm00.Grib2 as the trunk -11/21 15:34:07Z -fv3gefs test: your new post executable generates bit-identical geaer.t00z.master.grb2f060 as the trunk -11/21 15:34:12Z -fv3gefs pe test: your new post executable generates bit-identical geaer.t00z.master.grb2f060 as the trunk -11/21 15:34:19Z -fv3hafs test: your new post executable generates bit-identical HURPRS09.tm00 as the trunk -11/21 15:34:19Z -fv3hafs pe test: your new post executable generates bit-identical HURPRS09.tm00 as the trunk -11/21 15:35:10Z -rap pe test: your new post executable did generate changed results in WRFPRS.GrbF16 -11/21 15:35:11Z -rap pe test: your new post executable generates bit-identical WRFNAT.GrbF16 as the trunk -11/21 15:35:12Z -rap test: your new post executable generates bit-identical WRFPRS.GrbF16 as the trunk -11/21 15:35:13Z -rap test: your new post executable generates bit-identical WRFNAT.GrbF16 as the trunk -11/21 15:35:49Z -fv3r test: your new post executable generates bit-identical PRSLEV10.tm00 as the trunk -11/21 15:35:53Z -fv3r test: your new post executable generates bit-identical NATLEV10.tm00 as the trunk -11/21 15:35:59Z -fv3r pe test: your new post executable generates bit-identical PRSLEV10.tm00 as the trunk -11/21 15:36:02Z -fv3r pe test: your new post executable generates bit-identical NATLEV10.tm00 as the trunk -11/21 15:36:27Z -rtma pe test: your new post executable generates bit-identical NATLEV00.tm00 as the trunk -11/21 15:36:27Z -hrrr pe test: your new post executable generates bit-identical WRFTWO.GrbF04 as the trunk -11/21 15:36:28Z -hrrr pe test: your new post executable generates bit-identical WRFPRS.GrbF04 as the trunk -11/21 15:36:28Z -rtma test: your new post executable generates bit-identical NATLEV00.tm00 as the trunk -11/21 15:36:29Z -rtma pe test: your new post executable generates bit-identical PRSLEV00.tm00 as the trunk -11/21 15:36:29Z -hrrr pe test: your new post executable generates bit-identical WRFNAT.GrbF04 as the trunk -11/21 15:36:29Z -rtma pe test: your new post executable generates bit-identical IFIFIP00.tm00 as the trunk -11/21 15:36:30Z -rtma test: your new post executable generates bit-identical PRSLEV00.tm00 as the trunk -11/21 15:36:30Z -rtma test: your new post executable generates bit-identical IFIFIP00.tm00 as the trunk -11/21 15:41:05Z -hrrr test: your new post executable generates bit-identical WRFTWO.GrbF04 as the trunk -11/21 15:41:06Z -hrrr test: your new post executable generates bit-identical WRFPRS.GrbF04 as the trunk -11/21 15:41:07Z -hrrr test: your new post executable generates bit-identical WRFNAT.GrbF04 as the trunk -11/21 15:41:49Z -fv3gfs pe test: your new post executable generates bit-identical gfs.t00z.master.grb2f006 as the trunk -11/21 15:41:49Z -fv3gfs pe test: your new post executable generates bit-identical gfs.t00z.sfluxgrbf006.grib2 as the trunk -11/21 15:41:50Z -fv3gfs pe test: your new post executable generates bit-identical gfs.t00z.special.grb2f006 as the trunk -11/21 15:43:31Z -fv3gfs test: your new post executable generates bit-identical gfs.t00z.master.grb2f006 as the trunk -11/21 15:43:31Z -fv3gfs test: your new post executable generates bit-identical gfs.t00z.sfluxgrbf006.grib2 as the trunk -11/21 15:43:31Z -fv3gfs test: your new post executable generates bit-identical gfs.t00z.special.grb2f006 as the trunk -11/21 15:34:09Z -Runtime: nmmb_test 00:01:27 -- baseline 00:03:00 -11/21 15:34:10Z -Runtime: nmmb_pe_test 00:01:19 -- baseline 00:03:00 -11/21 15:34:10Z -Runtime: fv3gefs_test 00:00:21 -- baseline 01:20:00 -11/21 15:34:25Z -Runtime: fv3gefs_pe_test 00:00:26 -- baseline 01:20:00 -11/21 15:35:25Z -Runtime: rap_test 00:01:27 -- baseline 00:02:00 -11/21 15:35:25Z -Runtime: rap_pe_test 00:01:25 -- baseline 00:02:00 -11/21 15:41:11Z -Runtime: hrrr_test 00:07:21 -- baseline 00:02:00 -11/21 15:41:11Z -Runtime: hrrr_pe_test 00:02:43 -- baseline 00:02:00 -11/21 15:43:41Z -Runtime: fv3gfs_test 00:09:45 -- baseline 00:18:00 -11/21 15:43:41Z -Runtime: fv3gfs_pe_test 00:08:04 -- baseline 00:18:00 -11/21 15:43:41Z -Runtime: fv3r_test 00:02:07 -- baseline 00:03:00 -11/21 15:43:41Z -Runtime: fv3r_pe_test 00:02:16 -- baseline 00:03:00 -11/21 15:43:41Z -Runtime: fv3hafs_test 00:00:33 -- baseline 00:00:40 -11/21 15:43:41Z -Runtime: fv3hafs_pe_test 00:00:33 -- baseline 00:00:40 -11/21 15:43:42Z -Runtime: rtma_test 00:02:44 -- baseline 00:04:00 -11/21 15:43:42Z -Runtime: rtma_pe_test 00:02:43 -- baseline 00:04:00 -No changes in test results detected. +12/23 15:09:03Z -fv3gefs test: your new post executable generates bit-identical geaer.t00z.master.grb2f060 as the trunk +12/23 15:09:07Z -fv3gefs pe test: your new post executable generates bit-identical geaer.t00z.master.grb2f060 as the trunk +12/23 15:09:13Z -fv3hafs test: your new post executable generates bit-identical HURPRS09.tm00 as the trunk +12/23 15:09:13Z -fv3hafs pe test: your new post executable generates bit-identical HURPRS09.tm00 as the trunk +12/23 15:09:55Z -nmmb pe test: your new post executable generates bit-identical BGDAWP03.tm00.Grib2 as the trunk +12/23 15:09:56Z -nmmb pe test: your new post executable generates bit-identical BGRD3D03.tm00.Grib2 as the trunk +12/23 15:09:56Z -nmmb pe test: your new post executable generates bit-identical BGRDSF03.tm00.Grib2 as the trunk +12/23 15:10:04Z -rap pe test: your new post executable did generate changed results in WRFPRS.GrbF16 +12/23 15:10:05Z -rap pe test: your new post executable generates bit-identical WRFNAT.GrbF16 as the trunk +12/23 15:10:06Z -nmmb test: your new post executable generates bit-identical BGDAWP03.tm00.Grib2 as the trunk +12/23 15:10:07Z -nmmb test: your new post executable generates bit-identical BGRD3D03.tm00.Grib2 as the trunk +12/23 15:10:07Z -nmmb test: your new post executable generates bit-identical BGRDSF03.tm00.Grib2 as the trunk +12/23 15:10:29Z -rap test: your new post executable generates bit-identical WRFPRS.GrbF16 as the trunk +12/23 15:10:29Z -rap test: your new post executable generates bit-identical WRFNAT.GrbF16 as the trunk +12/23 15:10:45Z -fv3r test: your new post executable generates bit-identical PRSLEV10.tm00 as the trunk +12/23 15:10:50Z -fv3r pe test: your new post executable generates bit-identical PRSLEV10.tm00 as the trunk +12/23 15:11:19Z -hrrr pe test: your new post executable generates bit-identical WRFTWO.GrbF04 as the trunk +12/23 15:11:20Z -hrrr pe test: your new post executable generates bit-identical WRFPRS.GrbF04 as the trunk +12/23 15:11:21Z -hrrr pe test: your new post executable generates bit-identical WRFNAT.GrbF04 as the trunk +12/23 15:15:53Z -hrrr test: your new post executable generates bit-identical WRFTWO.GrbF04 as the trunk +12/23 15:15:54Z -hrrr test: your new post executable generates bit-identical WRFPRS.GrbF04 as the trunk +12/23 15:15:55Z -hrrr test: your new post executable generates bit-identical WRFNAT.GrbF04 as the trunk +12/23 15:15:56Z -fv3r test: your new post executable did not generate bit-identical NATLEV10.tm00 as the trunk +12/23 15:15:58Z -fv3r pe test: your new post executable did not generate bit-identical NATLEV10.tm00 as the trunk +12/23 15:16:21Z -rtma pe test: your new post executable did not generate bit-identical NATLEV00.tm00 as the trunk +12/23 15:16:23Z -rtma pe test: your new post executable generates bit-identical PRSLEV00.tm00 as the trunk +12/23 15:16:24Z -rtma pe test: your new post executable generates bit-identical IFIFIP00.tm00 as the trunk +12/23 15:16:30Z -rtma test: your new post executable did not generate bit-identical NATLEV00.tm00 as the trunk +12/23 15:16:32Z -rtma test: your new post executable generates bit-identical PRSLEV00.tm00 as the trunk +12/23 15:16:33Z -rtma test: your new post executable generates bit-identical IFIFIP00.tm00 as the trunk +12/23 15:16:37Z -fv3gfs pe test: your new post executable did not generate bit-identical gfs.t00z.master.grb2f006 as the trunk +12/23 15:16:37Z -fv3gfs pe test: your new post executable generates bit-identical gfs.t00z.sfluxgrbf006.grib2 as the trunk +12/23 15:16:38Z -fv3gfs pe test: your new post executable generates bit-identical gfs.t00z.special.grb2f006 as the trunk +12/23 15:18:16Z -fv3gfs test: your new post executable did not generate bit-identical gfs.t00z.master.grb2f006 as the trunk +12/23 15:18:17Z -fv3gfs test: your new post executable generates bit-identical gfs.t00z.sfluxgrbf006.grib2 as the trunk +12/23 15:18:17Z -fv3gfs test: your new post executable generates bit-identical gfs.t00z.special.grb2f006 as the trunk +12/23 15:10:10Z -Runtime: nmmb_test 00:01:26 -- baseline 00:03:00 +12/23 15:10:11Z -Runtime: nmmb_pe_test 00:01:15 -- baseline 00:03:00 +12/23 15:10:11Z -Runtime: fv3gefs_test 00:00:22 -- baseline 01:20:00 +12/23 15:10:11Z -Runtime: fv3gefs_pe_test 00:00:26 -- baseline 01:20:00 +12/23 15:10:41Z -Runtime: rap_test 00:01:48 -- baseline 00:02:00 +12/23 15:10:41Z -Runtime: rap_pe_test 00:01:24 -- baseline 00:02:00 +12/23 15:15:56Z -Runtime: hrrr_test 00:07:14 -- baseline 00:02:00 +12/23 15:15:57Z -Runtime: hrrr_pe_test 00:02:40 -- baseline 00:02:00 +12/23 15:18:27Z -Runtime: fv3gfs_test 00:09:36 -- baseline 00:18:00 +12/23 15:18:27Z -Runtime: fv3gfs_pe_test 00:07:57 -- baseline 00:18:00 +12/23 15:18:27Z -Runtime: fv3r_test 00:07:15 -- baseline 00:03:00 +12/23 15:18:27Z -Runtime: fv3r_pe_test 00:07:17 -- baseline 00:03:00 +12/23 15:18:27Z -Runtime: fv3hafs_test 00:00:32 -- baseline 00:00:40 +12/23 15:18:27Z -Runtime: fv3hafs_pe_test 00:00:32 -- baseline 00:00:40 +12/23 15:18:27Z -Runtime: rtma_test 00:07:52 -- baseline 00:04:00 +12/23 15:18:27Z -Runtime: rtma_pe_test 00:07:43 -- baseline 00:04:00 +There are changes in results for case rtma_pe_test in NATLEV00.tm00 +There are changes in results for case gfs in gfs.t00z.master.grb2f006 +There are changes in results for case fv3r in NATLEV10.tm00 +There are changes in results for case rtma in NATLEV00.tm00 +There are changes in results for case fv3r_pe_test in NATLEV10.tm00 +There are changes in results for case gfs_pe_test in gfs.t00z.master.grb2f006 +Refer to .diff files in rundir: /work/noaa/epic/gpetro/orion/RTs/upp-rts/1104/ci/rundir/upp-ORION for details on differences in results for each case. ===== End of UPP Regression Testing Log =====