Skip to content

Commit

Permalink
Final cleanup
Browse files Browse the repository at this point in the history
  • Loading branch information
dustinswales committed Oct 12, 2023
1 parent c65ee9e commit 06bb2bc
Show file tree
Hide file tree
Showing 4 changed files with 144 additions and 58 deletions.
83 changes: 66 additions & 17 deletions physics/GFS_phys_time_vary.scm.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2,15 +2,17 @@
!! Contains code related to GFS physics suite setup (physics part of time_vary_step)

!>\defgroup mod_GFS_phys_time_vary GFS Physics Time Update
!! This module contains GFS physics time vary subroutines including, stratospheric water vapor,
!! This module contains GFS physics time vary subroutines including stratospheric water vapor,
!! aerosol, IN&CCN and surface properties updates.
!> @{
module GFS_phys_time_vary

use machine, only : kind_phys
use machine, only : kind_phys, kind_dbl_prec, kind_sngl_prec

use mersenne_twister, only: random_setseed, random_number

use module_ozphys, only: ty_ozphys

use h2o_def, only : levh2o, h2o_coeff, h2o_lat, h2o_pres, h2o_time, h2oplin
use h2ointerp, only : read_h2odata, setindxh2o, h2ointerpol

Expand Down Expand Up @@ -58,8 +60,8 @@ module GFS_phys_time_vary
!>\section gen_GFS_phys_time_vary_init GFS_phys_time_vary_init General Algorithm
!! @{
subroutine GFS_phys_time_vary_init ( &
me, master, h2o_phys, iaerclm, iccn, iflip, im, nx, ny, idate, xlat_d, xlon_d, &
jindx1_h, jindx2_h, ddy_h, h2opl,fhour, &
me, master, ntoz, h2o_phys, iaerclm, iccn, iflip, im, nx, ny, idate, xlat_d, xlon_d, &
jindx1_o3, jindx2_o3, ddy_o3, ozphys, jindx1_h, jindx2_h, ddy_h, h2opl,fhour, &
jindx1_aer, jindx2_aer, ddy_aer, iindx1_aer, iindx2_aer, ddx_aer, aer_nm, &
jindx1_ci, jindx2_ci, ddy_ci, iindx1_ci, iindx2_ci, ddx_ci, imap, jmap, &
do_ugwp_v1, jindx1_tau, jindx2_tau, ddy_j1tau, ddy_j2tau, &
Expand All @@ -76,14 +78,14 @@ subroutine GFS_phys_time_vary_init (
implicit none

! Interface variables
integer, intent(in) :: me, master, iccn, iflip, im, nx, ny
integer, intent(in) :: me, master, ntoz, iccn, iflip, im, nx, ny
logical, intent(in) :: h2o_phys, iaerclm, lsm_cold_start
integer, intent(in) :: idate(:)
real(kind_phys), intent(in) :: fhour
real(kind_phys), intent(in) :: xlat_d(:), xlon_d(:)

integer, intent(inout) :: jindx1_h(:), jindx2_h(:)
real(kind_phys), intent(inout) :: ddy_h(:)
integer, intent(inout) :: jindx1_o3(:), jindx2_o3(:), jindx1_h(:), jindx2_h(:)
real(kind_phys), intent(inout) :: ddy_o3(:), ddy_h(:)
real(kind_phys), intent(in) :: h2opl(:,:,:)
integer, intent(inout) :: jindx1_aer(:), jindx2_aer(:), iindx1_aer(:), iindx2_aer(:)
real(kind_phys), intent(inout) :: ddy_aer(:), ddx_aer(:)
Expand All @@ -101,6 +103,7 @@ subroutine GFS_phys_time_vary_init (
real(kind_phys), intent(in) :: min_seaice, fice(:)
real(kind_phys), intent(in) :: landfrac(:)
real(kind_phys), intent(inout) :: weasd(:)
type(ty_ozphys), intent(in) :: ozphys

! NoahMP - only allocated when NoahMP is used
integer, intent(in) :: lsoil, lsnow_lsm_lbound, lsnow_lsm_ubound
Expand Down Expand Up @@ -244,6 +247,11 @@ subroutine GFS_phys_time_vary_init (
!> - Initialize soil vegetation (needed for sncovr calculation further down)
call set_soilveg(me, isot, ivegsrc, nlunit, errmsg, errflg)

!> - Setup spatial interpolation indices for ozone physics.
if (ntoz > 0) then
call ozphys%setup_o3prog(xlat_d, jindx1_o3, jindx2_o3, ddy_o3)
endif

!> - Call setindxh2o() to initialize stratospheric water vapor data
if (h2o_phys) then
call setindxh2o (im, xlat_d, jindx1_h, jindx2_h, ddy_h)
Expand Down Expand Up @@ -625,8 +633,8 @@ end subroutine GFS_phys_time_vary_init
!! @{
subroutine GFS_phys_time_vary_timestep_init ( &
me, master, cnx, cny, isc, jsc, nrcm, im, levs, kdt, idate, nsswr, fhswr, lsswr, fhour, &
imfdeepcnv, cal_pre, random_clds, h2o_phys, iaerclm, iccn, clstp, &
jindx1_h, jindx2_h, ddy_h, h2opl, iflip, &
imfdeepcnv, cal_pre, random_clds, ozphys, ntoz, h2o_phys, iaerclm, iccn, clstp, &
jindx1_o3, jindx2_o3, ddy_o3, ozpl, jindx1_h, jindx2_h, ddy_h, h2opl, iflip, &
jindx1_aer, jindx2_aer, ddy_aer, iindx1_aer, iindx2_aer, ddx_aer, aer_nm, &
jindx1_ci, jindx2_ci, ddy_ci, iindx1_ci, iindx2_ci, ddx_ci, in_nm, ccn_nm, &
imap, jmap, prsl, seed0, rann, do_ugwp_v1, jindx1_tau, jindx2_tau, ddy_j1tau, ddy_j2tau,&
Expand All @@ -636,14 +644,14 @@ subroutine GFS_phys_time_vary_timestep_init (

! Interface variables
integer, intent(in) :: me, master, cnx, cny, isc, jsc, nrcm, im, levs, kdt, &
nsswr, imfdeepcnv, iccn, iflip
nsswr, imfdeepcnv, iccn, ntoz, iflip
integer, intent(in) :: idate(:)
real(kind_phys), intent(in) :: fhswr, fhour
logical, intent(in) :: lsswr, cal_pre, random_clds, h2o_phys, iaerclm
real(kind_phys), intent(out) :: clstp
integer, intent(in) :: jindx1_h(:), jindx2_h(:)
real(kind_phys), intent(in) :: ddy_h(:)
real(kind_phys), intent(inout) :: h2opl(:,:,:)
integer, intent(in) :: jindx1_o3(:), jindx2_o3(:), jindx1_h(:), jindx2_h(:)
real(kind_phys), intent(in) :: ddy_o3(:), ddy_h(:)
real(kind_phys), intent(inout) :: ozpl(:,:,:), h2opl(:,:,:)
integer, intent(in) :: jindx1_aer(:), jindx2_aer(:), iindx1_aer(:), iindx2_aer(:)
real(kind_phys), intent(in) :: ddy_aer(:), ddx_aer(:)
real(kind_phys), intent(inout) :: aer_nm(:,:,:)
Expand All @@ -659,15 +667,19 @@ subroutine GFS_phys_time_vary_timestep_init (
integer, intent(in) :: jindx1_tau(:), jindx2_tau(:)
real(kind_phys), intent(in) :: ddy_j1tau(:), ddy_j2tau(:)
real(kind_phys), intent(inout) :: tau_amf(:)
type(ty_ozphys), intent(in) :: ozphys
integer, intent(in) :: nthrds
character(len=*), intent(out) :: errmsg
integer, intent(out) :: errflg

! Local variables
integer :: i, j, k, iseed, iskip, ix
real(kind=kind_phys) :: wrk(1)
real(kind=kind_phys) :: rannie(cny)
real(kind=kind_phys) :: rndval(cnx*cny*nrcm)
integer :: i, j, k, iseed, iskip, ix, idat(8), jdat(8), iday, j1, j2, nc, n1, n2, jdow, &
jdoy, jday, w3kindreal, w3kindint
real(kind_phys) :: wrk(1), tem, tx1, tx2, rjday
real(kind_phys) :: rannie(cny)
real(kind_phys) :: rndval(cnx*cny*nrcm)
real(kind_dbl_prec) :: rinc(5)
real(kind_sngl_prec) :: rinc4(5)

! Initialize CCPP error handling variables
errmsg = ''
Expand Down Expand Up @@ -721,6 +733,43 @@ subroutine GFS_phys_time_vary_timestep_init (

endif ! imfdeepcnv, cal_re, random_clds

!> - Compute temporal interpolation indices for updating gas concentrations.
idat=0
idat(1)=idate(4)
idat(2)=idate(2)
idat(3)=idate(3)
idat(5)=idate(1)
rinc=0.
rinc(2)=fhour
call w3kind(w3kindreal,w3kindint)
if(w3kindreal==4) then
rinc4=rinc
CALL w3movdat(rinc4,idat,jdat)
else
CALL w3movdat(rinc,idat,jdat)
endif
jdow = 0
jdoy = 0
jday = 0
call w3doxdat(jdat,jdow,jdoy,jday)
rjday = jdoy + jdat(5) / 24.
if (rjday < ozphys%time(1)) rjday = rjday + 365.

n2 = ozphys%ntime + 1
do j=2,ozphys%ntime
if (rjday < ozphys%time(j)) then
n2 = j
exit
endif
enddo
n1 = n2 - 1
if (n2 > ozphys%ntime) n2 = n2 - ozphys%ntime

!> - Update ozone concentration.
if (ntoz > 0) then
call ozphys%update_o3prog(jindx1_o3, jindx2_o3, ddy_o3, rjday, n1, n2, ozpl)
endif

!> - Call h2ointerpol() to make stratospheric water vapor data interpolation
if (h2o_phys) then
call h2ointerpol (me, im, idate, fhour, &
Expand Down
75 changes: 74 additions & 1 deletion physics/GFS_phys_time_vary.scm.meta
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
name = GFS_phys_time_vary
type = scheme
dependencies = aerclm_def.F,aerinterp.F90,h2o_def.f,h2ointerp.f90,iccn_def.F,iccninterp.F90,machine.F,mersenne_twister.f
dependencies = namelist_soilveg.f,set_soilveg.f,cires_tauamf_data.F90,noahmp_tables.f90
dependencies = namelist_soilveg.f,set_soilveg.f,module_ozphys.F90,cires_tauamf_data.F90,noahmp_tables.f90

########################################################################
[ccpp-arg-table]
Expand All @@ -23,6 +23,13 @@
dimensions = ()
type = integer
intent = in
[ntoz]
standard_name = index_of_ozone_mixing_ratio_in_tracer_concentration_array
long_name = tracer index for ozone mixing ratio
units = index
dimensions = ()
type = integer
intent = in
[h2o_phys]
standard_name = flag_for_stratospheric_water_vapor_physics
long_name = flag for stratospheric water vapor physics
Expand Down Expand Up @@ -95,6 +102,28 @@
type = real
kind = kind_phys
intent = in
[jindx1_o3]
standard_name = lower_latitude_index_of_ozone_forcing_for_interpolation
long_name = interpolation low index for ozone
units = index
dimensions = (horizontal_dimension)
type = integer
intent = inout
[jindx2_o3]
standard_name = upper_latitude_index_of_ozone_forcing_for_interpolation
long_name = interpolation high index for ozone
units = index
dimensions = (horizontal_dimension)
type = integer
intent = inout
[ddy_o3]
standard_name = latitude_interpolation_weight_for_ozone_forcing
long_name = interpolation high index for ozone
units = none
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = inout
[jindx1_h]
standard_name = lower_latitude_index_of_stratospheric_water_vapor_forcing_for_interpolation
long_name = interpolation low index for stratospheric water vapor
Expand Down Expand Up @@ -1019,6 +1048,13 @@
dimensions = ()
type = logical
intent = in
[ntoz]
standard_name = index_of_ozone_mixing_ratio_in_tracer_concentration_array
long_name = tracer index for ozone mixing ratio
units = index
dimensions = ()
type = integer
intent = in
[h2o_phys]
standard_name = flag_for_stratospheric_water_vapor_physics
long_name = flag for stratospheric water vapor physics
Expand Down Expand Up @@ -1048,6 +1084,36 @@
type = real
kind = kind_phys
intent = out
[jindx1_o3]
standard_name = lower_latitude_index_of_ozone_forcing_for_interpolation
long_name = interpolation low index for ozone
units = index
dimensions = (horizontal_dimension)
type = integer
intent = in
[jindx2_o3]
standard_name = upper_latitude_index_of_ozone_forcing_for_interpolation
long_name = interpolation high index for ozone
units = index
dimensions = (horizontal_dimension)
type = integer
intent = in
[ddy_o3]
standard_name = latitude_interpolation_weight_for_ozone_forcing
long_name = interpolation high index for ozone
units = none
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
[ozpl]
standard_name = ozone_forcing
long_name = ozone forcing data
units = mixed
dimensions = (horizontal_dimension,number_of_levels_in_ozone_data,number_of_coefficients_in_ozone_data)
type = real
kind = kind_phys
intent = inout
[jindx1_h]
standard_name = lower_latitude_index_of_stratospheric_water_vapor_forcing_for_interpolation
long_name = interpolation low index for stratospheric water vapor
Expand Down Expand Up @@ -1279,6 +1345,13 @@
type = real
kind = kind_phys
intent = inout
[ozphys]
standard_name = dataset_for_ozone_physics
long_name = dataset for NRL ozone physics
units = mixed
dimensions = ()
type = ty_ozphys
intent = in
[nthrds]
standard_name = number_of_openmp_threads
long_name = number of OpenMP threads available for physics schemes
Expand Down
24 changes: 4 additions & 20 deletions physics/GFS_physics_post.F90
Original file line number Diff line number Diff line change
Expand Up @@ -13,32 +13,16 @@ module GFS_physics_post
public GFS_physics_post_init, GFS_physics_post_run
contains

! ###########################################################################################
! SUBROUTINE GFS_physics_post_init
! ###########################################################################################
!! \section arg_table_GFS_physics_post_init Argument Table
!! \htmlinclude GFS_physics_post_init.html
!!
subroutine GFS_physics_post_init(errmsg, errflg)

! Outputs
character(len=*), intent(out) :: &
errmsg ! CCPP error message
integer, intent(out) :: &
errflg ! CCPP error flag

end subroutine GFS_physics_post_init

! ###########################################################################################
! SUBROUTINE GFS_physics_post_run
! ###########################################################################################
!! \section arg_table_GFS_physics_post_run Argument Table
!! \htmlinclude GFS_physics_post_run.html
!!
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)
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) :: &
Expand All @@ -49,7 +33,7 @@ subroutine GFS_physics_post_run(nCol, nLev, ntoz, ntracp100, nprocess, nprocess_
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_photochem, & ! Index for process in diagnostic tendency output
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
Expand Down
20 changes: 0 additions & 20 deletions physics/GFS_physics_post.meta
Original file line number Diff line number Diff line change
Expand Up @@ -3,26 +3,6 @@
type = scheme
dependencies = machine.F

########################################################################
[ccpp-arg-table]
name = GFS_physics_post_init
type = scheme
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
units = none
dimensions = ()
type = character
kind = len=*
intent = out
[errflg]
standard_name = ccpp_error_code
long_name = error code for error handling in CCPP
units = 1
dimensions = ()
type = integer
intent = out

########################################################################
[ccpp-arg-table]
name = GFS_physics_post_run
Expand Down

0 comments on commit 06bb2bc

Please sign in to comment.