Skip to content

Commit

Permalink
1)Add changes of total cloud fraction for FV3 GFS; 2)Tweak DBZI. (NOA…
Browse files Browse the repository at this point in the history
  • Loading branch information
WenMeng-NOAA committed Jul 20, 2020
1 parent e8f0f2e commit 8f2e0d9
Show file tree
Hide file tree
Showing 2 changed files with 37 additions and 3 deletions.
39 changes: 36 additions & 3 deletions sorc/ncep_post.fd/CLDRAD.f
Original file line number Diff line number Diff line change
Expand Up @@ -967,8 +967,9 @@ SUBROUTINE CLDRAD
endif
ENDIF
!
nmmb_clds1: IF ((MODELNAME=='NMM' .AND. GRIDTYPE=='B') .OR. &
MODELNAME=='FV3R'.OR. MODELNAME=='GFS') THEN
IF ((MODELNAME=='NMM' .AND. GRIDTYPE=='B') .OR. &
MODELNAME=='FV3R') THEN
!nmmb_clds1
!
!-- Initialize low, middle, high, and total cloud cover;
! also a method for cloud ceiling height
Expand Down Expand Up @@ -1024,7 +1025,39 @@ SUBROUTINE CLDRAD
ENDDO ! I
ENDDO ! J
ENDDO ! L
ENDIF nmmb_clds1
!end nmmb_clds1
ELSEIF (MODELNAME=='GFS') THEN
!Initialize for GLOBAL FV3 which has cluod fraction in range from
!0.0 to 1.0
!
!-- Initialize low, middle, high, and total cloud cover;
! also a method for cloud ceiling height
!
DO J=JSTA,JEND
DO I=1,IM
CFRACL(I,J)=0.
CFRACM(I,J)=0.
CFRACH(I,J)=0.
TCLD(I,J)=0.
ENDDO
ENDDO
DO L=LM,1,-1
DO J=JSTA,JEND
DO I=1,IM
FRAC=CFR(I,J,L) !- 3D cloud fraction at model layers
PCLDBASE=PMID(I,J,L) !-- Using PCLDBASE variable for convenience
IF (PCLDBASE>=PTOP_LOW) THEN
CFRACL(I,J)=MAX(CFRACL(I,J),FRAC)
ELSE IF (PCLDBASE>=PTOP_MID) THEN
CFRACM(I,J)=MAX(CFRACM(I,J),FRAC)
ELSE
CFRACH(I,J)=MAX(CFRACH(I,J),FRAC)
ENDIF
TCLD(I,J)=MAX(TCLD(I,J),FRAC)
ENDDO ! I
ENDDO ! J
ENDDO ! L
ENDIF
!
!*** BLOCK 2. 2-D CLOUD FIELDS.
!
Expand Down
1 change: 1 addition & 0 deletions sorc/ncep_post.fd/MDLFLD.f
Original file line number Diff line number Diff line change
Expand Up @@ -635,6 +635,7 @@ SUBROUTINE MDLFLD
DBZI(I,J,L) = DBZ(I,J,L)
ENDIF
ELSEIF (IICE == 1) THEN
DBZI(I,J,L) = 0.
QQG(I,J,L) = max(QQG(I,J,L),0.0)
if(QQR(I,J,L) < SPVAL .and. QQR(I,J,L)> 0.0) then
DBZR(I,J,L) = ((QQR(I,J,L)*DENS)**1.75) * 3.630803E-9 * 1.E18 ! Z FOR RAIN
Expand Down

0 comments on commit 8f2e0d9

Please sign in to comment.