Skip to content

Commit

Permalink
Make ozone physics CCPP compliant by removing 'optional' and 'pointer…
Browse files Browse the repository at this point in the history
…' attributes
  • Loading branch information
climbfuji committed Dec 27, 2023
1 parent 0cdfc9d commit 790960e
Show file tree
Hide file tree
Showing 3 changed files with 34 additions and 20 deletions.
15 changes: 8 additions & 7 deletions physics/GFS_suite_stateout_update.F90
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
7 changes: 7 additions & 0 deletions physics/GFS_suite_stateout_update.meta
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
32 changes: 19 additions & 13 deletions physics/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 790960e

Please sign in to comment.