Skip to content

Commit

Permalink
Aligo-use the dx of the 1st i poit to set an integer value of dx to b…
Browse files Browse the repository at this point in the history
…e used for determining RHgrd
  • Loading branch information
mzhangw committed Aug 26, 2019
1 parent 80fedc4 commit fb011da
Show file tree
Hide file tree
Showing 4 changed files with 53 additions and 24 deletions.
18 changes: 10 additions & 8 deletions physics/GFS_suite_interstitial.F90
Original file line number Diff line number Diff line change
Expand Up @@ -559,6 +559,7 @@ end subroutine GFS_suite_interstitial_3_finalize
!! | imp_physics_zhao_carr_pdf | flag_for_zhao_carr_pdf_microphysics_scheme | choice of Zhao-Carr microphysics scheme with PDF clouds | flag | 0 | integer | | in | F |
!! | imp_physics_gfdl | flag_for_gfdl_microphysics_scheme | choice of GFDL microphysics scheme | flag | 0 | integer | | in | F |
!! | imp_physics_thompson | flag_for_thompson_microphysics_scheme | choice of Thompson microphysics scheme | flag | 0 | integer | | in | F |
!! | imp_physics_fer_hires | flag_for_Ferrier_Aligo_microphysics_scheme | choice of Ferrier-Aligo microphysics scheme | flag | 0 | integer | | in | F |
!! | imp_physics_wsm6 | flag_for_wsm6_microphysics_scheme | choice of WSM6 microphysics scheme | flag | 0 | integer | | in | F |
!! | prsi | air_pressure_at_interface | air pressure at model layer interfaces | Pa | 2 | real | kind_phys | in | F |
!! | prsl | air_pressure | mean layer pressure | Pa | 2 | real | kind_phys | in | F |
Expand All @@ -582,9 +583,9 @@ end subroutine GFS_suite_interstitial_3_finalize
#endif
subroutine GFS_suite_interstitial_3_run (im, levs, nn, cscnv, satmedmf, trans_trac, do_shoc, ltaerosol, ntrac, ntcw, &
ntiw, ntclamt, ntrw, ntsw, ntrnc, ntsnc, ntgl, ntgnc, xlat, gq0, imp_physics, imp_physics_mg, imp_physics_zhao_carr,&
imp_physics_zhao_carr_pdf, imp_physics_gfdl, imp_physics_thompson, imp_physics_wsm6, prsi, prsl, prslk, rhcbot, &
rhcpbl, rhctop, rhcmax, islmsk, work1, work2, kpbl, kinver, &
clw, rhc, save_qc, save_qi, errmsg, errflg)
imp_physics_zhao_carr_pdf, imp_physics_gfdl, imp_physics_thompson, imp_physics_wsm6, imp_physics_fer_hires, prsi, &
prsl, prslk, rhcbot,hcpbl, rhctop, rhcmax, islmsk, work1, work2, kpbl, kinver,clw, rhc, save_qc, save_qi,errmsg, &
errflg)

use machine, only: kind_phys

