Skip to content

Commit dd49119

Browse files
Merge pull request NCAR#910 from ChunxiZhang-NOAA/grt_rad
Added coupling of GOCART aerosols with the RRTMG scheme and the Thompson scheme
2 parents a1885a2 + af1e2c0 commit dd49119

11 files changed

+299
-64
lines changed

physics/GFS_phys_time_vary.fv3.F90

+21-25
Original file line numberDiff line numberDiff line change
@@ -35,6 +35,7 @@ module GFS_phys_time_vary
3535
!--- variables needed for calculating 'sncovr'
3636
use namelist_soilveg, only: salp_data, snupx
3737
use set_soilveg_mod, only: set_soilveg
38+
use physparam, only : iaermdl
3839

3940
! --- needed for Noah MP init
4041
use noahmp_tables, only: laim_table,saim_table,sla_table, &
@@ -67,7 +68,8 @@ module GFS_phys_time_vary
6768
!>\section gen_GFS_phys_time_vary_init GFS_phys_time_vary_init General Algorithm
6869
!! @{
6970
subroutine GFS_phys_time_vary_init ( &
70-
me, master, ntoz, h2o_phys, iaerclm, iccn, iflip, im, nx, ny, idate, xlat_d, xlon_d, &
71+
me, master, ntoz, h2o_phys, iaerclm, iccn, iflip, im, levs, &
72+
nx, ny, idate, xlat_d, xlon_d, &
7173
jindx1_o3, jindx2_o3, ddy_o3, ozpl, jindx1_h, jindx2_h, ddy_h, h2opl,fhour, &
7274
jindx1_aer, jindx2_aer, ddy_aer, iindx1_aer, iindx2_aer, ddx_aer, aer_nm, &
7375
jindx1_ci, jindx2_ci, ddy_ci, iindx1_ci, iindx2_ci, ddx_ci, imap, jmap, &
@@ -85,7 +87,7 @@ subroutine GFS_phys_time_vary_init (
8587
implicit none
8688

8789
! Interface variables
88-
integer, intent(in) :: me, master, ntoz, iccn, iflip, im, nx, ny
90+
integer, intent(in) :: me, master, ntoz, iccn, iflip, im, nx, ny, levs
8991
logical, intent(in) :: h2o_phys, iaerclm, lsm_cold_start
9092
integer, intent(in) :: idate(:)
9193
real(kind_phys), intent(in) :: fhour
@@ -96,7 +98,7 @@ subroutine GFS_phys_time_vary_init (
9698
real(kind_phys), intent(in) :: ozpl(:,:,:), h2opl(:,:,:)
9799
integer, intent(inout) :: jindx1_aer(:), jindx2_aer(:), iindx1_aer(:), iindx2_aer(:)
98100
real(kind_phys), intent(inout) :: ddy_aer(:), ddx_aer(:)
99-
real(kind_phys), intent(in) :: aer_nm(:,:,:)
101+
real(kind_phys), intent(out) :: aer_nm(:,:,:)
100102
integer, intent(inout) :: jindx1_ci(:), jindx2_ci(:), iindx1_ci(:), iindx2_ci(:)
101103
real(kind_phys), intent(inout) :: ddy_ci(:), ddx_ci(:)
102104
integer, intent(inout) :: imap(:), jmap(:)
@@ -196,12 +198,12 @@ subroutine GFS_phys_time_vary_init (
196198
jamax=-999
197199

198200
!$OMP parallel num_threads(nthrds) default(none) &
199-
!$OMP shared (me,master,ntoz,h2o_phys,im,nx,ny,idate) &
201+
!$OMP shared (me,master,ntoz,h2o_phys,im,nx,ny,levs,idate) &
200202
!$OMP shared (xlat_d,xlon_d,imap,jmap,errmsg,errflg) &
201203
!$OMP shared (levozp,oz_coeff,oz_pres,ozpl) &
202204
!$OMP shared (levh2o,h2o_coeff,h2o_pres,h2opl) &
203205
!$OMP shared (iamin, iamax, jamin, jamax) &
204-
!$OMP shared (iaerclm,ntrcaer,aer_nm,iflip,iccn) &
206+
!$OMP shared (iaerclm,iaermdl,ntrcaer,aer_nm,iflip,iccn) &
205207
!$OMP shared (jindx1_o3,jindx2_o3,ddy_o3,jindx1_h,jindx2_h,ddy_h) &
206208
!$OMP shared (jindx1_aer,jindx2_aer,ddy_aer,iindx1_aer,iindx2_aer,ddx_aer) &
207209
!$OMP shared (jindx1_ci,jindx2_ci,ddy_ci,iindx1_ci,iindx2_ci,ddx_ci) &
@@ -253,28 +255,22 @@ subroutine GFS_phys_time_vary_init (
253255
end if
254256

255257
!$OMP section
256-
!> - Call read_aerdata() to read aerosol climatology
258+
!> - Call read_aerdata() to read aerosol climatology, Anning added coupled
259+
!> added coupled gocart and radiation option to initializing aer_nm
257260
if (iaerclm) then
258-
! Consistency check that the value for ntrcaerm set in GFS_typedefs.F90
259-
! and used to allocate aer_nm matches the value defined in aerclm_def
260-
if (size(aer_nm, dim=3).ne.ntrcaerm) then
261-
write(errmsg,'(2a,i0,a,i0)') "Value error in GFS_phys_time_vary_init: ", &
262-
"ntrcaerm from aerclm_def does not match value in GFS_typedefs.F90: ", &
263-
ntrcaerm, " /= ", size(aer_nm, dim=3)
264-
errflg = 1
265-
else
266-
! Update the value of ntrcaer in aerclm_def with the value defined
267-
! in GFS_typedefs.F90 that is used to allocate the Tbd DDT.
268-
! If iaerclm is .true., then ntrcaer == ntrcaerm
269-
ntrcaer = size(aer_nm, dim=3)
270-
! Read aerosol climatology
271-
call read_aerdata (me,master,iflip,idate,errmsg,errflg)
272-
endif
261+
ntrcaer = ntrcaerm
262+
call read_aerdata (me,master,iflip,idate,errmsg,errflg)
263+
else if(iaermdl ==2 ) then
264+
do ix=1,ntrcaerm
265+
do j=1,levs
266+
do i=1,im
267+
aer_nm(i,j,ix) = 1.e-20_kind_phys
268+
end do
269+
end do
270+
end do
271+
ntrcaer = ntrcaerm
273272
else
274-
! Update the value of ntrcaer in aerclm_def with the value defined
275-
! in GFS_typedefs.F90 that is used to allocate the Tbd DDT.
276-
! If iaerclm is .false., then ntrcaer == 1
277-
ntrcaer = size(aer_nm, dim=3)
273+
ntrcaer = 1
278274
endif
279275

280276
!$OMP section

physics/GFS_phys_time_vary.fv3.meta

+14-7
Original file line numberDiff line numberDiff line change
@@ -65,6 +65,13 @@
6565
dimensions = ()
6666
type = integer
6767
intent = in
68+
[levs]
69+
standard_name = vertical_layer_dimension
70+
long_name = number of vertical levels
71+
units = count
72+
dimensions = ()
73+
type = integer
74+
intent = in
6875
[nx]
6976
standard_name = number_of_points_in_x_direction_for_this_MPI_rank
7077
long_name = number of points in x direction for this MPI rank
@@ -215,13 +222,13 @@
215222
kind = kind_phys
216223
intent = inout
217224
[aer_nm]
218-
standard_name = mass_number_concentration_of_aerosol_from_gocart_climatology
219-
long_name = GOCART aerosol climatology number concentration
220-
units = kg-1
225+
standard_name = mass_mixing_ratio_of_aerosol_from_gocart_or_merra2
226+
long_name = mass mixing ratio of aerosol from gocart or merra2
227+
units = kg kg-1
221228
dimensions = (horizontal_dimension,vertical_layer_dimension,number_of_aerosol_tracers_MG)
222229
type = real
223230
kind = kind_phys
224-
intent = in
231+
intent = out
225232
[jindx1_ci]
226233
standard_name = lower_latitude_index_of_cloud_nuclei_forcing_for_interpolation
227234
long_name = interpolation low index for ice and cloud condensation nuclei in the y direction
@@ -1211,9 +1218,9 @@
12111218
kind = kind_phys
12121219
intent = in
12131220
[aer_nm]
1214-
standard_name = mass_number_concentration_of_aerosol_from_gocart_climatology
1215-
long_name = GOCART aerosol climatology number concentration
1216-
units = kg-1
1221+
standard_name = mass_mixing_ratio_of_aerosol_from_gocart_or_merra2
1222+
long_name = mass mixing ratio of aerosol from gocart or merra2
1223+
units = kg kg-1
12171224
dimensions = (horizontal_dimension,vertical_layer_dimension,number_of_aerosol_tracers_MG)
12181225
type = real
12191226
kind = kind_phys

physics/GFS_phys_time_vary.scm.meta

+6-6
Original file line numberDiff line numberDiff line change
@@ -215,9 +215,9 @@
215215
kind = kind_phys
216216
intent = inout
217217
[aer_nm]
218-
standard_name = mass_number_concentration_of_aerosol_from_gocart_climatology
219-
long_name = GOCART aerosol climatology number concentration
220-
units = kg-1
218+
standard_name = mass_mixing_ratio_of_aerosol_from_gocart_or_merra2
219+
long_name = mass mixing ratio of aerosol from gocart or merra2
220+
units = kg kg-1
221221
dimensions = (horizontal_dimension,vertical_layer_dimension,number_of_aerosol_tracers_MG)
222222
type = real
223223
kind = kind_phys
@@ -1204,9 +1204,9 @@
12041204
kind = kind_phys
12051205
intent = in
12061206
[aer_nm]
1207-
standard_name = mass_number_concentration_of_aerosol_from_gocart_climatology
1208-
long_name = GOCART aerosol climatology number concentration
1209-
units = kg-1
1207+
standard_name = mass_mixing_ratio_of_aerosol_from_gocart_or_merra2
1208+
long_name = mass mixing ratio of aerosol from gocart or merra2
1209+
units = kg kg-1
12101210
dimensions = (horizontal_dimension,vertical_layer_dimension,number_of_aerosol_tracers_MG)
12111211
type = real
12121212
kind = kind_phys

physics/GFS_rrtmg_pre.F90

+31-2
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,8 @@ subroutine GFS_rrtmg_pre_run (im, levs, lm, lmk, lmp, n_var_lndp, &
2121
ntqv, ntcw,ntiw, ntlnc, ntinc, ntrnc, ntsnc, ntccn, &
2222
ntrw, ntsw, ntgl, nthl, ntwa, ntoz, &
2323
ntclamt, nleffr, nieffr, nseffr, lndp_type, kdt, &
24+
ntdu1, ntdu2, ntdu3, ntdu4, ntdu5, ntss1, ntss2, &
25+
ntss3, ntss4, ntss5, ntsu, ntbcb, ntbcl, ntocb, ntocl, ntchm, &
2426
imp_physics,imp_physics_nssl, nssl_ccn_on, nssl_invertccn, &
2527
imp_physics_thompson, imp_physics_gfdl, imp_physics_zhao_carr, &
2628
imp_physics_zhao_carr_pdf, imp_physics_mg, imp_physics_wsm6, &
@@ -78,7 +80,7 @@ subroutine GFS_rrtmg_pre_run (im, levs, lm, lmk, lmp, n_var_lndp, &
7880
make_IceNumber, &
7981
make_DropletNumber, &
8082
make_RainNumber
81-
83+
use physparam, only : iaermdl
8284
implicit none
8385

8486
integer, intent(in) :: im, levs, lm, lmk, lmp, n_var_lndp, &
@@ -112,6 +114,9 @@ subroutine GFS_rrtmg_pre_run (im, levs, lm, lmk, lmp, n_var_lndp, &
112114
idcor_oreopoulos, &
113115
rrfs_smoke_band ! Band number for rrfs-smoke dust and smoke
114116

117+
integer, intent(in) :: ntdu1, ntdu2, ntdu3, ntdu4, ntdu5, ntss1, ntss2, ntss3, &
118+
ntss4, ntss5, ntsu, ntbcb, ntbcl, ntocb, ntocl, ntchm
119+
115120
character(len=3), dimension(:), intent(in) :: lndp_var_list
116121

117122
logical, intent(in) :: lsswr, lslwr, ltaerosol, lgfdlmprad, &
@@ -137,7 +142,8 @@ subroutine GFS_rrtmg_pre_run (im, levs, lm, lmk, lmp, n_var_lndp, &
137142
cnvw_in, cnvc_in, &
138143
sppt_wts
139144

140-
real(kind=kind_phys), dimension(:,:,:), intent(in) :: qgrs, aer_nm
145+
real(kind=kind_phys), dimension(:,:,:), intent(in) :: qgrs
146+
real(kind=kind_phys), dimension(:,:,:), intent(inout) :: aer_nm
141147

142148
real(kind=kind_phys), dimension(:), intent(inout) :: coszen, coszdg
143149

@@ -603,6 +609,29 @@ subroutine GFS_rrtmg_pre_run (im, levs, lm, lmk, lmp, n_var_lndp, &
603609

604610
!check print *,' in grrad : calling setaer '
605611

612+
if (ntchm>0 .and. iaermdl==2) then
613+
do k=1,levs
614+
do i=1,im
615+
aer_nm(i,k,1) = qgrs(i,k,ntdu1)*1.e-9_kind_phys
616+
aer_nm(i,k,2) = qgrs(i,k,ntdu2)*1.e-9_kind_phys
617+
aer_nm(i,k,3) = qgrs(i,k,ntdu3)*1.e-9_kind_phys
618+
aer_nm(i,k,4) = qgrs(i,k,ntdu4)*1.e-9_kind_phys
619+
aer_nm(i,k,5) = qgrs(i,k,ntdu5)*1.e-9_kind_phys
620+
aer_nm(i,k,6) = qgrs(i,k,ntss1)*1.e-9_kind_phys
621+
aer_nm(i,k,7) = qgrs(i,k,ntss2)*1.e-9_kind_phys
622+
aer_nm(i,k,8) = qgrs(i,k,ntss3)*1.e-9_kind_phys
623+
aer_nm(i,k,9) = qgrs(i,k,ntss4)*1.e-9_kind_phys
624+
aer_nm(i,k,10) = qgrs(i,k,ntss5)*1.e-9_kind_phys
625+
aer_nm(i,k,11) = qgrs(i,k,ntsu)*1.e-9_kind_phys
626+
aer_nm(i,k,12) = qgrs(i,k,ntbcb)*1.e-9_kind_phys
627+
aer_nm(i,k,13) = qgrs(i,k,ntbcl)*1.e-9_kind_phys
628+
aer_nm(i,k,14) = qgrs(i,k,ntocb)*1.e-9_kind_phys
629+
aer_nm(i,k,15) = qgrs(i,k,ntocl)*1.e-9_kind_phys
630+
enddo
631+
enddo
632+
endif
633+
634+
606635
call setaer (plvl, plyr, prslk1, tvly, rhly, slmsk, & ! --- inputs
607636
tracer1, aer_nm, xlon, xlat, IM, LMK, LMP,&
608637
lsswr,lslwr, &

physics/GFS_rrtmg_pre.meta

+116-4
Original file line numberDiff line numberDiff line change
@@ -261,6 +261,118 @@
261261
dimensions = ()
262262
type = integer
263263
intent = in
264+
[ntdu1]
265+
standard_name = index_for_dust_bin1
266+
long_name = index for dust bin1
267+
units = index
268+
dimensions = ()
269+
type = integer
270+
intent = in
271+
[ntdu2]
272+
standard_name = index_for_dust_bin2
273+
long_name = index for dust bin2
274+
units = index
275+
dimensions = ()
276+
type = integer
277+
intent = in
278+
[ntdu3]
279+
standard_name = index_for_dust_bin3
280+
long_name = index for dust bin3
281+
units = index
282+
dimensions = ()
283+
type = integer
284+
intent = in
285+
[ntdu4]
286+
standard_name = index_for_dust_bin4
287+
long_name = index for dust bin4
288+
units = index
289+
dimensions = ()
290+
type = integer
291+
intent = in
292+
[ntdu5]
293+
standard_name = index_for_dust_bin5
294+
long_name = index for dust bin5
295+
units = index
296+
dimensions = ()
297+
type = integer
298+
intent = in
299+
[ntss1]
300+
standard_name = index_for_seasalt_bin1
301+
long_name = index for seasalt bin1
302+
units = index
303+
dimensions = ()
304+
type = integer
305+
intent = in
306+
[ntss2]
307+
standard_name = index_for_seasalt_bin2
308+
long_name = index for seasalt bin2
309+
units = index
310+
dimensions = ()
311+
type = integer
312+
intent = in
313+
[ntss3]
314+
standard_name = index_for_seasalt_bin3
315+
long_name = index for seasalt bin3
316+
units = index
317+
dimensions = ()
318+
type = integer
319+
intent = in
320+
[ntss4]
321+
standard_name = index_for_seasalt_bin4
322+
long_name = index for seasalt bin4
323+
units = index
324+
dimensions = ()
325+
type = integer
326+
intent = in
327+
[ntss5]
328+
standard_name = index_for_seasalt_bin5
329+
long_name = index for seasalt bin5
330+
units = index
331+
dimensions = ()
332+
type = integer
333+
intent = in
334+
[ntsu]
335+
standard_name = index_for_sulfate
336+
long_name = index for sulfate
337+
units = index
338+
dimensions = ()
339+
type = integer
340+
intent = in
341+
[ntbcb]
342+
standard_name = index_for_bcphobic
343+
long_name = index for bcphobic
344+
units = index
345+
dimensions = ()
346+
type = integer
347+
intent = in
348+
[ntbcl]
349+
standard_name = index_for_bcphilic
350+
long_name = index for bcphilic
351+
units = index
352+
dimensions = ()
353+
type = integer
354+
intent = in
355+
[ntocb]
356+
standard_name = index_for_ocphobic
357+
long_name = index for ocphobic
358+
units = index
359+
dimensions = ()
360+
type = integer
361+
intent = in
362+
[ntocl]
363+
standard_name = index_for_ocphilic
364+
long_name = index for ocphilic
365+
units = index
366+
dimensions = ()
367+
type = integer
368+
intent = in
369+
[ntchm]
370+
standard_name = number_of_chemical_tracers
371+
long_name = number of chemical tracers
372+
units = count
373+
dimensions = ()
374+
type = integer
375+
intent = in
264376
[imp_physics]
265377
standard_name = control_for_microphysics_scheme
266378
long_name = choice of microphysics scheme
@@ -713,13 +825,13 @@
713825
kind = kind_phys
714826
intent = in
715827
[aer_nm]
716-
standard_name = mass_number_concentration_of_aerosol_from_gocart_climatology
717-
long_name = GOCART aerosol climatology number concentration
718-
units = kg-1
828+
standard_name = mass_mixing_ratio_of_aerosol_from_gocart_or_merra2
829+
long_name = mass mixing ratio of aerosol from gocart or merra2
830+
units = kg kg-1
719831
dimensions = (horizontal_loop_extent,vertical_layer_dimension,number_of_aerosol_tracers_MG)
720832
type = real
721833
kind = kind_phys
722-
intent = in
834+
intent = inout
723835
[dx]
724836
standard_name = characteristic_grid_lengthscale
725837
long_name = relative dx for the grid cell

physics/m_micro.meta

+3-3
Original file line numberDiff line numberDiff line change
@@ -735,9 +735,9 @@
735735
type = integer
736736
intent = in
737737
[aerfld_i]
738-
standard_name = mass_number_concentration_of_aerosol_from_gocart_climatology
739-
long_name = GOCART aerosol climatology number concentration
740-
units = kg-1
738+
standard_name = mass_mixing_ratio_of_aerosol_from_gocart_or_merra2
739+
long_name = mass mixing ratio of aerosol from gocart or merra2
740+
units = kg kg-1
741741
dimensions = (horizontal_loop_extent,vertical_layer_dimension,number_of_aerosol_tracers_MG)
742742
type = real
743743
kind = kind_phys

0 commit comments

Comments
 (0)