diff --git a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_ccpp_suite_sim_pre.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_ccpp_suite_sim_pre.F90 index fbaf5a1d9..2c276ca8c 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_ccpp_suite_sim_pre.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_ccpp_suite_sim_pre.F90 @@ -1,3 +1,6 @@ +!>\file GFS_ccpp_suite_sim_pre.F90 +!! Interstitial CCPP suite to couple UFS physics to CCPP suite simulator. + ! ######################################################################################## ! ! Description: Interstitial CCPP suite to couple UFS physics to ccpp_suite_simulator. @@ -22,7 +25,7 @@ module GFS_ccpp_suite_sim_pre ! SUBROUTINE GFS_ccpp_suite_sim_pre_run ! ! ###################################################################################### -!! \section arg_table_GFS_ccpp_suite_sim_pre_run +!> \section arg_table_GFS_ccpp_suite_sim_pre_run !! \htmlinclude GFS_ccpp_suite_sim_pre_run.html !! subroutine GFS_ccpp_suite_sim_pre_run(do_ccpp_suite_sim, dtend, ntqv, dtidx, dtp, & @@ -110,6 +113,7 @@ subroutine GFS_ccpp_suite_sim_pre_run(do_ccpp_suite_sim, dtend, ntqv, dtidx, dtp end subroutine GFS_ccpp_suite_sim_pre_run ! ###################################################################################### +!> subroutine load_ccpp_suite_sim(nlunit, nml_file, physics_process, iactive_T, & iactive_u, iactive_v, iactive_q, errmsg, errflg) diff --git a/physics/Interstitials/UFS_SCM_NEPTUNE/ccpp_suite_simulator.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/ccpp_suite_simulator.F90 index c1592263d..6a706456c 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/ccpp_suite_simulator.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/ccpp_suite_simulator.F90 @@ -1,20 +1,19 @@ -! ######################################################################################## -! -! Description: This suite simulates the evolution of the internal physics state -! represented by a CCPP Suite Definition File (SDF). -! -! To activate this suite it must be a) embedded within the SDF and b) activated through -! the physics namelist. -! The derived-data type "base_physics_process" contains the metadata needed to reconstruct -! the temporal evolution of the state. An array of base_physics_process, physics_process, -! is populated by the host during initialization and passed to the physics. Additionally, -! this type holds any data, or type-bound procedures, required by the suite simulator(s). -! -! For this initial demonstration we are using 2-dimensional (height, time) forcing data, -! which is on the same native vertical grid as the SCM. The dataset has a temporal -! resolution of 1-hour, created by averaging all local times from a Tropical Warm Pool -! International Cloud Experiment (TWPICE) case. This was to create a dataset with a -! (constant) diurnal cycle. +!>\file ccpp_suite_simulator.F90 +!! Description: This suite simulates the evolution of the internal physics state +!! represented by a CCPP Suite Definition File (SDF). +!! +!! To activate this suite it must be a) embedded within the SDF and b) activated through +!! the physics namelist. +!! The derived-data type "base_physics_process" contains the metadata needed to reconstruct +!! the temporal evolution of the state. An array of base_physics_process, physics_process, +!! is populated by the host during initialization and passed to the physics. Additionally, +!! this type holds any data, or type-bound procedures, required by the suite simulator(s). +!! +!! For this initial demonstration we are using 2-dimensional (height, time) forcing data, +!! which is on the same native vertical grid as the SCM. The dataset has a temporal +!! resolution of 1-hour, created by averaging all local times from a Tropical Warm Pool +!! International Cloud Experiment (TWPICE) case. This was to create a dataset with a +!! (constant) diurnal cycle. ! ! ######################################################################################## module ccpp_suite_simulator diff --git a/physics/Interstitials/UFS_SCM_NEPTUNE/module_ccpp_suite_simulator.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/module_ccpp_suite_simulator.F90 index c4f9fc4e4..e8a4188d3 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/module_ccpp_suite_simulator.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/module_ccpp_suite_simulator.F90 @@ -1,19 +1,15 @@ -! ######################################################################################## -! -! This module contains the type, base_physics_process, and supporting subroutines needed -! by the ccpp suite simulator. -! -! ######################################################################################## +!>\file module_ccpp_suite_simulator.F90 +!! This module contains the type, base_physics_process, and supporting subroutines needed +!! by the ccpp suite simulator. + module module_ccpp_suite_simulator -!> \section arg_table_module_ccpp_suite_simulator Argument table -!! \htmlinclude module_ccpp_suite_simulator.html -!! + use machine, only : kind_phys implicit none public base_physics_process - ! Type containing 1D (time) physics tendencies. +!> Type containing 1D (time) physics tendencies. type phys_tend_1d real(kind_phys), dimension(:), allocatable :: T real(kind_phys), dimension(:), allocatable :: u @@ -23,7 +19,7 @@ module module_ccpp_suite_simulator real(kind_phys), dimension(:), allocatable :: z end type phys_tend_1d - ! Type containing 2D (lev,time) physics tendencies. +!> Type containing 2D (lev,time) physics tendencies. type phys_tend_2d real(kind_phys), dimension(:), allocatable :: time real(kind_phys), dimension(:,:), allocatable :: T @@ -45,7 +41,7 @@ module module_ccpp_suite_simulator real(kind_phys), dimension(:,:,:), allocatable :: q end type phys_tend_3d - ! Type containing 4D (lon,lat,lev,time) physics tendencies. +!> Type containing 4D (lon,lat,lev,time) physics tendencies. type phys_tend_4d real(kind_phys), dimension(:), allocatable :: time real(kind_phys), dimension(:,:), allocatable :: lon @@ -56,24 +52,20 @@ module module_ccpp_suite_simulator real(kind_phys), dimension(:,:,:,:), allocatable :: q end type phys_tend_4d -! This type contains the meta information and data for each physics process. - -!> \section arg_table_base_physics_process Argument Table -!! \htmlinclude base_physics_process.html -!! +!> This type contains the meta information and data for each physics process. type base_physics_process - character(len=16) :: name ! Physics process name - logical :: time_split = .false. ! Is process time-split? - logical :: use_sim = .false. ! Is process "active"? - integer :: order ! Order of process in process-loop - type(phys_tend_1d) :: tend1d ! Instantaneous data - type(phys_tend_2d) :: tend2d ! 2-dimensional data - type(phys_tend_3d) :: tend3d ! Not used. Placeholder for 3-dimensional spatial data. - type(phys_tend_4d) :: tend4d ! Not used. Placeholder for 4-dimensional spatio-tempo data. - character(len=16) :: active_name ! "Active" scheme: Physics process name - integer :: iactive_scheme ! "Active" scheme: Order of process in process-loop - logical :: active_tsp ! "Active" scheme: Is process time-split? - integer :: nprg_active ! "Active" scheme: Number of prognostic variables + character(len=16) :: name !< Physics process name + logical :: time_split = .false. !< Is process time-split? + logical :: use_sim = .false. !< Is process "active"? + integer :: order !< Order of process in process-loop + type(phys_tend_1d) :: tend1d !< Instantaneous data + type(phys_tend_2d) :: tend2d !< 2-dimensional data + type(phys_tend_3d) :: tend3d !< Not used. Placeholder for 3-dimensional spatial data. + type(phys_tend_4d) :: tend4d !< Not used. Placeholder for 4-dimensional spatio-tempo data. + character(len=16) :: active_name !< "Active" scheme: Physics process name + integer :: iactive_scheme !< "Active" scheme: Order of process in process-loop + logical :: active_tsp !< "Active" scheme: Is process time-split? + integer :: nprg_active !< "Active" scheme: Number of prognostic variables contains generic, public :: linterp => linterp_1D, linterp_2D procedure, private :: linterp_1D @@ -84,11 +76,8 @@ module module_ccpp_suite_simulator contains - ! #################################################################################### - ! Type-bound procedure to compute tendency profile for time-of-day. - ! - ! For use with 1D data (level, time) tendencies with diurnal (24-hr) forcing. - ! #################################################################################### +!> Type-bound procedure to compute tendency profile for time-of-day. +!! For use with 1D data (level, time) tendencies with diurnal (24-hr) forcing. function linterp_1D(this, var_name, year, month, day, hour, min, sec) result(err_message) class(base_physics_process), intent(inout) :: this character(len=*), intent(in) :: var_name @@ -131,13 +120,10 @@ function linterp_1D(this, var_name, year, month, day, hour, min, sec) result(err end function linterp_1D - ! #################################################################################### - ! Type-bound procedure to compute tendency profile for time-of-day. - ! - ! For use with 2D data (location, level, time) tendencies with diurnal (24-hr) forcing. - ! This assumes that the location dimension has a [longitude, latitude] allocated with - ! each location. - ! #################################################################################### +!> Type-bound procedure to compute tendency profile for time-of-day. +!! For use with 2D data (location, level, time) tendencies with diurnal (24-hr) forcing. +!! This assumes that the location dimension has a [longitude, latitude] allocated with +!! each location. function linterp_2D(this, var_name, lon, lat, year, month, day, hour, min, sec) result(err_message) class(base_physics_process), intent(inout) :: this character(len=*), intent(in) :: var_name @@ -165,10 +151,8 @@ function linterp_2D(this, var_name, lon, lat, year, month, day, hour, min, sec) end select end function linterp_2D - ! #################################################################################### - ! Type-bound procedure to find nearest location. - ! For use with linterp_2D, NOT YET IMPLEMENTED. - ! #################################################################################### +!> Type-bound procedure to find nearest location. +!! For use with linterp_2D, NOT YET IMPLEMENTED. pure function find_nearest_loc_2d_1d(this, lon, lat) class(base_physics_process), intent(in) :: this real(kind_phys), intent(in) :: lon, lat @@ -177,10 +161,8 @@ pure function find_nearest_loc_2d_1d(this, lon, lat) find_nearest_loc_2d_1d = 1 end function find_nearest_loc_2d_1d - ! #################################################################################### - ! Type-bound procedure to compute linear interpolation weights for a diurnal (24-hour) - ! forcing. - ! #################################################################################### +!> Type-bound procedure to compute linear interpolation weights for a diurnal (24-hour) +!! forcing. subroutine cmp_time_wts(this, year, month, day, hour, minute, sec, w1, w2, ti, tf) ! Inputs class(base_physics_process), intent(in) :: this @@ -199,8 +181,7 @@ subroutine cmp_time_wts(this, year, month, day, hour, minute, sec, w1, w2, ti, t end subroutine cmp_time_wts - ! #################################################################################### - ! #################################################################################### +!> subroutine sim_LWRAD( year, month, day, hour, min, sec, process) type(base_physics_process), intent(inout) :: process integer, intent(in) :: year, month, day, hour, min, sec @@ -212,8 +193,7 @@ subroutine sim_LWRAD( year, month, day, hour, min, sec, process) end subroutine sim_LWRAD - ! #################################################################################### - ! #################################################################################### +!> subroutine sim_SWRAD( year, month, day, hour, min, sec, process) type(base_physics_process), intent(inout) :: process integer, intent(in) :: year, month, day, hour, min, sec @@ -225,8 +205,7 @@ subroutine sim_SWRAD( year, month, day, hour, min, sec, process) end subroutine sim_SWRAD - ! #################################################################################### - ! #################################################################################### +!> subroutine sim_GWD( year, month, day, hour, min, sec, process) type(base_physics_process), intent(inout) :: process integer, intent(in) :: year, month, day, hour, min, sec @@ -244,8 +223,7 @@ subroutine sim_GWD( year, month, day, hour, min, sec, process) end subroutine sim_GWD - ! #################################################################################### - ! #################################################################################### +!> subroutine sim_PBL( year, month, day, hour, min, sec, process) type(base_physics_process), intent(inout) :: process integer, intent(in) :: year, month, day, hour, min, sec @@ -266,8 +244,7 @@ subroutine sim_PBL( year, month, day, hour, min, sec, process) end subroutine sim_PBL - ! #################################################################################### - ! #################################################################################### +!> subroutine sim_DCNV( year, month, day, hour, min, sec, process) type(base_physics_process), intent(inout) :: process integer, intent(in) :: year, month, day, hour, min, sec @@ -288,8 +265,7 @@ subroutine sim_DCNV( year, month, day, hour, min, sec, process) end subroutine sim_DCNV - ! #################################################################################### - ! #################################################################################### +!> subroutine sim_SCNV( year, month, day, hour, min, sec, process) type(base_physics_process), intent(inout) :: process integer, intent(in) :: year, month, day, hour, min, sec @@ -310,8 +286,7 @@ subroutine sim_SCNV( year, month, day, hour, min, sec, process) end subroutine sim_SCNV - ! #################################################################################### - ! #################################################################################### +!> subroutine sim_cldMP( year, month, day, hour, min, sec, process) type(base_physics_process), intent(inout) :: process integer, intent(in) :: year, month, day, hour, min, sec diff --git a/physics/Radiation/RRTMG/iounitdef.f b/physics/Radiation/RRTMG/iounitdef.f index c6a4e591f..af3a700b8 100644 --- a/physics/Radiation/RRTMG/iounitdef.f +++ b/physics/Radiation/RRTMG/iounitdef.f @@ -1,3 +1,7 @@ +!>\file iounitdef.f +!! This file defines fortran unit numbers for input/output data +!! files for the NCEP GFS model. + !!!!! ========================================================== !!!!! !!!!! module "module_iounitdef description !!!!! !!!!! ========================================================== !!!!! diff --git a/physics/Radiation/RRTMG/module_bfmicrophysics.f b/physics/Radiation/RRTMG/module_bfmicrophysics.f index caff7fc61..6285653d2 100644 --- a/physics/Radiation/RRTMG/module_bfmicrophysics.f +++ b/physics/Radiation/RRTMG/module_bfmicrophysics.f @@ -1,5 +1,5 @@ -!>\file module_bfmicrophysics.f This file contains some subroutines used -!! in microphysics. +!>\file module_bfmicrophysics.f +!!This file contains some subroutines used in microphysics. !> This module contains some subroutines used in microphysics. MODULE module_microphysics diff --git a/physics/Radiation/RRTMG/rad_sw_pre.F90 b/physics/Radiation/RRTMG/rad_sw_pre.F90 index b7c3faf4c..83a0385a8 100644 --- a/physics/Radiation/RRTMG/rad_sw_pre.F90 +++ b/physics/Radiation/RRTMG/rad_sw_pre.F90 @@ -1,12 +1,11 @@ !>\file rad_sw_pre.F90 !! This file gathers the sunlit points for the shortwave radiation schemes. +!> This module gathers the sunlit points for the shortwave radiation schemes. module rad_sw_pre contains -!> \defgroup rad_sw_pre GFS Radiation-SW Pre -!! This module gathers the sunlit points for the shortwave radiation schemes. -!> @{ + !> \section arg_table_rad_sw_pre_run Argument Table !! \htmlinclude rad_sw_pre_run.html !! @@ -49,5 +48,4 @@ subroutine rad_sw_pre_run (im, lsswr, coszen, nday, idxday, errmsg, errflg) endif end subroutine rad_sw_pre_run -!> @} end module rad_sw_pre diff --git a/physics/Radiation/RRTMG/radcons.f90 b/physics/Radiation/RRTMG/radcons.f90 index 0ca7eeb19..decf79990 100644 --- a/physics/Radiation/RRTMG/radcons.f90 +++ b/physics/Radiation/RRTMG/radcons.f90 @@ -2,10 +2,6 @@ !! This file contains module radcons. -!> \defgroup radcons GFS RRTMG Constants Module -!> This module contains some of the most frequently used math and physics -!! constants for RRTMG. - !> This module contains some of the most frequently used math and physics !! constants for RRTMG. module radcons diff --git a/physics/Radiation/RRTMG/rrtmg_lw_cloud_optics.F90 b/physics/Radiation/RRTMG/rrtmg_lw_cloud_optics.F90 index 1dd225514..7477a498e 100644 --- a/physics/Radiation/RRTMG/rrtmg_lw_cloud_optics.F90 +++ b/physics/Radiation/RRTMG/rrtmg_lw_cloud_optics.F90 @@ -1,3 +1,6 @@ +!>\file rrtmg_lw_cloud_optics.F90 +!! + module mo_rrtmg_lw_cloud_optics use machine, only: kind_phys use mersenne_twister, only: random_setseed, random_number, random_stat diff --git a/physics/Radiation/RRTMGP/rrtmgp_lw_main.F90 b/physics/Radiation/RRTMGP/rrtmgp_lw_main.F90 index 39792eab7..2e22476d4 100644 --- a/physics/Radiation/RRTMGP/rrtmgp_lw_main.F90 +++ b/physics/Radiation/RRTMGP/rrtmgp_lw_main.F90 @@ -1,7 +1,6 @@ !> \file rrtmgp_lw_main.F90 !! This file contains the longwave RRTMGP radiation scheme. !! -! ########################################################################################### module rrtmgp_lw_main use mpi_f08 use machine, only: kind_phys, kind_dbl_prec @@ -25,15 +24,10 @@ module rrtmgp_lw_main public rrtmgp_lw_main_init, rrtmgp_lw_main_run contains -!! \section arg_table_rrtmgp_lw_main_init + +!> \section arg_table_rrtmgp_lw_main_init Argument Table !! \htmlinclude rrtmgp_lw_main_int.html !! -!> \ingroup rrtmgp_lw_main -!! -!! \brief -!! -!! \section rrtmgp_lw_main_init -!> @{ subroutine rrtmgp_lw_main_init(rrtmgp_root_dir, rrtmgp_lw_file_gas, rrtmgp_lw_file_clouds,& active_gases_array, doGP_cldoptics_PADE, doGP_cldoptics_LUT, doGP_sgs_pbl, & doGP_sgs_cnv, nrghice, mpicomm, mpirank, mpiroot, nLay, rrtmgp_phys_blksz, & @@ -41,33 +35,33 @@ subroutine rrtmgp_lw_main_init(rrtmgp_root_dir, rrtmgp_lw_file_gas, rrtmgp_lw_fi ! Inputs character(len=128),intent(in) :: & - rrtmgp_root_dir, & ! RTE-RRTMGP root directory - rrtmgp_lw_file_clouds, & ! RRTMGP file containing coefficients used to compute - ! clouds optical properties - rrtmgp_lw_file_gas ! RRTMGP file containing coefficients used to compute - ! gaseous optical properties + rrtmgp_root_dir, & !< RTE-RRTMGP root directory + rrtmgp_lw_file_clouds, & !< RRTMGP file containing coefficients used to compute + !< clouds optical properties + rrtmgp_lw_file_gas !< RRTMGP file containing coefficients used to compute + !! gaseous optical properties character(len=*), dimension(:), intent(in) :: & - active_gases_array ! List of active gases from namelist as array) + active_gases_array !< List of active gases from namelist as array) logical, intent(in) :: & - doGP_cldoptics_PADE, & ! Use RRTMGP cloud-optics: PADE approximation? - doGP_cldoptics_LUT, & ! Use RRTMGP cloud-optics: LUTs? - doGP_sgs_pbl, & ! Flag to include sgs PBL clouds - doGP_sgs_cnv ! Flag to include sgs convective clouds + doGP_cldoptics_PADE, & !< Use RRTMGP cloud-optics: PADE approximation? + doGP_cldoptics_LUT, & !< Use RRTMGP cloud-optics: LUTs? + doGP_sgs_pbl, & !< Flag to include sgs PBL clouds + doGP_sgs_cnv !< Flag to include sgs convective clouds integer, intent(inout) :: & - nrghice ! Number of ice-roughness categories + nrghice !< Number of ice-roughness categories type(MPI_Comm),intent(in) :: & - mpicomm ! MPI communicator + mpicomm !< MPI communicator integer,intent(in) :: & - mpirank, & ! Current MPI rank - mpiroot, & ! Master MPI rank - rrtmgp_phys_blksz, & ! Number of horizontal points to process at once. + mpirank, & !< Current MPI rank + mpiroot, & !< Master MPI rank + rrtmgp_phys_blksz, & !< Number of horizontal points to process at once. nLay ! Outputs character(len=*), intent(out) :: & - errmsg ! CCPP error message + errmsg !< CCPP error message integer, intent(out) :: & - errflg ! CCPP error code + errflg !< CCPP error code ! Initialize CCPP error handling variables errmsg = '' @@ -83,18 +77,10 @@ subroutine rrtmgp_lw_main_init(rrtmgp_root_dir, rrtmgp_lw_file_gas, rrtmgp_lw_fi errmsg, errflg) end subroutine rrtmgp_lw_main_init -!> @} - ! ###################################################################################### -!! \section arg_table_rrtmgp_lw_main_run + +!> \section arg_table_rrtmgp_lw_main_run Argument Table !! \htmlinclude rrtmgp_lw_main_run.html !! -!> \ingroup rrtmgp_lw_main -!! -!! \brief -!! -!! \section rrtmgp_lw_main_run -!> @{ - ! ###################################################################################### subroutine rrtmgp_lw_main_run(doLWrad, doLWclrsky, top_at_1, doGP_lwscat, & use_LW_jacobian, doGP_sgs_cnv, doGP_sgs_pbl, nCol, nLay, nGases,rrtmgp_phys_blksz,& nGauss_angles, icseed_lw, iovr, iovr_convcld, iovr_max, iovr_maxrand, iovr_rand, & @@ -109,83 +95,83 @@ subroutine rrtmgp_lw_main_run(doLWrad, doLWclrsky, top_at_1, doGP_lwscat, ! Inputs logical, intent(in) :: & - doLWrad, & ! Flag to perform longwave calculation - doLWclrsky, & ! Flag to compute clear-sky fluxes - top_at_1, & ! Flag for vertical ordering convention - use_LW_jacobian, & ! Flag to compute Jacobian of longwave surface flux - doGP_sgs_pbl, & ! Flag to include sgs PBL clouds - doGP_sgs_cnv, & ! Flag to include sgs convective clouds - doGP_lwscat ! Flag to include scattering in clouds + doLWrad, & !< Flag to perform longwave calculation + doLWclrsky, & !< Flag to compute clear-sky fluxes + top_at_1, & !< Flag for vertical ordering convention + use_LW_jacobian, & !< Flag to compute Jacobian of longwave surface flux + doGP_sgs_pbl, & !< Flag to include sgs PBL clouds + doGP_sgs_cnv, & !< Flag to include sgs convective clouds + doGP_lwscat !< Flag to include scattering in clouds integer,intent(in) :: & - nCol, & ! Number of horizontal points - nLay, & ! Number of vertical grid points. - nGases, & ! Number of active gases - rrtmgp_phys_blksz, & ! Number of horizontal points to process at once. - nGauss_angles, & ! Number of gaussian quadrature angles used - iovr, & ! Choice of cloud-overlap method - iovr_convcld, & ! Choice of convective cloud-overlap - iovr_max, & ! Flag for maximum cloud overlap method - iovr_maxrand, & ! Flag for maximum-random cloud overlap method - iovr_rand, & ! Flag for random cloud overlap method - iovr_dcorr, & ! Flag for decorrelation-length cloud overlap method - iovr_exp, & ! Flag for exponential cloud overlap method - iovr_exprand, & ! Flag for exponential-random cloud overlap method - isubc_lw ! Flag for cloud-seeding (rng) for cloud-sampling + nCol, & !< Number of horizontal points + nLay, & !< Number of vertical grid points. + nGases, & !< Number of active gases + rrtmgp_phys_blksz, & !< Number of horizontal points to process at once. + nGauss_angles, & !< Number of gaussian quadrature angles used + iovr, & !< Choice of cloud-overlap method + iovr_convcld, & !< Choice of convective cloud-overlap + iovr_max, & !< Flag for maximum cloud overlap method + iovr_maxrand, & !< Flag for maximum-random cloud overlap method + iovr_rand, & !< Flag for random cloud overlap method + iovr_dcorr, & !< Flag for decorrelation-length cloud overlap method + iovr_exp, & !< Flag for exponential cloud overlap method + iovr_exprand, & !< Flag for exponential-random cloud overlap method + isubc_lw !< Flag for cloud-seeding (rng) for cloud-sampling integer,intent(in),dimension(:) :: & - icseed_lw ! Seed for random number generation for longwave radiation + icseed_lw !< Seed for random number generation for longwave radiation real(kind_phys), dimension(:), intent(in) :: & - semis, & ! Surface-emissivity (1) - tsfg ! Skin temperature (K) + semis, & !< Surface-emissivity (1) + tsfg !< Skin temperature (K) real(kind_phys), dimension(:,:), intent(in) :: & - p_lay, & ! Pressure @ model layer-centers (Pa) - t_lay, & ! Temperature (K) - p_lev, & ! Pressure @ model layer-interfaces (Pa) - t_lev, & ! Temperature @ model levels (K) - vmr_o2, & ! Molar-mixing ratio oxygen - vmr_h2o, & ! Molar-mixing ratio water vapor - vmr_o3, & ! Molar-mixing ratio ozone - vmr_ch4, & ! Molar-mixing ratio methane - vmr_n2o, & ! Molar-mixing ratio nitrous oxide - vmr_co2, & ! Molar-mixing ratio carbon dioxide - cld_frac, & ! Cloud-fraction for stratiform clouds - cld_lwp, & ! Water path for stratiform liquid cloud-particles - cld_reliq, & ! Effective radius for stratiform liquid cloud-particles - cld_iwp, & ! Water path for stratiform ice cloud-particles - cld_reice, & ! Effective radius for stratiform ice cloud-particles - cld_swp, & ! Water path for snow hydrometeors - cld_resnow, & ! Effective radius for snow hydrometeors - cld_rwp, & ! Water path for rain hydrometeors - cld_rerain, & ! Effective radius for rain hydrometeors - precip_frac, & ! Precipitation fraction (not active, currently precipitation optics uses cloud-fraction) - cld_cnv_lwp, & ! Water path for convective liquid cloud-particles - cld_cnv_reliq, & ! Effective radius for convective liquid cloud-particles - cld_cnv_iwp, & ! Water path for convective ice cloud-particles - cld_cnv_reice, & ! Effective radius for convective ice cloud-particles - cld_pbl_lwp, & ! Water path for PBL liquid cloud-particles - cld_pbl_reliq, & ! Effective radius for PBL liquid cloud-particles - cld_pbl_iwp, & ! Water path for PBL ice cloud-particles - cld_pbl_reice, & ! Effective radius for PBL ice cloud-particles - cloud_overlap_param ! Cloud overlap parameter + p_lay, & !< Pressure @ model layer-centers (Pa) + t_lay, & !< Temperature (K) + p_lev, & !< Pressure @ model layer-interfaces (Pa) + t_lev, & !< Temperature @ model levels (K) + vmr_o2, & !< Molar-mixing ratio oxygen + vmr_h2o, & !< Molar-mixing ratio water vapor + vmr_o3, & !< Molar-mixing ratio ozone + vmr_ch4, & !< Molar-mixing ratio methane + vmr_n2o, & !< Molar-mixing ratio nitrous oxide + vmr_co2, & !< Molar-mixing ratio carbon dioxide + cld_frac, & !< Cloud-fraction for stratiform clouds + cld_lwp, & !< Water path for stratiform liquid cloud-particles + cld_reliq, & !< Effective radius for stratiform liquid cloud-particles + cld_iwp, & !< Water path for stratiform ice cloud-particles + cld_reice, & !< Effective radius for stratiform ice cloud-particles + cld_swp, & !< Water path for snow hydrometeors + cld_resnow, & !< Effective radius for snow hydrometeors + cld_rwp, & !< Water path for rain hydrometeors + cld_rerain, & !< Effective radius for rain hydrometeors + precip_frac, & !< Precipitation fraction (not active, currently precipitation optics uses cloud-fraction) + cld_cnv_lwp, & !< Water path for convective liquid cloud-particles + cld_cnv_reliq, & !< Effective radius for convective liquid cloud-particles + cld_cnv_iwp, & !< Water path for convective ice cloud-particles + cld_cnv_reice, & !< Effective radius for convective ice cloud-particles + cld_pbl_lwp, & !< Water path for PBL liquid cloud-particles + cld_pbl_reliq, & !< Effective radius for PBL liquid cloud-particles + cld_pbl_iwp, & !< Water path for PBL ice cloud-particles + cld_pbl_reice, & !< Effective radius for PBL ice cloud-particles + cloud_overlap_param !< Cloud overlap parameter real(kind_phys), dimension(:,:,:), intent(in) :: & - aerlw_tau, & ! Aerosol optical depth - aerlw_ssa, & ! Aerosol single scattering albedo - aerlw_g ! Aerosol asymmetry paramter + aerlw_tau, & !< Aerosol optical depth + aerlw_ssa, & !< Aerosol single scattering albedo + aerlw_g !< Aerosol asymmetry paramter character(len=*), dimension(:), intent(in) :: & - active_gases_array ! List of active gases from namelist as array + active_gases_array !< List of active gases from namelist as array ! Outputs real(kind_phys), dimension(:,:), intent(inout) :: & - fluxlwUP_jac, & ! Jacobian of upwelling LW surface radiation (W/m2/K) - fluxlwUP_allsky, & ! All-sky flux (W/m2) - fluxlwDOWN_allsky, & ! All-sky flux (W/m2) - fluxlwUP_clrsky, & ! Clear-sky flux (W/m2) - fluxlwDOWN_clrsky, & ! All-sky flux (W/m2) - fluxlwUP_radtime, & ! Copy of fluxes (Used for coupling) - fluxlwDOWN_radtime ! + fluxlwUP_jac, & !< Jacobian of upwelling LW surface radiation (W/m2/K) + fluxlwUP_allsky, & !< All-sky flux (W/m2) + fluxlwDOWN_allsky, & !< All-sky flux (W/m2) + fluxlwUP_clrsky, & !< Clear-sky flux (W/m2) + fluxlwDOWN_clrsky, & !< All-sky flux (W/m2) + fluxlwUP_radtime, & !< Copy of fluxes (Used for coupling) + fluxlwDOWN_radtime !< character(len=*), intent(out) :: & - errmsg ! CCPP error message + errmsg !< CCPP error message integer, intent(out) :: & - errflg ! CCPP error flag + errflg !< CCPP error flag ! Local variables type(ty_fluxes_byband) :: flux_allsky, flux_clrsky @@ -605,5 +591,4 @@ subroutine rrtmgp_lw_main_run(doLWrad, doLWclrsky, top_at_1, doGP_lwscat, enddo end subroutine rrtmgp_lw_main_run -!> @} end module rrtmgp_lw_main diff --git a/physics/Radiation/RRTMGP/rrtmgp_sw_gas_optics.F90 b/physics/Radiation/RRTMGP/rrtmgp_sw_gas_optics.F90 index 5713d188d..3229d2f16 100644 --- a/physics/Radiation/RRTMGP/rrtmgp_sw_gas_optics.F90 +++ b/physics/Radiation/RRTMGP/rrtmgp_sw_gas_optics.F90 @@ -1,10 +1,7 @@ !> \file rrtmgp_sw_gas_optics.F90 -!! -!> \defgroup rrtmgp_sw_gas_optics rrtmgp_sw_gas_optics.F90 -!! -!! \brief This module contains a routine to initialize the k-distribution data used +!! This module contains a routine to initialize the k-distribution data used !! by the RRTMGP shortwave radiation scheme. -!! + module rrtmgp_sw_gas_optics use machine, only: kind_phys use mo_rte_kind, only: wl @@ -79,43 +76,34 @@ module rrtmgp_sw_gas_optics scale_by_complement_upperSW ! Absorption is scaled by concentration of scaling_gas (F) or its complement (T) contains - ! ###################################################################################### -!>\defgroup rrtmgp_sw_gas_optics_mod GFS RRTMGP-SW Gas Optics Module -!> @{ -!! \section arg_table_rrtmgp_sw_gas_optics_init +!> \section arg_table_rrtmgp_sw_gas_optics_init Argument Table !! \htmlinclude rrtmgp_sw_gas_optics.html !! -!> \ingroup rrtmgp_sw_gas_optics -!! !! RRTMGP relies heavility on derived-data-types, which contain type-bound procedures !! that are referenced frequently throughout the RRTMGP shortwave scheme. The data needed !! for the correlated k-distribution is also contained within this type. Within this module, !! the full k-distribution data is read in, reduced by the "active gases" provided, and !! loaded into the RRTMGP DDT, ty_gas_optics_rrtmgp. -!! -!! \section rrtmgp_sw_gas_optics_init -!> @{ - ! ###################################################################################### subroutine rrtmgp_sw_gas_optics_init(rrtmgp_root_dir, rrtmgp_sw_file_gas, & active_gases_array, mpicomm, mpirank, mpiroot, errmsg, errflg) ! Inputs character(len=128),intent(in) :: & - rrtmgp_root_dir, & ! RTE-RRTMGP root directory - rrtmgp_sw_file_gas ! RRTMGP file containing K-distribution data + rrtmgp_root_dir, & !< RTE-RRTMGP root directory + rrtmgp_sw_file_gas !< RRTMGP file containing K-distribution data character(len=*), dimension(:), intent(in) :: & - active_gases_array ! List of active gases from namelist as array + active_gases_array !< List of active gases from namelist as array type(MPI_Comm),intent(in) :: & - mpicomm ! MPI communicator + mpicomm !< MPI communicator integer,intent(in) :: & - mpirank, & ! Current MPI rank - mpiroot ! Master MPI rank + mpirank, & !< Current MPI rank + mpiroot !< Master MPI rank ! Outputs character(len=*), intent(out) :: & - errmsg ! CCPP error message + errmsg !< CCPP error message integer, intent(out) :: & - errflg ! CCPP error code + errflg !< CCPP error code ! Local variables integer :: status, ncid, dimid, varID, mpierr, iChar @@ -497,6 +485,5 @@ subroutine rrtmgp_sw_gas_optics_init(rrtmgp_root_dir, rrtmgp_sw_file_gas, sb_defaultSW, rayl_lowerSW, rayl_upperSW)) end subroutine rrtmgp_sw_gas_optics_init -!> @} end module rrtmgp_sw_gas_optics diff --git a/physics/Radiation/RRTMGP/rrtmgp_sw_main.F90 b/physics/Radiation/RRTMGP/rrtmgp_sw_main.F90 index ab379cc9e..77691d836 100644 --- a/physics/Radiation/RRTMGP/rrtmgp_sw_main.F90 +++ b/physics/Radiation/RRTMGP/rrtmgp_sw_main.F90 @@ -99,95 +99,95 @@ subroutine rrtmgp_sw_main_run(doSWrad, doSWclrsky, top_at_1, doGP_sgs_cnv, doGP_ ! Inputs logical, intent(in) :: & - doSWrad, & ! Flag to perform shortwave calculation - doSWclrsky, & ! Flag to compute clear-sky fluxes - top_at_1, & ! Flag for vertical ordering convention - doGP_sgs_pbl, & ! Flag to include sgs PBL clouds - doGP_sgs_cnv ! Flag to include sgs convective clouds + doSWrad, & !< Flag to perform shortwave calculation + doSWclrsky, & !< Flag to compute clear-sky fluxes + top_at_1, & !< Flag for vertical ordering convention + doGP_sgs_pbl, & !< Flag to include sgs PBL clouds + doGP_sgs_cnv !< Flag to include sgs convective clouds integer,intent(in) :: & - nCol, & ! Number of horizontal points - nDay, & ! Number of daytime points - nLay, & ! Number of vertical grid points. - nGases, & ! Number of active gases - rrtmgp_phys_blksz, & ! Number of horizontal points to process at once. - iovr, & ! Choice of cloud-overlap method - iovr_convcld, & ! Choice of convective cloud-overlap - iovr_max, & ! Flag for maximum cloud overlap method - iovr_maxrand, & ! Flag for maximum-random cloud overlap method - iovr_rand, & ! Flag for random cloud overlap method - iovr_dcorr, & ! Flag for decorrelation-length cloud overlap method - iovr_exp, & ! Flag for exponential cloud overlap method - iovr_exprand, & ! Flag for exponential-random cloud overlap method - isubc_sw, & ! + nCol, & !< Number of horizontal points + nDay, & !< Number of daytime points + nLay, & !< Number of vertical grid points. + nGases, & !< Number of active gases + rrtmgp_phys_blksz, & !< Number of horizontal points to process at once. + iovr, & !< Choice of cloud-overlap method + iovr_convcld, & !< Choice of convective cloud-overlap + iovr_max, & !< Flag for maximum cloud overlap method + iovr_maxrand, & !< Flag for maximum-random cloud overlap method + iovr_rand, & !< Flag for random cloud overlap method + iovr_dcorr, & !< Flag for decorrelation-length cloud overlap method + iovr_exp, & !< Flag for exponential cloud overlap method + iovr_exprand, & !< Flag for exponential-random cloud overlap method + isubc_sw, & !< iSFC integer,intent(in),dimension(:) :: & - idx, & ! Index array for daytime points - icseed_sw ! Seed for random number generation for shortwave radiation + idx, & !< Index array for daytime points + icseed_sw !< Seed for random number generation for shortwave radiation real(kind_phys), dimension(:), intent(in) :: & - sfc_alb_nir_dir, & ! Surface albedo (direct) - sfc_alb_nir_dif, & ! Surface albedo (diffuse) - sfc_alb_uvvis_dir, & ! Surface albedo (direct) - sfc_alb_uvvis_dif, & ! Surface albedo (diffuse) - coszen ! Cosize of SZA + sfc_alb_nir_dir, & !< Surface albedo (direct) + sfc_alb_nir_dif, & !< Surface albedo (diffuse) + sfc_alb_uvvis_dir, & !< Surface albedo (direct) + sfc_alb_uvvis_dif, & !< Surface albedo (diffuse) + coszen !< Cosize of SZA real(kind_phys), dimension(:,:), intent(in) :: & - p_lay, & ! Pressure @ model layer-centers (Pa) - t_lay, & ! Temperature (K) - p_lev, & ! Pressure @ model layer-interfaces (Pa) - t_lev, & ! Temperature @ model levels (K) - vmr_o2, & ! Molar-mixing ratio oxygen - vmr_h2o, & ! Molar-mixing ratio water vapor - vmr_o3, & ! Molar-mixing ratio ozone - vmr_ch4, & ! Molar-mixing ratio methane - vmr_n2o, & ! Molar-mixing ratio nitrous oxide - vmr_co2, & ! Molar-mixing ratio carbon dioxide - cld_frac, & ! Cloud-fraction for stratiform clouds - cld_lwp, & ! Water path for stratiform liquid cloud-particles - cld_reliq, & ! Effective radius for stratiform liquid cloud-particles - cld_iwp, & ! Water path for stratiform ice cloud-particles - cld_reice, & ! Effective radius for stratiform ice cloud-particles - cld_swp, & ! Water path for snow hydrometeors - cld_resnow, & ! Effective radius for snow hydrometeors - cld_rwp, & ! Water path for rain hydrometeors - cld_rerain, & ! Effective radius for rain hydrometeors - precip_frac, & ! Precipitation fraction - cld_cnv_lwp, & ! Water path for convective liquid cloud-particles - cld_cnv_reliq, & ! Effective radius for convective liquid cloud-particles - cld_cnv_iwp, & ! Water path for convective ice cloud-particles - cld_cnv_reice, & ! Effective radius for convective ice cloud-particles - cld_pbl_lwp, & ! Water path for PBL liquid cloud-particles - cld_pbl_reliq, & ! Effective radius for PBL liquid cloud-particles - cld_pbl_iwp, & ! Water path for PBL ice cloud-particles - cld_pbl_reice, & ! Effective radius for PBL ice cloud-particles - cloud_overlap_param ! + p_lay, & !< Pressure @ model layer-centers (Pa) + t_lay, & !< Temperature (K) + p_lev, & !< Pressure @ model layer-interfaces (Pa) + t_lev, & !< Temperature @ model levels (K) + vmr_o2, & !< Molar-mixing ratio oxygen + vmr_h2o, & !< Molar-mixing ratio water vapor + vmr_o3, & !< Molar-mixing ratio ozone + vmr_ch4, & !< Molar-mixing ratio methane + vmr_n2o, & !< Molar-mixing ratio nitrous oxide + vmr_co2, & !< Molar-mixing ratio carbon dioxide + cld_frac, & !< Cloud-fraction for stratiform clouds + cld_lwp, & !< Water path for stratiform liquid cloud-particles + cld_reliq, & !< Effective radius for stratiform liquid cloud-particles + cld_iwp, & !< Water path for stratiform ice cloud-particles + cld_reice, & !< Effective radius for stratiform ice cloud-particles + cld_swp, & !< Water path for snow hydrometeors + cld_resnow, & !< Effective radius for snow hydrometeors + cld_rwp, & !< Water path for rain hydrometeors + cld_rerain, & !< Effective radius for rain hydrometeors + precip_frac, & !< Precipitation fraction + cld_cnv_lwp, & !< Water path for convective liquid cloud-particles + cld_cnv_reliq, & !< Effective radius for convective liquid cloud-particles + cld_cnv_iwp, & !< Water path for convective ice cloud-particles + cld_cnv_reice, & !< Effective radius for convective ice cloud-particles + cld_pbl_lwp, & !< Water path for PBL liquid cloud-particles + cld_pbl_reliq, & !< Effective radius for PBL liquid cloud-particles + cld_pbl_iwp, & !< Water path for PBL ice cloud-particles + cld_pbl_reice, & !< Effective radius for PBL ice cloud-particles + cloud_overlap_param !< real(kind_phys), dimension(:,:,:), intent(in) :: & - aersw_tau, & ! Aerosol optical depth - aersw_ssa, & ! Aerosol single scattering albedo - aersw_g ! Aerosol asymmetry paramter + aersw_tau, & !< Aerosol optical depth + aersw_ssa, & !< Aerosol single scattering albedo + aersw_g !< Aerosol asymmetry paramter character(len=*), dimension(:), intent(in) :: & - active_gases_array ! List of active gases from namelist as array + active_gases_array !< List of active gases from namelist as array real(kind_phys), intent(in) :: & - solcon ! Solar constant + solcon !< Solar constant ! Outputs character(len=*), intent(out) :: & - errmsg ! CCPP error message + errmsg !< CCPP error message integer, intent(out) :: & - errflg ! CCPP error flag + errflg !< CCPP error flag real(kind_phys), dimension(:,:), intent(inout) :: & - cldtausw ! Approx 10.mu band layer cloud optical depth + cldtausw !< Approx 10.mu band layer cloud optical depth real(kind_phys), dimension(:,:), intent(inout) :: & - fluxswUP_allsky, & ! RRTMGP upward all-sky flux profiles (W/m2) - fluxswDOWN_allsky, & ! RRTMGP downward all-sky flux profiles (W/m2) - fluxswUP_clrsky, & ! RRTMGP upward clear-sky flux profiles (W/m2) - fluxswDOWN_clrsky ! RRTMGP downward clear-sky flux profiles (W/m2) + fluxswUP_allsky, & !< RRTMGP upward all-sky flux profiles (W/m2) + fluxswDOWN_allsky, & !< RRTMGP downward all-sky flux profiles (W/m2) + fluxswUP_clrsky, & !< RRTMGP upward clear-sky flux profiles (W/m2) + fluxswDOWN_clrsky !< RRTMGP downward clear-sky flux profiles (W/m2) type(cmpfsw_type), dimension(:), intent(inout) :: & - scmpsw ! 2D surface fluxes, components: - ! uvbfc - total sky downward uv-b flux (W/m2) - ! uvbf0 - clear sky downward uv-b flux (W/m2) - ! nirbm - downward nir direct beam flux (W/m2) - ! nirdf - downward nir diffused flux (W/m2) - ! visbm - downward uv+vis direct beam flux (W/m2) - ! visdf - downward uv+vis diffused flux (W/m2) + scmpsw !< 2D surface fluxes, components: + !< uvbfc - total sky downward uv-b flux (W/m2) + !< uvbf0 - clear sky downward uv-b flux (W/m2) + !< nirbm - downward nir direct beam flux (W/m2) + !< nirdf - downward nir diffused flux (W/m2) + !< visbm - downward uv+vis direct beam flux (W/m2) + !< visdf - downward uv+vis diffused flux (W/m2) ! Local variables type(cmpfsw_type), dimension(rrtmgp_phys_blksz) :: scmpsw_clrsky, scmpsw_allsky diff --git a/physics/docs/_doxygen/custom.css b/physics/docs/_doxygen/custom.css new file mode 100644 index 000000000..ad6f35a52 --- /dev/null +++ b/physics/docs/_doxygen/custom.css @@ -0,0 +1,57 @@ +.github-corner svg { + fill: var(--primary-light-color); + color: var(--page-background-color); + width: 72px; + height: 72px; +} + +@media screen and (max-width: 767px) { + .github-corner svg { + width: 50px; + height: 50px; + } + #projectnumber { + margin-right: 22px; + } +} + +.alter-theme-button { + display: inline-block; + cursor: pointer; + background: var(--primary-color); + color: var(--page-background-color) !important; + border-radius: var(--border-radius-medium); + padding: var(--spacing-small) var(--spacing-medium); + text-decoration: none; +} + +.alter-theme-button:hover { + background: var(--primary-dark-color); +} + +html.dark-mode .darkmode_inverted_image img, /* < doxygen 1.9.3 */ +html.dark-mode .darkmode_inverted_image object[type="image/svg+xml"] /* doxygen 1.9.3 */ { + filter: brightness(89%) hue-rotate(180deg) invert(); +} + +.bordered_image { + border-radius: var(--border-radius-small); + border: 1px solid var(--separator-color); + display: inline-block; + overflow: hidden; +} + +html.dark-mode .bordered_image img, /* < doxygen 1.9.3 */ +html.dark-mode .bordered_image object[type="image/svg+xml"] /* doxygen 1.9.3 */ { + border-radius: var(--border-radius-small); +} + +.title_screenshot { + filter: drop-shadow(0px 3px 10px rgba(0,0,0,0.22)); + max-width: 500px; + margin: var(--spacing-large) 0; +} + +.title_screenshot .caption { + display: none; +} diff --git a/physics/docs/_doxygen/doxygen-awesome.css b/physics/docs/_doxygen/doxygen-awesome.css index 217fdedfc..5643749c2 100644 --- a/physics/docs/_doxygen/doxygen-awesome.css +++ b/physics/docs/_doxygen/doxygen-awesome.css @@ -894,7 +894,7 @@ div.contents p, div.contents li { } div.contents div.dyncontent { - margin: var(--spacing-medium) 0; + margin: var(--spacing-medium) 0; overflow-x: scroll; } @media (prefers-color-scheme: dark) { diff --git a/physics/docs/_doxygen/header.html b/physics/docs/_doxygen/header.html index 2e72051ea..8896efc85 100644 --- a/physics/docs/_doxygen/header.html +++ b/physics/docs/_doxygen/header.html @@ -1,22 +1,38 @@ - - +
+ + + + + + + + +