Skip to content

Commit

Permalink
Unify global and regional FV3 read interfaces (#453)
Browse files Browse the repository at this point in the history
* Unify the interfaces for reading FV3 outputs in netcdf.

* Remove interface INITPOST_GFS_NETCDF_PARA.

* Remove INITPOST_GFS_NETCDF.f.

* Remove the capability of serial netcdf reading FV3 outputs.

* Correct reading rswinc.

* Remove duplication in CLDRAD.f.

* Remove duplicated avgalbedo reading

* Add changes for reading pwat from model.

* Clean up commented out code

* Clean up duplicated lines
  • Loading branch information
WenMeng-NOAA authored Mar 30, 2022
1 parent 1ac2cd7 commit 5bdb289
Show file tree
Hide file tree
Showing 9 changed files with 325 additions and 5,634 deletions.
3 changes: 3 additions & 0 deletions sorc/ncep_post.fd/ALLOCATE_ALL.f
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@
!! - 21-04-06 Wen Meng - Initializing all allocated arrays
!! - 21-04-16 Wen Meng - Initializing aextc55 and extc55 as 0. These
!! two arrays are involved in GSL visibility computation.
!! - 22-03-22 Wen Meng - Initializing pwat.
!!
!! OUTPUT FILES:
!! - STDOUT - RUN TIME STANDARD OUT.
Expand Down Expand Up @@ -970,6 +971,7 @@ SUBROUTINE ALLOCATE_ALL()
allocate(tedir(im,jsta_2l:jend_2u))
allocate(twa(im,jsta_2l:jend_2u))
allocate(fdnsst(im,jsta_2l:jend_2u))
allocate(pwat(im,jsta_2l:jend_2u))
!Initialization
!$omp parallel do private(i,j)
do j=jsta_2l,jend_2u
Expand Down Expand Up @@ -1020,6 +1022,7 @@ SUBROUTINE ALLOCATE_ALL()
tedir(i,j)=spval
twa(i,j)=spval
fdnsst(i,j)=spval
pwat(i,j)=spval
enddo
enddo
!
Expand Down
25 changes: 22 additions & 3 deletions sorc/ncep_post.fd/CLDRAD.f
Original file line number Diff line number Diff line change
Expand Up @@ -107,18 +107,19 @@ SUBROUTINE CLDRAD
HBOT, HBOTD, HBOTS, HTOP, HTOPD, HTOPS, FIS, PBLH, &
PBOT, PBOTL, PBOTM, PBOTH, CNVCFR, PTOP, PTOPL, &
PTOPM, PTOPH, TTOPL, TTOPM, TTOPH, PBLCFR, CLDWORK, &
ASWIN, AUVBIN, AUVBINC, ASWIN, ASWOUT,ALWOUT, ASWTOA,&
ASWIN, AUVBIN, AUVBINC, ASWOUT,ALWOUT, ASWTOA, &
RLWTOA, CZMEAN, CZEN, RSWIN, ALWIN, ALWTOA, RLWIN, &
SIGT4, RSWOUT, RADOT, RSWINC, ASWINC, ASWOUTC, &
ASWTOAC, ALWOUTC, ASWTOAC, AVISBEAMSWIN, &
AVISDIFFSWIN, ASWINTOA, ASWINC, ASWTOAC, AIRBEAMSWIN,&
AVISDIFFSWIN, ASWINTOA, ASWTOAC, AIRBEAMSWIN, &
AIRDIFFSWIN, DUSMASS, DUSMASS25, DUCMASS, DUCMASS25, &
ALWINC, ALWTOAC, SWDDNI, SWDDIF, SWDNBC, SWDDNIC, &
SWDDIFC, SWUPBC, LWDNBC, LWUPBC, SWUPT, &
TAOD5502D, AERSSA2D, AERASY2D, MEAN_FRP, LWP, IWP, &
AVGCPRATE, &
DUSTCB,SSCB,BCCB,OCCB,SULFCB,DUSTPM,SSPM,aod550, &
du_aod550,ss_aod550,su_aod550,oc_aod550,bc_aod550
du_aod550,ss_aod550,su_aod550,oc_aod550,bc_aod550, &
PWAT
use masks, only: LMH, HTM
use params_mod, only: TFRZ, D00, H99999, QCLDMIN, SMALL, D608, H1, ROG, &
GI, RD, QCONV, ABSCOEFI, ABSCOEF, STBOL, PQ0, A2, &
Expand Down Expand Up @@ -254,6 +255,7 @@ SUBROUTINE CLDRAD
data INDX_EXT / 610, 611, 612, 613, 614 /
data INDX_SCA / 651, 652, 653, 654, 655 /
logical, parameter :: debugprint = .false.
logical :: Model_Pwat
!
!
!*************************************************************************
Expand Down Expand Up @@ -417,12 +419,29 @@ SUBROUTINE CLDRAD
IF (IGET(080) > 0) THEN
! dong
GRID1 = spval
Model_Pwat = .false.
DO J=JSTA,JEND
DO I=1,IM
IF(ABS(PWAT(I,J)-SPVAL)>SMALL) THEN
Model_Pwat = .true.
exit
ENDIF
END DO
END DO
IF (Model_Pwat) THEN
DO J=JSTA,JEND
DO I=1,IM
GRID1(I,J) = PWAT(I,J)
END DO
END DO
ELSE
CALL CALPW(GRID1(1,jsta),1)
DO J=JSTA,JEND
DO I=1,IM
IF(FIS(I,J) >= SPVAL) GRID1(I,J)=spval
END DO
END DO
ENDIF
CALL BOUND(GRID1,D00,H99999)
if(grib == "grib2" )then
cfld = cfld + 1
Expand Down
2 changes: 0 additions & 2 deletions sorc/ncep_post.fd/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -151,8 +151,6 @@ list(APPEND EXE_SRC
GFSPOSTSIG.F
INITPOST.F
INITPOST_GFS_NEMS_MPIIO.f
INITPOST_GFS_NETCDF.f
INITPOST_GFS_NETCDF_PARA.f
INITPOST_NEMS.f
INITPOST_NETCDF.f
WRFPOST.f
Expand Down
1 change: 1 addition & 0 deletions sorc/ncep_post.fd/DEALLOCATE.f
Original file line number Diff line number Diff line change
Expand Up @@ -386,6 +386,7 @@ SUBROUTINE DE_ALLOCATE
deallocate(tedir)
deallocate(twa)
deallocate(fdnsst)
deallocate(pwat)
! GSD
deallocate(rainc_bucket)
deallocate(rainc_bucket1)
Expand Down
Loading

0 comments on commit 5bdb289

Please sign in to comment.