Skip to content

Commit

Permalink
Merge branch 'production/RRFS.v1' into thompson_refactor_RRFS
Browse files Browse the repository at this point in the history
  • Loading branch information
grantfirl committed Mar 5, 2024
2 parents 09c7674 + 730ad5a commit 4354b24
Show file tree
Hide file tree
Showing 5 changed files with 153 additions and 63 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ module GFS_suite_stateout_update
subroutine GFS_suite_stateout_update_run (im, levs, ntrac, dtp, tgrs, ugrs, vgrs, qgrs, &
dudt, dvdt, dtdt, dqdt, gt0, gu0, gv0, gq0, oz0, ntiw, nqrimef, imp_physics, &
imp_physics_fer_hires, epsq, ozphys, oz_phys_2015, oz_phys_2006, con_1ovg, prsl, &
dp, ozpl, do3_dt_prd, do3_dt_ozmx, do3_dt_temp, do3_dt_ohoz, errmsg, errflg)
dp, ozpl, qdiag3d, do3_dt_prd, do3_dt_ozmx, do3_dt_temp, do3_dt_ohoz, errmsg, errflg)

! Inputs
integer, intent(in ) :: im
Expand All @@ -31,12 +31,13 @@ subroutine GFS_suite_stateout_update_run (im, levs, ntrac, dtp, tgrs, ugrs, vgrs
real(kind=kind_phys), intent(in ), dimension(:,:,:) :: qgrs, ozpl
real(kind=kind_phys), intent(in ), dimension(:,:) :: dudt, dvdt, dtdt
real(kind=kind_phys), intent(in ), dimension(:,:,:) :: dqdt
logical, intent(in) :: qdiag3d
logical, intent(in) :: oz_phys_2015
logical, intent(in) :: oz_phys_2006
type(ty_ozphys), intent(in) :: ozphys

! Outputs (optional)
real(kind=kind_phys), intent(inout), dimension(:,:), pointer, optional :: &
real(kind=kind_phys), intent(inout), dimension(:,:) :: &
do3_dt_prd, & ! Physics tendency: production and loss effect
do3_dt_ozmx, & ! Physics tendency: ozone mixing ratio effect
do3_dt_temp, & ! Physics tendency: temperature effect
Expand All @@ -50,7 +51,7 @@ subroutine GFS_suite_stateout_update_run (im, levs, ntrac, dtp, tgrs, ugrs, vgrs

! Locals
integer :: i, k

! Initialize CCPP error handling variables
errmsg = ''
errflg = 0
Expand All @@ -65,12 +66,12 @@ subroutine GFS_suite_stateout_update_run (im, levs, ntrac, dtp, tgrs, ugrs, vgrs
! If using photolysis physics schemes, update (prognostic) gas concentrations using
! updated state.
if (oz_phys_2015) then
call ozphys%run_o3prog_2015(con_1ovg, dtp, prsl, gt0, dp, ozpl, oz0, do3_dt_prd, &
do3_dt_ozmx, do3_dt_temp, do3_dt_ohoz)
call ozphys%run_o3prog_2015(con_1ovg, dtp, prsl, gt0, dp, ozpl, oz0, qdiag3d, &
do3_dt_prd, do3_dt_ozmx, do3_dt_temp, do3_dt_ohoz)
endif
if (oz_phys_2006) then
call ozphys%run_o3prog_2006(con_1ovg, dtp, prsl, gt0, dp, ozpl, oz0, do3_dt_prd, &
do3_dt_ozmx, do3_dt_temp, do3_dt_ohoz)
call ozphys%run_o3prog_2006(con_1ovg, dtp, prsl, gt0, dp, ozpl, oz0, qdiag3d, &
do3_dt_prd, do3_dt_ozmx, do3_dt_temp, do3_dt_ohoz)
endif

! If using Ferrier-Aligo microphysics, set bounds on the mass-weighted rime factor.
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,13 @@
dimensions = ()
type = ty_ozphys
intent = in
[qdiag3d]
standard_name = flag_for_tracer_diagnostics_3D
long_name = flag for 3d tracer diagnostic fields
units = flag
dimensions = ()
type = logical
intent = in
[oz_phys_2015]
standard_name = flag_for_nrl_2015_ozone_scheme
long_name = flag for new (2015) ozone physics
Expand Down
124 changes: 81 additions & 43 deletions physics/MP/Thompson/module_mp_thompson.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1207,49 +1207,87 @@ subroutine mp_gt_driver(qv, qc, qr, qi, qs, qg, ni, nr, nc, &
end if
end if test_only_once

! These must be alwyas allocated
!allocate (vtsk1(kts:kte))
!allocate (txri1(kts:kte))
!allocate (txrc1(kts:kte))
allocate_extended_diagnostics: if (ext_diag) then
allocate (prw_vcdc1(kts:kte))
allocate (prw_vcde1(kts:kte))
allocate (tpri_inu1(kts:kte))
allocate (tpri_ide1_d(kts:kte))
allocate (tpri_ide1_s(kts:kte))
allocate (tprs_ide1(kts:kte))
allocate (tprs_sde1_d(kts:kte))
allocate (tprs_sde1_s(kts:kte))
allocate (tprg_gde1_d(kts:kte))
allocate (tprg_gde1_s(kts:kte))
allocate (tpri_iha1(kts:kte))
allocate (tpri_wfz1(kts:kte))
allocate (tpri_rfz1(kts:kte))
allocate (tprg_rfz1(kts:kte))
allocate (tprs_scw1(kts:kte))
allocate (tprg_scw1(kts:kte))
allocate (tprg_rcs1(kts:kte))
allocate (tprs_rcs1(kts:kte))
allocate (tprr_rci1(kts:kte))
allocate (tprg_rcg1(kts:kte))
allocate (tprw_vcd1_c(kts:kte))
allocate (tprw_vcd1_e(kts:kte))
allocate (tprr_sml1(kts:kte))
allocate (tprr_gml1(kts:kte))
allocate (tprr_rcg1(kts:kte))
allocate (tprr_rcs1(kts:kte))
allocate (tprv_rev1(kts:kte))
allocate (tten1(kts:kte))
allocate (qvten1(kts:kte))
allocate (qrten1(kts:kte))
allocate (qsten1(kts:kte))
allocate (qgten1(kts:kte))
allocate (qiten1(kts:kte))
allocate (niten1(kts:kte))
allocate (nrten1(kts:kte))
allocate (ncten1(kts:kte))
allocate (qcten1(kts:kte))
end if allocate_extended_diagnostics
! These must be alwyas allocated
!allocate (vtsk1(kts:kte))
!allocate (txri1(kts:kte))
!allocate (txrc1(kts:kte))
allocate_extended_diagnostics: if (ext_diag) then
allocate (prw_vcdc1(kts:kte))
allocate (prw_vcde1(kts:kte))
allocate (tpri_inu1(kts:kte))
allocate (tpri_ide1_d(kts:kte))
allocate (tpri_ide1_s(kts:kte))
allocate (tprs_ide1(kts:kte))
allocate (tprs_sde1_d(kts:kte))
allocate (tprs_sde1_s(kts:kte))
allocate (tprg_gde1_d(kts:kte))
allocate (tprg_gde1_s(kts:kte))
allocate (tpri_iha1(kts:kte))
allocate (tpri_wfz1(kts:kte))
allocate (tpri_rfz1(kts:kte))
allocate (tprg_rfz1(kts:kte))
allocate (tprs_scw1(kts:kte))
allocate (tprg_scw1(kts:kte))
allocate (tprg_rcs1(kts:kte))
allocate (tprs_rcs1(kts:kte))
allocate (tprr_rci1(kts:kte))
allocate (tprg_rcg1(kts:kte))
allocate (tprw_vcd1_c(kts:kte))
allocate (tprw_vcd1_e(kts:kte))
allocate (tprr_sml1(kts:kte))
allocate (tprr_gml1(kts:kte))
allocate (tprr_rcg1(kts:kte))
allocate (tprr_rcs1(kts:kte))
allocate (tprv_rev1(kts:kte))
allocate (tten1(kts:kte))
allocate (qvten1(kts:kte))
allocate (qrten1(kts:kte))
allocate (qsten1(kts:kte))
allocate (qgten1(kts:kte))
allocate (qiten1(kts:kte))
allocate (niten1(kts:kte))
allocate (nrten1(kts:kte))
allocate (ncten1(kts:kte))
allocate (qcten1(kts:kte))
else
allocate (prw_vcdc1 (0))
allocate (prw_vcde1 (0))
allocate (tpri_inu1 (0))
allocate (tpri_ide1_d(0))
allocate (tpri_ide1_s(0))
allocate (tprs_ide1 (0))
allocate (tprs_sde1_d(0))
allocate (tprs_sde1_s(0))
allocate (tprg_gde1_d(0))
allocate (tprg_gde1_s(0))
allocate (tpri_iha1 (0))
allocate (tpri_wfz1 (0))
allocate (tpri_rfz1 (0))
allocate (tprg_rfz1 (0))
allocate (tprs_scw1 (0))
allocate (tprg_scw1 (0))
allocate (tprg_rcs1 (0))
allocate (tprs_rcs1 (0))
allocate (tprr_rci1 (0))
allocate (tprg_rcg1 (0))
allocate (tprw_vcd1_c(0))
allocate (tprw_vcd1_e(0))
allocate (tprr_sml1 (0))
allocate (tprr_gml1 (0))
allocate (tprr_rcg1 (0))
allocate (tprr_rcs1 (0))
allocate (tprv_rev1 (0))
allocate (tten1 (0))
allocate (qvten1 (0))
allocate (qrten1 (0))
allocate (qsten1 (0))
allocate (qgten1 (0))
allocate (qiten1 (0))
allocate (niten1 (0))
allocate (nrten1 (0))
allocate (ncten1 (0))
allocate (qcten1 (0))
end if allocate_extended_diagnostics

!+---+
i_start = its
Expand Down
38 changes: 38 additions & 0 deletions physics/MP/Thompson/mp_thompson.F90
Original file line number Diff line number Diff line change
Expand Up @@ -709,6 +709,44 @@ subroutine mp_thompson_run(ncol, nlev, con_g, con_rd, &
nrten3 => diag3d(:,:,35:35)
ncten3 => diag3d(:,:,36:36)
qcten3 => diag3d(:,:,37:37)
else
allocate(prw_vcdc (0,0,0))
allocate(prw_vcde (0,0,0))
allocate(tpri_inu (0,0,0))
allocate(tpri_ide_d (0,0,0))
allocate(tpri_ide_s (0,0,0))
allocate(tprs_ide (0,0,0))
allocate(tprs_sde_d (0,0,0))
allocate(tprs_sde_s (0,0,0))
allocate(tprg_gde_d (0,0,0))
allocate(tprg_gde_s (0,0,0))
allocate(tpri_iha (0,0,0))
allocate(tpri_wfz (0,0,0))
allocate(tpri_rfz (0,0,0))
allocate(tprg_rfz (0,0,0))
allocate(tprs_scw (0,0,0))
allocate(tprg_scw (0,0,0))
allocate(tprg_rcs (0,0,0))
allocate(tprs_rcs (0,0,0))
allocate(tprr_rci (0,0,0))
allocate(tprg_rcg (0,0,0))
allocate(tprw_vcd_c (0,0,0))
allocate(tprw_vcd_e (0,0,0))
allocate(tprr_sml (0,0,0))
allocate(tprr_gml (0,0,0))
allocate(tprr_rcg (0,0,0))
allocate(tprr_rcs (0,0,0))
allocate(tprv_rev (0,0,0))
allocate(tten3 (0,0,0))
allocate(qvten3 (0,0,0))
allocate(qrten3 (0,0,0))
allocate(qsten3 (0,0,0))
allocate(qgten3 (0,0,0))
allocate(qiten3 (0,0,0))
allocate(niten3 (0,0,0))
allocate(nrten3 (0,0,0))
allocate(ncten3 (0,0,0))
allocate(qcten3 (0,0,0))
end if set_extended_diagnostic_pointers
!> - Call mp_gt_driver() with or without aerosols, with or without effective radii, ...
if (is_aerosol_aware .or. merra2_aerosol_aware) then
Expand Down
32 changes: 19 additions & 13 deletions physics/photochem/module_ozphys.F90
Original file line number Diff line number Diff line change
Expand Up @@ -198,7 +198,7 @@ end subroutine update_o3prog
! #########################################################################################
! Procedure (type-bound) for NRL prognostic ozone (2015).
! #########################################################################################
subroutine run_o3prog_2015(this, con_1ovg, dt, p, t, dp, ozpl, oz, do3_dt_prd, &
subroutine run_o3prog_2015(this, con_1ovg, dt, p, t, dp, ozpl, oz, do_diag, do3_dt_prd, &
do3_dt_ozmx, do3_dt_temp, do3_dt_ohoz)
class(ty_ozphys), intent(in) :: this
real(kind_phys), intent(in) :: &
Expand All @@ -213,7 +213,8 @@ subroutine run_o3prog_2015(this, con_1ovg, dt, p, t, dp, ozpl, oz, do3_dt_prd,
ozpl ! Ozone forcing data
real(kind_phys), intent(inout), dimension(:,:) :: &
oz ! Ozone concentration updated by physics
real(kind_phys), intent(inout), dimension(:,:), pointer, optional :: &
logical, intent(in) :: do_diag
real(kind_phys), intent(inout), dimension(:,:) :: &
do3_dt_prd, & ! Physics tendency: production and loss effect
do3_dt_ozmx, & ! Physics tendency: ozone mixing ratio effect
do3_dt_temp, & ! Physics tendency: temperature effect
Expand Down Expand Up @@ -297,10 +298,12 @@ subroutine run_o3prog_2015(this, con_1ovg, dt, p, t, dp, ozpl, oz, do3_dt_prd,
enddo

! Diagnostics (optional)
if (associated(do3_dt_prd)) do3_dt_prd(:,iLev) = (prod(:,1)-prod(:,2)*prod(:,6))*dt
if (associated(do3_dt_ozmx)) do3_dt_ozmx(:,iLev) = (oz(:,iLev) - ozib(:))
if (associated(do3_dt_temp)) do3_dt_temp(:,iLev) = prod(:,3)*(t(:,iLev)-prod(:,5))*dt
if (associated(do3_dt_ohoz)) do3_dt_ohoz(:,iLev) = prod(:,4) * (colo3(:,iLev)-coloz(:,iLev))*dt
if (do_diag) then
do3_dt_prd(:,iLev) = (prod(:,1)-prod(:,2)*prod(:,6))*dt
do3_dt_ozmx(:,iLev) = (oz(:,iLev) - ozib(:))
do3_dt_temp(:,iLev) = prod(:,3)*(t(:,iLev)-prod(:,5))*dt
do3_dt_ohoz(:,iLev) = prod(:,4) * (colo3(:,iLev)-coloz(:,iLev))*dt
endif
enddo

return
Expand All @@ -309,7 +312,7 @@ end subroutine run_o3prog_2015
! #########################################################################################
! Procedure (type-bound) for NRL prognostic ozone (2006).
! #########################################################################################
subroutine run_o3prog_2006(this, con_1ovg, dt, p, t, dp, ozpl, oz, do3_dt_prd, &
subroutine run_o3prog_2006(this, con_1ovg, dt, p, t, dp, ozpl, oz, do_diag, do3_dt_prd, &
do3_dt_ozmx, do3_dt_temp, do3_dt_ohoz)
class(ty_ozphys), intent(in) :: this
real(kind_phys), intent(in) :: &
Expand All @@ -324,7 +327,8 @@ subroutine run_o3prog_2006(this, con_1ovg, dt, p, t, dp, ozpl, oz, do3_dt_prd,
ozpl ! Ozone forcing data
real(kind_phys), intent(inout), dimension(:,:) :: &
oz ! Ozone concentration updated by physics
real(kind_phys), intent(inout), dimension(:,:), pointer, optional :: &
logical, intent(in) :: do_diag
real(kind_phys), intent(inout), dimension(:,:) :: &
do3_dt_prd, & ! Physics tendency: production and loss effect
do3_dt_ozmx, & ! Physics tendency: ozone mixing ratio effect
do3_dt_temp, & ! Physics tendency: temperature effect
Expand Down Expand Up @@ -418,12 +422,14 @@ subroutine run_o3prog_2006(this, con_1ovg, dt, p, t, dp, ozpl, oz, do3_dt_prd,
oz(iCol,iLev) = (ozib(iCol) + tem*dt) / (1.0 + prod(iCol,2)*dt)
enddo
endif
! Diagnostics (optional)
if (associated(do3_dt_prd)) do3_dt_prd(:,iLev) = prod(:,1)*dt
if (associated(do3_dt_ozmx)) do3_dt_ozmx(:,iLev) = (oz(:,iLev) - ozib(:))
if (associated(do3_dt_temp)) do3_dt_temp(:,iLev) = prod(:,3) * t(:,iLev) * dt
if (associated(do3_dt_ohoz)) do3_dt_ohoz(:,iLev) = prod(:,4) * colo3(:,iLev) * dt

! Diagnostics (optional)
if (do_diag) then
do3_dt_prd(:,iLev) = prod(:,1)*dt
do3_dt_ozmx(:,iLev) = (oz(:,iLev) - ozib(:))
do3_dt_temp(:,iLev) = prod(:,3) * t(:,iLev) * dt
do3_dt_ohoz(:,iLev) = prod(:,4) * colo3(:,iLev) * dt
endif
enddo

return
Expand Down

0 comments on commit 4354b24

Please sign in to comment.