Skip to content

Commit

Permalink
Merge pull request #233 from GEOS-ESM/develop
Browse files Browse the repository at this point in the history
Sync develop into master
  • Loading branch information
sdrabenh authored Mar 9, 2020
2 parents a8f3ce7 + de08f7e commit a350a12
Show file tree
Hide file tree
Showing 3 changed files with 222 additions and 83 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -175,6 +175,7 @@ SUBROUTINE GF_GEOS5_INTERFACE(mxp,myp,mzp,mtp,ITRCR,LONS,LATS,dt_moist
,TA ,QA ,SH ,EVAP ,PHIS &
,KPBLIN &
,MAPL_GRAV &
,STOCHASTIC_SIG, SIGMA_DEEP, SIGMA_MID &
,DQDT_GF,DTDT_GF,MUPDP,MUPSH,MUPMD &
,MFDP,MFSH,MFMD,ERRDP,ERRSH,ERRMD &
,AA0,AA1,AA2,AA3,AA1_BL,AA1_CIN,TAU_BL,TAU_EC &
Expand Down Expand Up @@ -211,7 +212,9 @@ SUBROUTINE GF_GEOS5_INTERFACE(mxp,myp,mzp,mtp,ITRCR,LONS,LATS,dt_moist

REAL ,DIMENSION(MXP,MYP) ,INTENT(IN) :: FRLAND ,AREA ,USTAR ,TSTAR ,QSTAR &
,T2M ,Q2M ,TA ,QA ,SH ,EVAP ,PHIS &
,KPBLIN,LONS,LATS
,KPBLIN,LONS,LATS &
,STOCHASTIC_SIG
REAL ,DIMENSION(MXP,MYP) ,INTENT(OUT) :: SIGMA_DEEP, SIGMA_MID
REAL ,DIMENSION(MXP,MYP) ,INTENT(OUT) :: CNPCPRATE ! kg m-2 s-1

REAL ,INTENT(IN) :: DT_moist ,MAPL_GRAV, qcrit, c0_auto
Expand Down Expand Up @@ -544,6 +547,7 @@ SUBROUTINE GF_GEOS5_INTERFACE(mxp,myp,mzp,mtp,ITRCR,LONS,LATS,dt_moist
,mynum &
,dt_moist &
,dx2d &
,stochastic_sig &
,zm3d &
,zt3d &
,dm3d &
Expand Down Expand Up @@ -616,6 +620,10 @@ SUBROUTINE GF_GEOS5_INTERFACE(mxp,myp,mzp,mtp,ITRCR,LONS,LATS,dt_moist
)
!

! Fill sigma exports
SIGMA_DEEP = sigma4d(:,:,deep)
SIGMA_MID = sigma4d(:,:,mid )

IF(FEED_3DMODEL)THEN
!-- update GEOS-5 model state with the feedback from cumulus convection
!- to include the tendencies from the convection, update the vars th1,q1,v1 and u1
Expand Down Expand Up @@ -914,6 +922,7 @@ SUBROUTINE GF_GEOS5_DRV(mxp,myp,mzp,mtp &
,mynum &
,dt &
,dx2d &
,stochastic_sig &
,zm &
,zt &
,dm &
Expand Down Expand Up @@ -1011,7 +1020,8 @@ SUBROUTINE GF_GEOS5_DRV(mxp,myp,mzp,mtp &

INTEGER, DIMENSION(its:ite,jts:jte), INTENT(IN) :: kpbl
REAL, DIMENSION(its:ite,jts:jte), INTENT(IN) :: topt ,aot500 ,temp2m ,sfc_press &
,sflux_r ,sflux_t ,xland,lons,lats,dx2d
,sflux_r ,sflux_t ,xland,lons,lats,dx2d &
,stochastic_sig
REAL, DIMENSION(kts:kte,its:ite,jts:jte), INTENT(IN) :: &
rthften &
,rqvften &
Expand Down Expand Up @@ -1469,6 +1479,7 @@ SUBROUTINE GF_GEOS5_DRV(mxp,myp,mzp,mtp &
,use_excess (deep) &
! input data
,dx2d(:,j) &
,stochastic_sig(:,j) &
,dt &
,kpbli &
,ztexec &
Expand Down Expand Up @@ -1578,6 +1589,7 @@ SUBROUTINE GF_GEOS5_DRV(mxp,myp,mzp,mtp &
,use_excess (mid) &
! input data
,dx2d(:,j) &
,stochastic_sig(:,j) &
,dt &
,kpbli &
,ztexec &
Expand Down Expand Up @@ -1768,6 +1780,7 @@ SUBROUTINE CUP_gf(its,ite,kts,kte ,itf,ktf, mtp , FSCAV &
,use_excess &
!input data
,dx &
,stochastic_sig &
,dtime &
,kpbl &
,ztexec &
Expand Down Expand Up @@ -1869,7 +1882,8 @@ SUBROUTINE CUP_gf(its,ite,kts,kte ,itf,ktf, mtp , FSCAV &
REAL, DIMENSION (its:ite,kts:kte) ,INTENT (INOUT) :: &
q,qo
REAL, DIMENSION (its:ite) ,INTENT (IN ) :: &
ccn,Z1,PSUR,xland,xlons,xlats, h_sfc_flux,le_sfc_flux,tsur,dx
ccn,Z1,PSUR,xland,xlons,xlats, h_sfc_flux,le_sfc_flux,tsur,dx, &
stochastic_sig
REAL, DIMENSION (its:ite) ,INTENT (INOUT) :: &
zws,ztexec,zqexec
REAL ,INTENT (IN ) :: &
Expand Down Expand Up @@ -2380,7 +2394,10 @@ SUBROUTINE CUP_gf(its,ite,kts,kte ,itf,ktf, mtp , FSCAV &
do i=its,itf
sig(i) = 0.
if(ierr(i) /= 0) cycle
sig(i)= 1.0-0.9839*exp(-0.09835*(dx(i)/1000.))
sig(i)= (1.0-0.9839*exp(-0.09835*(dx(i)/1000.)))
if (stochastic_sig(i) /= 1.0) then
sig(i) = sig(i)**(stochastic_sig(i)*MAX(1.0,2.5*sig(i)))
endif
sig(i)= max(0.001,min(sig(i),1.))
!print*,"FORM2=",sig(i),dx(i)
enddo
Expand Down Expand Up @@ -4065,6 +4082,22 @@ SUBROUTINE CUP_gf(its,ite,kts,kte ,itf,ktf, mtp , FSCAV &
!--only for debug
!ENDIF

!-4) convert back mass fluxes, etc...
do i=its,itf
if(ierr(i) /= 0) cycle
pwavo (i) = pwavo (i) / (xmb(i) + 1.e-16)
pwevo (i) = pwevo (i) / (xmb(i) + 1.e-16)
zuo (i,:) = zuo (i,:)/ (xmb(i) + 1.e-16)
zdo (i,:) = zdo (i,:)/ (xmb(i) + 1.e-16)
pwo (i,:) = pwo (i,:)/ (xmb(i) + 1.e-16)
pwdo (i,:) = pwdo (i,:)/ (xmb(i) + 1.e-16)
up_massentro(i,:) = up_massentro(i,:)/ (xmb(i) + 1.e-16)
up_massdetro(i,:) = up_massdetro(i,:)/ (xmb(i) + 1.e-16)
dd_massentro(i,:) = dd_massentro(i,:)/ (xmb(i) + 1.e-16)
dd_massdetro(i,:) = dd_massdetro(i,:)/ (xmb(i) + 1.e-16)
zenv (i,:) = zenv (i,:)/ (xmb(i) + 1.e-16)
enddo

!--------------------------------------------------------------------------------------------!
ENDIF !- end of section for atmospheric composition
!--------------------------------------------------------------------------------------------!
Expand Down Expand Up @@ -4435,10 +4468,11 @@ SUBROUTINE cup_dd_moisture(cumulus,ierrc,zd,hcd,hes_cup,qcd,qes_cup, &
ierr(i)=73
ierrc(i)="problem2 with buoy in cup_dd_moisture"
endif
if(abs(pwev(i)) > pwavo(i) )then
ierr(i)=77
ierrc(i)="problem 3 with evap in cup_dd_moisture"
endif
! Ensure that precip re-evaporation does not excede total precip
! if(abs(pwev(i)) > pwavo(i) )then
! ierr(i)=77
! ierrc(i)="problem 3 with evap in cup_dd_moisture"
! endif

100 continue!--- end loop over i

Expand Down Expand Up @@ -6503,6 +6537,14 @@ SUBROUTINE CUP_gf_sh(itf,ktf ,its,ite, kts,kte, mtp, FSCAV &
! enddo
!19 FORMAT(1x,I3,1x,5E14.3);18 FORMAT(1x,I3,1x,4E14.3);20 FORMAT(1x,I3,1x,11E16.6)
!-- for debug only
!-4) convert back mass fluxes
do i=its,itf
if(ierr(i) /= 0) cycle
zuo (i,:) = zuo(i,:) / (xmb(i) + 1.e-16)
up_massentro(i,:) = up_massentro(i,:) / (xmb(i) + 1.e-16)
up_massdetro(i,:) = up_massdetro(i,:) / (xmb(i) + 1.e-16)
zenv (i,:) = zenv (i,:) / (xmb(i) + 1.e-16)
enddo
!
!--------------------------------------------------------------------------------------------!
ENDIF !- end of section for atmospheric composition
Expand Down
Loading

0 comments on commit a350a12

Please sign in to comment.