Skip to content

Commit

Permalink
Merge pull request #4 from climbfuji/anning_mraerosol_updates_dom_202…
Browse files Browse the repository at this point in the history
…11018

Anning mraerosol updates dom 20211018
  • Loading branch information
AnningCheng-NOAA authored Oct 18, 2021
2 parents ddf9636 + 32d9c3d commit 6d46c5f
Show file tree
Hide file tree
Showing 7 changed files with 132 additions and 81 deletions.
4 changes: 2 additions & 2 deletions physics/GFS_PBL_generic.F90
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ module GFS_PBL_generic_common
contains

subroutine set_aerosol_tracer_index(imp_physics, imp_physics_wsm6, &
imp_physics_thompson, ltaerosol,mraerosol, &
imp_physics_thompson, ltaerosol,mraerosol, &
imp_physics_mg, ntgl, imp_physics_gfdl, &
imp_physics_zhao_carr, kk, &
errmsg, errflg)
Expand Down Expand Up @@ -191,7 +191,7 @@ subroutine GFS_PBL_generic_pre_run (im, levs, nvdiff, ntrac, rtg_ozone_index,
vdftra(i,k,10) = qgrs(i,k,ntoz)
enddo
enddo
rtg_ozone_index = 8
rtg_ozone_index = 10
else
do k=1,levs
do i=1,im
Expand Down
3 changes: 1 addition & 2 deletions physics/GFS_rrtmg_pre.F90
Original file line number Diff line number Diff line change
Expand Up @@ -197,7 +197,7 @@ subroutine GFS_rrtmg_pre_run (im, levs, lm, lmk, lmp, n_var_lndp, &
real(kind=kind_phys), dimension(im,lm+LTP+1) :: tem2db, hz

real(kind=kind_phys), dimension(im,lm+LTP,min(4,ncnd)) :: ccnd
real(kind=kind_phys), dimension(im,lm+LTP,2:ntrac+2) :: tracer1
real(kind=kind_phys), dimension(im,lm+LTP,2:ntrac) :: tracer1
real(kind=kind_phys), dimension(im,lm+LTP,NF_CLDS) :: clouds
real(kind=kind_phys), dimension(im,lm+LTP,NF_VGAS) :: gasvmr
real(kind=kind_phys), dimension(im,lm+LTP,NBDSW,NF_AESW) :: faersw
Expand Down Expand Up @@ -651,7 +651,6 @@ subroutine GFS_rrtmg_pre_run (im, levs, lm, lmk, lmp, n_var_lndp, &
nwfa (i,k) = tracer1(i,k,ntwa)
enddo
enddo

elseif (imp_physics == imp_physics_thompson) then
do k=1,LMK
do i=1,IM
Expand Down
22 changes: 10 additions & 12 deletions physics/GFS_suite_interstitial.F90
Original file line number Diff line number Diff line change
Expand Up @@ -513,8 +513,7 @@ end subroutine GFS_suite_interstitial_3_finalize
!! \htmlinclude GFS_suite_interstitial_3_run.html
!!
subroutine GFS_suite_interstitial_3_run (im, levs, nn, cscnv, &
satmedmf, trans_trac, do_shoc, &
ltaerosol, mraerosol, ntrac, ntcw, &
satmedmf, trans_trac, do_shoc, ntrac, ntcw, &
ntiw, ntclamt, ntrw, ntsw, ntrnc, ntsnc, ntgl, ntgnc, &
xlon, xlat, gt0, gq0, imp_physics, imp_physics_mg, &
imp_physics_zhao_carr, imp_physics_zhao_carr_pdf, &
Expand All @@ -534,8 +533,7 @@ subroutine GFS_suite_interstitial_3_run (im, levs, nn, cscnv, &
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_fer_hires, me, index_of_process_conv_trans
integer, intent(in ), dimension(:) :: islmsk, kpbl, kinver
logical, intent(in ) :: cscnv, satmedmf, trans_trac, do_shoc, ltaerosol, ras
logical, intent(in ) :: mraerosol
logical, intent(in ) :: cscnv, satmedmf, trans_trac, do_shoc, ras

integer, intent(in) :: ntinc, ntlnc
logical, intent(in) :: ldiag3d, qdiag3d
Expand Down Expand Up @@ -658,11 +656,11 @@ subroutine GFS_suite_interstitial_3_run (im, levs, nn, cscnv, &
save_tcp(i,k) = gt0(i,k)
enddo
enddo
if(ltaerosol .or. mraerosol) then
if (ntinc>0) then
save_qi(:,:) = clw(:,:,1)
end if
if (ntlnc>0) then
save_qc(:,:) = clw(:,:,2)
else
save_qi(:,:) = clw(:,:,1)
endif
elseif (imp_physics == imp_physics_wsm6 .or. imp_physics == imp_physics_mg .or. imp_physics == imp_physics_fer_hires) then
do k=1,levs
Expand Down Expand Up @@ -699,10 +697,10 @@ end subroutine GFS_suite_interstitial_4_finalize
!> \section arg_table_GFS_suite_interstitial_4_run Argument Table
!! \htmlinclude GFS_suite_interstitial_4_run.html
!!
subroutine GFS_suite_interstitial_4_run (im, levs, ltaerosol, mraerosol, 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, convert_dry_rho, dtf, save_qc, save_qi, con_pi, dtidx, dtend,&
index_of_process_conv_trans, gq0, clw, prsl, save_tcp, con_rd, con_eps, nwfa, spechum, ldiag3d, &
subroutine GFS_suite_interstitial_4_run (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, convert_dry_rho, dtf, save_qc, save_qi, con_pi, dtidx, dtend, &
index_of_process_conv_trans, gq0, clw, prsl, save_tcp, con_rd, con_eps, nwfa, spechum, ldiag3d, &
qdiag3d, save_lnc, save_inc, ntk, ntke, errmsg, errflg)

use machine, only: kind_phys
Expand All @@ -716,7 +714,7 @@ subroutine GFS_suite_interstitial_4_run (im, levs, ltaerosol, mraerosol, tracers
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

logical, intent(in) :: ltaerosol, convert_dry_rho, mraerosol
logical, intent(in) :: convert_dry_rho

real(kind=kind_phys), intent(in ) :: con_pi, dtf
real(kind=kind_phys), intent(in ), dimension(:,:) :: save_qc
Expand Down
32 changes: 0 additions & 32 deletions physics/GFS_suite_interstitial.meta
Original file line number Diff line number Diff line change
Expand Up @@ -1223,22 +1223,6 @@
type = logical
intent = in
optional = F
[ltaerosol]
standard_name = flag_for_aerosol_physics
long_name = flag for aerosol physics
units = flag
dimensions = ()
type = logical
intent = in
optional = F
[mraerosol]
standard_name = flag_for_merra2_aerosol_aware_for_thompson
long_name = flag for merra2 aerosol-aware physics for thompson microphysics
units = flag
dimensions = ()
type = logical
intent = in
optional = F
[ntrac]
standard_name = number_of_tracers
long_name = number of tracers
Expand Down Expand Up @@ -1695,22 +1679,6 @@
type = integer
intent = in
optional = F
[ltaerosol]
standard_name = flag_for_aerosol_physics
long_name = flag for aerosol physics
units = flag
dimensions = ()
type = logical
intent = in
optional = F
[mraerosol]
standard_name = flag_for_merra2_aerosol_aware_for_thompson
long_name = flag for merra2 aerosol-aware physics for thompson microphysics
units = flag
dimensions = ()
type = logical
intent = in
optional = F
[tracers_total]
standard_name = number_of_total_tracers
long_name = total number of tracers
Expand Down
2 changes: 2 additions & 0 deletions physics/module_MYNNPBL_wrapper.F90
Original file line number Diff line number Diff line change
Expand Up @@ -449,6 +449,8 @@ SUBROUTINE mynnedmf_wrapper_run( &
qnc(i,k) = qgrs_cloud_droplet_num_conc(i,k)
qni(i,k) = qgrs_cloud_ice_num_conc(i,k)
ozone(i,k) = qgrs_ozone(i,k)
qnwfa(i,k) = 0.
qnifa(i,k) = 0.
enddo
enddo
else
Expand Down
31 changes: 17 additions & 14 deletions physics/module_mp_thompson.F90
Original file line number Diff line number Diff line change
Expand Up @@ -460,14 +460,20 @@ SUBROUTINE thompson_init(is_aerosol_aware_in, &
! Set module variable is_aerosol_aware/merra2_aerosol_aware
is_aerosol_aware = is_aerosol_aware_in
merra2_aerosol_aware = merra2_aerosol_aware_in
if (is_aerosol_aware .and. merra2_aerosol_aware) then
errmsg = 'Logic error in thompson_init: only one of the two options can be true, ' // &
'not both: is_aerosol_aware or merra2_aerosol_aware'
errflg = 1
return
end if
if (mpirank==mpiroot) then
if (is_aerosol_aware) then
write (0,'(a)') 'Using aerosol-aware version of Thompson microphysics'
else if(merra2_aerosol_aware) then
write (0,'(a)') 'Using merra2 aerosol-aware version of Thompson microphysics'
else
write (0,'(a)') 'Using non-aerosol-aware version of Thompson microphysics'
end if
if (is_aerosol_aware) then
write (0,'(a)') 'Using aerosol-aware version of Thompson microphysics'
else if(merra2_aerosol_aware) then
write (0,'(a)') 'Using merra2 aerosol-aware version of Thompson microphysics'
else
write (0,'(a)') 'Using non-aerosol-aware version of Thompson microphysics'
end if
end if

micro_init = .FALSE.
Expand Down Expand Up @@ -1026,9 +1032,7 @@ SUBROUTINE mp_gt_driver(qv, qc, qr, qi, qs, qg, ni, nr, nc, &
REAL, DIMENSION(ims:ime, kms:kme, jms:jme), OPTIONAL, INTENT(IN):: &
pii
REAL, DIMENSION(ims:ime, kms:kme, jms:jme), OPTIONAL, INTENT(INOUT):: &
nc
REAL, DIMENSION(ims:ime, kms:kme, jms:jme), OPTIONAL, INTENT(INOUT):: &
nwfa, nifa
nc, nwfa, nifa
REAL, DIMENSION(ims:ime, jms:jme), OPTIONAL, INTENT(IN):: nwfa2d, nifa2d
REAL, DIMENSION(ims:ime, kms:kme, jms:jme), OPTIONAL, INTENT(INOUT):: &
re_cloud, re_ice, re_snow
Expand All @@ -1054,7 +1058,6 @@ SUBROUTINE mp_gt_driver(qv, qc, qr, qi, qs, qg, ni, nr, nc, &
REAL, DIMENSION(ims:ime, kms:kme, jms:jme), OPTIONAL, INTENT(INOUT):: &
vt_dbz_wt
LOGICAL, INTENT(IN) :: first_time_step

REAL, INTENT(IN):: dt_in, dt_inner
! To support subcycling: current step and maximum number of steps
INTEGER, INTENT (IN) :: istep, nsteps
Expand Down Expand Up @@ -1179,9 +1182,9 @@ SUBROUTINE mp_gt_driver(qv, qc, qr, qi, qs, qg, ni, nr, nc, &
else
stop
end if
else if (merra2_aerosol_aware .and. (.not.present(nc) .or. &
.not.present(nwfa) .or. &
.not.present(nifa) )) then
else if (merra2_aerosol_aware .and. (.not.present(nc) .or. &
.not.present(nwfa) .or. &
.not.present(nifa) )) then
if (present(errmsg)) then
write(errmsg, '(*(a))') 'Logic error in mp_gt_driver: provide nc, nwfa, and nifa', &
' for merra2 aerosol-aware version of Thompson microphysics'
Expand Down
Loading

0 comments on commit 6d46c5f

Please sign in to comment.