Skip to content

Commit

Permalink
Some more cleanup
Browse files Browse the repository at this point in the history
  • Loading branch information
dustinswales committed Oct 12, 2023
1 parent 00d9060 commit 1b22397
Show file tree
Hide file tree
Showing 4 changed files with 134 additions and 205 deletions.
99 changes: 85 additions & 14 deletions physics/GFS_physics_post.F90
Original file line number Diff line number Diff line change
Expand Up @@ -35,47 +35,62 @@ end subroutine GFS_physics_post_init
!! \section arg_table_GFS_physics_post_run Argument Table
!! \htmlinclude GFS_physics_post_run.html
!!
subroutine GFS_physics_post_run(nCol, nLev, ntoz, dtidx, ip_prod_loss, ip_ozmix, ip_temp, &
ip_overhead_ozone, do3_dt_prd, do3_dt_ozmx, do3_dt_temp, do3_dt_ohoz, dtend, errmsg, &
errflg)
subroutine GFS_physics_post_run(nCol, nLev, ntoz, ntracp100, nprocess, nprocess_summed, &
dtidx, is_photochem, ldiag3d, ip_physics, ip_photochem, &
ip_prod_loss, ip_ozmix, ip_temp, ip_overhead_ozone, do3_dt_prd, do3_dt_ozmx, &
do3_dt_temp, do3_dt_ohoz, dtend, errmsg, errflg)

! Inputs
integer, intent(in) :: &
nCol, & ! Horizontal dimension
nLev, & ! Number of vertical layers
ntoz, & ! Index for ozone mixing ratio
ntracp100, & ! Number of tracers plus 100
nprocess, & ! Number of processes that cause changes in state variables
nprocess_summed,& ! Number of causes in dtidx per tracer summed for total physics tendency
ip_physics, & ! Index for process in diagnostic tendency output
ip_photochem, & !
ip_prod_loss, & ! Index for process in diagnostic tendency output
ip_ozmix, & ! Index for process in diagnostic tendency output
ip_temp, & ! Index for process in diagnostic tendency output
ip_overhead_ozone ! Index for process in diagnostic tendency output
integer, intent(in), dimension(:,:) :: &
dtidx ! Bookkeeping indices for GFS diagnostic tendencies
logical, intent(in) :: &
ldiag3d ! Flag for 3d diagnostic fields
logical, intent(in), dimension(:) :: &
is_photochem ! Flags for photochemistry processes to sum

! Inputs (optional)
real(kind=kind_phys), intent(in), dimension(:,:), pointer, optional :: &
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
do3_dt_ohoz ! Physics tendency: overhead ozone effect
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
do3_dt_ohoz ! Physics tendency: overhead ozone effect

! Outputs
real(kind=kind_phys), intent(inout), dimension(:,:,:) :: &
dtend ! Diagnostic tendencies for state variables
dtend ! Diagnostic tendencies for state variables
character(len=*), intent(out) :: &
errmsg ! CCPP error message
errmsg ! CCPP error message
integer, intent(out) :: &
errflg ! CCPP error flag
errflg ! CCPP error flag

! Locals
integer :: idtend

integer :: idtend, ichem, iphys, itrac
logical :: all_true(nprocess)

! Initialize CCPP error handling variables
errmsg = ''
errflg = 0

if(.not.ldiag3d) then
return
endif

! #######################################################################################
!
! Ozone physics diagnostic
! Ozone physics diagnostics
!
! #######################################################################################
idtend = dtidx(100+ntoz,ip_prod_loss)
Expand All @@ -98,6 +113,62 @@ subroutine GFS_physics_post_run(nCol, nLev, ntoz, dtidx, ip_prod_loss, ip_ozmix,
dtend(:,:,idtend) = dtend(:,:,idtend) + do3_dt_ohoz
endif

end subroutine GFS_physics_post_run
! #######################################################################################
!
! Total (photochemical) tendencies.
!
! #######################################################################################
itrac = ntoz+100
ichem = dtidx(itrac, ip_photochem)
if(ichem >= 1) then
call sum_it(ichem, itrac, is_photochem)
endif

! #######################################################################################
!
! Total (physics) tendencies
!
! #######################################################################################
all_true = .true.
do itrac = 2,ntracp100
iphys = dtidx(itrac,ip_physics)
if(iphys >= 1) then
call sum_it(iphys, itrac, all_true)
endif
enddo

contains

subroutine sum_it(isum,itrac,sum_me)
integer, intent(in) :: isum ! third index of dtend of summary process
integer, intent(in) :: itrac ! tracer or state variable being summed
logical, intent(in) :: sum_me(nprocess) ! false = skip this process
logical :: first
integer :: idtend, iprocess

first=.true.
do iprocess=1,nprocess
if(iprocess>nprocess_summed) then
exit ! Don't sum up the sums.
else if(.not.sum_me(iprocess)) then
cycle ! We were asked to skip this one.
endif
idtend = dtidx(itrac,iprocess)
if(idtend>=1) then
! This tendency was calculated for this tracer, so
! accumulate it into the total tendency.
if(first) then
dtend(:,:,isum) = dtend(:,:,idtend)
first=.false.
else
dtend(:,:,isum) = dtend(:,:,isum) + dtend(:,:,idtend)
endif
endif
enddo
if(first) then
! No tendencies were calculated, so sum is 0:
dtend(:,:,isum) = 0
endif
end subroutine sum_it
end subroutine GFS_physics_post_run
end module GFS_physics_post
49 changes: 49 additions & 0 deletions physics/GFS_physics_post.meta
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,55 @@
dimensions = ()
type = integer
intent = in
[ntracp100]
standard_name = number_of_tracers_plus_one_hundred
long_name = number of tracers plus one hundred
units = count
dimensions = ()
type = integer
intent = in
[nprocess]
standard_name = number_of_cumulative_change_processes
long_name = number of processes that cause changes in state variables
units = count
dimensions = ()
type = integer
intent = in
[nprocess_summed]
standard_name = number_of_physics_causes_of_tracer_changes
long_name = number of causes in dtidx per tracer summed for total physics tendency
units = count
dimensions = ()
type = integer
intent = in
[ip_physics]
standard_name = index_of_all_physics_process_in_cumulative_change_index
long_name = index of all physics transport process in second dimension of array cumulative change index
units = index
dimensions = ()
type = integer
intent = in
[ip_photochem]
standard_name = index_of_photochemistry_process_in_cumulative_change_index
long_name = index of photochemistry process in second dimension of array cumulative change index
units = index
dimensions = ()
type = integer
intent = in
[is_photochem]
standard_name = flags_for_photochemistry_processes_to_sum
long_name = flags for photochemistry processes to sum as the total photochemistry process cumulative change
units = flag
dimensions = (number_of_cumulative_change_processes)
type = logical
intent = in
[ldiag3d]
standard_name = flag_for_diagnostics_3D
long_name = flag for 3d diagnostic fields
units = flag
dimensions = ()
type = logical
intent = in
[ip_prod_loss]
standard_name = index_of_production_and_loss_process_in_cumulative_change_index
long_name = index of production and loss effect in photochemistry process in second dimension of array cumulative change index
Expand Down
96 changes: 0 additions & 96 deletions physics/phys_tend.F90

This file was deleted.

95 changes: 0 additions & 95 deletions physics/phys_tend.meta

This file was deleted.

0 comments on commit 1b22397

Please sign in to comment.