Expand All @@ -593,7 +594,7 @@ subroutine GFS_suite_interstitial_3_run (im, levs, nn, cscnv, satmedmf, trans_tr
! interface variables
integer, intent(in) :: im, levs, nn, ntrac, ntcw, ntiw, ntclamt, ntrw, &
ntsw, ntrnc, ntsnc, ntgl, ntgnc, imp_physics, imp_physics_mg, imp_physics_zhao_carr, imp_physics_zhao_carr_pdf, &
imp_physics_gfdl, imp_physics_thompson, imp_physics_wsm6
imp_physics_gfdl, imp_physics_thompson, imp_physics_wsm6,imp_physics_fer_hires
integer, dimension(im), intent(in) :: islmsk, kpbl, kinver
logical, intent(in) :: cscnv, satmedmf, trans_trac, do_shoc, ltaerosol

Expand Down Expand Up @@ -740,7 +741,7 @@ subroutine GFS_suite_interstitial_3_run (im, levs, nn, cscnv, satmedmf, trans_tr
else
save_qi(:,:) = clw(:,:,1)
endif
elseif (imp_physics == imp_physics_wsm6 .or. imp_physics == imp_physics_mg) then
elseif (imp_physics == imp_physics_wsm6 .or. imp_physics == imp_physics_mg .or. imp_physics == imp_physics_fer_hires) then
do k=1,levs
do i=1,im
clw(i,k,1) = gq0(i,k,ntiw) ! ice
Expand Down Expand Up @@ -795,6 +796,7 @@ end subroutine GFS_suite_interstitial_4_finalize
!! | imp_physics | flag_for_microphysics_scheme | choice of microphysics scheme | flag | 0 | integer | | in | F |
!! | imp_physics_gfdl | flag_for_gfdl_microphysics_scheme | choice of GFDL microphysics scheme | flag | 0 | integer | | in | F |
!! | imp_physics_thompson | flag_for_thompson_microphysics_scheme | choice of Thompson microphysics scheme | flag | 0 | integer | | in | F |
!! | imp_physics_fer_hires | flag_for_Ferrier_Aligo_microphysics_scheme | choice of Ferrier-Aligo microphysics scheme | flag | 0 | integer | | in | F |
!! | imp_physics_zhao_carr | flag_for_zhao_carr_microphysics_scheme | choice of Zhao-Carr microphysics scheme | flag | 0 | integer | | in | F |
!! | imp_physics_zhao_carr_pdf | flag_for_zhao_carr_pdf_microphysics_scheme | choice of Zhao-Carr microphysics scheme with PDF clouds | flag | 0 | integer | | in | F |
!! | dtf | time_step_for_dynamics | dynamics timestep | s | 0 | real | kind_phys | in | F |
Expand All @@ -809,7 +811,7 @@ end subroutine GFS_suite_interstitial_4_finalize
!!
subroutine GFS_suite_interstitial_4_run (im, levs, ltaerosol, lgocart, tracers_total, ntrac, ntcw, ntiw, ntclamt, &
ntrw, ntsw, ntrnc, ntsnc, ntgl, ntgnc, ntlnc, ntinc, nn, imp_physics, imp_physics_gfdl, imp_physics_thompson, &
imp_physics_zhao_carr, imp_physics_zhao_carr_pdf, dtf, save_qc, save_qi, con_pi, &
imp_physics_zhao_carr, imp_physics_zhao_carr_pdf, imp_physics_fer_hires, dtf, save_qc, save_qi, con_pi, &
gq0, clw, dqdti, errmsg, errflg)

use machine, only: kind_phys
Expand All @@ -820,7 +822,7 @@ subroutine GFS_suite_interstitial_4_run (im, levs, ltaerosol, lgocart, tracers_t

integer, intent(in) :: im, levs, tracers_total, ntrac, ntcw, ntiw, ntclamt, ntrw, &
ntsw, ntrnc, ntsnc, ntgl, ntgnc, ntlnc, ntinc, nn, imp_physics, imp_physics_gfdl, imp_physics_thompson, &
imp_physics_zhao_carr, imp_physics_zhao_carr_pdf
imp_physics_zhao_carr, imp_physics_zhao_carr_pdf,imp_physics_fer_hires

logical, intent(in) :: ltaerosol, lgocart

Expand Down Expand Up @@ -872,7 +874,7 @@ subroutine GFS_suite_interstitial_4_run (im, levs, ltaerosol, lgocart, tracers_t

! for microphysics
if (imp_physics == imp_physics_zhao_carr_pdf .or. imp_physics == imp_physics_zhao_carr &
.or. imp_physics == imp_physics_gfdl) then
.or. imp_physics == imp_physics_gfdl .or. imp_physics == imp_physics_fer_hires) then
gq0(1:im,:,ntcw) = clw(1:im,:,1) + clw(1:im,:,2)
elseif (ntiw > 0) then
do k=1,levs
Expand Down
8 changes: 5 additions & 3 deletions physics/maximum_hourly_diagnostics.F90
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,7 @@ end subroutine maximum_hourly_diagnostics_finalize
!! | imp_physics | flag_for_microphysics_scheme | choice of microphysics scheme | flag | 0 | integer | | in | F |
!! | imp_physics_gfdl | flag_for_gfdl_microphysics_scheme | choice of GFDL microphysics scheme | flag | 0 | integer | | in | F |
!! | imp_physics_thompson | flag_for_thompson_microphysics_scheme | choice of Thompson microphysics scheme | flag | 0 | integer | | in | F |
!! | imp_physics_fer_hires| flag_for_ferrier_aligo_microphysics_scheme | choice of Ferrier-Aligo microphysics scheme | flag | 0 | integer | | in | F |
!! | con_g | gravitational_acceleration | gravitational acceleration | m s-2 | 0 | real | kind_phys | in | F |
!! | phil | geopotential | geopotential at model layer centers | m2 s-2 | 2 | real | kind_phys | in | F |
!! | gt0 | air_temperature_updated_by_physics | temperature updated by physics | K | 2 | real | kind_phys | in | F |
Expand All @@ -54,15 +55,16 @@ end subroutine maximum_hourly_diagnostics_finalize
!!
#endif
subroutine maximum_hourly_diagnostics_run(im, levs, reset, lradar, imp_physics, &
imp_physics_gfdl, imp_physics_thompson, con_g, phil, &
imp_physics_gfdl, imp_physics_thompson, &
imp_physics_fer_hires,con_g, phil, &
gt0, refl_10cm, refdmax, refdmax263k, u10m, v10m, &
u10max, v10max, spd10max, pgr, t2m, q2m, t02max, &
t02min, rh02max, rh02min, errmsg, errflg)

! Interface variables
integer, intent(in) :: im, levs
logical, intent(in) :: reset, lradar
integer, intent(in) :: imp_physics, imp_physics_gfdl, imp_physics_thompson
integer, intent(in) :: imp_physics, imp_physics_gfdl, imp_physics_thompson, imp_physics_fer_hires
real(kind_phys), intent(in ) :: con_g
real(kind_phys), intent(in ) :: phil(im,levs)
real(kind_phys), intent(in ) :: gt0(im,levs)
Expand Down Expand Up @@ -94,7 +96,7 @@ subroutine maximum_hourly_diagnostics_run(im, levs, reset, lradar, imp_physics,
errflg = 0

!Calculate hourly max 1-km agl and -10C reflectivity
if (lradar .and. (imp_physics == imp_physics_gfdl .or. imp_physics == imp_physics_thompson)) then
if (lradar .and. (imp_physics == imp_physics_gfdl .or. imp_physics == imp_physics_thompson .or. imp_physics == imp_physics_fer_hires)) then
allocate(refd(im))
allocate(refd263k(im))
call max_fields(phil,refl_10cm,con_g,im,levs,refd,gt0,refd263k)
Expand Down
38 changes: 27 additions & 11 deletions physics/module_MP_FER_HIRES.F90
Original file line number Diff line number Diff line change
Expand Up @@ -213,7 +213,9 @@ MODULE MODULE_MP_FER_HIRES
! * NCW - number concentrations of cloud droplets (m**-3)
! ======================================================================
REAL, PUBLIC,PARAMETER :: &
& T_ICE=-40. &
& RHgrd_in=1. &
&, P_RHgrd_out=850.E2 &
& ,T_ICE=-40. &
& ,T_ICEK=T0C+T_ICE &
& ,T_ICE_init=-12. &
& ,NSI_max=250.E3 &
Expand All @@ -240,11 +242,11 @@ SUBROUTINE FER_HIRES (DT,RHgrd, &
& threads, &
& ims,ime, jms,jme, lm, &
& d_ss,mprates, &
& refl_10cm )
& refl_10cm,DX1 )
!-----------------------------------------------------------------------
IMPLICIT NONE
!-----------------------------------------------------------------------
INTEGER,INTENT(IN) :: D_SS,IMS,IME,JMS,JME,LM !ZM ,ITIMESTEP
INTEGER,INTENT(IN) :: D_SS,IMS,IME,JMS,JME,LM,DX1 !ZM ,ITIMESTEP
REAL, INTENT(IN) :: DT,RHgrd
INTEGER, INTENT(IN) :: THREADS
REAL, INTENT(IN), DIMENSION(ims:ime, jms:jme, lm):: &
Expand Down Expand Up @@ -291,7 +293,7 @@ SUBROUTINE FER_HIRES (DT,RHgrd, &
pidep1d,piacw1d,piacwi1d,piacwr1d,piacr1d,picnd1d,pievp1d, &
pimlt1d,praut1d,pracw1d,prevp1d,pisub1d,pevap1d,DBZ_col, & !jul28
NR_col,NS_col,vsnow1d,vrain11d,vrain21d,vci1d,NSmICE1d, &
INDEXS1d,INDEXR1d,RFlag1d !jul28 !jun01
INDEXS1d,INDEXR1d,RFlag1d,RHC_col !jul28 !jun01
!
!-----------------------------------------------------------------------
!**********************************************************************
Expand Down Expand Up @@ -452,6 +454,17 @@ SUBROUTINE FER_HIRES (DT,RHgrd, &
QI_col(L)=QI
QR_col(L)=QRdum
QW_col(L)=QW
!GFDL => New. Added RHC_col to allow for height- and grid-dependent values for
!GFDL the relative humidity threshold for condensation ("RHgrd")
!6/11/2010 mod - Use lower RHgrd_out threshold for < 850 hPa
!------------------------------------------------------------
IF(DX1 .GE. 10 .AND. P_col(L)<P_RHgrd_out) THEN ! gopal's doing
based on GFDL
RHC_col(L)=RHgrd
ELSE
RHC_col(L)=RHgrd_in
ENDIF

ENDDO
!
!#######################################################################
Expand All @@ -460,14 +473,14 @@ SUBROUTINE FER_HIRES (DT,RHgrd, &
!
I_index=I
J_index=J
CALL EGCP01COLUMN_hr ( ARAIN, ASNOW, DT, RHgrd, &
CALL EGCP01COLUMN_hr ( ARAIN, ASNOW, DT, RHC_col, &
& I_index, J_index, LSFC, &
& P_col, QI_col, QR_col, Q_col, QW_col, RimeF_col, T_col, &
& THICK_col, WC_col,LM,pcond1d,pidep1d, &
& piacw1d,piacwi1d,piacwr1d,piacr1d,picnd1d,pievp1d,pimlt1d, &
& praut1d,pracw1d,prevp1d,pisub1d,pevap1d, DBZ_col,NR_col,NS_col, &
& vsnow1d,vrain11d,vrain21d,vci1d,NSmICE1d,INDEXS1d,INDEXR1d, & !jul28
& RFlag1d) !jun01
& RFlag1d,DX1) !jun01
!#######################################################################
!
!--- Update storage arrays
Expand Down Expand Up @@ -653,14 +666,14 @@ END SUBROUTINE FER_HIRES
!###############################################################################
!###############################################################################
!
SUBROUTINE EGCP01COLUMN_hr ( ARAIN, ASNOW, DTPH, RHgrd, &
SUBROUTINE EGCP01COLUMN_hr ( ARAIN, ASNOW, DTPH, RHC_col, &
& I_index, J_index, LSFC, &
& P_col, QI_col, QR_col, Q_col, QW_col, RimeF_col, T_col, &
& THICK_col, WC_col ,LM,pcond1d,pidep1d, &
& piacw1d,piacwi1d,piacwr1d,piacr1d,picnd1d,pievp1d,pimlt1d, &
& praut1d,pracw1d,prevp1d,pisub1d,pevap1d, DBZ_col,NR_col,NS_col, &
& vsnow1d,vrain11d,vrain21d,vci1d,NSmICE1d,INDEXS1d,INDEXR1d, & !jul28
& RFlag1d) !jun01
& RFlag1d,DX1) !jun01
!
!###############################################################################
!###############################################################################
Expand Down Expand Up @@ -702,6 +715,7 @@ SUBROUTINE EGCP01COLUMN_hr ( ARAIN, ASNOW, DTPH, RHgrd, &
! T_col - vertical column of model temperature (deg K)
! THICK_col - vertical column of model mass thickness (density*height increment)
! WC_col - vertical column of model mixing ratio of total condensate (kg/kg)
! RHC_col - vertical column of threshold relative humidity for onset of condensation (ratio) !GFDL
!
!
! OUTPUT ARGUMENT LIST:
Expand Down Expand Up @@ -740,15 +754,15 @@ SUBROUTINE EGCP01COLUMN_hr ( ARAIN, ASNOW, DTPH, RHgrd, &
!
IMPLICIT NONE
!
INTEGER,INTENT(IN) :: LM,I_index, J_index, LSFC
REAL,INTENT(IN) :: DTPH,RHgrd
INTEGER,INTENT(IN) :: LM,I_index, J_index, LSFC,DX1
REAL,INTENT(IN) :: DTPH
REAL,INTENT(INOUT) :: ARAIN, ASNOW
REAL,DIMENSION(LM),INTENT(INOUT) :: P_col, QI_col,QR_col &
& ,Q_col ,QW_col, RimeF_col, T_col, THICK_col,WC_col,pcond1d &
& ,pidep1d,piacw1d,piacwi1d,piacwr1d,piacr1d,picnd1d,pievp1d &
& ,pimlt1d,praut1d,pracw1d,prevp1d,pisub1d,pevap1d,DBZ_col,NR_col &
& ,NS_col,vsnow1d,vrain11d,vrain21d,vci1d,NSmICE1d,INDEXS1d & !jun01
& ,INDEXR1d,RFlag1d !jun01
& ,INDEXR1d,RFlag1d,RHC_col !jun01
!
!--------------------------------------------------------------------------------
!--- The following arrays are integral calculations based on the mean
Expand Down Expand Up @@ -816,6 +830,7 @@ SUBROUTINE EGCP01COLUMN_hr ( ARAIN, ASNOW, DTPH, RHgrd, &
!-----------------------------------------------------------------------
!
REAL :: EMAIRI, N0r, NLICE, NSmICE, NInuclei, Nrain, Nsnow, Nmix
REAL :: RHgrd
LOGICAL :: CLEAR, ICE_logical, DBG_logical, RAIN_logical, &
STRAT, DRZL
INTEGER :: INDEX_MY,INDEXR,INDEXR1,INDEXR2,INDEXS,IPASS,ITDX,IXRF,&
Expand Down Expand Up @@ -923,6 +938,7 @@ SUBROUTINE EGCP01COLUMN_hr ( ARAIN, ASNOW, DTPH, RHgrd, &
Q=Q_col(L) ! Specific humidity of water vapor (kg/kg)
WV=Q/(1.-Q) ! Water vapor mixing ratio (kg/kg)
WC=WC_col(L) ! Grid-scale mixing ratio of total condensate (water or ice; kg/kg)
RHgrd=RHC_col(L) ! Threshold relative humidity for the onset of condensation
!
!-----------------------------------------------------------------------
!--- Moisture variables below are mixing ratios & not specifc humidities
Expand Down
Loading

0 comments on commit fb011da

Please sign in to comment.