diff --git a/physics/CONV/Grell_Freitas/cu_gf_deep.F90 b/physics/CONV/Grell_Freitas/cu_gf_deep.F90 index 0f324244a..34960f037 100644 --- a/physics/CONV/Grell_Freitas/cu_gf_deep.F90 +++ b/physics/CONV/Grell_Freitas/cu_gf_deep.F90 @@ -1,6 +1,7 @@ !>\file cu_gf_deep.F90 !! This file is the Grell-Freitas deep convection scheme. +!> This module contains the Grell_Freitas deep convection scheme module cu_gf_deep use machine , only : kind_phys use physcons, only : qamin diff --git a/physics/CONV/Grell_Freitas/cu_gf_driver.F90 b/physics/CONV/Grell_Freitas/cu_gf_driver.F90 index df5a196b1..e14e3786d 100644 --- a/physics/CONV/Grell_Freitas/cu_gf_driver.F90 +++ b/physics/CONV/Grell_Freitas/cu_gf_driver.F90 @@ -1,7 +1,7 @@ !>\file cu_gf_driver.F90 !! This file is scale-aware Grell-Freitas cumulus scheme driver. - +!> This module contains the scale-aware Grell-Freitas cumulus scheme driver. module cu_gf_driver ! DH* TODO: replace constants with arguments to cu_gf_driver_run diff --git a/physics/CONV/Grell_Freitas/cu_gf_driver_post.F90 b/physics/CONV/Grell_Freitas/cu_gf_driver_post.F90 index 02bb3cb84..8380e2dae 100644 --- a/physics/CONV/Grell_Freitas/cu_gf_driver_post.F90 +++ b/physics/CONV/Grell_Freitas/cu_gf_driver_post.F90 @@ -1,6 +1,7 @@ !> \file cu_gf_driver_post.F90 !! Contains code related to GF convective schemes to be used within the GFS physics suite. +!> This module contains code related to GF convective schemes to be used within the GFS physics suite module cu_gf_driver_post implicit none diff --git a/physics/CONV/Grell_Freitas/cu_gf_driver_pre.F90 b/physics/CONV/Grell_Freitas/cu_gf_driver_pre.F90 index 1bc9aed34..1266d7a62 100644 --- a/physics/CONV/Grell_Freitas/cu_gf_driver_pre.F90 +++ b/physics/CONV/Grell_Freitas/cu_gf_driver_pre.F90 @@ -1,6 +1,7 @@ !> \file cu_gf_driver_pre.F90 !! Contains code related to GF convective schemes to be used within the GFS physics suite. +!> This module contains code related to GF convective schemes to be used within the GFS physics suite. module cu_gf_driver_pre implicit none diff --git a/physics/CONV/Grell_Freitas/cu_gf_sh.F90 b/physics/CONV/Grell_Freitas/cu_gf_sh.F90 index 9af9567ad..527b662e5 100644 --- a/physics/CONV/Grell_Freitas/cu_gf_sh.F90 +++ b/physics/CONV/Grell_Freitas/cu_gf_sh.F90 @@ -1,6 +1,7 @@ !>\file cu_gf_sh.F90 !! This file contains Grell-Freitas shallow convection scheme. +!> This module contains the Grell-Freitas shallow convection scheme module cu_gf_sh use machine , only : kind_phys !real(kind=kind_phys), parameter:: c1_shal=0.0015! .0005 diff --git a/physics/CONV/SAMF/samfaerosols.F b/physics/CONV/SAMF/samfaerosols.F index 66faf1fb9..ade8f1b5a 100644 --- a/physics/CONV/SAMF/samfaerosols.F +++ b/physics/CONV/SAMF/samfaerosols.F @@ -1,3 +1,5 @@ +!>\file samfaerosols.F +!! module samfcnv_aerosols implicit none diff --git a/physics/CONV/SAMF/samfshalcnv.f b/physics/CONV/SAMF/samfshalcnv.f index f720c4701..184f302cd 100644 --- a/physics/CONV/SAMF/samfshalcnv.f +++ b/physics/CONV/SAMF/samfshalcnv.f @@ -1,6 +1,7 @@ !> \file samfshalcnv.f -!! This file contains the Scale-Aware mass flux Shallow Convection scheme. +!! +!> This module contains the Scale-Aware mass flux Shallow Convection scheme. module samfshalcnv use samfcnv_aerosols, only : samfshalcnv_aerosols diff --git a/physics/CONV/SAS/shalcnv.F b/physics/CONV/SAS/shalcnv.F index 3224ed125..d8753cba6 100644 --- a/physics/CONV/SAS/shalcnv.F +++ b/physics/CONV/SAS/shalcnv.F @@ -1,16 +1,12 @@ -!> \defgroup SASHAL Mass-Flux Shallow Convection -!! @{ -!! \brief The Mass-Flux shallow convection scheme parameterizes the effect of shallow convection on the environment much like the \ref SAS scheme with a few key modifications. Perhaps most importantly, no quasi-equilibrium assumption is necessary since the shallow cloud base mass flux is parameterized from the surface buoyancy flux. Further, there are no convective downdrafts, the entrainment rate is greater than for deep convection, and the shallow convection is limited to not extend over the level where \f$p=0.7p_{sfc}\f$. +!> \file shalcnv.F +!! Contains the entire SAS shallow convection scheme. + +!> \brief The Mass-Flux shallow convection scheme parameterizes the effect of shallow convection on the environment much like the \ref SAS scheme with a few key modifications. Perhaps most importantly, no quasi-equilibrium assumption is necessary since the shallow cloud base mass flux is parameterized from the surface buoyancy flux. Further, there are no convective downdrafts, the entrainment rate is greater than for deep convection, and the shallow convection is limited to not extend over the level where \f$p=0.7p_{sfc}\f$. !! !! This scheme was designed to replace the previous eddy-diffusivity approach to shallow convection with a mass-flux based approach as it is used for deep convection. Differences between the shallow and deep SAS schemes are presented in Han and Pan (2011) \cite han_and_pan_2011 . Like the deep scheme, it uses the working concepts put forth in Arakawa and Schubert (1974) \cite arakawa_and_schubert_1974 but includes modifications and simplifications from Grell (1993) \cite grell_1993 such as only one cloud type (the deepest possible, up to \f$p=0.7p_{sfc}\f$), rather than a spectrum based on cloud top heights or assumed entrainment rates, although it assumes no convective downdrafts. It contains many modifications associated with deep scheme as discussed in Han and Pan (2011) \cite han_and_pan_2011 , including the calculation of cloud top, a greater CFL-criterion-based maximum cloud base mass flux, and the inclusion of convective overshooting. !! -!! \section diagram Calling Hierarchy Diagram +!! \section diagram_sashal Calling Hierarchy Diagram !! \image html Shallow_SAS_Flowchart.png "Diagram depicting how the SAS shallow convection scheme is called from the GSM physics time loop" height=2cm -!! \section intraphysics Intraphysics Communication -!! This space is reserved for a description of how this scheme uses information from other scheme types and/or how information calculated in this scheme is used in other scheme types. - -!> \file shalcnv.F -!! Contains the entire SAS shallow convection scheme. module shalcnv implicit none @@ -80,17 +76,17 @@ end subroutine shalcnv_init !! \param[out] cnvw convective cloud water (kg/kg) !! \param[out] cnvc convective cloud cover (unitless) !! -!! \section general General Algorithm +!! \section general_shalcnv General Algorithm !! -# Compute preliminary quantities needed for the static and feedback control portions of the algorithm. !! -# Perform calculations related to the updraft of the entraining/detraining cloud model ("static control"). !! -# Calculate the tendencies of the state variables (per unit cloud base mass flux) and the cloud base mass flux. !! -# For the "feedback control", calculate updated values of the state variables by multiplying the cloud base mass flux and the tendencies calculated per unit cloud base mass flux from the static control. -!! \section detailed Detailed Algorithm +!! \section detailed_shalcnv Detailed Algorithm !! !! \section arg_table_shalcnv_run Argument Table !! \htmlinclude shalcnv_run.html !! -!! @{ +!> @{ subroutine shalcnv_run( & & grav,cp,hvap,rv,fv,t0c,rd,cvap,cliq,eps,epsm1, & & im,km,jcap,delt,delp,prslp,psp,phil,qlc,qli, & @@ -1341,4 +1337,3 @@ end subroutine shalcnv_run end module shalcnv !> @} -!! @} diff --git a/physics/CONV/progsigma_calc.f90 b/physics/CONV/progsigma_calc.f90 index 469df49f6..9da238429 100644 --- a/physics/CONV/progsigma_calc.f90 +++ b/physics/CONV/progsigma_calc.f90 @@ -1,3 +1,9 @@ +!>\file progsigma_calc.f90 + +!> This module contains the subroutine that calculates the prognostic +!! updraft area fraction that is used for closure computations in +!! saSAS deep and shallow convection, based on a moisture budget +!! as described in Bengtsson et al. 2022 \cite Bengtsson_2022. module progsigma implicit none @@ -6,14 +12,6 @@ module progsigma contains -!>\file progsigma_calc.f90 -!! This file contains the subroutine that calculates the prognostic -!! updraft area fraction that is used for closure computations in -!! saSAS deep and shallow convection, based on a moisture budget -!! as described in Bengtsson et al. 2022 \cite Bengtsson_2022. - -!>\ingroup SAMFdeep -!>\ingroup SAMF_shal !> This subroutine computes a prognostic updraft area fraction !! used in the closure computations in the samfdeepcnv.f scheme !! This subroutine computes a prognostic updraft area fracftion diff --git a/physics/GWD/cires_orowam2017.f b/physics/GWD/cires_orowam2017.f index 9f04ac3b0..8f9599f24 100644 --- a/physics/GWD/cires_orowam2017.f +++ b/physics/GWD/cires_orowam2017.f @@ -1,12 +1,12 @@ !>\file cires_orowam2017.f +!! - +!> This module includes the OROGW solver of WAM2017. module cires_orowam2017 contains !>\defgroup cires_orowam2017_mod CIRES UGWP orowam2017 Module !>This is the OROGW-solver of WAM2017. -!>@{ !> subroutine oro_wam_2017(im, levs,npt,ipt, kref,kdt,me,master, @@ -394,4 +394,3 @@ subroutine ugwpv0_tofd1d(levs, sigflt, elvmax, zsurf, ! end subroutine ugwpv0_tofd1d end module cires_orowam2017 -!>@} diff --git a/physics/GWD/cires_tauamf_data.F90 b/physics/GWD/cires_tauamf_data.F90 index 4f12b2ec1..364c79409 100644 --- a/physics/GWD/cires_tauamf_data.F90 +++ b/physics/GWD/cires_tauamf_data.F90 @@ -1,3 +1,6 @@ +!>\file cires_tauamf_data.F90 +!! + module cires_tauamf_data use machine, only: kind_phys @@ -16,6 +19,7 @@ module cires_tauamf_data contains +!> subroutine read_tau_amf(me, master, errmsg, errflg) use netcdf @@ -70,6 +74,7 @@ subroutine read_tau_amf(me, master, errmsg, errflg) end subroutine read_tau_amf +!> subroutine cires_indx_ugwp (npts, me, master, dlat,j1_tau,j2_tau, w1_j1tau, w2_j2tau) use machine, only: kind_phys @@ -110,6 +115,7 @@ subroutine cires_indx_ugwp (npts, me, master, dlat,j1_tau,j2_tau, w1_j1tau, w2_j return end subroutine cires_indx_ugwp +!> subroutine tau_amf_interp(me, master, im, idate, fhour, j1_tau,j2_tau, ddy_j1, ddy_j2, tau_ddd) use machine, only: kind_phys implicit none @@ -163,6 +169,7 @@ subroutine tau_amf_interp(me, master, im, idate, fhour, j1_tau,j2_tau, ddy_j1, d end subroutine tau_amf_interp +!> subroutine gfs_idate_calendar(idate, fhour, ddd, fddd) use machine, only: kind_phys diff --git a/physics/GWD/cires_ugwp.F90 b/physics/GWD/cires_ugwp.F90 index cab602252..beb7dbbc7 100644 --- a/physics/GWD/cires_ugwp.F90 +++ b/physics/GWD/cires_ugwp.F90 @@ -1,16 +1,17 @@ !> \file cires_ugwp.F90 !! This file contains the Unified Gravity Wave Physics (UGWP) scheme by Valery Yudin (University of Colorado, CIRES) + +!> This module contains the UGWP v0 scheme by Valery Yudin (University of Colorado, CIRES) +!! !! See Valery Yudin's presentation at 2017 NGGPS PI meeting: !! Gravity waves (GWs): Mesoscale GWs transport momentum, energy (heat) , and create eddy mixing in the whole atmosphere domain; Breaking and dissipating GWs deposit: (a) momentum; (b) heat (energy); and create (c) turbulent mixing of momentum, heat, and tracers !! To properly incorporate GW effects (a-c) unresolved by DYCOREs we need GW physics !! "Unified": a) all GW effects due to both dissipation/breaking; b) identical GW solvers for all GW sources; c) ability to replace solvers. !! Unified Formalism: -!! 1. GW Sources: Stochastic and physics based mechanisms for GW-excitations in the lower atmosphere, calibrated by the high-res analyses/forecasts, and observations (3 types of GW sources: orography, convection, fronts/jets). -!! 2. GW Propagation: Unified solver for "propagation, dissipation and breaking" excited from all type of GW sources. -!! 3. GW Effects: Unified representation of GW impacts on the "resolved" flow for all sources (energy-balanced schemes for momentum, heat and mixing). +!! - GW Sources: Stochastic and physics based mechanisms for GW-excitations in the lower atmosphere, calibrated by the high-res analyses/forecasts, and observations (3 types of GW sources: orography, convection, fronts/jets). +!! - GW Propagation: Unified solver for "propagation, dissipation and breaking" excited from all type of GW sources. +!! - GW Effects: Unified representation of GW impacts on the "resolved" flow for all sources (energy-balanced schemes for momentum, heat and mixing). !! https://www.weather.gov/media/sti/nggps/Presentations%202017/02%20NGGPS_VYUDIN_2017_.pdf - - module cires_ugwp use machine, only: kind_phys @@ -33,9 +34,7 @@ module cires_ugwp ! ------------------------------------------------------------------------ ! CCPP entry points for CIRES Unified Gravity Wave Physics (UGWP) scheme v0 ! ------------------------------------------------------------------------ -!>\defgroup cires_ugwp_run_mod CIRES Unified Gravity Wave Physics v0 Module -!> @{ -!>@ The subroutine initializes the CIRES UGWP V0. +!> The subroutine initializes the CIRES UGWP V0. !> \section arg_table_cires_ugwp_init Argument Table !! \htmlinclude cires_ugwp_init.html !! @@ -112,7 +111,7 @@ end subroutine cires_ugwp_init ! finalize of cires_ugwp (_finalize) ! ----------------------------------------------------------------------- -!>@brief The subroutine finalizes the CIRES UGWP +!> The subroutine finalizes the CIRES UGWP #if 0 !> \section arg_table_cires_ugwp_finalize Argument Table !! \htmlinclude cires_ugwp_finalize.html @@ -445,5 +444,4 @@ subroutine cires_ugwp_run(do_ugwp, me, master, im, levs, ntrac, dtp, kdt, lonr endif end subroutine cires_ugwp_run -!> @} end module cires_ugwp diff --git a/physics/GWD/cires_ugwp_initialize.F90 b/physics/GWD/cires_ugwp_initialize.F90 index ddcbdadf7..ae923671d 100644 --- a/physics/GWD/cires_ugwp_initialize.F90 +++ b/physics/GWD/cires_ugwp_initialize.F90 @@ -6,7 +6,7 @@ ! init gw-background dissipation !=============================== -!> Define constants +!> This module contains UGWP v0 initialization schemes module ugwp_common_v0 ! use machine, only: kind_phys @@ -95,6 +95,7 @@ end subroutine init_global_gwdis_v0 ! ugwpv0_oro_init ! !========================================================================= +!> This module contains orographic wave source schemes for UGWP v0. module ugwpv0_oro_init use ugwp_common_v0, only : bnv2min, grav, grcp, fv, grav, cpd, grcp, pi @@ -225,6 +226,7 @@ end module ugwpv0_oro_init ! Part -3 init wave solvers !=============================== +!> This module contains initialization of wave solvers for UGWP v0 module ugwpv0_lsatdis_init implicit none @@ -270,6 +272,7 @@ end subroutine initsolv_lsatdis_v0 end module ugwpv0_lsatdis_init ! ! +!>This module contains init-solvers for "broad" non-stationary multi-wave spectra module ugwpv0_wmsdis_init use ugwp_common_v0, only : pi, pi2 diff --git a/physics/GWD/cires_ugwp_module.F90 b/physics/GWD/cires_ugwp_module.F90 index 3b3ce3114..a454a5eae 100644 --- a/physics/GWD/cires_ugwp_module.F90 +++ b/physics/GWD/cires_ugwp_module.F90 @@ -1,5 +1,7 @@ !>\file cires_ugwp_module.F90 +!! +!>This module contains the UGWPv0 driver module cires_ugwpv0_module ! @@ -9,8 +11,8 @@ module cires_ugwpv0_module implicit none logical :: module_is_initialized - logical :: do_physb_gwsrcs = .false. ! control for physics-based GW-sources - logical :: do_rfdamp = .false. ! control for Rayleigh friction inside ugwp_driver + logical :: do_physb_gwsrcs = .false. !< control for physics-based GW-sources + logical :: do_rfdamp = .false. !< control for Rayleigh friction inside ugwp_driver real, parameter :: arad=6370.e3 real, parameter :: pi = atan(1.0) @@ -18,24 +20,24 @@ module cires_ugwpv0_module real, parameter :: hps = 7000. real, parameter :: hpskm = hps/1000. ! - real :: kxw = 6.28e-3/100. ! single horizontal wavenumber of ugwp schemes + real :: kxw = 6.28e-3/100. !< single horizontal wavenumber of ugwp schemes real, parameter :: ricrit = 0.25 real, parameter :: frcrit = 0.50 real, parameter :: linsat = 1.00 real, parameter :: linsat2 = linsat*linsat ! - integer :: knob_ugwp_solver=1 ! 1, 2, 3, 4 - (linsat, ifs_2010, ad_gfdl, dsp_dis) - integer, dimension(4) :: knob_ugwp_source ! [1,1,1,0] - (oro, fronts, conv, imbf-owp] - integer, dimension(4) :: knob_ugwp_wvspec ! number of waves for- (oro, fronts, conv, imbf-owp] - integer, dimension(4) :: knob_ugwp_azdir ! number of wave azimuths for- (oro, fronts, conv, imbf-owp] - integer, dimension(4) :: knob_ugwp_stoch ! 1 - deterministic ; 0 - stochastic - real, dimension(4) :: knob_ugwp_effac ! efficiency factors for- (oro, fronts, conv, imbf-owp] + integer :: knob_ugwp_solver=1 !< 1, 2, 3, 4 - (linsat, ifs_2010, ad_gfdl, dsp_dis) + integer, dimension(4) :: knob_ugwp_source !< [1,1,1,0] - (oro, fronts, conv, imbf-owp] + integer, dimension(4) :: knob_ugwp_wvspec !< number of waves for- (oro, fronts, conv, imbf-owp] + integer, dimension(4) :: knob_ugwp_azdir !< number of wave azimuths for- (oro, fronts, conv, imbf-owp] + integer, dimension(4) :: knob_ugwp_stoch !< 1 - deterministic ; 0 - stochastic + real, dimension(4) :: knob_ugwp_effac !< efficiency factors for- (oro, fronts, conv, imbf-owp] - integer :: knob_ugwp_doaxyz=1 ! 1 -gwdrag - integer :: knob_ugwp_doheat=1 ! 1 -gwheat - integer :: knob_ugwp_dokdis=0 ! 1 -gwmixing - integer :: knob_ugwp_ndx4lh = 2 ! n-number of "unresolved" "n*dx" for lh_gw + integer :: knob_ugwp_doaxyz=1 !< 1 -gwdrag + integer :: knob_ugwp_doheat=1 !< 1 -gwheat + integer :: knob_ugwp_dokdis=0 !< 1 -gwmixing + integer :: knob_ugwp_ndx4lh = 2 !< n-number of "unresolved" "n*dx" for lh_gw ! integer :: ugwp_azdir integer :: ugwp_stoch @@ -45,12 +47,12 @@ module cires_ugwpv0_module real :: ugwp_effac ! - data knob_ugwp_source / 1,0, 1, 0 / ! oro-conv-fjet-okw-taub_lat: 1-active 0-off - data knob_ugwp_wvspec /1,32,32,32/ ! number of waves for- (oro, fronts, conv, imbf-owp, taulat] - data knob_ugwp_azdir /2, 4, 4,4/ ! number of wave azimuths for- (oro, fronts, conv, imbf-okwp] - data knob_ugwp_stoch /0, 0, 0,0/ ! 0 - deterministic ; 1 - stochastic, non-activated option - data knob_ugwp_effac /1.,1.,1.,1./ ! efficiency factors for- (oro, fronts, conv, imbf-owp] - integer :: knob_ugwp_version = 0 ! version control had sense under IPD in CCPP=> to SUITES + data knob_ugwp_source / 1,0, 1, 0 / !< oro-conv-fjet-okw-taub_lat: 1-active 0-off + data knob_ugwp_wvspec /1,32,32,32/ !< number of waves for- (oro, fronts, conv, imbf-owp, taulat] + data knob_ugwp_azdir /2, 4, 4,4/ !< number of wave azimuths for- (oro, fronts, conv, imbf-okwp] + data knob_ugwp_stoch /0, 0, 0,0/ !< 0 - deterministic ; 1 - stochastic, non-activated option + data knob_ugwp_effac /1.,1.,1.,1./ !< efficiency factors for- (oro, fronts, conv, imbf-owp] + integer :: knob_ugwp_version = 0 !< version control had sense under IPD in CCPP=> to SUITES integer :: launch_level = 55 ! namelist /cires_ugwp_nml/ knob_ugwp_solver, knob_ugwp_source,knob_ugwp_wvspec, knob_ugwp_azdir, & diff --git a/physics/GWD/cires_ugwp_post.F90 b/physics/GWD/cires_ugwp_post.F90 index 3efb2b7e8..2ae20ac84 100644 --- a/physics/GWD/cires_ugwp_post.F90 +++ b/physics/GWD/cires_ugwp_post.F90 @@ -1,6 +1,7 @@ !> \file cires_ugwp_post.F90 -!! This file contains +!! This file contains the calcualtion of the UGWP v0 diagnostics +!> This module contains the calculation of the UGWP v0 diagnostics (ldiag_ugwp) module cires_ugwp_post contains diff --git a/physics/GWD/cires_ugwp_triggers.F90 b/physics/GWD/cires_ugwp_triggers.F90 index ba7483eca..95cb79684 100644 --- a/physics/GWD/cires_ugwp_triggers.F90 +++ b/physics/GWD/cires_ugwp_triggers.F90 @@ -1,10 +1,13 @@ !>\file cires_ugwp_triggers.F90 !! +!> This module contains routines describing the the latitudinal shape of +!! vertical momentum flux function in UGWP v0. module cires_ugwp_triggers contains ! +!> subroutine slat_geos5_tamp_v0(im, tau_amp, xlatdeg, tau_gw) !================= ! GEOS-5 & MERRA-2 lat-dependent GW-source function tau(z=Zlaunch) =rho* @@ -38,6 +41,7 @@ subroutine slat_geos5_tamp_v0(im, tau_amp, xlatdeg, tau_gw) ! end subroutine slat_geos5_tamp_v0 +!> subroutine slat_geos5_v0(im, xlatdeg, tau_gw) !================= ! GEOS-5 & MERRA-2 lat-dependent GW-source function tau(z=Zlaunch) =rho* @@ -76,7 +80,8 @@ subroutine slat_geos5_v0(im, xlatdeg, tau_gw) enddo ! end subroutine slat_geos5_v0 -! + +!> subroutine init_nazdir_v0(naz, xaz, yaz) use ugwp_common_v0 , only : pi2 implicit none diff --git a/physics/GWD/cires_ugwpv1_initialize.F90 b/physics/GWD/cires_ugwpv1_initialize.F90 index aa54a46f3..65c96cf0d 100644 --- a/physics/GWD/cires_ugwpv1_initialize.F90 +++ b/physics/GWD/cires_ugwpv1_initialize.F90 @@ -12,7 +12,7 @@ ! Part-0 specifications of common constants, limiters and "criiical" values ! ! - +!> This module contains common constants, limiters and "critical" values in module ugwp_common ! use machine, only : kind_phys diff --git a/physics/GWD/drag_suite.F90 b/physics/GWD/drag_suite.F90 index 5c2bf6c2c..e78f2924a 100644 --- a/physics/GWD/drag_suite.F90 +++ b/physics/GWD/drag_suite.F90 @@ -1,17 +1,12 @@ !> \file drag_suite.F90 -!! This file is the parameterization of orographic gravity wave +!! This file is the parameterization of orographic drag !! drag, mountain blocking, and form drag. +!> This module contains the orographic drag scheme module drag_suite contains -!> \defgroup gfs_drag_suite_mod GSL drag_suite Module -!> This module contains the CCPP-compliant GSL orographic gravity wave drag scheme. -!> @{ -!! -!> \brief This subroutine initializes the orographic gravity wave drag scheme. -!! !> \section arg_table_drag_suite_init Argument Table !! \htmlinclude drag_suite_init.html !! @@ -35,7 +30,7 @@ subroutine drag_suite_init(gwd_opt, errmsg, errflg) end if end subroutine drag_suite_init -!> \brief This subroutine includes orographic gravity wave drag, mountain +!> This subroutine includes orographic drag, mountain !! blocking, and form drag. !! !> The time tendencies of zonal and meridional wind are altered to @@ -46,7 +41,7 @@ end subroutine drag_suite_init !> \section arg_table_drag_suite_run Argument Table !! \htmlinclude drag_suite_run.html !! -!> \section gen_drag_suite GFS Orographic GWD Scheme General Algorithm +!> \section gen_drag_suite Orographic drag Scheme General Algorithm !! -# Calculate subgrid mountain blocking !! -# Calculate orographic wave drag !! diff --git a/physics/GWD/ugwp_driver_v0.F b/physics/GWD/ugwp_driver_v0.F index 0f4ad447e..1bbb2770d 100644 --- a/physics/GWD/ugwp_driver_v0.F +++ b/physics/GWD/ugwp_driver_v0.F @@ -1,4 +1,6 @@ !>\file ugwp_driver_v0.F + +!> This module contains the UGWP v0 driver module module ugwp_driver_v0 use cires_orowam2017 contains @@ -9,7 +11,7 @@ module ugwp_driver_v0 ! !===================================================================== !>\ingroup cires_ugwp_run_mod -!>\defgroup ugwp_driverv0_mod GFS UGWP V0 Driver Module +!>\defgroup ugwp_driverv0_mod UGWP V0 Driver Module !! This is the CIRES UGWP V0 driver module !! !! Note for the sub-grid scale orography scheme in UGWP-v0: Due to degraded forecast diff --git a/physics/GWD/ugwpv1_gsldrag.F90 b/physics/GWD/ugwpv1_gsldrag.F90 index fc90955bd..5dd76b8d1 100644 --- a/physics/GWD/ugwpv1_gsldrag.F90 +++ b/physics/GWD/ugwpv1_gsldrag.F90 @@ -1,5 +1,7 @@ !> \file ugwpv1_gsldrag.F90 -!! This introduces two gravity wave drag schemes ugwpv1/CIRES and GSL/drag_suite.F90 under "ugwpv1_gsldrag" suite: + +!> This module introduces two gravity wave drag schemes: UGWPv1 and orographic drag scheme +!! !! 1) The "V1 CIRES UGWP" scheme as tested in the FV3GFSv16-127L atmosphere model and workflow, which includes: !! a) the orograhic gravity wave drag, flow blocking scheme and TOFD (Beljaars et al, 2004). !! b) the v1 CIRE ugwp non-stationary GW scheme, new revision that generate realistic climate of FV3GFS-127L @@ -33,7 +35,6 @@ !! do_ugwp_v1_w_gsldrag -- activates V1 CIRES UGWP scheme with orographic drag of GSL !! Note that only one "large-scale" scheme can be activated at a time. !! - module ugwpv1_gsldrag use machine, only: kind_phys @@ -63,8 +64,6 @@ module ugwpv1_gsldrag !> \section arg_table_ugwpv1_gsldrag_init Argument Table !! \htmlinclude ugwpv1_gsldrag_init.html !! -! ----------------------------------------------------------------------- -! subroutine ugwpv1_gsldrag_init ( & me, master, nlunit, input_nml_file, logunit, & fn_nml2, jdat, lonr, latr, levs, ak, bk, dtp, & @@ -291,18 +290,14 @@ end subroutine ugwpv1_gsldrag_finalize ! ----------------------------------------------------------------------- ! order = dry-adj=>conv=mp-aero=>radiation -sfc/land- chem -> vertdiff-> [rf-gws]=> ion-re ! ----------------------------------------------------------------------- -!>@brief These subroutines and modules execute the CIRES UGWP Version 0 -!>\defgroup ugwpv1_gsldrag_run Unified Gravity Wave Physics General Algorithm -!> @{ -!! The physics of NGWs in the UGWP framework (Yudin et al. 2018 \cite yudin_et_al_2018) is represented by four GW-solvers, which is introduced in Lindzen (1981) \cite lindzen_1981, Hines (1997) \cite hines_1997, Alexander and Dunkerton (1999) \cite alexander_and_dunkerton_1999, and Scinocca (2003) \cite scinocca_2003. The major modification of these GW solvers is represented by the addition of the background dissipation of temperature and winds to the saturation criteria for wave breaking. This feature is important in the mesosphere and thermosphere for WAM applications and it considers appropriate scale-dependent dissipation of waves near the model top lid providing the momentum and energy conservation in the vertical column physics (Shaw and Shepherd 2009 \cite shaw_and_shepherd_2009). In the UGWP-v0, the modification of Scinocca (2003) \cite scinocca_2003 scheme for NGWs with non-hydrostatic and rotational effects for GW propagations and background dissipation is represented by the subroutine \ref fv3_ugwp_solv2_v0. In the next release of UGWP, additional GW-solvers will be implemented along with physics-based triggering of waves and stochastic approaches for selection of GW modes characterized by horizontal phase velocities, azimuthal directions and magnitude of the vertical momentum flux (VMF). +!>\section gen_ugwpv1_gsldrag_run Unified Gravity Wave Physics General Algorithm +!! The physics of NGWs in the UGWP framework (Yudin et al. 2018 \cite yudin_et_al_2018) is represented by four GW-solvers, which is introduced in Lindzen (1981) \cite lindzen_1981, Hines (1997) \cite hines_1997, Alexander and Dunkerton (1999) \cite alexander_and_dunkerton_1999, and Scinocca (2003) \cite scinocca_2003. The major modification of these GW solvers is represented by the addition of the background dissipation of temperature and winds to the saturation criteria for wave breaking. This feature is important in the mesosphere and thermosphere for WAM applications and it considers appropriate scale-dependent dissipation of waves near the model top lid providing the momentum and energy conservation in the vertical column physics (Shaw and Shepherd 2009 \cite shaw_and_shepherd_2009). In the UGWP-v0, the modification of Scinocca (2003) \cite scinocca_2003 scheme for NGWs with non-hydrostatic and rotational effects for GW propagations and background dissipation is represented by the subroutine fv3_ugwp_solv2_v0. In the next release of UGWP, additional GW-solvers will be implemented along with physics-based triggering of waves and stochastic approaches for selection of GW modes characterized by horizontal phase velocities, azimuthal directions and magnitude of the vertical momentum flux (VMF). !! !! In UGWP-v0, the specification for the VMF function is adopted from the GEOS-5 global atmosphere model of GMAO NASA/GSFC, as described in Molod et al. (2015) \cite molod_et_al_2015 and employed in the MERRRA-2 reanalysis (Gelaro et al., 2017 \cite gelaro_et_al_2017). The Fortran subroutine \ref slat_geos5_tamp describes the latitudinal shape of VMF-function as displayed in Figure 3 of Molod et al. (2015) \cite molod_et_al_2015. It shows that the enhanced values of VMF in the equatorial region gives opportunity to simulate the QBO-like oscillations in the equatorial zonal winds and lead to more realistic simulations of the equatorial dynamics in GEOS-5 operational and MERRA-2 reanalysis products. For the first vertically extended version of FV3GFS in the stratosphere and mesosphere, this simplified function of VMF allows us to tune the model climate and to evaluate multi-year simulations of FV3GFS with the MERRA-2 and ERA-5 reanalysis products, along with temperature, ozone, and water vapor observations of current satellite missions. After delivery of the UGWP-code, the EMC group developed and tested approach to modulate the zonal mean NGW forcing by 3D-distributions of the total precipitation as a proxy for the excitation of NGWs by convection and the vertically-integrated (surface - tropopause) Turbulent Kinetic Energy (TKE). The verification scores with updated NGW forcing, as reported elsewhere by EMC researchers, display noticeable improvements in the forecast scores produced by FV3GFS configuration extended into the mesosphere. !! !> \section arg_table_ugwpv1_gsldrag_run Argument Table !! \htmlinclude ugwpv1_gsldrag_run.html !! -!> \section gen_ugwpv1_gsldrag CIRES UGWP Scheme General Algorithm -!! @{ subroutine ugwpv1_gsldrag_run(me, master, im, levs, ak, bk, ntrac, lonr, dtp, & fhzero, kdt, ldiag3d, lssav, flag_for_gwd_generic_tend, do_gsl_drag_ls_bl, & do_gsl_drag_ss, do_gsl_drag_tofd, & @@ -762,6 +757,4 @@ subroutine ugwpv1_gsldrag_run(me, master, im, levs, ak, bk, ntrac, lonr, dtp, dtdt = dtdt + dtdt_gw end subroutine ugwpv1_gsldrag_run -!! @} -!>@} end module ugwpv1_gsldrag diff --git a/physics/GWD/ugwpv1_gsldrag_post.F90 b/physics/GWD/ugwpv1_gsldrag_post.F90 index 2b1d3e018..c57ce55f5 100644 --- a/physics/GWD/ugwpv1_gsldrag_post.F90 +++ b/physics/GWD/ugwpv1_gsldrag_post.F90 @@ -1,11 +1,11 @@ !> \file ugwpv1_gsldrag_post.F90 -!! This file contains + +!> This module contains code to be executed after the UGWP v1 scheme module ugwpv1_gsldrag_post contains !>\defgroup ugwpv1_gsldrag_post ugwpv1_gsldrag Scheme Post -!! @{ !> \section arg_table_ugwpv1_gsldrag_post_run Argument Table !! \htmlinclude ugwpv1_gsldrag_post_run.html !! @@ -142,5 +142,4 @@ subroutine ugwpv1_gsldrag_post_run ( im, levs, ldiag_ugwp, & !===================================================================== end subroutine ugwpv1_gsldrag_post_run -!! @} end module ugwpv1_gsldrag_post diff --git a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_GWD_generic_pre.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_GWD_generic_pre.F90 index 53dce2b4c..f0d708d5b 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_GWD_generic_pre.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_GWD_generic_pre.F90 @@ -9,7 +9,6 @@ module GFS_GWD_generic_pre !> \section arg_table_GFS_GWD_generic_pre_run Argument Table !! \htmlinclude GFS_GWD_generic_pre_run.html !! -!! \section gfs_gwd_ge_pre_ga General Algorithm subroutine GFS_GWD_generic_pre_run( & & im, levs, nmtvr, mntvar, & & oc, oa4, clx, theta, & diff --git a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_MP_generic_post.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_MP_generic_post.F90 index 108005dc1..129b3203e 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_MP_generic_post.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_MP_generic_post.F90 @@ -8,16 +8,13 @@ module GFS_MP_generic_post contains -!>\defgroup gfs_calpreciptype GFS Precipitation Type Diagnostics Module -!! \brief If dominant precip type is requested (i.e., Zhao-Carr MP scheme), 4 more algorithms in calpreciptype() +!> If dominant precip type is requested (i.e., Zhao-Carr MP scheme), 4 more algorithms in calpreciptype() !! will be called. the tallies are then summed in calwxt_dominant(). For GFDL cloud MP scheme, determine convective !! rain/snow by surface temperature; and determine explicit rain/snow by rain/snow coming out directly from MP. !! !> \section arg_table_GFS_MP_generic_post_run Argument Table !! \htmlinclude GFS_MP_generic_post_run.html !! -!> \section gfs_mp_gen GFS MP Generic Post General Algorithm -!> @{ subroutine GFS_MP_generic_post_run( & im, levs, kdt, nrcm, nncl, ntcw, ntrac, imp_physics, imp_physics_gfdl, imp_physics_thompson, imp_physics_nssl, & imp_physics_mg, imp_physics_fer_hires, cal_pre, cplflx, cplchm, cpllnd, progsigma, con_g, rhowater, rainmin, dtf, & @@ -545,6 +542,5 @@ subroutine GFS_MP_generic_post_run( endif end subroutine GFS_MP_generic_post_run -!> @} end module GFS_MP_generic_post 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 44461c8df..9a5ce6112 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. @@ -17,12 +20,7 @@ module GFS_ccpp_suite_sim_pre public GFS_ccpp_suite_sim_pre_run, load_ccpp_suite_sim contains - ! ###################################################################################### - ! - ! 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 Argument Table !! \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 +108,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/GFS_cloud_diagnostics.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_cloud_diagnostics.F90 index 2fd553c8e..f46b19f5a 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_cloud_diagnostics.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_cloud_diagnostics.F90 @@ -28,7 +28,7 @@ module GFS_cloud_diagnostics !! This was bundled together with the prognostic cloud modules within the RRTMG implementation. !! For the RRTMGP implementation we propose to keep these diagnostics independent. !> @{ -!> \section arg_table_GFS_cloud_diagnostics_run +!> \section arg_table_GFS_cloud_diagnostics_run Argument Table !! \htmlinclude GFS_cloud_diagnostics_run.html !! subroutine GFS_cloud_diagnostics_run(nCol, nLev, iovr, iovr_rand, iovr_maxrand, & diff --git a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_phys_time_vary.scm.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_phys_time_vary.scm.F90 index 49c465971..0b5bbbb3e 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_phys_time_vary.scm.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_phys_time_vary.scm.F90 @@ -238,7 +238,7 @@ subroutine GFS_phys_time_vary_init ( ntrcaer = size(aer_nm, dim=3) endif -!> - Call read_cidata() to read IN and CCN data +!> - Call iccninterp::read_cidata() to read IN and CCN data if (iccn == 1) then call read_cidata (me,master) ! No consistency check needed for in/ccn data, all values are diff --git a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_physics_post.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_physics_post.F90 index ec041623c..37ac9b320 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_physics_post.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_physics_post.F90 @@ -1,4 +1,3 @@ -! ########################################################################################### !> \file GFS_physics_post.F90 !! !! This module contains GFS specific calculations (e.g. diagnostics) and suite specific @@ -13,10 +12,7 @@ module GFS_physics_post public GFS_physics_post_run contains -! ########################################################################################### -! SUBROUTINE GFS_physics_post_run -! ########################################################################################### -!! \section arg_table_GFS_physics_post_run Argument Table +!> \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, & @@ -26,39 +22,39 @@ subroutine GFS_physics_post_run(nCol, nLev, ntoz, ntracp100, nprocess, nprocess_ ! 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, & ! 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 - ip_overhead_ozone ! Index for process in diagnostic tendency output + 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, & !< 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 + ip_overhead_ozone !< Index for process in diagnostic tendency output integer, intent(in), dimension(:,:) :: & - dtidx ! Bookkeeping indices for GFS diagnostic tendencies + dtidx !< Bookkeeping indices for GFS diagnostic tendencies logical, intent(in) :: & - ldiag3d ! Flag for 3d diagnostic fields + ldiag3d !< Flag for 3d diagnostic fields logical, intent(in), dimension(:) :: & - is_photochem ! Flags for photochemistry processes to sum + 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(:,:,:), optional :: & - 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, ichem, iphys, itrac @@ -123,6 +119,7 @@ subroutine GFS_physics_post_run(nCol, nLev, ntoz, ntracp100, nprocess, nprocess_ 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 diff --git a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rad_time_vary.fv3.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rad_time_vary.fv3.F90 index d55fac983..cbd660414 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rad_time_vary.fv3.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rad_time_vary.fv3.F90 @@ -10,9 +10,8 @@ module GFS_rad_time_vary contains -!>\defgroup mod_GFS_rad_time_vary GFS Radiation Time Update -!! This module contains code related to GFS radiation setup. -!> @{ +!> This module contains code related to GFS radiation setup. + !> \section arg_table_GFS_rad_time_vary_timestep_init Argument Table !! \htmlinclude GFS_rad_time_vary_timestep_init.html !! @@ -97,6 +96,5 @@ subroutine GFS_rad_time_vary_timestep_init (lrseeds, rseeds, endif end subroutine GFS_rad_time_vary_timestep_init -!> @} end module GFS_rad_time_vary diff --git a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rad_time_vary.scm.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rad_time_vary.scm.F90 index 3f730eaf5..46585c9da 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rad_time_vary.scm.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rad_time_vary.scm.F90 @@ -10,9 +10,8 @@ module GFS_rad_time_vary contains -!>\defgroup mod_GFS_rad_time_vary GFS Radiation Time Update -!! This module contains code related to GFS radiation setup. -!> @{ +!> This module contains code related to GFS radiation setup. + !> \section arg_table_GFS_rad_time_vary_timestep_init Argument Table !! \htmlinclude GFS_rad_time_vary_timestep_init.html !! @@ -97,6 +96,5 @@ subroutine GFS_rad_time_vary_timestep_init (lrseeds, rseeds, endif end subroutine GFS_rad_time_vary_timestep_init -!> @} end module GFS_rad_time_vary diff --git a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_radiation_surface.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_radiation_surface.F90 index 6f05c93db..5e8c5bc9d 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_radiation_surface.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_radiation_surface.F90 @@ -9,11 +9,10 @@ module GFS_radiation_surface contains -!>\defgroup GFS_radiation_surface_mod GFS Radiation Surface Module -!! This module contains calls to module_radiation_surface::setemis() to set up +!> This module contains calls to module_radiation_surface::setemis() to set up !! surface emissivity for LW radiation and to module_radiation_surface::setalb() !! to set up surface albedo for SW radiation. -!> @{ + !> \section arg_table_GFS_radiation_surface_init Argument Table !! \htmlinclude GFS_radiation_surface_init.html !! @@ -192,5 +191,4 @@ subroutine GFS_radiation_surface_run ( & end subroutine GFS_radiation_surface_run -!> @} end module GFS_radiation_surface diff --git a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_cloud_mp.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_cloud_mp.F90 index f61ea76c6..1022acac9 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_cloud_mp.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_cloud_mp.F90 @@ -1,8 +1,5 @@ !> \file GFS_rrtmgp_cloud_mp.F90 -!! -!> \defgroup GFS_rrtmgp_cloud_mp GFS_rrtmgp_cloud_mp.F90 -!! -!! \brief This module contains the interface for ALL cloud microphysics assumptions and +!! This module contains the interface for ALL cloud microphysics assumptions and !! the RRTMGP radiation scheme. Specific details below in subroutines. !! module GFS_rrtmgp_cloud_mp @@ -20,28 +17,23 @@ module GFS_rrtmgp_cloud_mp real (kind_phys), parameter :: & cld_limit_lower = 0.001, & cld_limit_ovcst = 1.0 - 1.0e-8, & - reliq_def = 10.0 , & ! Default liq radius to 10 micron (used when effr_in=F) - reice_def = 50.0, & ! Default ice radius to 50 micron (used when effr_in=F) - rerain_def = 1000.0, & ! Default rain radius to 1000 micron (used when effr_in=F) - resnow_def = 250.0, & ! Default snow radius to 250 micron (used when effr_in=F) - reice_min = 10.0, & ! Minimum ice size allowed by GFDL MP scheme - reice_max = 150.0 ! Maximum ice size allowed by GFDL MP scheme + reliq_def = 10.0 , & !< Default liq radius to 10 micron (used when effr_in=F) + reice_def = 50.0, & !< Default ice radius to 50 micron (used when effr_in=F) + rerain_def = 1000.0, & !< Default rain radius to 1000 micron (used when effr_in=F) + resnow_def = 250.0, & !< Default snow radius to 250 micron (used when effr_in=F) + reice_min = 10.0, & !< Minimum ice size allowed by GFDL MP scheme + reice_max = 150.0 !< Maximum ice size allowed by GFDL MP scheme public GFS_rrtmgp_cloud_mp_init, GFS_rrtmgp_cloud_mp_run, GFS_rrtmgp_cloud_mp_finalize contains -!>\defgroup gfs_rrtmgp_cloud_mp_mod GFS RRTMGP Cloud MP Module -!! \section arg_table_GFS_rrtmgp_cloud_mp_run -!! \htmlinclude GFS_rrtmgp_cloud_mp_run_html -!! -!> \ingroup GFS_rrtmgp_cloud_mp -!! -!! Here the cloud-radiative properties (optical-path, particle-size and sometimes cloud- +!> Here the cloud-radiative properties (optical-path, particle-size and sometimes cloud- !! fraction) are computed for cloud producing physics schemes (e.g GFDL-MP, Thompson-MP, !! MYNN-EDMF-pbl, GF-convective, and SAMF-convective clouds). +!> \section arg_table_GFS_rrtmgp_cloud_mp_run Argument Table +!! \htmlinclude GFS_rrtmgp_cloud_mp_run.html !! -!! \section GFS_rrtmgp_cloud_mp_run subroutine GFS_rrtmgp_cloud_mp_run(nCol, nLev, nTracers, ncnd, i_cldliq, i_cldice, & i_cldrain, i_cldsnow, i_cldgrpl, i_cldtot, i_cldliq_nc, i_cldice_nc, i_twa, kdt, & imfdeepcnv, imfdeepcnv_gf, imfdeepcnv_samf, doSWrad, doLWrad, effr_in, lmfshal, & @@ -60,113 +52,113 @@ subroutine GFS_rrtmgp_cloud_mp_run(nCol, nLev, nTracers, ncnd, i_cldliq, i_cldic ! Inputs integer, intent(in) :: & - nCol, & ! Number of horizontal grid points - nLev, & ! Number of vertical layers - ncnd, & ! Number of cloud condensation types. - nTracers, & ! Number of tracers from model. - i_cldliq, & ! Index into tracer array for cloud liquid. - i_cldice, & ! Index into tracer array for cloud ice. - i_cldrain, & ! Index into tracer array for cloud rain. - i_cldsnow, & ! Index into tracer array for cloud snow. - i_cldgrpl, & ! Index into tracer array for cloud groupel. - i_cldtot, & ! Index into tracer array for cloud total amount. - i_cldliq_nc, & ! cloud liquid number concentration. - i_cldice_nc, & ! cloud ice number concentration. - i_twa, & ! water friendly aerosol. - imfdeepcnv, & ! Choice of mass-flux deep convection scheme - imfdeepcnv_gf, & ! Flag for Grell-Freitas deep convection scheme - imfdeepcnv_samf, & ! Flag for scale awware mass flux convection scheme - kdt, & ! Current forecast iteration - imp_physics, & ! Choice of microphysics scheme - imp_physics_thompson, & ! Choice of Thompson - imp_physics_gfdl, & ! Choice of GFDL - icloud ! Control for cloud are fraction option + nCol, & !< Number of horizontal grid points + nLev, & !< Number of vertical layers + ncnd, & !< Number of cloud condensation types. + nTracers, & !< Number of tracers from model. + i_cldliq, & !< Index into tracer array for cloud liquid. + i_cldice, & !< Index into tracer array for cloud ice. + i_cldrain, & !< Index into tracer array for cloud rain. + i_cldsnow, & !< Index into tracer array for cloud snow. + i_cldgrpl, & !< Index into tracer array for cloud groupel. + i_cldtot, & !< Index into tracer array for cloud total amount. + i_cldliq_nc, & !< cloud liquid number concentration. + i_cldice_nc, & !< cloud ice number concentration. + i_twa, & !< water friendly aerosol. + imfdeepcnv, & !< Choice of mass-flux deep convection scheme + imfdeepcnv_gf, & !< Flag for Grell-Freitas deep convection scheme + imfdeepcnv_samf, & !< Flag for scale awware mass flux convection scheme + kdt, & !< Current forecast iteration + imp_physics, & !< Choice of microphysics scheme + imp_physics_thompson, & !< Choice of Thompson + imp_physics_gfdl, & !< Choice of GFDL + icloud !< Control for cloud are fraction option logical, intent(in) :: & - doSWrad, & ! Call SW radiation? - doLWrad, & ! Call LW radiation? - effr_in, & ! Provide hydrometeor radii from macrophysics? - lmfshal, & ! Flag for mass-flux shallow convection scheme used by Xu-Randall - ltaerosol, & ! Flag for aerosol option - mraerosol, & ! Flag for aerosol option - lgfdlmprad, & ! Flag for GFDLMP radiation interaction - do_mynnedmf, & ! Flag to activate MYNN-EDMF - uni_cld, & ! Flag for unified cloud scheme - lmfdeep2, & ! Flag for mass flux deep convection - doGP_cldoptics_LUT, & ! Flag to do GP cloud-optics (LUTs) - doGP_cldoptics_PADE, & ! (PADE approximation) - doGP_smearclds ! If true, add sgs clouds to gridmean clouds + doSWrad, & !< Call SW radiation? + doLWrad, & !< Call LW radiation? + effr_in, & !< Provide hydrometeor radii from macrophysics? + lmfshal, & !< Flag for mass-flux shallow convection scheme used by Xu-Randall + ltaerosol, & !< Flag for aerosol option + mraerosol, & !< Flag for aerosol option + lgfdlmprad, & !< Flag for GFDLMP radiation interaction + do_mynnedmf, & !< Flag to activate MYNN-EDMF + uni_cld, & !< Flag for unified cloud scheme + lmfdeep2, & !< Flag for mass flux deep convection + doGP_cldoptics_LUT, & !< Flag to do GP cloud-optics (LUTs) + doGP_cldoptics_PADE, & !< (PADE approximation) + doGP_smearclds !< If true, add sgs clouds to gridmean clouds real(kind_phys), intent(in) :: & - con_g, & ! Physical constant: gravitational constant - con_rd, & ! Physical constant: gas-constant for dry air - con_ttp, & ! Triple point temperature of water (K) - con_eps ! Physical constant: gas constant air / gas constant H2O + con_g, & !< Physical constant: gravitational constant + con_rd, & !< Physical constant: gas-constant for dry air + con_ttp, & !< Triple point temperature of water (K) + con_eps !< Physical constant: gas constant air / gas constant H2O real(kind_phys), dimension(:), intent(in) :: & - lsmask, & ! Land/Sea mask - xlon, & ! Longitude - xlat, & ! Latitude - dx ! Characteristic grid lengthscale (m) + lsmask, & !< Land/Sea mask + xlon, & !< Longitude + xlat, & !< Latitude + dx !< Characteristic grid lengthscale (m) real(kind_phys), dimension(:,:), intent(in), optional :: & - tv_lay, & ! Virtual temperature (K) - t_lay, & ! Temperature (K) - qs_lay, & ! Saturation vapor pressure (Pa) - q_lay, & ! water-vapor mixing ratio (kg/kg) - relhum, & ! Relative humidity - p_lay ! Pressure at model-layers (Pa) + tv_lay, & !< Virtual temperature (K) + t_lay, & !< Temperature (K) + qs_lay, & !< Saturation vapor pressure (Pa) + q_lay, & !< water-vapor mixing ratio (kg/kg) + relhum, & !< Relative humidity + p_lay !< Pressure at model-layers (Pa) real(kind_phys), dimension(:,:), intent(in) :: & - cnv_mixratio ! Convective cloud mixing-ratio (kg/kg) + cnv_mixratio !< Convective cloud mixing-ratio (kg/kg) real(kind_phys), dimension(:,:), intent(in), optional :: & - qci_conv, & ! Convective cloud condesate after rainout (kg/kg) - deltaZ, & ! Layer-thickness (m) - deltaZc, & ! Layer-thickness, from layer centers (m) - deltaP, & ! Layer-thickness (Pa) - qc_mynn, & ! - qi_mynn ! + qci_conv, & !< Convective cloud condesate after rainout (kg/kg) + deltaZ, & !< Layer-thickness (m) + deltaZc, & !< Layer-thickness, from layer centers (m) + deltaP, & !< Layer-thickness (Pa) + qc_mynn, & !< + qi_mynn !< real(kind_phys), dimension(:,:), intent(in), optional :: & - cld_pbl_frac ! + cld_pbl_frac !< real(kind_phys), dimension(:,:), intent(inout), optional :: & - effrin_cldliq, & ! Effective radius for stratiform liquid cloud-particles (microns) - effrin_cldice, & ! Effective radius for stratiform ice cloud-particles (microns) - effrin_cldsnow ! Effective radius for stratiform snow cloud-particles (microns) + effrin_cldliq, & !< Effective radius for stratiform liquid cloud-particles (microns) + effrin_cldice, & !< Effective radius for stratiform ice cloud-particles (microns) + effrin_cldsnow !< Effective radius for stratiform snow cloud-particles (microns) real(kind_phys), dimension(:,:), intent(in), optional :: & - effrin_cldrain ! Effective radius for stratiform rain cloud-particles (microns) + effrin_cldrain !< Effective radius for stratiform rain cloud-particles (microns) real(kind_phys), dimension(:,:), intent(in), optional :: & - p_lev ! Pressure at model-level interfaces (Pa) + p_lev !< Pressure at model-level interfaces (Pa) real(kind_phys), dimension(:,:,:),intent(in) :: & - tracer ! Cloud condensate amount in layer by type () + tracer !< Cloud condensate amount in layer by type () ! Outputs real(kind_phys), dimension(:), intent(inout) :: & - lwp_ex, & ! Total liquid water path from explicit microphysics - iwp_ex, & ! Total ice water path from explicit microphysics - lwp_fc, & ! Total liquid water path from cloud fraction scheme - iwp_fc ! Total ice water path from cloud fraction scheme + lwp_ex, & !< Total liquid water path from explicit microphysics + iwp_ex, & !< Total ice water path from explicit microphysics + lwp_fc, & !< Total liquid water path from cloud fraction scheme + iwp_fc !< Total ice water path from cloud fraction scheme real(kind_phys), dimension(:), intent(out) :: & - cldfra2d ! Instantaneous 2D (max-in-column) cloud fraction + cldfra2d !< Instantaneous 2D (max-in-column) cloud fraction real(kind_phys), dimension(:,:),intent(inout) :: & - 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 + 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 real(kind_phys), dimension(:,:),intent(inout), optional :: & - precip_frac, & ! Precipitation fraction - cld_cnv_frac, & ! Cloud-fraction for convective clouds - 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 SGS PBL liquid cloud-particles - cld_pbl_reliq, & ! Effective radius for SGS PBL liquid cloud-particles - cld_pbl_iwp, & ! Water path for SGS PBL ice cloud-particles - cld_pbl_reice ! Effective radius for SGS PBL ice cloud-particles + precip_frac, & !< Precipitation fraction + cld_cnv_frac, & !< Cloud-fraction for convective clouds + 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 SGS PBL liquid cloud-particles + cld_pbl_reliq, & !< Effective radius for SGS PBL liquid cloud-particles + cld_pbl_iwp, & !< Water path for SGS PBL ice cloud-particles + cld_pbl_reice !< Effective radius for SGS PBL ice cloud-particles character(len=*), intent(out) :: & - errmsg ! Error message + errmsg !< Error message integer, intent(out) :: & - errflg ! Error flag + errflg !< Error flag ! Local integer :: iCol, iLay @@ -314,8 +306,7 @@ subroutine GFS_rrtmgp_cloud_mp_run(nCol, nLev, nTracers, ncnd, i_cldliq, i_cldic end subroutine GFS_rrtmgp_cloud_mp_run -!> \ingroup GFS_rrtmgp_cloud_mp -!! Compute cloud radiative properties for Grell-Freitas convective cloud scheme. +!> Compute cloud radiative properties for Grell-Freitas convective cloud scheme. !! (Adopted from module_SGSCloud_RadPre) !! !! - The total convective cloud condensate is partitoned by phase, using temperature, into @@ -329,7 +320,6 @@ end subroutine GFS_rrtmgp_cloud_mp_run !! Xu-Randall? Xu-Randall is consistent with the Thompson MP scheme, but !! not GFDL-EMC) !! -!! \section cloud_mp_GF_gen General Algorithm subroutine cloud_mp_GF(nCol, nLev, lsmask, t_lay, p_lev, p_lay, qs_lay, relhum, & qci_conv, con_ttp, con_g, alpha0, cld_cnv_lwp, cld_cnv_reliq, cld_cnv_iwp, & cld_cnv_reice, cld_cnv_frac) @@ -337,28 +327,28 @@ subroutine cloud_mp_GF(nCol, nLev, lsmask, t_lay, p_lev, p_lay, qs_lay, relhum, ! Inputs integer, intent(in) :: & - nCol, & ! Number of horizontal grid points - nLev ! Number of vertical layers + nCol, & !< Number of horizontal grid points + nLev !< Number of vertical layers real(kind_phys), dimension(:), intent(in) :: & - lsmask ! Land/Sea mask + lsmask !< Land/Sea mask real(kind_phys), intent(in) :: & - con_g, & ! Physical constant: gravitational constant - con_ttp, & ! Triple point temperature of water (K) - alpha0 ! + con_g, & !< Physical constant: gravitational constant + con_ttp, & !< Triple point temperature of water (K) + alpha0 !< real(kind_phys), dimension(:,:),intent(in) :: & - t_lay, & ! Temperature at layer centers (K) - p_lev, & ! Pressure at layer interfaces (Pa) - p_lay, & ! - qs_lay, & ! - relhum, & ! - qci_conv ! + t_lay, & !< Temperature at layer centers (K) + p_lev, & !< Pressure at layer interfaces (Pa) + p_lay, & !< + qs_lay, & !< + relhum, & !< + qci_conv !< ! Outputs real(kind_phys), dimension(:,:),intent(inout) :: & - cld_cnv_lwp, & ! Convective cloud liquid water path - cld_cnv_reliq, & ! Convective cloud liquid effective radius - cld_cnv_iwp, & ! Convective cloud ice water path - cld_cnv_reice, & ! Convective cloud ice effecive radius - cld_cnv_frac ! Convective cloud-fraction (1) + cld_cnv_lwp, & !< Convective cloud liquid water path + cld_cnv_reliq, & !< Convective cloud liquid effective radius + cld_cnv_iwp, & !< Convective cloud ice water path + cld_cnv_reice, & !< Convective cloud ice effecive radius + cld_cnv_frac !< Convective cloud-fraction (1) ! Local integer :: iCol, iLay real(kind_phys) :: tem1, deltaP, clwc, qc, qi @@ -394,8 +384,7 @@ subroutine cloud_mp_GF(nCol, nLev, lsmask, t_lay, p_lev, p_lay, qs_lay, relhum, enddo end subroutine cloud_mp_GF -!> \ingroup GFS_rrtmgp_cloud_mp -!! Compute cloud radiative properties for MYNN-EDMF PBL cloud scheme. +!> Compute cloud radiative properties for MYNN-EDMF PBL cloud scheme. !! (Adopted from module_SGSCloud_RadPre) !! !! - Cloud-fraction, liquid, and ice condensate mixing-ratios from MYNN-EDMF cloud scheme @@ -404,7 +393,6 @@ end subroutine cloud_mp_GF !! - The liquid and ice cloud effective particle sizes are assigned reference values*. !! *TODO* Find references, include DOIs, parameterize magic numbers, etc... !! -!! \section cloud_mp_MYNN_gen General Algorithm subroutine cloud_mp_MYNN(nCol, nLev, lsmask, t_lay, p_lev, p_lay, qs_lay, relhum, & qc_mynn, qi_mynn, con_ttp, con_g, cld_pbl_lwp, cld_pbl_reliq, cld_pbl_iwp, & cld_pbl_reice, cld_pbl_frac) @@ -412,28 +400,28 @@ subroutine cloud_mp_MYNN(nCol, nLev, lsmask, t_lay, p_lev, p_lay, qs_lay, relhum ! Inputs integer, intent(in) :: & - nCol, & ! Number of horizontal grid points - nLev ! Number of vertical layers + nCol, & !< Number of horizontal grid points + nLev !< Number of vertical layers real(kind_phys), dimension(:), intent(in) :: & - lsmask ! Land/Sea mask + lsmask !< Land/Sea mask real(kind_phys), intent(in) :: & - con_g, & ! Physical constant: gravitational constant - con_ttp ! Triple point temperature of water (K) + con_g, & !< Physical constant: gravitational constant + con_ttp !< Triple point temperature of water (K) real(kind_phys), dimension(:,:),intent(in) :: & - t_lay, & ! Temperature at layer centers (K) - p_lev, & ! Pressure at layer interfaces (Pa) - p_lay, & ! - qs_lay, & ! - relhum, & ! - qc_mynn, & ! Liquid cloud mixing-ratio (MYNN PBL cloud) - qi_mynn, & ! Ice cloud mixing-ratio (MYNN PBL cloud) - cld_pbl_frac ! Cloud-fraction (MYNN PBL cloud) + t_lay, & !< Temperature at layer centers (K) + p_lev, & !< Pressure at layer interfaces (Pa) + p_lay, & !< + qs_lay, & !< + relhum, & !< + qc_mynn, & !< Liquid cloud mixing-ratio (MYNN PBL cloud) + qi_mynn, & !< Ice cloud mixing-ratio (MYNN PBL cloud) + cld_pbl_frac !< Cloud-fraction (MYNN PBL cloud) ! Outputs real(kind_phys), dimension(:,:),intent(inout) :: & - cld_pbl_lwp, & ! Convective cloud liquid water path - cld_pbl_reliq, & ! Convective cloud liquid effective radius - cld_pbl_iwp, & ! Convective cloud ice water path - cld_pbl_reice ! Convective cloud ice effecive radius + cld_pbl_lwp, & !< Convective cloud liquid water path + cld_pbl_reliq, & !< Convective cloud liquid effective radius + cld_pbl_iwp, & !< Convective cloud ice water path + cld_pbl_reice !< Convective cloud ice effecive radius ! Local integer :: iCol, iLay @@ -467,8 +455,7 @@ subroutine cloud_mp_MYNN(nCol, nLev, lsmask, t_lay, p_lev, p_lay, qs_lay, relhum end subroutine cloud_mp_MYNN -!> \ingroup GFS_rrtmgp_cloud_mp -!! Compute cloud radiative properties for SAMF convective cloud scheme. +!> Compute cloud radiative properties for SAMF convective cloud scheme. !! !! - The total-cloud convective mixing-ratio is partitioned by phase into liquid/ice !! cloud properties. LWP and IWP are computed. @@ -478,7 +465,6 @@ end subroutine cloud_mp_MYNN !! - The convective cloud-fraction is computed using Xu-Randall (1996). !! (DJS asks: Does the SAMF scheme produce a cloud-fraction?) !! -!! \section cloud_mp_SAMF_gen General Algorithm subroutine cloud_mp_SAMF(nCol, nLev, t_lay, p_lev, p_lay, qs_lay, relhum, & cnv_mixratio, con_ttp, con_g, alpha0, cld_cnv_lwp, cld_cnv_reliq, cld_cnv_iwp, & cld_cnv_reice, cld_cnv_frac) @@ -486,26 +472,26 @@ subroutine cloud_mp_SAMF(nCol, nLev, t_lay, p_lev, p_lay, qs_lay, relhum, ! Inputs integer, intent(in) :: & - nCol, & ! Number of horizontal grid points - nLev ! Number of vertical layers + nCol, & !< Number of horizontal grid points + nLev !< Number of vertical layers real(kind_phys), intent(in) :: & - con_g, & ! Physical constant: gravity (m s-2) - con_ttp, & ! Triple point temperature of water (K) - alpha0 ! + con_g, & !< Physical constant: gravity (m s-2) + con_ttp, & !< Triple point temperature of water (K) + alpha0 !< real(kind_phys), dimension(:,:),intent(in) :: & - t_lay, & ! Temperature at layer-centers (K) - p_lev, & ! Pressure at layer-interfaces (Pa) - p_lay, & ! Presure at layer-centers (Pa) - qs_lay, & ! Specific-humidity at layer-centers (kg/kg) - relhum, & ! Relative-humidity (1) - cnv_mixratio ! Convective cloud mixing-ratio (kg/kg) + t_lay, & !< Temperature at layer-centers (K) + p_lev, & !< Pressure at layer-interfaces (Pa) + p_lay, & !< Presure at layer-centers (Pa) + qs_lay, & !< Specific-humidity at layer-centers (kg/kg) + relhum, & !< Relative-humidity (1) + cnv_mixratio !< Convective cloud mixing-ratio (kg/kg) ! Outputs real(kind_phys), dimension(:,:),intent(inout) :: & - cld_cnv_lwp, & ! Convective cloud liquid water path - cld_cnv_reliq, & ! Convective cloud liquid effective radius - cld_cnv_iwp, & ! Convective cloud ice water path - cld_cnv_reice, & ! Convective cloud ice effecive radius - cld_cnv_frac ! Convective cloud-fraction + cld_cnv_lwp, & !< Convective cloud liquid water path + cld_cnv_reliq, & !< Convective cloud liquid effective radius + cld_cnv_iwp, & !< Convective cloud ice water path + cld_cnv_reice, & !< Convective cloud ice effecive radius + cld_cnv_frac !< Convective cloud-fraction ! Local integer :: iCol, iLay real(kind_phys) :: tem0, tem1, deltaP, clwc @@ -531,12 +517,10 @@ subroutine cloud_mp_SAMF(nCol, nLev, t_lay, p_lev, p_lay, qs_lay, relhum, end subroutine cloud_mp_SAMF -!> \ingroup GFS_rrtmgp_cloud_mp -!! This routine computes the cloud radiative properties for a "unified cloud". +!> This routine computes the cloud radiative properties for a "unified cloud". !! - "unified cloud" implies that the cloud-fraction is PROVIDED. !! - The cloud water path is computed for all provided cloud mixing-ratios and hydrometeors. !! - If particle sizes are provided, they are used. If not, default values are assigned. -!! \section cloud_mp_uni_gen General Algorithm subroutine cloud_mp_uni(nCol, nLev, nTracers, ncnd, i_cldliq, i_cldice, i_cldrain, & i_cldsnow, i_cldgrpl, i_cldtot, effr_in, kdt, lsmask, p_lev, p_lay, t_lay, tv_lay,& effrin_cldliq, effrin_cldice, effrin_cldsnow, tracer, con_g, con_rd, con_ttp, & @@ -546,50 +530,50 @@ subroutine cloud_mp_uni(nCol, nLev, nTracers, ncnd, i_cldliq, i_cldice, i_cldrai ! Inputs integer, intent(in) :: & - nCol, & ! Number of horizontal grid points - nLev, & ! Number of vertical layers - ncnd, & ! Number of cloud condensation types. - nTracers, & ! Number of tracers from model. - i_cldliq, & ! Index into tracer array for cloud liquid. - i_cldice, & ! Index into tracer array for cloud ice. - i_cldrain, & ! Index into tracer array for cloud rain. - i_cldsnow, & ! Index into tracer array for cloud snow. - i_cldgrpl, & ! Index into tracer array for cloud groupel. - i_cldtot, & ! Index into tracer array for cloud total amount. + nCol, & !< Number of horizontal grid points + nLev, & !< Number of vertical layers + ncnd, & !< Number of cloud condensation types. + nTracers, & !< Number of tracers from model. + i_cldliq, & !< Index into tracer array for cloud liquid. + i_cldice, & !< Index into tracer array for cloud ice. + i_cldrain, & !< Index into tracer array for cloud rain. + i_cldsnow, & !< Index into tracer array for cloud snow. + i_cldgrpl, & !< Index into tracer array for cloud groupel. + i_cldtot, & !< Index into tracer array for cloud total amount. kdt logical, intent(in) :: & - effr_in ! Provide hydrometeor radii from macrophysics? + effr_in !< Provide hydrometeor radii from macrophysics? real(kind_phys), intent(in) :: & - con_g, & ! Physical constant: gravitational constant - con_ttp, & ! Triple point temperature of water (K) - con_rd ! Physical constant: gas-constant for dry air + con_g, & !< Physical constant: gravitational constant + con_ttp, & !< Triple point temperature of water (K) + con_rd !< Physical constant: gas-constant for dry air real(kind_phys), dimension(:), intent(in) :: & lsmask real(kind_phys), dimension(:,:), intent(in) :: & - t_lay, & ! Temperature at model-layers (K) - tv_lay, & ! Virtual temperature (K) - p_lay, & ! Pressure at model-layers (Pa) - cld_frac, & ! Total cloud fraction - effrin_cldliq, & ! Effective radius for liquid cloud-particles (microns) - effrin_cldice, & ! Effective radius for ice cloud-particles (microns) - effrin_cldsnow ! Effective radius for snow cloud-particles (microns) + t_lay, & !< Temperature at model-layers (K) + tv_lay, & !< Virtual temperature (K) + p_lay, & !< Pressure at model-layers (Pa) + cld_frac, & !< Total cloud fraction + effrin_cldliq, & !< Effective radius for liquid cloud-particles (microns) + effrin_cldice, & !< Effective radius for ice cloud-particles (microns) + effrin_cldsnow !< Effective radius for snow cloud-particles (microns) real(kind_phys), dimension(:,:), intent(in), optional :: & - effrin_cldrain ! Effective radius for rain cloud-particles (microns) + effrin_cldrain !< Effective radius for rain cloud-particles (microns) real(kind_phys), dimension(:,:), intent(in) :: & - p_lev ! Pressure at model-level interfaces (Pa) + p_lev !< Pressure at model-level interfaces (Pa) real(kind_phys), dimension(:,:,:),intent(in) :: & - tracer ! Cloud condensate amount in layer by type () + tracer !< Cloud condensate amount in layer by type () ! Outputs real(kind_phys), dimension(:,:),intent(inout) :: & - cld_lwp, & ! Cloud liquid water path - cld_reliq, & ! Cloud liquid effective radius - cld_iwp, & ! Cloud ice water path - cld_reice, & ! Cloud ice effecive radius - cld_swp, & ! Cloud snow water path - cld_resnow, & ! Cloud snow effective radius - cld_rwp, & ! Cloud rain water path - cld_rerain ! Cloud rain effective radius + cld_lwp, & !< Cloud liquid water path + cld_reliq, & !< Cloud liquid effective radius + cld_iwp, & !< Cloud ice water path + cld_reice, & !< Cloud ice effecive radius + cld_swp, & !< Cloud snow water path + cld_resnow, & !< Cloud snow effective radius + cld_rwp, & !< Cloud rain water path + cld_rerain !< Cloud rain effective radius ! Local variables real(kind_phys) :: tem1,tem2,tem3,pfac,deltaP @@ -662,8 +646,8 @@ subroutine cloud_mp_uni(nCol, nLev, nTracers, ncnd, i_cldliq, i_cldice, i_cldrai enddo ! nLev end subroutine cloud_mp_uni -!> \ingroup GFS_rrtmgp_cloud_mp -!! This routine computes the cloud radiative properties for the Thompson cloud micro- + +!> This routine computes the cloud radiative properties for the Thompson cloud micro- !! physics scheme. !! !! - The cloud water path is computed for all provided cloud mixing-ratios and hydrometeors. @@ -674,7 +658,6 @@ end subroutine cloud_mp_uni !! - The cloud-fraction is computed using Xu-Randall** (1996). !! **Additionally, Conditioned on relative-humidity** !! -!! \section cloud_mp_thompson_gen General Algorithm subroutine cloud_mp_thompson(nCol, nLev, nTracers, ncnd, i_cldliq, i_cldice, i_cldrain,& i_cldsnow, i_cldgrpl, p_lev, p_lay, tv_lay, t_lay, tracer, qs_lay, q_lay, relhum, & con_ttp, con_g, con_rd, con_eps, alpha0, cnv_mixratio, lwp_ex, iwp_ex, lwp_fc, & @@ -683,49 +666,49 @@ subroutine cloud_mp_thompson(nCol, nLev, nTracers, ncnd, i_cldliq, i_cldice, i_c ! Inputs logical, intent(in), optional :: & - cond_cfrac_onRH, & ! If true, cloud-fracion set to unity when rh>99% - doGP_smearclds ! If true, add sgs clouds to gridmean clouds + cond_cfrac_onRH, & !< If true, cloud-fracion set to unity when rh>99% + doGP_smearclds !< If true, add sgs clouds to gridmean clouds integer, intent(in) :: & - nCol, & ! Number of horizontal grid points - nLev, & ! Number of vertical layers - ncnd, & ! Number of cloud condensation types. - nTracers, & ! Number of tracers from model. - i_cldliq, & ! Index into tracer array for cloud liquid amount. - i_cldice, & ! cloud ice amount. - i_cldrain, & ! cloud rain amount. - i_cldsnow, & ! cloud snow amount. - i_cldgrpl ! cloud groupel amount. + nCol, & !< Number of horizontal grid points + nLev, & !< Number of vertical layers + ncnd, & !< Number of cloud condensation types. + nTracers, & !< Number of tracers from model. + i_cldliq, & !< Index into tracer array for cloud liquid amount. + i_cldice, & !< cloud ice amount. + i_cldrain, & !< cloud rain amount. + i_cldsnow, & !< cloud snow amount. + i_cldgrpl !< cloud groupel amount. real(kind_phys), intent(in) :: & - con_ttp, & ! Triple point temperature of water (K) - con_g, & ! Physical constant: gravitational constant - con_rd, & ! Physical constant: gas-constant for dry air - con_eps, & ! Physical constant: gas constant air / gas constant H2O - alpha0 ! + con_ttp, & !< Triple point temperature of water (K) + con_g, & !< Physical constant: gravitational constant + con_rd, & !< Physical constant: gas-constant for dry air + con_eps, & !< Physical constant: gas constant air / gas constant H2O + alpha0 !< real(kind_phys), dimension(:,:), intent(in) :: & - tv_lay, & ! Virtual temperature (K) - t_lay, & ! Temperature (K) - qs_lay, & ! Saturation vapor pressure (Pa) - q_lay, & ! water-vapor mixing ratio (kg/kg) - relhum, & ! Relative humidity - p_lay, & ! Pressure at model-layers (Pa) - cnv_mixratio ! Convective cloud mixing-ratio (kg/kg) + tv_lay, & !< Virtual temperature (K) + t_lay, & !< Temperature (K) + qs_lay, & !< Saturation vapor pressure (Pa) + q_lay, & !< water-vapor mixing ratio (kg/kg) + relhum, & !< Relative humidity + p_lay, & !< Pressure at model-layers (Pa) + cnv_mixratio !< Convective cloud mixing-ratio (kg/kg) real(kind_phys), dimension(:,:), intent(in) :: & - p_lev ! Pressure at model-level interfaces (Pa) + p_lev !< Pressure at model-level interfaces (Pa) real(kind_phys), dimension(:,:,:),intent(in) :: & - tracer ! Cloud condensate amount in layer by type () + tracer !< Cloud condensate amount in layer by type () ! In/Outs real(kind_phys), dimension(:), intent(inout) :: & - lwp_ex, & ! total liquid water path from explicit microphysics - iwp_ex, & ! total ice water path from explicit microphysics - lwp_fc, & ! total liquid water path from cloud fraction scheme - iwp_fc ! total ice water path from cloud fraction scheme + lwp_ex, & !< total liquid water path from explicit microphysics + iwp_ex, & !< total ice water path from explicit microphysics + lwp_fc, & !< total liquid water path from cloud fraction scheme + iwp_fc !< total ice water path from cloud fraction scheme real(kind_phys), dimension(:,:), intent(inout) :: & - cld_frac, & ! Total cloud fraction - cld_lwp, & ! Cloud liquid water path - cld_iwp, & ! Cloud ice water path - cld_swp, & ! Cloud snow water path - cld_rwp ! Cloud rain water path + cld_frac, & !< Total cloud fraction + cld_lwp, & !< Cloud liquid water path + cld_iwp, & !< Cloud ice water path + cld_swp, & !< Cloud snow water path + cld_rwp !< Cloud rain water path ! Local variables real(kind_phys) :: tem1, pfac, cld_mr, deltaP, tem2 @@ -795,23 +778,18 @@ subroutine cloud_mp_thompson(nCol, nLev, nTracers, ncnd, i_cldliq, i_cldice, i_c end subroutine cloud_mp_thompson -!> \ingroup GFS_rrtmgp_cloud_mp -!! This function computes the cloud-fraction following. -!! Xu-Randall(1996) A Semiempirical Cloudiness Parameterization for Use in Climate Models -!! https://doi.org/10.1175/1520-0469(1996)053<3084:ASCPFU>2.0.CO;2 -!! -!! cld_frac = {1-exp[-alpha*cld_mr/((1-relhum)*qs_lay)**lambda]}*relhum**P +!> This function computes the cloud-fraction following +!! Xu-Randall(1996) \cite xu_and_randall_1996 !! -!! \section cld_frac_XuRandall_gen General Algorithm function cld_frac_XuRandall(p_lay, qs_lay, relhum, cld_mr, alpha) implicit none ! Inputs real(kind_phys), intent(in) :: & - p_lay, & ! Pressure (Pa) - qs_lay, & ! Saturation vapor-pressure (Pa) - relhum, & ! Relative humidity - cld_mr, & ! Total cloud mixing ratio - alpha ! Scheme parameter (default=100) + p_lay, & !< Pressure (Pa) + qs_lay, & !< Saturation vapor-pressure (Pa) + relhum, & !< Relative humidity + cld_mr, & !< Total cloud mixing ratio + alpha !< Scheme parameter (default=100) ! Outputs real(kind_phys) :: cld_frac_XuRandall @@ -839,11 +817,8 @@ function cld_frac_XuRandall(p_lay, qs_lay, relhum, cld_mr, alpha) return end function - ! ###################################################################################### - ! This routine is a wrapper to update the Thompson effective particle sizes used by the - ! RRTMGP radiation scheme. - ! - ! ###################################################################################### + !> This routine is a wrapper to update the Thompson effective particle sizes used by the + !! RRTMGP radiation scheme. subroutine cmp_reff_Thompson(nLev, nCol, i_cldliq, i_cldice, i_cldsnow, i_cldice_nc, & i_cldliq_nc, i_twa, q_lay, p_lay, t_lay, tracer, con_eps, con_rd, ltaerosol, & mraerosol, lsmask, effrin_cldliq, effrin_cldice, effrin_cldsnow) diff --git a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_cloud_overlap.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_cloud_overlap.F90 index db660148e..069f7545c 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_cloud_overlap.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_cloud_overlap.F90 @@ -1,8 +1,5 @@ !> \file GFS_rrtmgp_cloud_overlap.F90 -!! -!> \defgroup GFS_rrtmgp_cloud_overlap GFS_rrtmgp_cloud_overlap.F90 -!! -!! \brief This module contains EMC's interface to the different assumptions of vertical cloud +!! This file contains EMC's interface to the different assumptions of vertical cloud !! structuce, cloud overlap, used by McICA for cloud sampling in the RRTMGP longwave !! and shortwave schemes. !! @@ -15,20 +12,15 @@ module GFS_rrtmgp_cloud_overlap contains -!>\defgroup gfs_rrtmgp_cloud_overlap_mod GFS RRTMGP Cloud Overlap Module -!! \section arg_table_GFS_rrtmgp_cloud_overlap_run +!> \section arg_table_GFS_rrtmgp_cloud_overlap_run Argument Table !! \htmlinclude GFS_rrtmgp_cloud_overlap_run.html !! -!> \ingroup GFS_rrtmgp_cloud_overlap -!! !! This is identical (shares common-code) to RRTMG. The motivation for RRTMGP to have !! its own scheme is both organizational and philosophical*. !! !! *The number of "clouds" being produced by the model physics is often greater than one. !! rte-rrtmgp can accomodate multiple cloud-types. This module preservers this enhancement !! in the EMCs coupling to the RRTMGP scheme. -!! -!! \section GFS_rrtmgp_cloud_overlap_run subroutine GFS_rrtmgp_cloud_overlap_run(nCol, nLev, yearlen, doSWrad, doLWrad, & julian, lat, deltaZc, con_pi, con_g, con_rd, con_epsq, & dcorr_con, idcor, iovr, iovr_dcorr, iovr_exp, iovr_exprand, idcor_con, & @@ -39,52 +31,52 @@ subroutine GFS_rrtmgp_cloud_overlap_run(nCol, nLev, yearlen, doSWrad, doLWrad, ! Inputs integer, intent(in) :: & - nCol, & ! Number of horizontal grid points - nLev, & ! Number of vertical layers - yearlen, & ! Length of current year (365/366) WTF? - imfdeepcnv, & ! - imfdeepcnv_gf, & ! - imfdeepcnv_samf, & ! - iovr, & ! Choice of cloud-overlap method - iovr_convcld, & ! Choice of convective 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 - idcor, & ! Choice of method for decorrelation length computation - idcor_con, & ! Flag for decorrelation-length. Use constant value - idcor_hogan, & ! Flag for decorrelation-length. (https://rmets.onlinelibrary.wiley.com/doi/full/10.1002/qj.647) - idcor_oreopoulos ! Flag for decorrelation-length. (10.5194/acp-12-9097-2012) + nCol, & !< Number of horizontal grid points + nLev, & !< Number of vertical layers + yearlen, & !< Length of current year (365/366) WTF? + imfdeepcnv, & !< + imfdeepcnv_gf, & !< + imfdeepcnv_samf, & !< + iovr, & !< Choice of cloud-overlap method + iovr_convcld, & !< Choice of convective 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 + idcor, & !< Choice of method for decorrelation length computation + idcor_con, & !< Flag for decorrelation-length. Use constant value + idcor_hogan, & !< Flag for decorrelation-length. (https://rmets.onlinelibrary.wiley.com/doi/full/10.1002/qj.647) + idcor_oreopoulos !< Flag for decorrelation-length. (10.5194/acp-12-9097-2012) logical, intent(in) :: & - top_at_1, & ! Vertical ordering flag - doSWrad, & ! Call SW radiation? - doLWrad ! Call LW radiation + top_at_1, & !< Vertical ordering flag + doSWrad, & !< Call SW radiation? + doLWrad !< Call LW radiation real(kind_phys), intent(in) :: & - julian, & ! Julian day - con_pi, & ! Physical constant: pi - con_g, & ! Physical constant: gravitational constant - con_rd, & ! Physical constant: gas-constant for dry air - con_epsq, & ! Physical constant: Minimum value for specific humidity - dcorr_con ! Decorrelation-length (used if idcor = idcor_con) + julian, & !< Julian day + con_pi, & !< Physical constant: pi + con_g, & !< Physical constant: gravitational constant + con_rd, & !< Physical constant: gas-constant for dry air + con_epsq, & !< Physical constant: Minimum value for specific humidity + dcorr_con !< Decorrelation-length (used if idcor = idcor_con) real(kind_phys), dimension(:), intent(in) :: & - lat ! Latitude + lat !< Latitude real(kind_phys), dimension(:,:), intent(in) :: & - cld_frac ! Total cloud fraction + cld_frac !< Total cloud fraction real(kind_phys), dimension(:,:), intent(in), optional :: & - cld_cnv_frac ! Convective cloud-fraction + cld_cnv_frac !< Convective cloud-fraction real(kind_phys), dimension(:,:), intent(in), optional :: & - deltaZc ! Layer thickness (from layer-centers)(m) + deltaZc !< Layer thickness (from layer-centers)(m) ! Outputs real(kind_phys), dimension(:),intent(out) :: & - de_lgth ! Decorrelation length + de_lgth !< Decorrelation length real(kind_phys), dimension(:,:),intent(out), optional :: & - cloud_overlap_param, & ! Cloud-overlap parameter - cnv_cloud_overlap_param,& ! Convective cloud-overlap parameter - precip_overlap_param ! Precipitation overlap parameter + cloud_overlap_param, & !< Cloud-overlap parameter + cnv_cloud_overlap_param,& !< Convective cloud-overlap parameter + precip_overlap_param !< Precipitation overlap parameter character(len=*), intent(out) :: & - errmsg ! Error message + errmsg !< Error message integer, intent(out) :: & - errflg ! Error flag + errflg !< Error flag ! Local variables integer :: iCol,iLay diff --git a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_post.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_post.F90 index 34dc7de86..ec22f24d3 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_post.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_post.F90 @@ -1,8 +1,5 @@ !> \file GFS_rrtmgp_post.F90 -!! -!> \defgroup GFS_rrtmgp_post GFS_rrtmgp_post.F90 -!! -!! \brief RRTMGP post-processing routine. +!! RRTMGP post-processing routine. !! module GFS_rrtmgp_post use machine, only: kind_phys @@ -15,23 +12,17 @@ module GFS_rrtmgp_post public GFS_rrtmgp_post_run contains - ! ######################################################################################## -!>\defgroup gfs_rrtmgp_post_mod GFS RRTMGP Post Module -!> \section arg_table_GFS_rrtmgp_post_run -!! \htmlinclude GFS_rrtmgp_post.html -!! -!! \ingroup GFS_rrtmgp_post + +!> \section arg_table_GFS_rrtmgp_post_run Argument Table +!! \htmlinclude GFS_rrtmgp_post_run.html !! -!! \brief The all-sky radiation tendency is computed, the clear-sky tendency is computed +!!The all-sky radiation tendency is computed, the clear-sky tendency is computed !! if requested. !! !! RRTMGP surface and TOA fluxes are copied to fields that persist between radiation/physics !! calls. !! !! (optional) Save additional diagnostics. -!! -!! \section GFS_rrtmgp_post_run - ! ######################################################################################## subroutine GFS_rrtmgp_post_run (nCol, nLev, nDay, iSFC, iTOA, idxday, doLWrad, doSWrad, & do_lw_clrsky_hr, do_sw_clrsky_hr, save_diag, fhlwr, fhswr, sfc_alb_nir_dir, & sfc_alb_nir_dif, sfc_alb_uvvis_dir, sfc_alb_uvvis_dif, p_lev, tsfa, coszen, coszdg, & @@ -44,100 +35,100 @@ subroutine GFS_rrtmgp_post_run (nCol, nLev, nDay, iSFC, iTOA, idxday, doLWrad, d ! Inputs integer, intent(in) :: & - nCol, & ! Horizontal loop extent - nLev, & ! Number of vertical layers - nDay, & ! Number of daylit columns - iSFC, & ! Vertical index for surface level - iTOA ! Vertical index for TOA level + nCol, & !< Horizontal loop extent + nLev, & !< Number of vertical layers + nDay, & !< Number of daylit columns + iSFC, & !< Vertical index for surface level + iTOA !< Vertical index for TOA level integer, intent(in), dimension(:) :: & - idxday ! Index array for daytime points + idxday !< Index array for daytime points integer, intent(in), dimension(:,:) :: & - mbota, & ! Vertical indices for low, middle and high cloud tops - mtopa ! ertical indices for low, middle and high cloud bases + mbota, & !< Vertical indices for low, middle and high cloud tops + mtopa !< ertical indices for low, middle and high cloud bases logical, intent(in) :: & - doLWrad, & ! Logical flags for lw radiation calls - doSWrad, & ! Logical flags for sw radiation calls - do_lw_clrsky_hr, & ! Output clear-sky LW heating-rate? - do_sw_clrsky_hr, & ! Output clear-sky SW heating-rate? - save_diag ! Output radiation diagnostics? + doLWrad, & !< Logical flags for lw radiation calls + doSWrad, & !< Logical flags for sw radiation calls + do_lw_clrsky_hr, & !< Output clear-sky LW heating-rate? + do_sw_clrsky_hr, & !< Output clear-sky SW heating-rate? + save_diag !< Output radiation diagnostics? real(kind_phys), intent(in) :: & - fhlwr, & ! Frequency for LW radiation calls - fhswr ! Frequency for SW radiation calls + fhlwr, & !< Frequency for LW radiation calls + fhswr !< Frequency for SW radiation calls real(kind_phys), dimension(:), intent(in) :: & - tsfa, & ! Lowest model layer air temperature for radiation (K) - coszen, & ! Cosine(SZA) - coszdg, & ! Cosine(SZA), daytime - 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) + tsfa, & !< Lowest model layer air temperature for radiation (K) + coszen, & !< Cosine(SZA) + coszdg, & !< Cosine(SZA), daytime + 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) real(kind_phys), dimension(:,:), intent(in), optional :: & - p_lev, & ! Pressure @ model layer-interfaces (Pa) - fluxlwUP_allsky, & ! RRTMGP longwave all-sky flux (W/m2) - fluxlwDOWN_allsky, & ! RRTMGP longwave all-sky flux (W/m2) - fluxlwUP_clrsky, & ! RRTMGP longwave clear-sky flux (W/m2) - fluxlwDOWN_clrsky, & ! RRTMGP longwave clear-sky flux (W/m2) - fluxswUP_allsky, & ! RRTMGP shortwave all-sky flux (W/m2) - fluxswDOWN_allsky, & ! RRTMGP shortwave all-sky flux (W/m2) - fluxswUP_clrsky, & ! RRTMGP shortwave clear-sky flux (W/m2) - fluxswDOWN_clrsky ! RRTMGP shortwave clear-sky flux (W/m2) + p_lev, & !< Pressure @ model layer-interfaces (Pa) + fluxlwUP_allsky, & !< RRTMGP longwave all-sky flux (W/m2) + fluxlwDOWN_allsky, & !< RRTMGP longwave all-sky flux (W/m2) + fluxlwUP_clrsky, & !< RRTMGP longwave clear-sky flux (W/m2) + fluxlwDOWN_clrsky, & !< RRTMGP longwave clear-sky flux (W/m2) + fluxswUP_allsky, & !< RRTMGP shortwave all-sky flux (W/m2) + fluxswDOWN_allsky, & !< RRTMGP shortwave all-sky flux (W/m2) + fluxswUP_clrsky, & !< RRTMGP shortwave clear-sky flux (W/m2) + fluxswDOWN_clrsky !< RRTMGP shortwave clear-sky flux (W/m2) real(kind_phys), intent(in) :: & - raddt ! Radiation time step + raddt !< Radiation time step real(kind_phys), dimension(:,:), intent(in) :: & - aerodp, & ! Vertical integrated optical depth for various aerosol species - cldsa, & ! Fraction of clouds for low, middle, high, total and BL - cld_frac, & ! Total cloud fraction in each layer - cldtaulw, & ! approx 10.mu band layer cloud optical depth - cldtausw ! approx .55mu band layer cloud optical depth + aerodp, & !< Vertical integrated optical depth for various aerosol species + cldsa, & !< Fraction of clouds for low, middle, high, total and BL + cld_frac, & !< Total cloud fraction in each layer + cldtaulw, & !< approx 10.mu band layer cloud optical depth + cldtausw !< approx .55mu band layer cloud optical depth type(cmpfsw_type), dimension(:), intent(in) :: & - scmpsw ! 2D surface fluxes, components: - ! uvbfc - total sky downward uv-b flux at (W/m2) - ! uvbf0 - clear sky downward uv-b flux at (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: + !!\n uvbfc - total sky downward uv-b flux at (W/m2) + !!\n uvbf0 - clear sky downward uv-b flux at (W/m2) + !!\n nirbm - downward nir direct beam flux (W/m2) + !!\n nirdf - downward nir diffused flux (W/m2) + !!\n visbm - downward uv+vis direct beam flux (W/m2) + !!\n visdf - downward uv+vis diffused flux (W/m2) real(kind=kind_phys), dimension(:,:), intent(inout) :: fluxr ! Outputs (mandatory) real(kind_phys), dimension(:), intent(inout) :: & - tsflw, & ! LW sfc air temp during calculation (K) - sfcdlw, & ! LW sfc all-sky downward flux (W/m2) - sfculw, & ! LW sfc all-sky upward flux (W/m2) - nirbmdi, & ! SW sfc nir beam downward flux (W/m2) - nirdfdi, & ! SW sfc nir diff downward flux (W/m2) - visbmdi, & ! SW sfc uv+vis beam downward flux (W/m2) - visdfdi, & ! SW sfc uv+vis diff downward flux (W/m2) - nirbmui, & ! SW sfc nir beam upward flux (W/m2) - nirdfui, & ! SW sfc nir diff upward flux (W/m2) - visbmui, & ! SW sfc uv+vis beam upward flux (W/m2) - visdfui, & ! SW sfc uv+vis diff upward flux (W/m2) - sfcnsw, & ! SW sfc all-sky net flux (W/m2) flux into ground - sfcdsw ! SW sfc all-sky downward flux (W/m2) + tsflw, & !< LW sfc air temp during calculation (K) + sfcdlw, & !< LW sfc all-sky downward flux (W/m2) + sfculw, & !< LW sfc all-sky upward flux (W/m2) + nirbmdi, & !< SW sfc nir beam downward flux (W/m2) + nirdfdi, & !< SW sfc nir diff downward flux (W/m2) + visbmdi, & !< SW sfc uv+vis beam downward flux (W/m2) + visdfdi, & !< SW sfc uv+vis diff downward flux (W/m2) + nirbmui, & !< SW sfc nir beam upward flux (W/m2) + nirdfui, & !< SW sfc nir diff upward flux (W/m2) + visbmui, & !< SW sfc uv+vis beam upward flux (W/m2) + visdfui, & !< SW sfc uv+vis diff upward flux (W/m2) + sfcnsw, & !< SW sfc all-sky net flux (W/m2) flux into ground + sfcdsw !< SW sfc all-sky downward flux (W/m2) real(kind_phys), dimension(:,:), intent(inout) :: & - htrlw, & ! LW all-sky heating rate (K/s) - htrsw ! SW all-sky heating rate (K/s) + htrlw, & !< LW all-sky heating rate (K/s) + htrsw !< SW all-sky heating rate (K/s) real(kind_phys), dimension(:,:), intent(inout), optional :: & - htrlwu ! LW all-sky heating-rate updated in-between radiation calls. + htrlwu !< LW all-sky heating-rate updated in-between radiation calls. type(sfcflw_type), dimension(:), intent(inout) :: & - sfcflw ! LW radiation fluxes at sfc + sfcflw !< LW radiation fluxes at sfc type(sfcfsw_type), dimension(:), intent(inout) :: & - sfcfsw ! SW radiation fluxes at sfc + sfcfsw !< SW radiation fluxes at sfc type(topfsw_type), dimension(:), intent(inout) :: & - topfsw ! SW fluxes at top atmosphere + topfsw !< SW fluxes at top atmosphere type(topflw_type), dimension(:), intent(inout) :: & - topflw ! LW fluxes at top atmosphere + topflw !< LW fluxes at top atmosphere character(len=*), intent(out) :: & - errmsg ! CCPP error message + errmsg !< CCPP error message integer, intent(out) :: & - errflg ! CCPP error code + errflg !< CCPP error code ! Outputs (optional) real(kind_phys),dimension(:,:),intent(inout),optional :: & - htrlwc, & ! LW clear-sky heating-rate (K/s) - htrswc ! SW clear-sky heating rate (K/s) + htrlwc, & !< LW clear-sky heating-rate (K/s) + htrswc !< SW clear-sky heating rate (K/s) ! Local variables integer :: i, j, k, itop, ibtc diff --git a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_pre.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_pre.F90 index ba5e2ad58..0a747aa44 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_pre.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_pre.F90 @@ -1,9 +1,7 @@ !> \file GFS_rrtmgp_pre.F90 -!! -!> \defgroup GFS_rrtmgp_pre GFS_rrtmgp_pre.F90 -!! !! \brief This module contains code to prepare model fields for use by the RRTMGP !! radiation scheme. + module GFS_rrtmgp_pre use machine, only: kind_phys use funcphys, only: fpvs @@ -33,29 +31,24 @@ module GFS_rrtmgp_pre public GFS_rrtmgp_pre_run,GFS_rrtmgp_pre_init contains -!>\defgroup gfs_rrtmgp_pre GFS RRTMGP Pre Module -!! \section arg_table_GFS_rrtmgp_pre_init +!> \section arg_table_GFS_rrtmgp_pre_init Argument Table !! \htmlinclude GFS_rrtmgp_pre_init.html !! -!> \ingroup GFS_rrtmgp_pre -!! -!! \brief Actuve gas-names are read from namelist. Set to interstitial%active_gases. -!! -!! \section GFS_rrtmgp_pre_init +!! Actuve gas-names are read from namelist. Set to interstitial%active_gases. subroutine GFS_rrtmgp_pre_init(nGases, active_gases, active_gases_array, errmsg, errflg) ! Inputs integer, intent(in) :: & - nGases ! Number of active gases in RRTMGP + nGases !< Number of active gases in RRTMGP character(len=*), intent(in) :: & - active_gases ! List of active gases from namelist + active_gases !< List of active gases from namelist character(len=*), dimension(:), intent(out), optional :: & - active_gases_array ! List of active gases from namelist as array + active_gases_array !< List of active gases from namelist as array ! Outputs character(len=*), intent(out) :: & - errmsg ! Error message + errmsg !< Error message integer, intent(out) :: & - errflg ! Error flag + errflg !< Error flag ! Local variables character(len=1) :: tempstr @@ -101,16 +94,10 @@ subroutine GFS_rrtmgp_pre_init(nGases, active_gases, active_gases_array, errmsg, end subroutine GFS_rrtmgp_pre_init - ! ######################################################################################### -!> \section arg_table_GFS_rrtmgp_pre_run +!> \section arg_table_GFS_rrtmgp_pre_run Argument Table !! \htmlinclude GFS_rrtmgp_pre_run.html !! -!> \ingroup GFS_rrtmgp_pre -!! -!! \brief Sanitize inputs for use in RRTMGP. -!! -!! \section GFS_rrtmgp_pre_run - ! ######################################################################################### +!! Sanitize inputs for use in RRTMGP. subroutine GFS_rrtmgp_pre_run(me, nCol, nLev, i_o3, doSWrad, doLWrad, fhswr, fhlwr, & xlat, xlon, prsl, tgrs, prslk, prsi, qgrs, tsfc, coslat, sinlat, con_g, con_rd, & con_eps, con_epsm1, con_fvirt, con_epsqs, solhr, raddt, p_lay, t_lay, p_lev, t_lev, & @@ -122,79 +109,79 @@ subroutine GFS_rrtmgp_pre_run(me, nCol, nLev, i_o3, doSWrad, doLWrad, fhswr, fhl ! Inputs integer, intent(in) :: & - me, & ! MPI rank - nCol, & ! Number of horizontal grid points - nLev, & ! Number of vertical layers - ico2, & ! Flag for co2 radiation scheme - i_o3 ! Index into tracer array for ozone + me, & !< MPI rank + nCol, & !< Number of horizontal grid points + nLev, & !< Number of vertical layers + ico2, & !< Flag for co2 radiation scheme + i_o3 !< Index into tracer array for ozone type(ty_ozphys),intent(in) :: & ozphys logical, intent(in) :: & - doSWrad, & ! Call SW radiation? - doLWrad ! Call LW radiation + doSWrad, & !< Call SW radiation? + doLWrad !< Call LW radiation real(kind_phys), intent(in) :: & - fhswr, & ! Frequency of SW radiation call. - fhlwr ! Frequency of LW radiation call. + fhswr, & !< Frequency of SW radiation call. + fhlwr !< Frequency of LW radiation call. real(kind_phys), intent(in) :: & - con_g, & ! Physical constant: gravitational constant - con_rd, & ! Physical constant: gas-constant for dry air - con_eps, & ! Physical constant: Epsilon (Rd/Rv) - con_epsm1, & ! Physical constant: Epsilon (Rd/Rv) minus one - con_fvirt, & ! Physical constant: Inverse of epsilon minus one - con_epsqs, & ! Physical constant: Minimum saturation mixing-ratio (kg/kg) - con_pi, & ! Physical constant: Pi - solhr ! Time in hours after 00z at the current timestep + con_g, & !< Physical constant: gravitational constant + con_rd, & !< Physical constant: gas-constant for dry air + con_eps, & !< Physical constant: Epsilon (Rd/Rv) + con_epsm1, & !< Physical constant: Epsilon (Rd/Rv) minus one + con_fvirt, & !< Physical constant: Inverse of epsilon minus one + con_epsqs, & !< Physical constant: Minimum saturation mixing-ratio (kg/kg) + con_pi, & !< Physical constant: Pi + solhr !< Time in hours after 00z at the current timestep real(kind_phys), dimension(:), intent(in) :: & - xlon, & ! Longitude - xlat, & ! Latitude - tsfc, & ! Surface skin temperature (K) - coslat, & ! Cosine(latitude) - sinlat, & ! Sine(latitude) + xlon, & !< Longitude + xlat, & !< Latitude + tsfc, & !< Surface skin temperature (K) + coslat, & !< Cosine(latitude) + sinlat, & !< Sine(latitude) semis real(kind_phys), dimension(:,:), intent(in) :: & - prsl, & ! Pressure at model-layer centers (Pa) - tgrs, & ! Temperature at model-layer centers (K) - prslk, & ! Exner function at model layer centers (1) - prsi ! Pressure at model-interfaces (Pa) + prsl, & !< Pressure at model-layer centers (Pa) + tgrs, & !< Temperature at model-layer centers (K) + prslk, & !< Exner function at model layer centers (1) + prsi !< Pressure at model-interfaces (Pa) real(kind_phys), dimension(:,:,:), intent(in) :: & - qgrs ! Tracer concentrations (kg/kg) + qgrs !< Tracer concentrations (kg/kg) character(len=*), dimension(:), intent(in), optional :: & - active_gases_array ! List of active gases from namelist as array + active_gases_array !< List of active gases from namelist as array ! Outputs character(len=*), intent(out) :: & - errmsg ! Error message + errmsg !< Error message integer, intent(out) :: & - errflg, & ! Error flag + errflg, & !< Error flag nDay integer, intent(inout) :: & - iSFC, & ! Vertical index for surface - iTOA ! Vertical index for TOA + iSFC, & !< Vertical index for surface + iTOA !< Vertical index for TOA logical, intent(inout) :: & - top_at_1 ! Vertical ordering flag + top_at_1 !< Vertical ordering flag real(kind_phys), intent(inout) :: & - raddt ! Radiation time-step + raddt !< Radiation time-step real(kind_phys), dimension(:), intent(inout) :: & - tsfg, & ! Ground temperature - tsfa, & ! Skin temperature - tsfc_radtime, & ! Surface temperature at radiation timestep - coszen, & ! Cosine of SZA - coszdg ! Cosine of SZA, daytime + tsfg, & !< Ground temperature + tsfa, & !< Skin temperature + tsfc_radtime, & !< Surface temperature at radiation timestep + coszen, & !< Cosine of SZA + coszdg !< Cosine of SZA, daytime integer, dimension(:), intent(inout) :: & - idxday ! Indices for daylit points + idxday !< Indices for daylit points real(kind_phys), dimension(:,:), intent(inout), optional :: & - p_lay, & ! Pressure at model-layer - t_lay, & ! Temperature at model layer - q_lay, & ! Water-vapor mixing ratio (kg/kg) - tv_lay, & ! Virtual temperature at model-layers - relhum, & ! Relative-humidity at model-layers - qs_lay, & ! Saturation vapor pressure at model-layers - deltaZ, & ! Layer thickness (m) - deltaZc, & ! Layer thickness (m) (between layer centers) - deltaP, & ! Layer thickness (Pa) - p_lev, & ! Pressure at model-interface - sfc_emiss_byband, & ! - t_lev, & ! Temperature at model-interface + p_lay, & !< Pressure at model-layer + t_lay, & !< Temperature at model layer + q_lay, & !< Water-vapor mixing ratio (kg/kg) + tv_lay, & !< Virtual temperature at model-layers + relhum, & !< Relative-humidity at model-layers + qs_lay, & !< Saturation vapor pressure at model-layers + deltaZ, & !< Layer thickness (m) + deltaZc, & !< Layer thickness (m) (between layer centers) + deltaP, & !< Layer thickness (Pa) + p_lev, & !< Pressure at model-interface + sfc_emiss_byband, & !< + t_lev, & !< Temperature at model-interface vmr_o2, vmr_h2o, vmr_o3, vmr_ch4, vmr_n2o, vmr_co2 ! Local variables diff --git a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_setup.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_setup.F90 index 2739c951b..0ed936410 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_setup.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmgp_setup.F90 @@ -31,8 +31,7 @@ module GFS_rrtmgp_setup contains -!> \defgroup GFS_rrtmgp_setup_mod GFS RRTMGP Scheme Setup Module -!! \section arg_table_GFS_rrtmgp_setup_init +!> \section arg_table_GFS_rrtmgp_setup_init Argument Table !! \htmlinclude GFS_rrtmgp_setup_init.html !! subroutine GFS_rrtmgp_setup_init(do_RRTMGP, imp_physics, imp_physics_fer_hires, & @@ -46,14 +45,14 @@ subroutine GFS_rrtmgp_setup_init(do_RRTMGP, imp_physics, imp_physics_fer_hires, ! Inputs logical, intent(in) :: do_RRTMGP integer, intent(in) :: & - imp_physics, & ! Flag for MP scheme - imp_physics_fer_hires, & ! Flag for fer-hires scheme - imp_physics_gfdl, & ! Flag for gfdl scheme - imp_physics_thompson, & ! Flag for thompsonscheme - imp_physics_wsm6, & ! Flag for wsm6 scheme - imp_physics_zhao_carr, & ! Flag for zhao-carr scheme - imp_physics_zhao_carr_pdf, & ! Flag for zhao-carr+PDF scheme - imp_physics_mg ! Flag for MG scheme + imp_physics, & !< Flag for MP scheme + imp_physics_fer_hires, & !< Flag for fer-hires scheme + imp_physics_gfdl, & !< Flag for gfdl scheme + imp_physics_thompson, & !< Flag for thompsonscheme + imp_physics_wsm6, & !< Flag for wsm6 scheme + imp_physics_zhao_carr, & !< Flag for zhao-carr scheme + imp_physics_zhao_carr_pdf, & !< Flag for zhao-carr+PDF scheme + imp_physics_mg !< Flag for MG scheme real(kind_phys), intent(in) :: & con_pi, con_t0c, con_c, con_boltz, con_plnk, con_solr_2008, con_solr_2002 real(kind_phys), dimension(:), intent(in) :: & @@ -140,10 +139,7 @@ subroutine GFS_rrtmgp_setup_init(do_RRTMGP, imp_physics, imp_physics_fer_hires, return end subroutine GFS_rrtmgp_setup_init - ! ######################################################################################### - ! SUBROUTINE GFS_rrtmgp_setup_timestep_init - ! ######################################################################################### -!> \section arg_table_GFS_rrtmgp_setup_timestep_init +!> \section arg_table_GFS_rrtmgp_setup_timestep_init Argument Table !! \htmlinclude GFS_rrtmgp_setup_timestep_init.html !! subroutine GFS_rrtmgp_setup_timestep_init (idate, jdate, deltsw, deltim, doSWrad, me, & @@ -251,10 +247,7 @@ subroutine GFS_rrtmgp_setup_timestep_init (idate, jdate, deltsw, deltim, doSWrad return end subroutine GFS_rrtmgp_setup_timestep_init - ! ######################################################################################### - ! SUBROUTINE GFS_rrtmgp_setup_finalize - ! ######################################################################################### -!> \section arg_table_GFS_rrtmgp_setup_finalize +!> \section arg_table_GFS_rrtmgp_setup_finalize Argument Table !! \htmlinclude GFS_rrtmgp_setup_finalize.html !! subroutine GFS_rrtmgp_setup_finalize (errmsg, errflg) diff --git a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_stochastics.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_stochastics.F90 index 2fb1b185d..974e9dc71 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_stochastics.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_stochastics.F90 @@ -5,9 +5,7 @@ module GFS_stochastics contains -!>\defgroup gfs_stoch_mod GFS Stochastics Physics Module -!> @{ -!! This is the GFS stochastics physics driver module. +!> This is the GFS stochastics physics driver module. !! !> \section arg_table_GFS_stochastics_init Argument Table !! \htmlinclude GFS_stochastics_init.html @@ -372,5 +370,4 @@ subroutine GFS_stochastics_run (im, km, kdt, delt, do_sppt, pert_mp, use_zmtnblc endif end subroutine GFS_stochastics_run -!> @} end module GFS_stochastics diff --git a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_suite_stateout_update.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_suite_stateout_update.F90 index c2f5266fd..82bcddac8 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_suite_stateout_update.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_suite_stateout_update.F90 @@ -1,20 +1,17 @@ -! ######################################################################################### !> \file GFS_suite_stateout_update.f90 !! Update the state variables due to process-split physics from accumulated tendencies !! during that phase. !! Update gas concentrations, if using prognostic photolysis schemes. !! Also, set bounds on the mass-weighted rime factor when using Ferrier-Aligo microphysics. -! ######################################################################################### module GFS_suite_stateout_update use machine, only: kind_phys use module_ozphys, only: ty_ozphys implicit none contains -! ######################################################################################### + !> \section arg_table_GFS_suite_stateout_update_run Argument Table !! \htmlinclude GFS_suite_stateout_update_run.html !! -! ######################################################################################### 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, & diff --git a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_surface_loop_control_part1.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_surface_loop_control_part1.F90 index c3030c144..913c1a7b6 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_surface_loop_control_part1.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/GFS_surface_loop_control_part1.F90 @@ -1,19 +1,15 @@ !> \file GFS_surface_loop_control_part1.F90 !! This file contains the GFS_surface_loop_control_part1 scheme. -!> \defgroup GFS_surface_loop_control GFS_surface_loop_control_part1 scheme -!! This module contains the GFS_surface_loop_control_part1 scheme. -!! @{ +!> This module contains the GFS_surface_loop_control_part1 scheme. module GFS_surface_loop_control_part1 contains -!> \brief Brief description of the subroutine +!> Brief description of the subroutine !! !! \section arg_table_GFS_surface_loop_control_part1_run Arguments !! \htmlinclude GFS_surface_loop_control_part1_run.html !! -!! \section gen_loop1 General Algorithm -!! \section detailed_loop1 Detailed Algorithm subroutine GFS_surface_loop_control_part1_run (im, iter, & wind, flag_guess, errmsg, errflg) @@ -45,4 +41,3 @@ subroutine GFS_surface_loop_control_part1_run (im, iter, & end subroutine GFS_surface_loop_control_part1_run end module GFS_surface_loop_control_part1 -!> @} 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/iccninterp.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/iccninterp.F90 index dd752d9b8..b90b6fca7 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/iccninterp.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/iccninterp.F90 @@ -15,6 +15,7 @@ module iccninterp contains +!> SUBROUTINE read_cidata (me, master) use machine, only: kind_phys use iccn_def @@ -65,6 +66,7 @@ END SUBROUTINE read_cidata ! !********************************************************************** ! +!> SUBROUTINE setindxci(npts,dlat,jindx1,jindx2,ddy,dlon, & iindx1,iindx2,ddx) ! @@ -126,6 +128,7 @@ END SUBROUTINE setindxci !********************************************************************** !********************************************************************** ! +!> SUBROUTINE ciinterpol(me,npts,IDATE,FHOUR,jindx1,jindx2,ddy, & iindx1,iindx2,ddx,lev, prsl, ciplout,ccnout) ! 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..45d3dd4e0 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,24 @@ 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 +80,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 +124,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 +155,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 +165,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 +185,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 +197,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 +209,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 +227,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 +248,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 +269,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 +290,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/Interstitials/UFS_SCM_NEPTUNE/scm_sfc_flux_spec.F90 b/physics/Interstitials/UFS_SCM_NEPTUNE/scm_sfc_flux_spec.F90 index a3cf2d740..797a1cd95 100644 --- a/physics/Interstitials/UFS_SCM_NEPTUNE/scm_sfc_flux_spec.F90 +++ b/physics/Interstitials/UFS_SCM_NEPTUNE/scm_sfc_flux_spec.F90 @@ -15,8 +15,7 @@ module scm_sfc_flux_spec CONTAINS !******************************************************************************************* -!! -!! \section arg_table_scm_sfc_flux_spec_init Argument Table +!> \section arg_table_scm_sfc_flux_spec_init Argument Table !! \htmlinclude scm_sfc_flux_spec_init.html !! subroutine scm_sfc_flux_spec_init(lheatstrg, errmsg, errflg) diff --git a/physics/MP/GFDL/GFDL_parse_tracers.F90 b/physics/MP/GFDL/GFDL_parse_tracers.F90 index c81127101..670c292ee 100644 --- a/physics/MP/GFDL/GFDL_parse_tracers.F90 +++ b/physics/MP/GFDL/GFDL_parse_tracers.F90 @@ -1,3 +1,7 @@ +!>\file GFDL_parse_tracers.F90 +!! + +!> This module contains code to parse tracers in GFDL MP module parse_tracers integer, parameter :: NO_TRACER = -99 diff --git a/physics/MP/GFDL/gfdl_cloud_microphys.F90 b/physics/MP/GFDL/gfdl_cloud_microphys.F90 index 8b149616e..b0b632646 100644 --- a/physics/MP/GFDL/gfdl_cloud_microphys.F90 +++ b/physics/MP/GFDL/gfdl_cloud_microphys.F90 @@ -1,6 +1,9 @@ !> \file gfdl_cloud_microphys.F90 !! This file contains the CCPP entry point for the column GFDL cloud microphysics ( Chen and Lin (2013) !! \cite chen_and_lin_2013 ). + +!> This module contains the CCPP entry point for the column GFDL cloud microphysics ( Chen and Lin (2013) +!! \cite chen_and_lin_2013 ). module gfdl_cloud_microphys use gfdl_cloud_microphys_mod, only: gfdl_cloud_microphys_mod_init, & diff --git a/physics/MP/GFDL/module_gfdl_cloud_microphys.F90 b/physics/MP/GFDL/module_gfdl_cloud_microphys.F90 index 5cab1abbc..72f3211b5 100644 --- a/physics/MP/GFDL/module_gfdl_cloud_microphys.F90 +++ b/physics/MP/GFDL/module_gfdl_cloud_microphys.F90 @@ -27,7 +27,8 @@ ! ======================================================================= !>\defgroup mod_gfdl_cloud_mp GFDL Cloud MP modules !!\ingroup gfdlmp -!! This module contains the column GFDL Cloud microphysics scheme. + +!> This module contains the column GFDL Cloud microphysics scheme. module gfdl_cloud_microphys_mod ! use mpp_mod, only: stdlog, mpp_pe, mpp_root_pe, mpp_clock_id, & diff --git a/physics/MP/Morrison_Gettelman/micro_mg3_0.F90 b/physics/MP/Morrison_Gettelman/micro_mg3_0.F90 index bca005bc9..a28de2d74 100644 --- a/physics/MP/Morrison_Gettelman/micro_mg3_0.F90 +++ b/physics/MP/Morrison_Gettelman/micro_mg3_0.F90 @@ -2,12 +2,9 @@ !! This file contains Morrison-Gettelman MP version 3.0 - !! Update of MG microphysics with prognostic hail OR graupel. -!>\ingroup mg2mg3 -!>\defgroup mg3_mp Morrison-Gettelman MP version 3.0 -!> @{ -!!--------------------------------------------------------------------------------- -!! Purpose: -!! MG microphysics version 3.0 - Update of MG microphysics with +!--------------------------------------------------------------------------------- +! Purpose: +!> MG microphysics version 3.0 - Update of MG microphysics with !! prognostic hail OR graupel. !! !! \authors Andrew Gettelman, Hugh Morrison @@ -248,8 +245,7 @@ module micro_mg3_0 contains !=============================================================================== -!>\ingroup mg3_mp -!! This subroutine initializes the microphysics +!> This subroutine initializes the microphysics !! and needs to be called once at start of simulation. !!\author Andrew Gettelman, Dec 2005 subroutine micro_mg_init( & @@ -433,8 +429,7 @@ end subroutine micro_mg_init !=============================================================================== !microphysics routine for each timestep goes here... -!>\ingroup mg3_mp -!! This subroutine calculates the MG3 microphysical processes. +!> This subroutine calculates the MG3 microphysical processes. !>\authors Hugh Morrison, Andrew Gettelman, NCAR, Peter Caldwell, LLNL !! e-mail: morrison@ucar.edu, andrew@ucar.edu !!\section mg3_micro_mg_tend MG3 micro_mg_tend General Algorithm @@ -4484,8 +4479,7 @@ end subroutine micro_mg_tend !OUTPUT CALCULATIONS !======================================================================== -!>\ingroup mg3_mp -!! This subroutine calculates effective radii for rain and cloud. +!> This subroutine calculates effective radii for rain and cloud. subroutine calc_rercld(lamr, n0r, lamc, pgam, qric, qcic, ncic, rercld, mgncol,nlev) integer, intent(in) :: mgncol, nlev ! horizontal and vertical dimension real(r8), dimension(mgncol,nlev), intent(in) :: lamr ! rain size parameter (slope) @@ -4528,4 +4522,3 @@ end subroutine calc_rercld !======================================================================== end module micro_mg3_0 -!>@} diff --git a/physics/MP/NSSL/module_mp_nssl_2mom.F90 b/physics/MP/NSSL/module_mp_nssl_2mom.F90 index ad90ec81f..c57110bad 100644 --- a/physics/MP/NSSL/module_mp_nssl_2mom.F90 +++ b/physics/MP/NSSL/module_mp_nssl_2mom.F90 @@ -1,11 +1,5 @@ !> \file module_mp_nssl_2mom.F90 - - - - - - - +!! !--------------------------------------------------------------------- ! code snapshot: "Sep 22 2023" at "22:01:53" @@ -176,8 +170,11 @@ !>\defgroup mod_nsslmp NSSL 2-moment microphysics modules -!!\ingroup nsslmp testphrase one -!! Module for NSSL cloud physics +!!\ingroup nsslmp + +!> This module contains 1/2/3-moment bulk microphysics scheme based on a combination of +!! Straka and Mansell (2005, JAM) and Zeigler (1985, JAS) and modified/upgraded in +!! in Mansell, Zeigler, and Bruning (2010, JAS). MODULE module_mp_nssl_2mom IMPLICIT NONE diff --git a/physics/MP/NSSL/mp_nssl.F90 b/physics/MP/NSSL/mp_nssl.F90 index 7b21fbbe1..38621d591 100644 --- a/physics/MP/NSSL/mp_nssl.F90 +++ b/physics/MP/NSSL/mp_nssl.F90 @@ -3,7 +3,8 @@ !>\defgroup nsslmp NSSL MP Module -!! This module contains the front end to NSSL microphysics scheme. + +!> This module contains the front end to NSSL microphysics scheme. module mp_nssl use machine, only : kind_phys diff --git a/physics/MP/Thompson/module_mp_thompson.F90 b/physics/MP/Thompson/module_mp_thompson.F90 index aa1361c3b..c19df1eaa 100644 --- a/physics/MP/Thompson/module_mp_thompson.F90 +++ b/physics/MP/Thompson/module_mp_thompson.F90 @@ -3,7 +3,7 @@ !>\ingroup aathompson -!! This module computes the moisture tendencies of water vapor, +!> This module computes the moisture tendencies of water vapor, !! cloud droplets, rain, cloud ice (pristine), snow, and graupel. !! Prior to WRFv2.2 this code was based on Reisner et al (1998), but !! few of those pieces remain. A complete description is now found in diff --git a/physics/MP/Thompson/module_mp_thompson_make_number_concentrations.F90 b/physics/MP/Thompson/module_mp_thompson_make_number_concentrations.F90 index 72a1055dd..b00242966 100644 --- a/physics/MP/Thompson/module_mp_thompson_make_number_concentrations.F90 +++ b/physics/MP/Thompson/module_mp_thompson_make_number_concentrations.F90 @@ -2,6 +2,8 @@ !! This file contains !>\ingroup aathompson + +!>This module ocntains lookup tables of radiative effective radius of cloud ice, rain and water. module module_mp_thompson_make_number_concentrations use physcons, only: PI => con_pi diff --git a/physics/MP/Thompson/mp_thompson.F90 b/physics/MP/Thompson/mp_thompson.F90 index 3b99deec1..6bc6bcb98 100644 --- a/physics/MP/Thompson/mp_thompson.F90 +++ b/physics/MP/Thompson/mp_thompson.F90 @@ -3,7 +3,8 @@ !>\defgroup aathompson Aerosol-Aware Thompson MP Module -!! This module contains the aerosol-aware Thompson microphysics scheme. + +!> This module contains the aerosol-aware Thompson microphysics scheme. module mp_thompson use mpi_f08 diff --git a/physics/MP/Thompson/mp_thompson_post.F90 b/physics/MP/Thompson/mp_thompson_post.F90 index c48c932f7..7b333f2b1 100644 --- a/physics/MP/Thompson/mp_thompson_post.F90 +++ b/physics/MP/Thompson/mp_thompson_post.F90 @@ -1,3 +1,7 @@ +!> \file mp_thompson_post.F90 +!! + +!>This module contain the post processing of Thompson microphysics module mp_thompson_post use mpi_f08 @@ -15,7 +19,7 @@ module mp_thompson_post contains -!! \section arg_table_mp_thompson_post_init Argument Table +!> \section arg_table_mp_thompson_post_init Argument Table !! \htmlinclude mp_thompson_post_init.html !! subroutine mp_thompson_post_init(ttendlim, errmsg, errflg) @@ -125,7 +129,7 @@ subroutine mp_thompson_post_run(ncol, nlev, tgrs_save, tgrs, prslk, dtp, ttendli end subroutine mp_thompson_post_run -!! \section arg_table_mp_thompson_post_finalize Argument Table +!> \section arg_table_mp_thompson_post_finalize Argument Table !! \htmlinclude mp_thompson_post_finalize.html !! subroutine mp_thompson_post_finalize(errmsg, errflg) diff --git a/physics/MP/Thompson/mp_thompson_pre.F90 b/physics/MP/Thompson/mp_thompson_pre.F90 index 3e65fd478..3fe78e4d1 100644 --- a/physics/MP/Thompson/mp_thompson_pre.F90 +++ b/physics/MP/Thompson/mp_thompson_pre.F90 @@ -1,8 +1,9 @@ !>\file mp_thompson_pre.F90 !! -! CCPP license goes here, as well as further documentation !>\ingroup aathompson + +!> This module contains the pre-processing of Thompson cloud microphysics module mp_thompson_pre use machine, only : kind_phys diff --git a/physics/MP/calpreciptype.f90 b/physics/MP/calpreciptype.f90 index 2166e1b5c..792c0ba84 100644 --- a/physics/MP/calpreciptype.f90 +++ b/physics/MP/calpreciptype.f90 @@ -1,12 +1,11 @@ !>\file calpreciptype.f90 !! This file contains the subroutines that calculates dominant precipitation type. +!> This module defines four algorithms that are called to calculate dominant precipitation type, and the +!!tallies are sumed in calwxt_dominant(). module calpreciptype_mod contains -!>\ingroup gfs_calpreciptype -!! Foure algorithms are called to calculate dominant precipitation type, and the -!!tallies are sumed in calwxt_dominant(). -!! + !>\section gen_calp GFS calpreciptype General Algorithm subroutine calpreciptype(kdt,nrcm,im,ix,lm,lp1,randomno, & xlat,xlon, & @@ -215,10 +214,8 @@ subroutine calpreciptype(kdt,nrcm,im,ix,lm,lp1,randomno, & deallocate (twet,rh,td) return end -! -!&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&& -!>\ingroup gfs_calpreciptype -!! This subroutine computes precipitation type using a decision tree approach that uses + +!> This subroutine computes precipitation type using a decision tree approach that uses !! variables such as integrated wet bulb temperatue below freezing and lowest layer !! temperature (Baldwin et al. 1994 \cite baldwin_et_al_1994) subroutine calwxt(lm,lp1,t,q,pmid,pint, & @@ -472,7 +469,6 @@ subroutine calwxt(lm,lp1,t,q,pmid,pint, & ! ! code adapted for wrf post 24 august 2005 g manikin !ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc -!>\ingroup gfs_calpreciptype !> This subroutine is written and provided by Jim Ramer at NOAA/ESRL !!(Ramer (1993) \cite ramer_1993). subroutine calwxt_ramer(lm,lp1,t,q,pmid,rh,td,pint,ptyp) @@ -875,7 +871,6 @@ function xmytw(t,td,p) ! and layer lmh = bottom ! !$$$ -!>\ingroup gfs_calpreciptype !>this routine computes precipitation type using a decision tree !! approach that uses the so-called "energy method" of Bourgouin(2000) !! \cite bourgouin_2000. @@ -1044,7 +1039,6 @@ subroutine calwxt_bourg(lm,lp1,rn,g,t,q,pmid,pint,zint,ptype) return end ! -!>\ingroup gfs_calpreciptype !> This subroutine computes precipitation type using a decision tree !! approach that uses variables such as integrated wet bulb temperature !! below freezing and lowest layer temperature (Baldwin et al.1994 @@ -1307,7 +1301,6 @@ subroutine calwxt_revised(lm,lp1,t,q,pmid,pint, & return end ! -!>\ingroup gfs_calpreciptype !> This subroutine takes the precipitation type solutions from !! different algorithms and sums them up to give a dominant type. !! diff --git a/physics/MP/module_mp_radar.F90 b/physics/MP/module_mp_radar.F90 index 96a4348d0..bf290e516 100644 --- a/physics/MP/module_mp_radar.F90 +++ b/physics/MP/module_mp_radar.F90 @@ -68,8 +68,7 @@ MODULE module_mp_radar !+---+-----------------------------------------------------------------+ !+---+-----------------------------------------------------------------+ -!>\ingroup thompson_radar -!! +!> subroutine radar_init IMPLICIT NONE @@ -189,13 +188,11 @@ end subroutine radar_init !+---+-----------------------------------------------------------------+ !+---+-----------------------------------------------------------------+ -!>\ingroup thompson_radar - COMPLEX*16 FUNCTION m_complex_water_ray(lambda,T) - !> Complex refractive Index of Water as function of Temperature T !! [deg C] and radar wavelength lambda [m]; valid for !! lambda in [0.001,1.0] m; T in [-10.0,30.0] deg C !! after Ray (1972) + COMPLEX*16 FUNCTION m_complex_water_ray(lambda,T) IMPLICIT NONE DOUBLE PRECISION, INTENT(IN):: T,lambda @@ -264,8 +261,7 @@ END FUNCTION m_complex_ice_maetzler !+---+-----------------------------------------------------------------+ -!>ingroup thompson_radar -!! +!> subroutine rayleigh_soak_wetgraupel (x_g, a_geo, b_geo, fmelt, & meltratio_outside, m_w, m_i, lambda, C_back, & mixingrule,matrix,inclusion, & @@ -362,8 +358,7 @@ subroutine rayleigh_soak_wetgraupel (x_g, a_geo, b_geo, fmelt, & end subroutine rayleigh_soak_wetgraupel !+---+-----------------------------------------------------------------+ -!>\ingroup thompson_radar -!! +!> complex*16 function get_m_mix_nested (m_a, m_i, m_w, volair, & volice, volwater, mixingrule, host, matrix, & inclusion, hostmatrix, hostinclusion, cumulerror) @@ -493,8 +488,7 @@ complex*16 function get_m_mix_nested (m_a, m_i, m_w, volair, & end function get_m_mix_nested !+---+-----------------------------------------------------------------+ -!>\ingroup thompson_radar -!! +!> COMPLEX*16 FUNCTION get_m_mix (m_a, m_i, m_w, volair, volice, & volwater, mixingrule, matrix, inclusion, error) @@ -535,8 +529,7 @@ COMPLEX*16 FUNCTION get_m_mix (m_a, m_i, m_w, volair, volice, & END FUNCTION get_m_mix !+---+-----------------------------------------------------------------+ -!>\ingroup thompson_radar -!! +!> COMPLEX*16 FUNCTION m_complex_maxwellgarnett(vol1, vol2, vol3, & m1, m2, m3, inclusion, error) @@ -584,7 +577,7 @@ COMPLEX*16 FUNCTION m_complex_maxwellgarnett(vol1, vol2, vol3, & END FUNCTION m_complex_maxwellgarnett !+---+-----------------------------------------------------------------+ -!>\ingroup thompson_radar +!> REAL FUNCTION GAMMLN(XX) ! --- RETURNS THE VALUE LN(GAMMA(XX)) FOR XX > 0. IMPLICIT NONE @@ -610,7 +603,7 @@ REAL FUNCTION GAMMLN(XX) END FUNCTION GAMMLN ! (C) Copr. 1986-92 Numerical Recipes Software 2.02 !+---+-----------------------------------------------------------------+ -!>\ingroup thompson_radar +!> REAL FUNCTION WGAMMA(y) IMPLICIT NONE diff --git a/physics/PBL/MYNN_EDMF/bl_mynn_common.f90 b/physics/PBL/MYNN_EDMF/bl_mynn_common.f90 index 3e02f94b0..47b172808 100644 --- a/physics/PBL/MYNN_EDMF/bl_mynn_common.f90 +++ b/physics/PBL/MYNN_EDMF/bl_mynn_common.f90 @@ -7,7 +7,7 @@ !! module (module_bl_mynn) further below: !>\ingroup gp_mynnedmf -!! Define Model-specific constants/parameters +!! This module defines model-specific constants/parameters. module bl_mynn_common !------------------------------------------ diff --git a/physics/PBL/MYNN_EDMF/module_bl_mynn.F90 b/physics/PBL/MYNN_EDMF/module_bl_mynn.F90 index e7d483423..aa81e0999 100644 --- a/physics/PBL/MYNN_EDMF/module_bl_mynn.F90 +++ b/physics/PBL/MYNN_EDMF/module_bl_mynn.F90 @@ -248,6 +248,7 @@ ! Many of these changes are now documented in references listed above. !==================================================================== +!> This module contains the entity of MYNN-EDMF PBL scheme MODULE module_bl_mynn use bl_mynn_common,only: & @@ -350,12 +351,12 @@ MODULE module_bl_mynn CONTAINS ! ================================================================== -!>\ingroup gsd_mynn_edmf -!! This subroutine is the GSD MYNN-EDNF PBL driver routine,which +!>\ingroup gp_mynnedmf +!! This subroutine is the MYNN-EDNF PBL driver routine,which !! encompassed the majority of the subroutines that comprise the !! procedures that ultimately solve for tendencies of !! \f$U, V, \theta, q_v, q_c, and q_i\f$. -!!\section gen_mynn_bl_driver GSD mynn_bl_driver General Algorithm +!!\section gen_mynn_bl_driver mynn_bl_driver General Algorithm !> @{ SUBROUTINE mynn_bl_driver( & &initflag,restart,cycling, & @@ -1506,10 +1507,10 @@ END SUBROUTINE mynn_bl_driver ! !------------------------------------------------------------------- -!>\ingroup gsd_mynn_edmf +!>\ingroup gp_mynnedmf !! This subroutine initializes the mixing length, TKE, \f$\theta^{'2}\f$, !! \f$q^{'2}\f$, and \f$\theta^{'}q^{'}\f$. -!!\section gen_mym_ini GSD MYNN-EDMF mym_initialize General Algorithm +!!\section gen_mym_ini MYNN-EDMF mym_initialize General Algorithm !> @{ SUBROUTINE mym_initialize ( & & kts,kte,xland, & @@ -1692,7 +1693,7 @@ END SUBROUTINE mym_initialize ! These are defined on the walls of the grid boxes. ! -!>\ingroup gsd_mynn_edmf +!>\ingroup gp_mynnedmf !! This subroutine calculates the level 2, non-dimensional wind shear !! \f$G_M\f$ and vertical temperature gradient \f$G_H\f$ as well as !! the level 2 stability funcitons \f$S_h\f$ and \f$S_m\f$. @@ -1713,7 +1714,7 @@ END SUBROUTINE mym_initialize !!\param gh \f$G_H\f$ divided by \f$L^{2}/q^{2}\f$ (\f$s^{-2}\f$) !!\param sm stability function for momentum, at Level 2 !!\param sh stability function for heat, at Level 2 -!!\section gen_mym_level2 GSD MYNN-EDMF mym_level2 General Algorithm +!!\section gen_mym_level2 MYNN-EDMF mym_level2 General Algorithm !! @ { SUBROUTINE mym_level2 (kts,kte, & & dz, & @@ -1844,7 +1845,7 @@ END SUBROUTINE mym_level2 ! NOTE: the mixing lengths are meant to be calculated at the full- ! sigmal levels (or interfaces beween the model layers). ! -!>\ingroup gsd_mynn_edmf +!>\ingroup gp_mynnedmf !! This subroutine calculates the mixing lengths. SUBROUTINE mym_length ( & & kts,kte,xland, & @@ -2243,7 +2244,7 @@ SUBROUTINE mym_length ( & END SUBROUTINE mym_length ! ================================================================== -!>\ingroup gsd_mynn_edmf +!>\ingroup gp_mynnedmf !! This subroutine was taken from the BouLac scheme in WRF-ARW and modified for !! integration into the MYNN PBL scheme. WHILE loops were added to reduce the !! computational expense. This subroutine computes the length scales up and down @@ -2406,7 +2407,7 @@ SUBROUTINE boulac_length0(k,kts,kte,zw,dz,qtke,theta,lb1,lb2) END SUBROUTINE boulac_length0 ! ================================================================== -!>\ingroup gsd_mynn_edmf +!>\ingroup gp_mynnedmf !! This subroutine was taken from the BouLac scheme in WRF-ARW !! and modified for integration into the MYNN PBL scheme. !! WHILE loops were added to reduce the computational expense. @@ -2597,10 +2598,10 @@ END SUBROUTINE boulac_length ! # dtl, dqw, dtv, gm and gh are allowed to share storage units with ! dfm, dfh, dfq, tcd and qcd, respectively, for saving memory. ! -!>\ingroup gsd_mynn_edmf +!>\ingroup gp_mynnedmf !! This subroutine calculates the vertical diffusivity coefficients and the !! production terms for the turbulent quantities. -!>\section gen_mym_turbulence GSD mym_turbulence General Algorithm +!>\section gen_mym_turbulence mym_turbulence General Algorithm !! Two subroutines mym_level2() and mym_length() are called within this !!subrouine to collect variable to carry out successive calculations: !! - mym_level2() calculates the level 2 nondimensional wind shear \f$G_M\f$ @@ -3191,7 +3192,7 @@ END SUBROUTINE mym_turbulence ! scheme (program). ! !------------------------------------------------------------------- -!>\ingroup gsd_mynn_edmf +!>\ingroup gp_mynnedmf !! This subroutine predicts the turbulent quantities at the next step. SUBROUTINE mym_predict (kts,kte, & & closure, & @@ -3594,7 +3595,7 @@ END SUBROUTINE mym_predict ! Set these values to those adopted by you. ! !------------------------------------------------------------------- -!>\ingroup gsd_mynn_edmf +!>\ingroup gp_mynnedmf !! This subroutine calculates the nonconvective component of the !! subgrid cloud fraction and mixing ratio as well as the functions used to !! calculate the buoyancy flux. Different cloud PDFs can be selected by @@ -4021,7 +4022,7 @@ SUBROUTINE mym_condensation (kts,kte, & END SUBROUTINE mym_condensation ! ================================================================== -!>\ingroup gsd_mynn_edmf +!>\ingroup gp_mynnedmf !! This subroutine solves for tendencies of U, V, \f$\theta\f$, qv, !! qc, and qi SUBROUTINE mynn_tendencies(kts,kte,i, & @@ -5355,7 +5356,7 @@ SUBROUTINE mynn_mix_chem(kts,kte,i, & END SUBROUTINE mynn_mix_chem ! ================================================================== -!>\ingroup gsd_mynn_edmf +!>\ingroup gp_mynnedmf SUBROUTINE retrieve_exchange_coeffs(kts,kte,& &dfm,dfh,dz,K_m,K_h) @@ -5383,7 +5384,7 @@ SUBROUTINE retrieve_exchange_coeffs(kts,kte,& END SUBROUTINE retrieve_exchange_coeffs ! ================================================================== -!>\ingroup gsd_mynn_edmf +!>\ingroup gp_mynnedmf SUBROUTINE tridiag(n,a,b,c,d) !! to solve system of linear eqs on tridiagonal matrix n times n @@ -5419,7 +5420,7 @@ SUBROUTINE tridiag(n,a,b,c,d) END SUBROUTINE tridiag ! ================================================================== -!>\ingroup gsd_mynn_edmf +!>\ingroup gp_mynnedmf subroutine tridiag2(n,a,b,c,d,x) implicit none ! a - sub-diagonal (means it is the diagonal below the main diagonal) @@ -5454,7 +5455,7 @@ subroutine tridiag2(n,a,b,c,d,x) end subroutine tridiag2 ! ================================================================== -!>\ingroup gsd_mynn_edmf +!>\ingroup gp_mynnedmf subroutine tridiag3(kte,a,b,c,d,x) !ccccccccccccccccccccccccccccccc @@ -5496,7 +5497,7 @@ subroutine tridiag3(kte,a,b,c,d,x) end subroutine tridiag3 ! ================================================================== -!>\ingroup gsd_mynn_edmf +!>\ingroup gp_mynnedmf !! This subroutine calculates hybrid diagnotic boundary-layer height (PBLH). !! !! NOTES ON THE PBLH FORMULATION: The 1.5-theta-increase method defines @@ -5513,7 +5514,7 @@ end subroutine tridiag3 !!the TKE-method more during stable conditions (PBLH < 400 m). !!A variable tke threshold (TKEeps) is used since no hard-wired !!value could be found to work best in all conditions. -!>\section gen_get_pblh GSD get_pblh General Algorithm +!>\section gen_get_pblh get_pblh General Algorithm !> @{ SUBROUTINE GET_PBLH(KTS,KTE,zi,thetav1D,qke1D,zw1D,dz1D,landsea,kzi) @@ -5659,7 +5660,7 @@ END SUBROUTINE GET_PBLH !> @} ! ================================================================== -!>\ingroup gsd_mynn_edmf +!>\ingroup gp_mynnedmf !! This subroutine is the Dynamic Multi-Plume (DMP) Mass-Flux Scheme. !! !! dmp_mf() calculates the nonlocal turbulent transport from the dynamic @@ -6825,7 +6826,7 @@ SUBROUTINE DMP_mf( & END SUBROUTINE DMP_MF !================================================================= -!>\ingroup gsd_mynn_edmf +!>\ingroup gp_mynnedmf !! This subroutine subroutine condensation_edmf(QT,THL,P,zagl,THV,QC) ! @@ -7385,7 +7386,7 @@ SUBROUTINE SCALE_AWARE(dx,PBL1,Psig_bl,Psig_shcu) END SUBROUTINE SCALE_AWARE ! ===================================================================== -!>\ingroup gsd_mynn_edmf +!>\ingroup gp_mynnedmf !! \author JAYMES- added 22 Apr 2015 !! This function calculates saturation vapor pressure. Separate ice and liquid functions !! are used (identical to those in module_mp_thompson.F, v3.6). Then, the @@ -7439,7 +7440,7 @@ END FUNCTION esat_blend ! ==================================================================== -!>\ingroup gsd_mynn_edmf +!>\ingroup gp_mynnedmf !! This function extends function "esat" and returns a "blended" !! saturation mixing ratio. Tice currently set to 240 K, t0c = 273.15 K. !!\author JAYMES @@ -7496,7 +7497,7 @@ END FUNCTION qsat_blend ! =================================================================== -!>\ingroup gsd_mynn_edmf +!>\ingroup gp_mynnedmf !! This function interpolates the latent heats of vaporization and sublimation into !! a single, temperature-dependent, "blended" value, following !! Chaboureau and Bechtold (2002) \cite Chaboureau_2002, Appendix. diff --git a/physics/PBL/SATMEDMF/mfscu.f b/physics/PBL/SATMEDMF/mfscu.f index e0c184139..a9faa735e 100644 --- a/physics/PBL/SATMEDMF/mfscu.f +++ b/physics/PBL/SATMEDMF/mfscu.f @@ -1,6 +1,8 @@ !>\file mfscu.f !! This file contains the mass flux and downdraft parcel preperties !! parameterization for stratocumulus-top-driven turbulence. + + module mfscu_mod contains !>\ingroup satmedmf diff --git a/physics/PBL/SATMEDMF/mfscuq.f b/physics/PBL/SATMEDMF/mfscuq.f index d690dce05..b2a48d1b6 100644 --- a/physics/PBL/SATMEDMF/mfscuq.f +++ b/physics/PBL/SATMEDMF/mfscuq.f @@ -1,5 +1,7 @@ !>\file mfscuq.f -!! This file contains the mass flux and downdraft parcel preperties +!! + +!> This module contains the mass flux and downdraft parcel properties !! parameterization for stratocumulus-top-driven turbulence (updated version). module mfscuq_mod contains diff --git a/physics/PBL/SATMEDMF/satmedmfvdif.F b/physics/PBL/SATMEDMF/satmedmfvdif.F index 7e2d511f1..43995f88a 100644 --- a/physics/PBL/SATMEDMF/satmedmfvdif.F +++ b/physics/PBL/SATMEDMF/satmedmfvdif.F @@ -42,7 +42,6 @@ subroutine satmedmfvdif_init (satmedmf, end subroutine satmedmfvdif_init !> \defgroup satmedmf GFS Scale-aware TKE-based Moist Eddy-Diffusivity Mass-flux (TKE-EDMF) Scheme Module -!! @{ !! \brief This subroutine contains all of the logic for the !! scale-aware TKE-based moist eddy-diffusion mass-flux (TKE-EDMF) scheme. !! @@ -60,7 +59,6 @@ end subroutine satmedmfvdif_init !! -# A mass-flux approach is also used to represent the stratocumulus-top-induced turbulence !! (mfscu.f). !! \section detail_satmedmfvidf GFS satmedmfvdif Detailed Algorithm -!> @{ subroutine satmedmfvdif_run(im,km,ntrac,ntcw,ntiw,ntke, & & grav,rd,cp,rv,hvap,hfus,fv,eps,epsm1, & & dv,du,tdt,rtg,u1,v1,t1,q1,swh,hlw,xmu,garea, & @@ -1543,6 +1541,5 @@ subroutine satmedmfvdif_run(im,km,ntrac,ntcw,ntiw,ntke, & !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! return end subroutine satmedmfvdif_run -!> @} end module satmedmfvdif diff --git a/physics/PBL/SATMEDMF/satmedmfvdifq.F b/physics/PBL/SATMEDMF/satmedmfvdifq.F index 95a1e35e5..e8dbb0f91 100644 --- a/physics/PBL/SATMEDMF/satmedmfvdifq.F +++ b/physics/PBL/SATMEDMF/satmedmfvdifq.F @@ -1,8 +1,8 @@ !> \file satmedmfvdifq.F -!! This file contains the CCPP-compliant SATMEDMF scheme (updated version) which + +!> This file contains the CCPP-compliant SATMEDMF scheme (updated version) which !! computes subgrid vertical turbulence mixing using scale-aware TKE-based moist !! eddy-diffusion mass-flux (TKE-EDMF) parameterization (by Jongil Han). - module satmedmfvdifq use mfpbltq_mod use tridi_mod diff --git a/physics/PBL/mfpbl.f b/physics/PBL/mfpbl.f index dac548711..ef4fa3860 100644 --- a/physics/PBL/mfpbl.f +++ b/physics/PBL/mfpbl.f @@ -1,5 +1,8 @@ !> \file mfpbl.f !! This file contains the subroutine that calculates the updraft properties and mass flux for use in the Hybrid EDMF PBL scheme. + +!> This module contains the subroutine that calculates the updraft properties and mass flux +!! for use in the Hybrid EDMF PBL scheme. module mfpbl_mod contains !> \ingroup HEDMF diff --git a/physics/PBL/mfpblt.f b/physics/PBL/mfpblt.f index 67e554b92..68b8d67a7 100644 --- a/physics/PBL/mfpblt.f +++ b/physics/PBL/mfpblt.f @@ -1,6 +1,10 @@ !>\file mfpblt.f !! This file contains the subroutine that calculates mass flux and !! updraft parcel properties for thermals driven by surface heating +!! for use in the TKE-EDMF PBL scheme. + +!> This module contains the subroutine that calculates mass flux and +!! updraft parcel properties for thermals driven by surface heating !! for use in the TKE-EDMF PBL scheme. module mfpblt_mod contains diff --git a/physics/PBL/mfpbltq.f b/physics/PBL/mfpbltq.f index a93862a41..2812a7eab 100644 --- a/physics/PBL/mfpbltq.f +++ b/physics/PBL/mfpbltq.f @@ -1,5 +1,9 @@ !>\file mfpbltq.f -!! This file contains the subroutine that calculates mass flux and +!! This file contains the subroutine that computes mass flux and +!! updraft parcel properties for +!! thermals driven by surface heating + +!> This module contains the subroutine that calculates mass flux and !! updraft parcel properties for thermals driven by surface heating !! for use in the TKE-EDMF PBL scheme (updated version). module mfpbltq_mod diff --git a/physics/PBL/tridi.f b/physics/PBL/tridi.f index 13898ad43..28faaed2e 100644 --- a/physics/PBL/tridi.f +++ b/physics/PBL/tridi.f @@ -1,5 +1,8 @@ !>\file tridi.f !! These subroutines are originally internal subroutines in moninedmf.f + +!> This module contains routine to compute tridiagonal matrix elements for TKE, heat, moist +!! and momentum module tridi_mod contains diff --git a/physics/Radiation/RRTMG/iounitdef.f b/physics/Radiation/RRTMG/iounitdef.f index c6a4e591f..3f298b9d3 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 !!!!! !!!!! ========================================================== !!!!! @@ -44,6 +48,8 @@ !!!!! ========================================================== !!!!! !========================================! +!> this module defines fortran unit numbers for input/output data +!! files for the ncep gfs model. module module_iounitdef ! !........................................! ! 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/radlw_main.F90 b/physics/Radiation/RRTMG/radlw_main.F90 index cdf5c69ef..95ffd2f97 100644 --- a/physics/Radiation/RRTMG/radlw_main.F90 +++ b/physics/Radiation/RRTMG/radlw_main.F90 @@ -759,7 +759,7 @@ subroutine rrtmg_lw_run & end if endif ! end if_ilwcliq -!> -# Change random number seed value for each radiation invocation +!> - Change random number seed value for each radiation invocation !! (isubclw =1 or 2). if ( isubclw == 1 ) then ! advance prescribed permutation seed @@ -781,7 +781,7 @@ subroutine rrtmg_lw_run & lab_do_iplon : do iplon = 1, npts -!> -# Read surface emissivity. +!> - Read surface emissivity. if (sfemis(iplon) > eps .and. sfemis(iplon) <= 1.0) then ! input surface emissivity do j = 1, nbands semiss(j) = sfemis(iplon) @@ -795,7 +795,7 @@ subroutine rrtmg_lw_run & stemp = sfgtmp(iplon) ! surface ground temp if (iovr == iovr_dcorr) delgth= de_lgth(iplon) ! clouds decorr-length -!> -# Prepare atmospheric profile for use in rrtm. +!> - Prepare atmospheric profile for use in rrtm. ! the vertical index of internal array is from surface to top ! --- ... molecular amounts are input or converted to volume mixing ratio @@ -819,7 +819,7 @@ subroutine rrtmg_lw_run & dz(k) = dzlyr(iplon,k1) if (iovr == iovr_exp .or. iovr == iovr_exprand) alph(k) = alpha(iplon,k) ! alpha decorrelation -!> -# Set absorber amount for h2o, co2, and o3. +!> - Set absorber amount for h2o, co2, and o3. !test use ! h2ovmr(k)= max(f_zero,qlyr(iplon,k1)*amdw) ! input mass mixing ratio @@ -840,7 +840,7 @@ subroutine rrtmg_lw_run & colamt(k,3) = max(temcol(k), coldry(k)*o3vmr(k)) ! o3 enddo -!> -# Set up column amount for rare gases n2o,ch4,o2,co,ccl4,cf11,cf12, +!> - Set up column amount for rare gases n2o,ch4,o2,co,ccl4,cf11,cf12, !! cf22, convert from volume mixing ratio to molec/cm2 based on !! coldry (scaled to 1.0e-20). @@ -871,7 +871,7 @@ subroutine rrtmg_lw_run & enddo endif -!> -# Set aerosol optical properties. +!> - Set aerosol optical properties. do k = 1, nlay k1 = nlp1 - k @@ -881,7 +881,7 @@ subroutine rrtmg_lw_run & enddo enddo -!> -# Read cloud optical properties. +!> - Read cloud optical properties. if (ilwcliq > 0) then ! use prognostic cloud method do k = 1, nlay k1 = nlp1 - k @@ -906,7 +906,7 @@ subroutine rrtmg_lw_run & cldfrc(0) = f_one ! padding value only cldfrc(nlp1) = f_zero ! padding value only -!> -# Compute precipitable water vapor for diffusivity angle adjustments. +!> - Compute precipitable water vapor for diffusivity angle adjustments. tem1 = f_zero tem2 = f_zero @@ -1026,7 +1026,7 @@ subroutine rrtmg_lw_run & endif ! top_at_1 -!> -# Compute column amount for broadening gases. +!> - Compute column amount for broadening gases. do k = 1, nlay summol = f_zero @@ -1036,7 +1036,7 @@ subroutine rrtmg_lw_run & colbrd(k) = coldry(k) - summol enddo -!> -# Compute diffusivity angle adjustments. +!> - Compute diffusivity angle adjustments. tem1 = 1.80 tem2 = 1.50 @@ -1064,7 +1064,7 @@ subroutine rrtmg_lw_run & ! print *,' o3vmr ',o3vmr ! endif -!> -# For cloudy atmosphere, call cldprop() to set cloud optical +!> - For cloudy atmosphere, call cldprop() to set cloud optical !! properties. lcf1 = .false. @@ -1115,7 +1115,7 @@ subroutine rrtmg_lw_run & ! print *,' cldfrac',cldfrc ! endif -!> -# Calling setcoef() to compute various coefficients needed in +!> - Calling setcoef() to compute various coefficients needed in !! radiative transfer calculations. call setcoef & ! --- inputs: @@ -1150,7 +1150,7 @@ subroutine rrtmg_lw_run & ! print *,'indfor',indfor ! endif -!> -# Call taumol() to calculte the gaseous optical depths and Plank +!> - Call taumol() to calculte the gaseous optical depths and Plank !! fractions for each longwave spectral band. call taumol & @@ -1177,7 +1177,7 @@ subroutine rrtmg_lw_run & ! enddo ! endif -!> -# Call the radiative transfer routine based on cloud scheme +!> - Call the radiative transfer routine based on cloud scheme !! selection. Compute the upward/downward radiative fluxes, and !! heating rates for both clear or cloudy atmosphere. !!\n - call rtrn(): clouds are assumed as randomly overlaping in a @@ -1223,7 +1223,7 @@ subroutine rrtmg_lw_run & endif ! end if_isubclw_block -!> -# Save outputs. +!> - Save outputs. topflx(iplon)%upfxc = totuflux(nlay) topflx(iplon)%upfx0 = totuclfl(nlay) @@ -1441,11 +1441,11 @@ subroutine rlwinit( me, rad_hr_units, inc_minor_gas, ilwcliq, & endif endif -!> -# Setup default surface emissivity for each band. +!> - Setup default surface emissivity for each band. semiss0(:) = f_one -!> -# Setup constant factors for flux and heating rate +!> - Setup constant factors for flux and heating rate !! the 1.0e-2 is to convert pressure from mb to \f$N/m^2\f$. pival = 2.0 * asin(f_one) @@ -1460,7 +1460,7 @@ subroutine rlwinit( me, rad_hr_units, inc_minor_gas, ilwcliq, & heatfac = con_g * 1.0e-2 / con_cp ! (in k/second) endif -!> -# Compute lookup tables for transmittance, tau transition +!> - Compute lookup tables for transmittance, tau transition !! function, and clear sky tau (for the cloudy sky radiative !! transfer). tau is computed as a function of the tau !! transition function, transmittance is calculated as a @@ -1668,7 +1668,7 @@ subroutine cldprop & enddo enddo -!> -# Compute cloud radiative properties for a cloudy column: +!> - Compute cloud radiative properties for a cloudy column: !!\n - Compute cloud radiative properties for rain and snow (tauran,tausnw) !!\n - Calculation of absorption coefficients due to water clouds(tauliq) !!\n - Calculation of absorption coefficients due to ice clouds (tauice). @@ -1796,7 +1796,7 @@ subroutine cldprop & endif lab_if_ilwcliq -!> -# if GFS_typedefs::isubclw > 0, call mcica_subcol() to distribute +!> - if GFS_typedefs::isubclw > 0, call mcica_subcol() to distribute !! cloud properties to each g-point. if ( isubclw > 0 ) then ! mcica sub-col clouds approx @@ -1894,7 +1894,7 @@ subroutine mcica_subcol & ! !===> ... begin here ! -!> -# Call random_setseed() to advance randum number generator by ipseed values. +!> - Call random_setseed() to advance randum number generator by ipseed values. call random_setseed & ! --- inputs: @@ -1903,7 +1903,7 @@ subroutine mcica_subcol & & stat & & ) -!> -# Sub-column set up according to overlapping assumption: +!> - Sub-column set up according to overlapping assumption: !! - For random overlap, pick a random value at every level !! - For max-random overlap, pick a random value at every level !! - For maximum overlap, pick same random numebr at every level @@ -2092,7 +2092,7 @@ subroutine mcica_subcol & end select -!> -# Generate subcolumns for homogeneous clouds. +!> - Generate subcolumns for homogeneous clouds. do k = 1, nlay tem1 = f_one - cldf(k) @@ -2243,7 +2243,7 @@ subroutine setcoef & ! !===> ... begin here ! -!> -# Calculate information needed by the radiative transfer routine +!> - Calculate information needed by the radiative transfer routine !! that is specific to this atmosphere, especially some of the !! coefficients and indices needed to compute the optical depths !! by interpolating data from stored reference atmospheres. @@ -2260,7 +2260,7 @@ subroutine setcoef & enddo ! --- ... begin layer loop -!> -# Calculate the integrated Planck functions for each band at the +!> - Calculate the integrated Planck functions for each band at the !! surface, level, and layer temperatures. laytrop = 0 @@ -2282,7 +2282,7 @@ subroutine setcoef & & * (totplnk(indlev+1,i) - totplnk(indlev,i)) ) enddo -!> -# Find the two reference pressures on either side of the +!> - Find the two reference pressures on either side of the !! layer pressure. store them in jp and jp1. store in fp the !! fraction of the difference (in ln(pressure)) between these !! two values that the layer pressure lies. @@ -2294,7 +2294,7 @@ subroutine setcoef & fp = max(f_zero, min(f_one, 5.0*(preflog(jp(k))-plog) )) !org fp = 5.0 * (preflog(jp(k)) - plog) -!> -# Determine, for each reference pressure (jp and jp1), which +!> - Determine, for each reference pressure (jp and jp1), which !! reference temperature (these are different for each !! reference pressure) is nearest the layer temperature but does !! not exceed it. store these indices in jt and jt1, resp. @@ -2312,7 +2312,7 @@ subroutine setcoef & !org ft = tem1 - float(jt (k) - 3) !org ft1 = tem2 - float(jt1(k) - 3) -!> -# We have now isolated the layer ln pressure and temperature, +!> - We have now isolated the layer ln pressure and temperature, !! between two reference pressures and two reference temperatures !!(for each reference pressure). we multiply the pressure !! fraction fp with the appropriate temperature fractions to get @@ -2328,7 +2328,7 @@ subroutine setcoef & forfac(k) = pavel(k)*stpfac / (tavel(k)*(1.0 + h2ovmr(k))) selffac(k) = h2ovmr(k) * forfac(k) -!> -# Set up factors needed to separately include the minor gases +!> - Set up factors needed to separately include the minor gases !! in the calculation of absorption coefficient. scaleminor(k) = pavel(k) / tavel(k) @@ -2338,7 +2338,7 @@ subroutine setcoef & indminor(k) = min(18, max(1, int(tem1))) minorfrac(k) = tem1 - float(indminor(k)) -!> -# If the pressure is less than ~100mb, perform a different +!> - If the pressure is less than ~100mb, perform a different !! set of species interpolations. if (plog > 4.56) then @@ -2349,14 +2349,14 @@ subroutine setcoef & indfor(k) = min(2, max(1, int(tem1))) forfrac(k) = tem1 - float(indfor(k)) -!> -# Set up factors needed to separately include the water vapor +!> - Set up factors needed to separately include the water vapor !! self-continuum in the calculation of absorption coefficient. tem1 = (tavel(k) - 188.0) / 7.2 indself(k) = min(9, max(1, int(tem1)-7)) selffrac(k) = tem1 - float(indself(k) + 7) -!> -# Setup reference ratio to be used in calculation of binary +!> - Setup reference ratio to be used in calculation of binary !! species parameter in lower atmosphere. rfrate(k,1,1) = chi_mls(1,jp(k)) / chi_mls(2,jp(k)) @@ -2383,7 +2383,7 @@ subroutine setcoef & indself(k) = 0 selffrac(k) = f_zero -!> -# Setup reference ratio to be used in calculation of binary +!> - Setup reference ratio to be used in calculation of binary !! species parameter in upper atmosphere. rfrate(k,1,1) = chi_mls(1,jp(k)) / chi_mls(2,jp(k)) @@ -2394,7 +2394,7 @@ subroutine setcoef & endif -!> -# Rescale \a selffac and \a forfac for use in taumol. +!> - Rescale \a selffac and \a forfac for use in taumol. selffac(k) = colamt(k,1) * selffac(k) forfac(k) = colamt(k,1) * forfac(k) @@ -2613,7 +2613,7 @@ subroutine rtrn & radtotd = f_zero radclrd = f_zero -!> -# Downward radiative transfer loop. +!> - Downward radiative transfer loop. do k = nlay, 1, -1 @@ -2692,7 +2692,7 @@ subroutine rtrn & enddo ! end do_k_loop -!> -# Compute spectral emissivity & reflectance, include the +!> - Compute spectral emissivity & reflectance, include the !! contribution of spectrally varying longwave emissivity and !! reflection from the surface to the upward radiative transfer. @@ -2702,15 +2702,15 @@ subroutine rtrn & reflct = f_one - semiss(ib) rad0 = semiss(ib) * fracs(ig,1) * pklay(ib,0) -!> -# Compute total sky radiance. +!> - Compute total sky radiance. radtotu = rad0 + reflct*radtotd toturad(0,ib) = toturad(0,ib) + radtotu -!> -# Compute clear sky radiance +!> - Compute clear sky radiance radclru = rad0 + reflct*radclrd clrurad(0,ib) = clrurad(0,ib) + radclru -!> -# Upward radiative transfer loop. +!> - Upward radiative transfer loop. do k = 1, nlay clfr = cldfrc(k) @@ -2746,7 +2746,7 @@ subroutine rtrn & enddo ! end do_ig_loop -!> -# Process longwave output from band for total and clear streams. +!> - Process longwave output from band for total and clear streams. !! Calculate upward, downward, and net flux. flxfac = wtdiff * fluxfac @@ -2999,7 +2999,7 @@ subroutine rtrnmr & if (cldfrc(k) > eps) then -!> -# Setup maximum/random cloud overlap. +!> - Setup maximum/random cloud overlap. if (cldfrc(k+1) >= cldfrc(k)) then if (lstcldu(k)) then @@ -3143,7 +3143,7 @@ subroutine rtrnmr & enddo -!> -# Initialize for radiative transfer +!> - Initialize for radiative transfer do ib = 1, NBANDS do k = 0, NLAY @@ -3169,7 +3169,7 @@ subroutine rtrnmr & radtotd = f_zero radclrd = f_zero -!> -# Downward radiative transfer loop: +!> - Downward radiative transfer loop: do k = nlay, 1, -1 @@ -3266,7 +3266,7 @@ subroutine rtrnmr & enddo ! end do_k_loop -!> -# Compute spectral emissivity & reflectance, include the +!> - Compute spectral emissivity & reflectance, include the !! contribution of spectrally varying longwave emissivity and !! reflection from the surface to the upward radiative transfer. @@ -3276,15 +3276,15 @@ subroutine rtrnmr & reflct = f_one - semiss(ib) rad0 = semiss(ib) * fracs(ig,1) * pklay(ib,0) -!> -# Compute total sky radiance. +!> - Compute total sky radiance. radtotu = rad0 + reflct*radtotd toturad(0,ib) = toturad(0,ib) + radtotu -!> -# Compute clear sky radiance. +!> - Compute clear sky radiance. radclru = rad0 + reflct*radclrd clrurad(0,ib) = clrurad(0,ib) + radclru -!> -# Upward radiative transfer loop: +!> - Upward radiative transfer loop: do k = 1, nlay @@ -3338,7 +3338,7 @@ subroutine rtrnmr & enddo ! end do_ig_loop -!> -# Process longwave output from band for total and clear streams. +!> - Process longwave output from band for total and clear streams. !! calculate upward, downward, and net flux. flxfac = wtdiff * fluxfac @@ -3588,7 +3588,7 @@ subroutine rtrnmc & radtotd = f_zero radclrd = f_zero -!> -# Downward radiative transfer loop. +!> - Downward radiative transfer loop. !!\n - Clear sky, gases contribution !!\n - Total sky, gases+clouds contribution !!\n - Cloudy layer @@ -3672,7 +3672,7 @@ subroutine rtrnmc & enddo ! end do_k_loop -!> -# Compute spectral emissivity & reflectance, include the +!> - Compute spectral emissivity & reflectance, include the !! contribution of spectrally varying longwave emissivity and !! reflection from the surface to the upward radiative transfer. @@ -3682,15 +3682,15 @@ subroutine rtrnmc & reflct = f_one - semiss(ib) rad0 = semiss(ib) * fracs(ig,1) * pklay(ib,0) -!> -# Compute total sky radiance. +!> - Compute total sky radiance. radtotu = rad0 + reflct*radtotd toturad(0,ib) = toturad(0,ib) + radtotu -!> -# Compute clear sky radiance. +!> - Compute clear sky radiance. radclru = rad0 + reflct*radclrd clrurad(0,ib) = clrurad(0,ib) + radclru -!> -# Upward radiative transfer loop. +!> - Upward radiative transfer loop. !!\n - Compute total sky radiance !!\n - Compute clear sky radiance @@ -3731,7 +3731,7 @@ subroutine rtrnmc & enddo ! end do_ig_loop -!> -# Process longwave output from band for total and clear streams. +!> - Process longwave output from band for total and clear streams. !! Calculate upward, downward, and net flux. flxfac = wtdiff * fluxfac @@ -3750,7 +3750,7 @@ subroutine rtrnmc & totdclfl(k) = totdclfl(k) * flxfac enddo -!> -# Calculate net fluxes and heating rates. +!> - Calculate net fluxes and heating rates. fnet(0) = totuflux(0) - totdflux(0) do k = 1, nlay @@ -3759,7 +3759,7 @@ subroutine rtrnmc & htr (k) = (fnet(k-1) - fnet(k)) * rfdelp(k) enddo -!> -# Optional clear sky heating rates. +!> - Optional clear sky heating rates. if ( lhlw0 ) then fnetc(0) = totuclfl(0) - totdclfl(0) @@ -3769,7 +3769,7 @@ subroutine rtrnmc & enddo endif -!> -# Optional spectral band heating rates. +!> - Optional spectral band heating rates. if ( lhlwb ) then do ib = 1, nbands fnet(0) = (toturad(0,ib) - totdrad(0,ib)) * flxfac diff --git a/physics/Radiation/RRTMG/rrtmg_lw_cloud_optics.F90 b/physics/Radiation/RRTMG/rrtmg_lw_cloud_optics.F90 index 1dd225514..082428b08 100644 --- a/physics/Radiation/RRTMG/rrtmg_lw_cloud_optics.F90 +++ b/physics/Radiation/RRTMG/rrtmg_lw_cloud_optics.F90 @@ -1,13 +1,17 @@ +!>\file rrtmg_lw_cloud_optics.F90 +!! + +!>This module contains the cloud optics property module for RRTMG-LW module mo_rrtmg_lw_cloud_optics use machine, only: kind_phys use mersenne_twister, only: random_setseed, random_number, random_stat implicit none - !< Parameter used for RRTMG cloud-optics + !> Parameter used for RRTMG cloud-optics integer,parameter :: & nBandsLW_RRTMG = 16 - !< ipat is bands index for ebert & curry ice cloud (for iflagice=1) + !> ipat is bands index for ebert & curry ice cloud (for iflagice=1) integer,dimension(nBandsLW_RRTMG),parameter :: & ipat = (/ 1, 2, 3, 3, 3, 4, 4, 4, 5, 5, 5, 5, 5, 5, 5, 5 /) real(kind_phys), parameter :: & @@ -15,7 +19,7 @@ module mo_rrtmg_lw_cloud_optics abssnow0 = 1.5, & !< Snow flake absorption coefficient (micron), fu coeff abssnow1 = 2.34e-3 !< Snow flake absorption coefficient \f$(m^{2}/g)\f$, ncar coef - !< Reset diffusivity angle for Bands 2-3 and 5-9 to vary (between 1.50 + !> Reset diffusivity angle for Bands 2-3 and 5-9 to vary (between 1.50 !! and 1.80) as a function of total column water vapor. the function !! has been defined to minimize flux and cooling rate errors in these bands !! over a wide range of precipitable water values. @@ -32,7 +36,7 @@ module mo_rrtmg_lw_cloud_optics diffusivityHigh = 1.80, & !< Maximum diffusivity angle for bands 2-3 and 5-9 diffusivityB1410 = 1.66 !< Diffusivity for bands 1, 4, and 10 - !< RRTMG LW cloud property coefficients + !> RRTMG LW cloud property coefficients real(kind_phys) , dimension(58,nBandsLW_RRTMG),parameter :: & absliq1 = reshape(source=(/ & 1.64047e-03, 6.90533e-02, 7.72017e-02, 7.78054e-02, 7.69523e-02, & !1 diff --git a/physics/Radiation/RRTMG/rrtmg_lw_post.F90 b/physics/Radiation/RRTMG/rrtmg_lw_post.F90 index d9d3aa520..36661973d 100644 --- a/physics/Radiation/RRTMG/rrtmg_lw_post.F90 +++ b/physics/Radiation/RRTMG/rrtmg_lw_post.F90 @@ -1,5 +1,6 @@ !>\file rrtmg_lw_post.F90 -!!This file contains GFS RRTMG scheme post. + +!> This module contains code executed after RRTMG-LW scheme module rrtmg_lw_post contains diff --git a/physics/Radiation/RRTMG/rrtmg_sw_cloud_optics.F90 b/physics/Radiation/RRTMG/rrtmg_sw_cloud_optics.F90 index 01cab76e2..ea38f85cd 100644 --- a/physics/Radiation/RRTMG/rrtmg_sw_cloud_optics.F90 +++ b/physics/Radiation/RRTMG/rrtmg_sw_cloud_optics.F90 @@ -1,3 +1,7 @@ +!>\file rrtmg_sw_cloud_optics.F90 +!! + +!> This module contains the cloud optics property module for RRTMG-SW module mo_rrtmg_sw_cloud_optics use machine, only: kind_phys use mersenne_twister, only: random_setseed, random_number, random_stat diff --git a/physics/Radiation/RRTMG/rrtmg_sw_post.F90 b/physics/Radiation/RRTMG/rrtmg_sw_post.F90 index f39cba71c..893c093e9 100644 --- a/physics/Radiation/RRTMG/rrtmg_sw_post.F90 +++ b/physics/Radiation/RRTMG/rrtmg_sw_post.F90 @@ -1,5 +1,6 @@ !>\file rrtmg_sw_post.F90 -!! This file contains GFS RRTMG scheme post. + +!> This module contains RRTMG-SW scheme post module rrtmg_sw_post contains diff --git a/physics/Radiation/RRTMGP/rrtmgp_aerosol_optics.F90 b/physics/Radiation/RRTMGP/rrtmgp_aerosol_optics.F90 index 7e78c19a3..974d71b9a 100644 --- a/physics/Radiation/RRTMGP/rrtmgp_aerosol_optics.F90 +++ b/physics/Radiation/RRTMGP/rrtmgp_aerosol_optics.F90 @@ -1,6 +1,7 @@ !>\file rrtmgp_aerosol_optics.F90 !! +!> This module contains aerosol optics properties for RRTMGP module rrtmgp_aerosol_optics use machine, only: kind_phys use radiation_tools, only: check_error_msg @@ -15,13 +16,7 @@ module rrtmgp_aerosol_optics contains - ! ######################################################################################### - ! SUBROUTINE rrtmgp_aerosol_optics_run() - ! ######################################################################################### - -!>\defgroup rrtmgp_aerosol_optics_mod GFS RRTMGP Aerosol Optics Module -!> @{ -!! \section arg_table_rrtmgp_aerosol_optics_run +!> \section arg_table_rrtmgp_aerosol_optics_run Argument Table !! \htmlinclude rrtmgp_aerosol_optics_run.html !! subroutine rrtmgp_aerosol_optics_run(doSWrad, doLWrad, nCol, nLev, nDay, idxday, p_lev, & @@ -125,5 +120,4 @@ subroutine rrtmgp_aerosol_optics_run(doSWrad, doLWrad, nCol, nLev, nDay, idxday, endif end subroutine rrtmgp_aerosol_optics_run -!> @} end module rrtmgp_aerosol_optics diff --git a/physics/Radiation/RRTMGP/rrtmgp_lw_cloud_optics.F90 b/physics/Radiation/RRTMGP/rrtmgp_lw_cloud_optics.F90 index 059086a97..df44fbeda 100644 --- a/physics/Radiation/RRTMGP/rrtmgp_lw_cloud_optics.F90 +++ b/physics/Radiation/RRTMGP/rrtmgp_lw_cloud_optics.F90 @@ -1,13 +1,11 @@ !> \file rrtmgp_lw_cloud_optics.F90 !! -!> \defgroup rrtmgp_lw_cloud_optics rrtmgp_lw_cloud_optics.F90 -!! -!! \brief This module contains two routines: The first initializes data and functions + +!> This module contains two routines: The first initializes data and functions !! needed to compute the longwave cloud radiative properteis in RRTMGP. The second routine !! is a ccpp scheme within the "radiation loop", where the shortwave optical prperties !! (optical-depth, single-scattering albedo, asymmetry parameter) are computed for ALL !! cloud types visible to RRTMGP. -!! module rrtmgp_lw_cloud_optics use machine, only: kind_phys use mo_rte_kind, only: wl @@ -26,80 +24,81 @@ module rrtmgp_lw_cloud_optics nrghice_fromfileLW, nBandLW, nSize_liqLW, nSize_iceLW, nSizeRegLW, & nCoeff_extLW, nCoeff_ssa_gLW, nBoundLW, npairsLW real(kind_phys) :: & - radliq_facLW, & ! Factor for calculating LUT interpolation indices for liquid - radice_facLW ! Factor for calculating LUT interpolation indices for ice + radliq_facLW, & !< Factor for calculating LUT interpolation indices for liquid + radice_facLW !< Factor for calculating LUT interpolation indices for ice real(kind_phys), dimension(:,:), allocatable :: & - lut_extliqLW, & ! LUT shortwave liquid extinction coefficient - lut_ssaliqLW, & ! LUT shortwave liquid single scattering albedo - lut_asyliqLW, & ! LUT shortwave liquid asymmetry parameter - band_limsCLDLW ! Beginning and ending wavenumber [cm -1] for each band + lut_extliqLW, & !< LUT shortwave liquid extinction coefficient + lut_ssaliqLW, & !< LUT shortwave liquid single scattering albedo + lut_asyliqLW, & !< LUT shortwave liquid asymmetry parameter + band_limsCLDLW !< Beginning and ending wavenumber [cm -1] for each band real(kind_phys), dimension(:,:,:), allocatable :: & - lut_exticeLW, & ! LUT shortwave ice extinction coefficient - lut_ssaiceLW, & ! LUT shortwave ice single scattering albedo - lut_asyiceLW ! LUT shortwave ice asymmetry parameter + lut_exticeLW, & !< LUT shortwave ice extinction coefficient + lut_ssaiceLW, & !< LUT shortwave ice single scattering albedo + lut_asyiceLW !< LUT shortwave ice asymmetry parameter real(kind_phys), dimension(:), allocatable :: & - pade_sizereg_extliqLW, & ! Particle size regime boundaries for shortwave liquid extinction - ! coefficient for Pade interpolation - pade_sizereg_ssaliqLW, & ! Particle size regime boundaries for shortwave liquid single - ! scattering albedo for Pade interpolation - pade_sizereg_asyliqLW, & ! Particle size regime boundaries for shortwave liquid asymmetry - ! parameter for Pade interpolation - pade_sizereg_exticeLW, & ! Particle size regime boundaries for shortwave ice extinction - ! coefficient for Pade interpolation - pade_sizereg_ssaiceLW, & ! Particle size regime boundaries for shortwave ice single - ! scattering albedo for Pade interpolation - pade_sizereg_asyiceLW ! Particle size regime boundaries for shortwave ice asymmetry - ! parameter for Pade interpolation + pade_sizereg_extliqLW, & !< Particle size regime boundaries for shortwave liquid extinction + !< coefficient for Pade interpolation + pade_sizereg_ssaliqLW, & !< Particle size regime boundaries for shortwave liquid single + !< scattering albedo for Pade interpolation + pade_sizereg_asyliqLW, & !< Particle size regime boundaries for shortwave liquid asymmetry + !< parameter for Pade interpolation + pade_sizereg_exticeLW, & !< Particle size regime boundaries for shortwave ice extinction + !< coefficient for Pade interpolation + pade_sizereg_ssaiceLW, & !< Particle size regime boundaries for shortwave ice single + !< scattering albedo for Pade interpolation + pade_sizereg_asyiceLW !< Particle size regime boundaries for shortwave ice asymmetry + !< parameter for Pade interpolation real(kind_phys), dimension(:,:,:), allocatable :: & - pade_extliqLW, & ! PADE coefficients for shortwave liquid extinction - pade_ssaliqLW, & ! PADE coefficients for shortwave liquid single scattering albedo - pade_asyliqLW ! PADE coefficients for shortwave liquid asymmetry parameter + pade_extliqLW, & !< PADE coefficients for shortwave liquid extinction + pade_ssaliqLW, & !< PADE coefficients for shortwave liquid single scattering albedo + pade_asyliqLW !< PADE coefficients for shortwave liquid asymmetry parameter real(kind_phys), dimension(:,:,:,:), allocatable :: & - pade_exticeLW, & ! PADE coefficients for shortwave ice extinction - pade_ssaiceLW, & ! PADE coefficients for shortwave ice single scattering albedo - pade_asyiceLW ! PADE coefficients for shortwave ice asymmetry parameter + pade_exticeLW, & !< PADE coefficients for shortwave ice extinction + pade_ssaiceLW, & !< PADE coefficients for shortwave ice single scattering albedo + pade_asyiceLW !< PADE coefficients for shortwave ice asymmetry parameter ! Parameters used for rain and snow(+groupel) RRTMGP cloud-optics real(kind_phys), parameter :: & - absrain = 0.33e-3, & ! Rain drop absorption coefficient \f$(m^{2}/g)\f$ . - abssnow0 = 1.5, & ! Snow flake absorption coefficient (micron), fu coeff - abssnow1 = 2.34e-3 ! Snow flake absorption coefficient \f$(m^{2}/g)\f$, ncar coef + absrain = 0.33e-3, & !< Rain drop absorption coefficient m2/g . + abssnow0 = 1.5, & !< Snow flake absorption coefficient (micron), fu coeff + abssnow1 = 2.34e-3 !< Snow flake absorption coefficient m2/g, ncar coef real(kind_phys) :: & - radliq_lwrLW, & ! Liquid particle size lower bound for LUT interpolation - radliq_uprLW, & ! Liquid particle size upper bound for LUT interpolation - radice_lwrLW, & ! Ice particle size upper bound for LUT interpolation - radice_uprLW ! Ice particle size lower bound for LUT interpolation + radliq_lwrLW, & !< Liquid particle size lower bound for LUT interpolation + radliq_uprLW, & !< Liquid particle size upper bound for LUT interpolation + radice_lwrLW, & !< Ice particle size upper bound for LUT interpolation + radice_uprLW !< Ice particle size lower bound for LUT interpolation contains ! ###################################################################################### ! SUBROUTINE rrtmgp_lw_cloud_optics_init() ! ###################################################################################### +!> subroutine rrtmgp_lw_cloud_optics_init(rrtmgp_root_dir, rrtmgp_lw_file_clouds, & doGP_cldoptics_PADE, doGP_cldoptics_LUT, nrghice, mpicomm, mpirank, mpiroot, & errmsg, errflg) ! Inputs character(len=128),intent(in) :: & - rrtmgp_root_dir, & ! RTE-RRTMGP root directory - rrtmgp_lw_file_clouds ! RRTMGP file containing clouds optics data + rrtmgp_root_dir, & !< RTE-RRTMGP root directory + rrtmgp_lw_file_clouds !< RRTMGP file containing clouds optics data logical, intent(in) :: & - doGP_cldoptics_PADE,& ! Use RRTMGP cloud-optics: PADE approximation? - doGP_cldoptics_LUT ! Use RRTMGP cloud-optics: LUTs? + doGP_cldoptics_PADE,& !< Use RRTMGP cloud-optics: PADE approximation? + doGP_cldoptics_LUT !< Use RRTMGP cloud-optics: LUTs? 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 + mpirank, & !< Current MPI rank + mpiroot !< Master MPI rank ! Outputs character(len=*), intent(out) :: & - errmsg ! Error message + errmsg !< Error message integer, intent(out) :: & - errflg ! Error code + errflg !< Error code ! Local variables integer :: dimID,varID,status,ncid,mpierr diff --git a/physics/Radiation/RRTMGP/rrtmgp_lw_gas_optics.F90 b/physics/Radiation/RRTMGP/rrtmgp_lw_gas_optics.F90 index 7cf80e3f3..0bfdd87e5 100644 --- a/physics/Radiation/RRTMGP/rrtmgp_lw_gas_optics.F90 +++ b/physics/Radiation/RRTMGP/rrtmgp_lw_gas_optics.F90 @@ -1,12 +1,10 @@ !> \file rrtmgp_lw_gas_optics.F90 !! -!> \defgroup rrtmgp_lw_gas_optics rrtmgp_lw_gas_optics.F90 -!! -!! \brief This module contains two routines: One to initialize the k-distribution data + +!> This module contains two routines: One to initialize the k-distribution data !! and functions needed to compute the longwave gaseous optical properties in RRTMGP. !! The second routine is a ccpp scheme within the "radiation loop", where the longwave !! optical prperties (optical-depth) are computed for clear-sky conditions (no aerosols). -!! module rrtmgp_lw_gas_optics use machine, only: kind_phys use mo_rte_kind, only: wl @@ -27,77 +25,75 @@ module rrtmgp_lw_gas_optics nminor_absorber_intervals_lowerLW, nminor_absorber_intervals_upperLW, & ncontributors_lowerLW, ncontributors_upperLW, nfit_coeffsLW integer, dimension(:), allocatable :: & - kminor_start_lowerLW, & ! Starting index in the [1, nContributors] vector for a contributor - ! given by \"minor_gases_lower\" (lower atmosphere) - kminor_start_upperLW ! Starting index in the [1, nContributors] vector for a contributor - ! given by \"minor_gases_upper\" (upper atmosphere) + kminor_start_lowerLW, & !< Starting index in the [1, nContributors] vector for a contributor + !< given by \"minor_gases_lower\" (lower atmosphere) + kminor_start_upperLW !< Starting index in the [1, nContributors] vector for a contributor + !< given by \"minor_gases_upper\" (upper atmosphere) integer, dimension(:,:), allocatable :: & - band2gptLW, & ! Beginning and ending gpoint for each band - minor_limits_gpt_lowerLW, & ! Beginning and ending gpoint for each minor interval in lower atmosphere - minor_limits_gpt_upperLW ! Beginning and ending gpoint for each minor interval in upper atmosphere + band2gptLW, & !< Beginning and ending gpoint for each band + minor_limits_gpt_lowerLW, & !< Beginning and ending gpoint for each minor interval in lower atmosphere + minor_limits_gpt_upperLW !< Beginning and ending gpoint for each minor interval in upper atmosphere integer, dimension(:,:,:), allocatable :: & - key_speciesLW ! Key species pair for each band + key_speciesLW !< Key species pair for each band real(kind_phys) :: & - press_ref_tropLW, & ! Reference pressure separating the lower and upper atmosphere [Pa] - temp_ref_pLW, & ! Standard spectroscopic reference pressure [Pa] - temp_ref_tLW ! Standard spectroscopic reference temperature [K] + press_ref_tropLW, & !< Reference pressure separating the lower and upper atmosphere [Pa] + temp_ref_pLW, & !< Standard spectroscopic reference pressure [Pa] + temp_ref_tLW !< Standard spectroscopic reference temperature [K] real(kind_phys), dimension(:), allocatable :: & - press_refLW, & ! Pressures for reference atmosphere; press_ref(# reference layers) [Pa] - temp_refLW ! Temperatures for reference atmosphere; temp_ref(# reference layers) [K] + press_refLW, & !< Pressures for reference atmosphere; press_ref(# reference layers) [Pa] + temp_refLW !< Temperatures for reference atmosphere; temp_ref(# reference layers) [K] real(kind_phys), dimension(:,:), allocatable :: & - band_limsLW, & ! Beginning and ending wavenumber [cm -1] for each band - totplnkLW, & ! Integrated Planck function by band + band_limsLW, & !< Beginning and ending wavenumber [cm -1] for each band + totplnkLW, & !< Integrated Planck function by band optimal_angle_fitLW real(kind_phys), dimension(:,:,:), allocatable :: & - vmr_refLW, & ! volume mixing ratios for reference atmospherer - kminor_lowerLW, & ! (transformed from [nTemp x nEta x nGpt x nAbsorbers] array to - ! [nTemp x nEta x nContributors] array) - kminor_upperLW, & ! (transformed from [nTemp x nEta x nGpt x nAbsorbers] array to - ! [nTemp x nEta x nContributors] array) - rayl_lowerLW, & ! Not used in LW, rather allocated(rayl_lower) is used - rayl_upperLW ! Not used in LW, rather allocated(rayl_upper) is used + vmr_refLW, & !< volume mixing ratios for reference atmospherer + kminor_lowerLW, & !< (transformed from [nTemp x nEta x nGpt x nAbsorbers] array to + !< [nTemp x nEta x nContributors] array) + kminor_upperLW, & !< (transformed from [nTemp x nEta x nGpt x nAbsorbers] array to + !< [nTemp x nEta x nContributors] array) + rayl_lowerLW, & !< Not used in LW, rather allocated(rayl_lower) is used + rayl_upperLW !< Not used in LW, rather allocated(rayl_upper) is used real(kind_phys), dimension(:,:,:,:), allocatable :: & - kmajorLW, & ! Stored absorption coefficients due to major absorbing gases - planck_fracLW ! Planck fractions + kmajorLW, & !< Stored absorption coefficients due to major absorbing gases + planck_fracLW !< Planck fractions character(len=32), dimension(:), allocatable :: & - gas_namesLW, & ! Names of absorbing gases - gas_minorLW, & ! Name of absorbing minor gas - identifier_minorLW, & ! Unique string identifying minor gas - minor_gases_lowerLW, & ! Names of minor absorbing gases in lower atmosphere - minor_gases_upperLW, & ! Names of minor absorbing gases in upper atmosphere - scaling_gas_lowerLW, & ! Absorption also depends on the concentration of this gas - scaling_gas_upperLW ! Absorption also depends on the concentration of this gas + gas_namesLW, & !< Names of absorbing gases + gas_minorLW, & !< Name of absorbing minor gas + identifier_minorLW, & !< Unique string identifying minor gas + minor_gases_lowerLW, & !< Names of minor absorbing gases in lower atmosphere + minor_gases_upperLW, & !< Names of minor absorbing gases in upper atmosphere + scaling_gas_lowerLW, & !< Absorption also depends on the concentration of this gas + scaling_gas_upperLW !< Absorption also depends on the concentration of this gas logical(wl), dimension(:), allocatable :: & - minor_scales_with_density_lowerLW, & ! Density scaling is applied to minor absorption coefficients - minor_scales_with_density_upperLW, & ! Density scaling is applied to minor absorption coefficients - scale_by_complement_lowerLW, & ! Absorption is scaled by concentration of scaling_gas (F) or its complement (T) - scale_by_complement_upperLW ! Absorption is scaled by concentration of scaling_gas (F) or its complement (T) + minor_scales_with_density_lowerLW, & !< Density scaling is applied to minor absorption coefficients + minor_scales_with_density_upperLW, & !< Density scaling is applied to minor absorption coefficients + scale_by_complement_lowerLW, & !< Absorption is scaled by concentration of scaling_gas (F) or its complement (T) + scale_by_complement_upperLW !< Absorption is scaled by concentration of scaling_gas (F) or its complement (T) contains - ! ######################################################################################### - ! SUBROUTINE rrtmgp_lw_gas_optics_init - ! ######################################################################################### +!> subroutine rrtmgp_lw_gas_optics_init(rrtmgp_root_dir, rrtmgp_lw_file_gas, & active_gases_array, mpicomm, mpirank, mpiroot, errmsg, errflg) ! Inputs character(len=128),intent(in) :: & - rrtmgp_root_dir, & ! RTE-RRTMGP root directory - rrtmgp_lw_file_gas ! RRTMGP file containing K-distribution data + rrtmgp_root_dir, & !< RTE-RRTMGP root directory + rrtmgp_lw_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 :: ncid, dimID, varID, status, ii, mpierr, iChar diff --git a/physics/Radiation/RRTMGP/rrtmgp_lw_main.F90 b/physics/Radiation/RRTMGP/rrtmgp_lw_main.F90 index 82a5e274a..2e8de2dd4 100644 --- a/physics/Radiation/RRTMGP/rrtmgp_lw_main.F90 +++ b/physics/Radiation/RRTMGP/rrtmgp_lw_main.F90 @@ -1,11 +1,7 @@ -! ########################################################################################### !> \file rrtmgp_lw_main.F90 -!! -!> \defgroup rrtmgp_lw_main rrtmgp_lw_main.F90 -!! -!! \brief This module contains the longwave RRTMGP radiation scheme. -!! -! ########################################################################################### +!! This file contains the longwave RRTMGP radiation scheme. + +!> This module contains the RRTMGP-LW radiation scheme module rrtmgp_lw_main use mpi_f08 use machine, only: kind_phys, kind_dbl_prec @@ -29,17 +25,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, & @@ -47,33 +36,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), optional :: & - 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 = '' @@ -89,18 +78,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, & @@ -613,5 +594,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_sampling.F90 b/physics/Radiation/RRTMGP/rrtmgp_sampling.F90 index 9e2360083..a678d3163 100644 --- a/physics/Radiation/RRTMGP/rrtmgp_sampling.F90 +++ b/physics/Radiation/RRTMGP/rrtmgp_sampling.F90 @@ -1,4 +1,5 @@ -! This code is part of RRTM for GCM Applications - Parallel (RRTMGP) +!>\file rrtmgp_sampling.F90 +!! This code is part of RRTM for GCM Applications - Parallel (RRTMGP) ! ! Contacts: Robert Pincus and Eli Mlawer ! email: rrtmgp@aer.com @@ -10,8 +11,8 @@ ! BSD 3-clause license, see http://opensource.org/licenses/BSD-3-Clause ! ------------------------------------------------------------------------------------------------- ! -! This module provides a simple implementation of sampling for the -! Monte Carlo Independent Pixel Approximation (McICA, doi:10.1029/2002jd003322) +!> This module provides a simple implementation of sampling for the +!! Monte Carlo Independent Pixel Approximation (McICA, doi:10.1029/2002jd003322) ! Cloud optical properties, defined by band and assumed homogenous within each cell (column/layer), ! are randomly sampled to preserve the mean cloud fraction and one of several possible overlap assumptions ! Users supply random numbers with order ngpt,nlay,ncol @@ -30,12 +31,8 @@ module rrtmgp_sampling private public :: draw_samples, sampled_mask contains - ! ------------------------------------------------------------------------------------------------- - ! - ! Apply a T/F sampled cloud mask to cloud optical properties defined by band to produce - ! McICA-sampled cloud optical properties - ! - ! ------------------------------------------------------------------------------------------------- +!> Apply a T/F sampled cloud mask to cloud optical properties defined by band to produce +!! McICA-sampled cloud optical properties function draw_samples(cloud_mask,do_twostream,clouds,clouds_sampled) result(error_msg) ! Inputs logical, dimension(:,:,:), intent(in ) :: cloud_mask ! Dimensions ncol,nlay,ngpt @@ -76,11 +73,8 @@ function draw_samples(cloud_mask,do_twostream,clouds,clouds_sampled) result(erro end select end select end function draw_samples - ! ------------------------------------------------------------------------------------------------- - ! - ! Generate a McICA-sampled cloud mask - ! - ! ------------------------------------------------------------------------------------------------- + +!> Generate a McICA-sampled cloud mask subroutine sampled_mask(randoms, cloud_frac, cloud_mask, overlap_param, randoms2) ! Inputs real(wp), dimension(:,:,:), intent(in ) :: randoms ! ngpt,nlay,ncol @@ -180,12 +174,9 @@ subroutine sampled_mask(randoms, cloud_frac, cloud_mask, overlap_param, randoms2 end do ! END LOOP: Columns end subroutine sampled_mask - ! ------------------------------------------------------------------------------------------------- - ! - ! Apply a true/false cloud mask to a homogeneous field - ! This could be a kernel - ! - ! ------------------------------------------------------------------------------------------------- + +!> Apply a true/false cloud mask to a homogeneous field +!! This could be a kernel subroutine apply_cloud_mask(ncol,nlay,nbnd,ngpt,band_lims_gpt,cloud_mask,input_field,sampled_field) integer, intent(in ) :: ncol,nlay,nbnd,ngpt integer, dimension(2,nbnd), intent(in ) :: band_lims_gpt diff --git a/physics/Radiation/RRTMGP/rrtmgp_sw_cloud_optics.F90 b/physics/Radiation/RRTMGP/rrtmgp_sw_cloud_optics.F90 index 552fda295..d7d54846f 100644 --- a/physics/Radiation/RRTMGP/rrtmgp_sw_cloud_optics.F90 +++ b/physics/Radiation/RRTMGP/rrtmgp_sw_cloud_optics.F90 @@ -1,3 +1,7 @@ +!>\file rrtmgp_sw_cloud_optics.F90 +!! + +!> This module contains the cloud optics properties calculation for RRTMGP-SW module rrtmgp_sw_cloud_optics use machine, only: kind_phys use mo_rte_kind, only: wl @@ -16,43 +20,43 @@ module rrtmgp_sw_cloud_optics nrghice_fromfileSW, nBandSW, nSize_liqSW, nSize_iceSW, nSizeregSW, & nCoeff_extSW, nCoeff_ssa_gSW, nBoundSW, nPairsSW real(kind_phys) :: & - radliq_facSW, & ! Factor for calculating LUT interpolation indices for liquid - radice_facSW ! Factor for calculating LUT interpolation indices for ice + radliq_facSW, & !< Factor for calculating LUT interpolation indices for liquid + radice_facSW !< Factor for calculating LUT interpolation indices for ice real(kind_phys), dimension(:,:), allocatable :: & - lut_extliqSW, & ! LUT shortwave liquid extinction coefficient - lut_ssaliqSW, & ! LUT shortwave liquid single scattering albedo - lut_asyliqSW, & ! LUT shortwave liquid asymmetry parameter - band_limsCLDSW ! Beginning and ending wavenumber [cm -1] for each band + lut_extliqSW, & !< LUT shortwave liquid extinction coefficient + lut_ssaliqSW, & !< LUT shortwave liquid single scattering albedo + lut_asyliqSW, & !< LUT shortwave liquid asymmetry parameter + band_limsCLDSW !< Beginning and ending wavenumber [cm -1] for each band real(kind_phys), dimension(:,:,:), allocatable :: & - lut_exticeSW, & ! LUT shortwave ice extinction coefficient - lut_ssaiceSW, & ! LUT shortwave ice single scattering albedo - lut_asyiceSW ! LUT shortwave ice asymmetry parameter + lut_exticeSW, & !< LUT shortwave ice extinction coefficient + lut_ssaiceSW, & !< LUT shortwave ice single scattering albedo + lut_asyiceSW !< LUT shortwave ice asymmetry parameter real(kind_phys), dimension(:), allocatable :: & - pade_sizereg_extliqSW, & ! Particle size regime boundaries for shortwave liquid extinction - ! coefficient for Pade interpolation - pade_sizereg_ssaliqSW, & ! Particle size regime boundaries for shortwave liquid single - ! scattering albedo for Pade interpolation - pade_sizereg_asyliqSW, & ! Particle size regime boundaries for shortwave liquid asymmetry - ! parameter for Pade interpolation - pade_sizereg_exticeSW, & ! Particle size regime boundaries for shortwave ice extinction - ! coefficient for Pade interpolation - pade_sizereg_ssaiceSW, & ! Particle size regime boundaries for shortwave ice single - ! scattering albedo for Pade interpolation - pade_sizereg_asyiceSW ! Particle size regime boundaries for shortwave ice asymmetry - ! parameter for Pade interpolation + pade_sizereg_extliqSW, & !< Particle size regime boundaries for shortwave liquid extinction + !< coefficient for Pade interpolation + pade_sizereg_ssaliqSW, & !< Particle size regime boundaries for shortwave liquid single + !< scattering albedo for Pade interpolation + pade_sizereg_asyliqSW, & !< Particle size regime boundaries for shortwave liquid asymmetry + !< parameter for Pade interpolation + pade_sizereg_exticeSW, & !< Particle size regime boundaries for shortwave ice extinction + !< coefficient for Pade interpolation + pade_sizereg_ssaiceSW, & !< Particle size regime boundaries for shortwave ice single + !< scattering albedo for Pade interpolation + pade_sizereg_asyiceSW !< Particle size regime boundaries for shortwave ice asymmetry + !< parameter for Pade interpolation real(kind_phys), dimension(:,:,:), allocatable :: & - pade_extliqSW, & ! PADE coefficients for shortwave liquid extinction - pade_ssaliqSW, & ! PADE coefficients for shortwave liquid single scattering albedo - pade_asyliqSW ! PADE coefficients for shortwave liquid asymmetry parameter + pade_extliqSW, & !< PADE coefficients for shortwave liquid extinction + pade_ssaliqSW, & !< PADE coefficients for shortwave liquid single scattering albedo + pade_asyliqSW !< PADE coefficients for shortwave liquid asymmetry parameter real(kind_phys), dimension(:,:,:,:), allocatable :: & - pade_exticeSW, & ! PADE coefficients for shortwave ice extinction - pade_ssaiceSW, & ! PADE coefficients for shortwave ice single scattering albedo - pade_asyiceSW ! PADE coefficients for shortwave ice asymmetry parameter + pade_exticeSW, & !< PADE coefficients for shortwave ice extinction + pade_ssaiceSW, & !< PADE coefficients for shortwave ice single scattering albedo + pade_asyiceSW !< PADE coefficients for shortwave ice asymmetry parameter real(kind_phys) :: & - radliq_lwrSW, & ! Liquid particle size lower bound for LUT interpolation - radliq_uprSW, & ! Liquid particle size upper bound for LUT interpolation - radice_lwrSW, & ! Ice particle size upper bound for LUT interpolation - radice_uprSW ! Ice particle size lower bound for LUT interpolation + radliq_lwrSW, & !< Liquid particle size lower bound for LUT interpolation + radliq_uprSW, & !< Liquid particle size upper bound for LUT interpolation + radice_lwrSW, & !< Ice particle size upper bound for LUT interpolation + radice_uprSW !< Ice particle size lower bound for LUT interpolation ! Parameters used for rain and snow(+groupel) RRTMGP cloud-optics. *NOTE* Same as in RRTMG ! Need to document these magic numbers below. @@ -66,30 +70,31 @@ module rrtmgp_sw_cloud_optics ! ###################################################################################### ! SUBROUTINE sw_cloud_optics_init ! ###################################################################################### +!> subroutine rrtmgp_sw_cloud_optics_init( rrtmgp_root_dir, rrtmgp_sw_file_clouds, & doGP_cldoptics_PADE, doGP_cldoptics_LUT, nrghice, mpicomm, mpirank, mpiroot, & errmsg, errflg) ! Inputs character(len=128),intent(in) :: & - rrtmgp_root_dir, & ! RTE-RRTMGP root directory - rrtmgp_sw_file_clouds ! RRTMGP file containing cloud-optic data + rrtmgp_root_dir, & !< RTE-RRTMGP root directory + rrtmgp_sw_file_clouds !< RRTMGP file containing cloud-optic data logical, intent(in) :: & - doGP_cldoptics_PADE,& ! Use RRTMGP cloud-optics: PADE approximation? - doGP_cldoptics_LUT ! Use RRTMGP cloud-optics: LUTs? + doGP_cldoptics_PADE,& !< Use RRTMGP cloud-optics: PADE approximation? + doGP_cldoptics_LUT !< Use RRTMGP cloud-optics: LUTs? 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 + 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 diff --git a/physics/Radiation/RRTMGP/rrtmgp_sw_gas_optics.F90 b/physics/Radiation/RRTMGP/rrtmgp_sw_gas_optics.F90 index 5713d188d..7872bc04d 100644 --- a/physics/Radiation/RRTMGP/rrtmgp_sw_gas_optics.F90 +++ b/physics/Radiation/RRTMGP/rrtmgp_sw_gas_optics.F90 @@ -1,10 +1,8 @@ !> \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 @@ -29,93 +27,84 @@ module rrtmgp_sw_gas_optics nmixingfracsSW, nlayersSW, nbndsSW, npairsSW, nminor_absorber_intervals_lowerSW,& nminor_absorber_intervals_upperSW, ncontributors_lowerSW, ncontributors_upperSW integer, dimension(:), allocatable :: & - kminor_start_lowerSW, & ! Starting index in the [1, nContributors] vector for a contributor - ! given by \"minor_gases_lower\" (lower atmosphere) - kminor_start_upperSW ! Starting index in the [1, nContributors] vector for a contributor - ! given by \"minor_gases_upper\" (upper atmosphere) + kminor_start_lowerSW, & !< Starting index in the [1, nContributors] vector for a contributor + !< given by \"minor_gases_lower\" (lower atmosphere) + kminor_start_upperSW !< Starting index in the [1, nContributors] vector for a contributor + !< given by \"minor_gases_upper\" (upper atmosphere) integer, dimension(:,:), allocatable :: & - band2gptSW, & ! Beginning and ending gpoint for each band - minor_limits_gpt_lowerSW, & ! Beginning and ending gpoint for each minor interval in lower atmosphere - minor_limits_gpt_upperSW ! Beginning and ending gpoint for each minor interval in upper atmosphere + band2gptSW, & !< Beginning and ending gpoint for each band + minor_limits_gpt_lowerSW, & !< Beginning and ending gpoint for each minor interval in lower atmosphere + minor_limits_gpt_upperSW !< Beginning and ending gpoint for each minor interval in upper atmosphere integer, dimension(:,:,:), allocatable :: & - key_speciesSW ! Key species pair for each band + key_speciesSW !< Key species pair for each band real(kind_phys) :: & - press_ref_tropSW, & ! Reference pressure separating the lower and upper atmosphere [Pa] - temp_ref_pSW, & ! Standard spectroscopic reference pressure [Pa] - temp_ref_tSW, & ! Standard spectroscopic reference temperature [K] - tsi_defaultSW, & ! - mg_defaultSW, & ! Mean value of Mg2 index over the average solar cycle from the NRLSSI2 model of solar variability - sb_defaultSW ! Mean value of sunspot index over the average solar cycle from the NRLSSI2 model of solar variability + press_ref_tropSW, & !< Reference pressure separating the lower and upper atmosphere [Pa] + temp_ref_pSW, & !< Standard spectroscopic reference pressure [Pa] + temp_ref_tSW, & !< Standard spectroscopic reference temperature [K] + tsi_defaultSW, & !< + mg_defaultSW, & !< Mean value of Mg2 index over the average solar cycle from the NRLSSI2 model of solar variability + sb_defaultSW !< Mean value of sunspot index over the average solar cycle from the NRLSSI2 model of solar variability real(kind_phys), dimension(:), allocatable :: & - press_refSW, & ! Pressures for reference atmosphere; press_ref(# reference layers) [Pa] - temp_refSW, & ! Temperatures for reference atmosphere; temp_ref(# reference layers) [K] - solar_quietSW, & ! Spectrally-dependent quiet sun irradiance from the NRLSSI2 model of solar variability - solar_facularSW, & ! Spectrally-dependent facular term from the NRLSSI2 model of solar variability - solar_sunspotSW ! Spectrally-dependent sunspot term from the NRLSSI2 model of solar variability + press_refSW, & !< Pressures for reference atmosphere; press_ref(# reference layers) [Pa] + temp_refSW, & !< Temperatures for reference atmosphere; temp_ref(# reference layers) [K] + solar_quietSW, & !< Spectrally-dependent quiet sun irradiance from the NRLSSI2 model of solar variability + solar_facularSW, & !< Spectrally-dependent facular term from the NRLSSI2 model of solar variability + solar_sunspotSW !< Spectrally-dependent sunspot term from the NRLSSI2 model of solar variability real(kind_phys), dimension(:,:), allocatable :: & - band_limsSW ! Beginning and ending wavenumber [cm -1] for each band + band_limsSW !< Beginning and ending wavenumber [cm -1] for each band real(kind_phys), dimension(:,:,:), allocatable :: & - vmr_refSW, & ! Volume mixing ratios for reference atmosphere - kminor_lowerSW, & ! (transformed from [nTemp x nEta x nGpt x nAbsorbers] array to - ! [nTemp x nEta x nContributors] array) - kminor_upperSW, & ! (transformed from [nTemp x nEta x nGpt x nAbsorbers] array to - ! [nTemp x nEta x nContributors] array) - rayl_lowerSW, & ! Stored coefficients due to rayleigh scattering contribution - rayl_upperSW ! Stored coefficients due to rayleigh scattering contribution + vmr_refSW, & !< Volume mixing ratios for reference atmosphere + kminor_lowerSW, & !< (transformed from [nTemp x nEta x nGpt x nAbsorbers] array to + !< [nTemp x nEta x nContributors] array) + kminor_upperSW, & !< (transformed from [nTemp x nEta x nGpt x nAbsorbers] array to + !< [nTemp x nEta x nContributors] array) + rayl_lowerSW, & !< Stored coefficients due to rayleigh scattering contribution + rayl_upperSW !< Stored coefficients due to rayleigh scattering contribution real(kind_phys), dimension(:,:,:,:), allocatable :: & - kmajorSW ! Stored absorption coefficients due to major absorbing gases + kmajorSW !< Stored absorption coefficients due to major absorbing gases character(len=32), dimension(:), allocatable :: & - gas_namesSW, & ! Names of absorbing gases - gas_minorSW, & ! Name of absorbing minor gas - identifier_minorSW, & ! Unique string identifying minor gas - minor_gases_lowerSW, & ! Names of minor absorbing gases in lower atmosphere - minor_gases_upperSW, & ! Names of minor absorbing gases in upper atmosphere - scaling_gas_lowerSW, & ! Absorption also depends on the concentration of this gas - scaling_gas_upperSW ! Absorption also depends on the concentration of this gas + gas_namesSW, & !< Names of absorbing gases + gas_minorSW, & !< Name of absorbing minor gas + identifier_minorSW, & !< Unique string identifying minor gas + minor_gases_lowerSW, & !< Names of minor absorbing gases in lower atmosphere + minor_gases_upperSW, & !< Names of minor absorbing gases in upper atmosphere + scaling_gas_lowerSW, & !< Absorption also depends on the concentration of this gas + scaling_gas_upperSW !< Absorption also depends on the concentration of this gas logical(wl), dimension(:), allocatable :: & - minor_scales_with_density_lowerSW, & ! Density scaling is applied to minor absorption coefficients - minor_scales_with_density_upperSW, & ! Density scaling is applied to minor absorption coefficients - scale_by_complement_lowerSW, & ! Absorption is scaled by concentration of scaling_gas (F) or its complement (T) - scale_by_complement_upperSW ! Absorption is scaled by concentration of scaling_gas (F) or its complement (T) + minor_scales_with_density_lowerSW, & !< Density scaling is applied to minor absorption coefficients + minor_scales_with_density_upperSW, & !< Density scaling is applied to minor absorption coefficients + scale_by_complement_lowerSW, & !< Absorption is scaled by concentration of scaling_gas (F) or its complement (T) + 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 +486,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 fb0fe2052..2138356a9 100644 --- a/physics/Radiation/RRTMGP/rrtmgp_sw_main.F90 +++ b/physics/Radiation/RRTMGP/rrtmgp_sw_main.F90 @@ -1,5 +1,7 @@ -! ########################################################################################### -! ########################################################################################### +!>\file rrtmgp_sw_main.F90 +!! + +!> This module contain the RRTMGP-SW radiation scheme module rrtmgp_sw_main use mpi_f08 use machine, only: kind_phys, kind_dbl_prec @@ -25,10 +27,7 @@ module rrtmgp_sw_main contains - ! ######################################################################################### - ! SUBROUTINE rrtmgp_sw_main_init - ! ######################################################################################### -!! \section arg_table_rrtmgp_sw_main_init +!> \section arg_table_rrtmgp_sw_main_init Argument Table !! \htmlinclude rrtmgp_sw_main_init.html !! subroutine rrtmgp_sw_main_init(rrtmgp_root_dir, rrtmgp_sw_file_gas, rrtmgp_sw_file_clouds,& @@ -38,30 +37,30 @@ subroutine rrtmgp_sw_main_init(rrtmgp_root_dir, rrtmgp_sw_file_gas, rrtmgp_sw_fi ! Inputs character(len=128),intent(in) :: & - rrtmgp_root_dir, & ! RTE-RRTMGP root directory - rrtmgp_sw_file_clouds, & ! RRTMGP file containing K-distribution data - rrtmgp_sw_file_gas ! RRTMGP file containing cloud-optics data + rrtmgp_root_dir, & !< RTE-RRTMGP root directory + rrtmgp_sw_file_clouds, & !< RRTMGP file containing K-distribution data + rrtmgp_sw_file_gas !< RRTMGP file containing cloud-optics data character(len=*), dimension(:), intent(in), optional :: & - 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 = '' @@ -78,10 +77,7 @@ subroutine rrtmgp_sw_main_init(rrtmgp_root_dir, rrtmgp_sw_file_gas, rrtmgp_sw_fi end subroutine rrtmgp_sw_main_init - ! ######################################################################################### - ! SUBROUTINE rrtmgp_sw_main_run - ! ######################################################################################### -!! \section arg_table_rrtmgp_sw_main_run +!> \section arg_table_rrtmgp_sw_main_run Argument Table !! \htmlinclude rrtmgp_sw_main_run.html !! subroutine rrtmgp_sw_main_run(doSWrad, doSWclrsky, top_at_1, doGP_sgs_cnv, doGP_sgs_pbl, & diff --git a/physics/Radiation/mersenne_twister.f b/physics/Radiation/mersenne_twister.f index 58bf43487..bdd0da080 100644 --- a/physics/Radiation/mersenne_twister.f +++ b/physics/Radiation/mersenne_twister.f @@ -2,10 +2,10 @@ !! This file contains the module that calculates random numbers using the !! Mersenne twister -!> \defgroup mersenne_ge Mersenne Twister Module -!! Module: mersenne_twister Modern random number generator -!!\author Iredell Org: W/NX23 date: 2005-06-14 -!! Abstract: This module calculates random numbers using the Mersenne twister. +! Module: mersenne_twister Modern random number generator +!\author Iredell Org: W/NX23 date: 2005-06-14 +!> This module calculates random numbers using the Mersenne twister. +!! !! (It has been adapted to a Fortran 90 module from open source software. !! The comments from the original software are given below in the remarks.) !! The Mersenne twister (aka MT19937) is a state-of-the-art random number diff --git a/physics/Radiation/radiation_aerosols.f b/physics/Radiation/radiation_aerosols.f index bbd2f25cb..983d592c1 100644 --- a/physics/Radiation/radiation_aerosols.f +++ b/physics/Radiation/radiation_aerosols.f @@ -122,9 +122,9 @@ !!!!! ========================================================== !!!!! -!========================================! - module module_radiation_aerosols ! -!........................................! +!> This module contains climatological atmospheric aerosol schemes for +!! radiation computations. + module module_radiation_aerosols ! use machine, only : kind_phys, kind_io4, kind_io8 use module_iounitdef, only : NIAERCM @@ -3871,6 +3871,8 @@ subroutine gocart_aerinit & ! ================= !----------------------------- +!> read GMAO pre-tabultaed aerosol optical data for dust, seasalt, ! +!! sulfate, black carbon, and organic carbon aerosols subroutine rd_gocart_luts !............................. ! --- inputs: (in scope variables, module variables) @@ -4073,6 +4075,10 @@ end subroutine rd_gocart_luts !----------------------------------- !-------------------------------- +!> compute mean aerosol optical properties over each sw radiation +!! spectral band for each of the species components. This program +!! follows optavg routine (in turn follows gfdl's approach for thick +!! cloud opertical property in sw radiation scheme (2000). subroutine optavg_gocart !................................ ! --- inputs: (in-scope variables, module variables) @@ -4527,6 +4533,8 @@ subroutine aer_property_gocart & ! ================= !-------------------------------- +!> compute aerosols optical properties in NSWLWBD bands for gocart +!! aerosol species subroutine aeropt !................................ diff --git a/physics/Radiation/radiation_cloud_overlap.F90 b/physics/Radiation/radiation_cloud_overlap.F90 index 737b9be61..358db5cd0 100644 --- a/physics/Radiation/radiation_cloud_overlap.F90 +++ b/physics/Radiation/radiation_cloud_overlap.F90 @@ -1,8 +1,7 @@ !>\file radiation_cloud_overlap.F90 !! -!>\defgroup rad_cld_ovr_mod Radiation Cloud Overlap Module -!! This module contains the calculation of cloud overlap parameters for both RRTMG and RRTMGP. +!> This module contains the calculation of cloud overlap parameters for both RRTMG and RRTMGP. module module_radiation_cloud_overlap use machine, only : kind_phys implicit none @@ -15,9 +14,6 @@ module module_radiation_cloud_overlap contains -!>\defgroup rad_cld_ovr_mod Radiation Cloud Overlap Module -!! This module contains the calculation of cloud overlap parameters for both RRTMG and RRTMGP. -!>@{ ! ###################################################################################### ! Hogan et al. (2010) ! "Effect of improving representation of horizontal and vertical cloud structure on the @@ -92,9 +88,6 @@ subroutine cmp_dcorr_lgth_oreopoulos(nCol, lat, juldat, yearlength, dcorr_lgth) end subroutine cmp_dcorr_lgth_oreopoulos - ! ###################################################################################### - ! - ! ###################################################################################### !>This subroutine provides the alpha cloud overlap parameter for both RRTMG and RRTMGP subroutine get_alpha_exper(nCol, nLay, iovr, iovr_exprand, dzlay, & dcorr_lgth, cld_frac, alpha) @@ -143,5 +136,4 @@ subroutine get_alpha_exper(nCol, nLay, iovr, iovr_exprand, dzlay, & return end subroutine get_alpha_exper -!>@} end module module_radiation_cloud_overlap diff --git a/physics/Radiation/radiation_clouds.f b/physics/Radiation/radiation_clouds.f index 979405cdb..286b2535b 100644 --- a/physics/Radiation/radiation_clouds.f +++ b/physics/Radiation/radiation_clouds.f @@ -1712,7 +1712,7 @@ end subroutine progcld_gfdl_lin !----------------------------------- !----------------------------------- -!! This subroutine computes cloud related quantities using +!> This subroutine computes cloud related quantities using !! Ferrier-Aligo cloud microphysics scheme. subroutine progcld_fer_hires & & ( plyr,plvl,tlyr,tvly,qlyr,qstl,rhly,clw, & ! --- inputs: @@ -1960,7 +1960,7 @@ end subroutine progcld_fer_hires !................................... -! This subroutine is used by Thompson/WSM6/NSSL cloud microphysics (EMC) +!> This subroutine is used by Thompson/WSM6/NSSL cloud microphysics (EMC) subroutine progcld_thompson_wsm6 & & ( plyr,plvl,tlyr,qlyr,qstl,rhly,clw, & ! --- inputs: & xlat,xlon,slmsk,dz,delp, & diff --git a/physics/Radiation/radiation_tools.F90 b/physics/Radiation/radiation_tools.F90 index 28384f32a..e941a3461 100644 --- a/physics/Radiation/radiation_tools.F90 +++ b/physics/Radiation/radiation_tools.F90 @@ -1,6 +1,7 @@ !>\file radiation_tools.F90 !! +!> This module contains tools for radiation module radiation_tools use machine, only: & kind_phys ! Working type @@ -11,8 +12,7 @@ module radiation_tools rrtmgp_minT ! Minimum temperature allowed in RRTMGP contains - ! ######################################################################################### - ! ######################################################################################### +!> subroutine cmp_tlev(nCol,nLev,minP,p_lay,t_lay,p_lev,tsfc,t_lev) ! Inputs integer, intent(in) :: & @@ -83,9 +83,7 @@ subroutine cmp_tlev(nCol,nLev,minP,p_lay,t_lay,p_lev,tsfc,t_lev) end subroutine cmp_tlev - ! ######################################################################################### - ! SUBROUTINE check_error_msg - ! ######################################################################################### +!> subroutine check_error_msg(routine_name, error_msg) character(len=*), intent(in) :: & error_msg, routine_name diff --git a/physics/SFC_Layer/GFDL/gfdl_sfc_layer.F90 b/physics/SFC_Layer/GFDL/gfdl_sfc_layer.F90 index e235acc52..ce6501908 100644 --- a/physics/SFC_Layer/GFDL/gfdl_sfc_layer.F90 +++ b/physics/SFC_Layer/GFDL/gfdl_sfc_layer.F90 @@ -1,4 +1,4 @@ -!> \file gfdl_sfc_layer.f +!> \file gfdl_sfc_layer.F90 !! This file contains ... !> This module contains the CCPP-compliant GFDL surface layer scheme. diff --git a/physics/SFC_Layer/GFDL/module_sf_exchcoef.f90 b/physics/SFC_Layer/GFDL/module_sf_exchcoef.f90 index 6ec9ed835..e82fd4371 100644 --- a/physics/SFC_Layer/GFDL/module_sf_exchcoef.f90 +++ b/physics/SFC_Layer/GFDL/module_sf_exchcoef.f90 @@ -1,4 +1,5 @@ -! This MODULE holds the routines that calculate air-sea exchange coefficients +!>\file module_sf_exchcoef.f90 +!! This MODULE holds the routines that calculate air-sea exchange coefficients MODULE module_sf_exchcoef CONTAINS diff --git a/physics/SFC_Layer/MYNN/module_sf_mynn.F90 b/physics/SFC_Layer/MYNN/module_sf_mynn.F90 index 588cb0898..06db25441 100644 --- a/physics/SFC_Layer/MYNN/module_sf_mynn.F90 +++ b/physics/SFC_Layer/MYNN/module_sf_mynn.F90 @@ -3,6 +3,8 @@ !WRF:MODEL_LAYER:PHYSICS ! !>\ingroup mynn_sfc +!> This module contain routines to calculate stability parameters, kinematic siscosity +!! in MYNN surface layer scheme MODULE module_sf_mynn !------------------------------------------------------------------- @@ -3173,19 +3175,18 @@ SUBROUTINE znot_m_v6(uref, znotm) END SUBROUTINE znot_m_v6 !-------------------------------------------------------------------- !>\ingroup mynn_sfc -!! - SUBROUTINE znot_t_v6(uref, znott) - - !$acc routine seq - IMPLICIT NONE -!> Calculate scalar roughness over water with input 10-m wind +!> Calculate scalar roughness over water with input 10-m wind !! For low-to-moderate winds, try to match the Ck-U10 relationship from COARE algorithm !! For high winds, try to retain the Ck-U10 relationship of FY2015 HWRF !! !!\author Bin Liu, NOAA/NCEP/EMC 2017 -! +! ! uref(m/s) : wind speed at 10-m height ! znott(meter): scalar roughness scale over water + SUBROUTINE znot_t_v6(uref, znott) + + !$acc routine seq + IMPLICIT NONE ! REAL(kind_phys), INTENT(IN) :: uref REAL(kind_phys), INTENT(OUT):: znott @@ -3240,17 +3241,16 @@ END SUBROUTINE znot_t_v6 !------------------------------------------------------------------- !>\ingroup mynn_sfc -!! - SUBROUTINE znot_m_v7(uref, znotm) - - !$acc routine seq - IMPLICIT NONE !> Calculate areodynamical roughness over water with input 10-m wind !! For low-to-moderate winds, try to match the Cd-U10 relationship from COARE V3.5 (Edson et al. 2013) !! For high winds, try to fit available observational data !! Comparing to znot_t_v6, slightly decrease Cd for higher wind speed -!! +!! !!\author Bin Liu, NOAA/NCEP/EMC 2018 + SUBROUTINE znot_m_v7(uref, znotm) + + !$acc routine seq + IMPLICIT NONE ! ! uref(m/s) : wind speed at 10-m height ! znotm(meter): areodynamical roughness scale over water @@ -3290,17 +3290,16 @@ SUBROUTINE znot_m_v7(uref, znotm) END SUBROUTINE znot_m_v7 !-------------------------------------------------------------------- !>\ingroup mynn_sfc -!! - SUBROUTINE znot_t_v7(uref, znott) - - !$acc routine seq - IMPLICIT NONE !> Calculate scalar roughness over water with input 10-m wind !! For low-to-moderate winds, try to match the Ck-U10 relationship from COARE algorithm !! For high winds, try to retain the Ck-U10 relationship of FY2015 HWRF !! To be compatible with the slightly decreased Cd for higher wind speed -!! +!! !!\author Bin Liu, NOAA/NCEP/EMC 2018 + SUBROUTINE znot_t_v7(uref, znott) + + !$acc routine seq + IMPLICIT NONE ! ! uref(m/s) : wind speed at 10-m height ! znott(meter): scalar roughness scale over water diff --git a/physics/SFC_Layer/MYNN/mynnsfc_wrapper.F90 b/physics/SFC_Layer/MYNN/mynnsfc_wrapper.F90 index 8df0116a8..779a56da4 100644 --- a/physics/SFC_Layer/MYNN/mynnsfc_wrapper.F90 +++ b/physics/SFC_Layer/MYNN/mynnsfc_wrapper.F90 @@ -1,6 +1,7 @@ !> \file mynnsfc_wrapper.F90 -!! Contains all of the code related to running the MYNN surface layer scheme +!! +!> This Model ontains all of the code related to running the MYNN surface layer scheme MODULE mynnsfc_wrapper USE module_sf_mynn diff --git a/physics/SFC_Layer/UFS/date_def.f b/physics/SFC_Layer/UFS/date_def.f index fceb4334f..958d8b8b9 100644 --- a/physics/SFC_Layer/UFS/date_def.f +++ b/physics/SFC_Layer/UFS/date_def.f @@ -1,3 +1,5 @@ +!>\file date_def.f +!! module date_def use machine, ONLY: kind_phys implicit none diff --git a/physics/SFC_Layer/UFS/module_nst_parameters.f90 b/physics/SFC_Layer/UFS/module_nst_parameters.f90 index 5308345e2..984335cc8 100644 --- a/physics/SFC_Layer/UFS/module_nst_parameters.f90 +++ b/physics/SFC_Layer/UFS/module_nst_parameters.f90 @@ -4,11 +4,12 @@ !>\defgroup nst_parameters GFS NSST Parameter Module !! \ingroup gfs_nst_main_mod -!! This module contains constants and parameters used in GFS + +!> This module contains constants and parameters used in GFS !! near surface sea temperature scheme. -!! history: -!! 20210305: X.Li, reduce z_w_max from 30 m to 20 m module module_nst_parameters +! history: +! 20210305: X.Li, reduce z_w_max from 30 m to 20 m use machine, only : kind_phys ! diff --git a/physics/SFC_Layer/UFS/module_nst_water_prop.f90 b/physics/SFC_Layer/UFS/module_nst_water_prop.f90 index 858659e90..f71c35e8b 100644 --- a/physics/SFC_Layer/UFS/module_nst_water_prop.f90 +++ b/physics/SFC_Layer/UFS/module_nst_water_prop.f90 @@ -1,10 +1,10 @@ - !>\file module_nst_water_prop.f90 !! This file contains GFS NSST water property subroutines. !>\defgroup waterprop GFS NSST Water Property -!!This module contains GFS NSST water property subroutines. !!\ingroup gfs_nst_main_mod + +!> This module contains GFS NSST water property subroutines. module module_nst_water_prop use machine , only : kind_phys use module_nst_parameters , only : t0k, zero, one, half diff --git a/physics/SFC_Layer/UFS/sfc_diag.f b/physics/SFC_Layer/UFS/sfc_diag.f index c8ef19e8f..66ec95c50 100644 --- a/physics/SFC_Layer/UFS/sfc_diag.f +++ b/physics/SFC_Layer/UFS/sfc_diag.f @@ -1,18 +1,15 @@ !> \file sfc_diag.f !! This file contains the land surface diagnose calculation scheme. +!> This module contains the land surface diagnose calcualtion module sfc_diag contains !> \defgroup sfc_diag_mod GFS sfc_diag module -!! This module contains the land surface diagose calculation. -!> @{ !! \section arg_table_sfc_diag_run Argument Table !! \htmlinclude sfc_diag_run.html !! -!! \section general General Algorithm -!! \section detailed Detailed Algorithm -!! @{ +!> @{ subroutine sfc_diag_run (im,xlat_d,xlon_d, & & lsm,lsm_ruc,grav,cp,eps,epsm1,con_rocp, & & con_karman, & diff --git a/physics/SFC_Layer/UFS/sfc_diag_post.F90 b/physics/SFC_Layer/UFS/sfc_diag_post.F90 index c1e69ae48..ce3d9c595 100644 --- a/physics/SFC_Layer/UFS/sfc_diag_post.F90 +++ b/physics/SFC_Layer/UFS/sfc_diag_post.F90 @@ -1,12 +1,12 @@ !> \file sfc_diag_post.F90 !! Contains code related to the surface diagnostic scheme. +!> This module contains code related to the surface diagnostic scheme. module sfc_diag_post contains !>\defgroup sfc_diag_post_mod GFS sfc_diag_post Module -!! This module contains code related to the surface diagnostic scheme. !> @{ #if 0 !> \section arg_table_sfc_diag_post_run Argument Table diff --git a/physics/SFC_Layer/UFS/sfc_diff.f b/physics/SFC_Layer/UFS/sfc_diff.f index e5cb4292e..2b1d285f3 100644 --- a/physics/SFC_Layer/UFS/sfc_diff.f +++ b/physics/SFC_Layer/UFS/sfc_diff.f @@ -648,9 +648,8 @@ end subroutine stability !--------------------------------- -!! add fitted z0,zt curves for hurricane application (used in HWRF/HMON) +!> add fitted z0,zt curves for hurricane application (used in HWRF/HMON) !! Weiguo Wang, 2019-0425 - SUBROUTINE znot_m_v6(uref, znotm) use machine , only : kind_phys IMPLICIT NONE @@ -697,18 +696,19 @@ SUBROUTINE znot_m_v6(uref, znotm) END SUBROUTINE znot_m_v6 +!> Calculate scalar roughness over water with input 10-m wind +!! For low-to-moderate winds, try to match the Ck-U10 relationship from COARE algorithm +!! For high winds, try to retain the Ck-U10 relationship of FY2015 HWRF +!! +!! Bin Liu, NOAA/NCEP/EMC 2017 +! +!! uref(m/s) : wind speed at 10-m height +!! znott(meter): scalar roughness scale over water SUBROUTINE znot_t_v6(uref, znott) use machine , only : kind_phys IMPLICIT NONE -! Calculate scalar roughness over water with input 10-m wind -! For low-to-moderate winds, try to match the Ck-U10 relationship from COARE algorithm -! For high winds, try to retain the Ck-U10 relationship of FY2015 HWRF -! -! Bin Liu, NOAA/NCEP/EMC 2017 -! -! uref(m/s) : wind speed at 10-m height -! znott(meter): scalar roughness scale over water -! + + REAL(kind=kind_phys), INTENT(IN) :: uref REAL(kind=kind_phys), INTENT(OUT):: znott @@ -762,19 +762,20 @@ SUBROUTINE znot_t_v6(uref, znott) END SUBROUTINE znot_t_v6 +!> Calculate areodynamical roughness over water with input 10-m wind +!! For low-to-moderate winds, try to match the Cd-U10 relationship from COARE V3.5 (Edson et al. 2013) +!! For high winds, try to fit available observational data +!! Comparing to znot_t_v6, slightly decrease Cd for higher wind speed +! +!! Bin Liu, NOAA/NCEP/EMC 2018 +! +!! uref(m/s) : wind speed at 10-m height +!! znotm(meter): areodynamical roughness scale over water SUBROUTINE znot_m_v7(uref, znotm) use machine , only : kind_phys IMPLICIT NONE -! Calculate areodynamical roughness over water with input 10-m wind -! For low-to-moderate winds, try to match the Cd-U10 relationship from COARE V3.5 (Edson et al. 2013) -! For high winds, try to fit available observational data -! Comparing to znot_t_v6, slightly decrease Cd for higher wind speed -! -! Bin Liu, NOAA/NCEP/EMC 2018 -! -! uref(m/s) : wind speed at 10-m height -! znotm(meter): areodynamical roughness scale over water -! + + REAL(kind=kind_phys), INTENT(IN) :: uref REAL(kind=kind_phys), INTENT(OUT):: znotm @@ -808,18 +809,20 @@ SUBROUTINE znot_m_v7(uref, znotm) endif END SUBROUTINE znot_m_v7 + +!> Calculate scalar roughness over water with input 10-m wind +!! For low-to-moderate winds, try to match the Ck-U10 relationship from COARE algorithm +!! For high winds, try to retain the Ck-U10 relationship of FY2015 HWRF +!! To be compatible with the slightly decreased Cd for higher wind speed +!! +!! Bin Liu, NOAA/NCEP/EMC 2018 +!! +!! uref(m/s) : wind speed at 10-m height +!! znott(meter): scalar roughness scale over water SUBROUTINE znot_t_v7(uref, znott) use machine , only : kind_phys IMPLICIT NONE -! Calculate scalar roughness over water with input 10-m wind -! For low-to-moderate winds, try to match the Ck-U10 relationship from COARE algorithm -! For high winds, try to retain the Ck-U10 relationship of FY2015 HWRF -! To be compatible with the slightly decreased Cd for higher wind speed -! -! Bin Liu, NOAA/NCEP/EMC 2018 -! -! uref(m/s) : wind speed at 10-m height -! znott(meter): scalar roughness scale over water + ! REAL(kind=kind_phys), INTENT(IN) :: uref diff --git a/physics/SFC_Layer/UFS/sfc_nst_post.f90 b/physics/SFC_Layer/UFS/sfc_nst_post.f90 index 0357a86f0..ca1194e3d 100644 --- a/physics/SFC_Layer/UFS/sfc_nst_post.f90 +++ b/physics/SFC_Layer/UFS/sfc_nst_post.f90 @@ -1,6 +1,7 @@ !> \file sfc_nst_post.f90 -!! This file contains code to be executed after the GFS NSST model. +!! This file contains code to be executed after the near-surface sea temperature scheme. +!> This module contains code to be executed after the near-surface sea temperature scheme module sfc_nst_post use machine , only : kind_phys, kp => kind_phys diff --git a/physics/SFC_Layer/UFS/sfc_nst_pre.f90 b/physics/SFC_Layer/UFS/sfc_nst_pre.f90 index c61f9b903..dec6722ed 100644 --- a/physics/SFC_Layer/UFS/sfc_nst_pre.f90 +++ b/physics/SFC_Layer/UFS/sfc_nst_pre.f90 @@ -1,6 +1,7 @@ !> \file sfc_nst_pre.f90 -!! This file contains preparation for the GFS NSST model. +!! This file contains preparation for the near-surface sea temperature scheme. +!> This module contain preparation for the near-surface sea temperature scheme module sfc_nst_pre use machine , only : kind_phys @@ -11,7 +12,7 @@ module sfc_nst_pre contains - !> \defgroup GFS_NSST_PRE GFS Near-Surface Sea Temperature Pre + !> \defgroup GFS_NSST_PRE Near-Surface Sea Temperature Pre !! !! The NSST scheme is one of the three schemes used to represent the !! surface in the GFS physics suite. The other two are the Noah land diff --git a/physics/SFC_Models/Lake/CLM/clm_lake.f90 b/physics/SFC_Models/Lake/CLM/clm_lake.f90 index 8686221fa..c004e6c32 100644 --- a/physics/SFC_Models/Lake/CLM/clm_lake.f90 +++ b/physics/SFC_Models/Lake/CLM/clm_lake.f90 @@ -1,5 +1,7 @@ !> \file clm_lake.f90 !! Contains code related to the CLM lake model + +!> This module contains the CLM Lake model. !! !! This lake scheme was taken from module_sf_lake in WRF 4.3.1, and !! modified for CCPP by Sam Trahan in June 2022. @@ -17,7 +19,6 @@ !! can be used with any land surface scheme embedded in WRF. The lake scheme !! developments and evaluations were included in Subin et al. (2012) \cite Subin_2012 !! and Gu et al. (2015) \cite Gu2015 . - MODULE clm_lake use machine, only: kind_phys, kind_dbl_prec diff --git a/physics/SFC_Models/Land/Noah/namelist_soilveg.f b/physics/SFC_Models/Land/Noah/namelist_soilveg.f index c0517000e..7b3c41a72 100644 --- a/physics/SFC_Models/Land/Noah/namelist_soilveg.f +++ b/physics/SFC_Models/Land/Noah/namelist_soilveg.f @@ -1,6 +1,8 @@ !>\file namelist_soilveg.f !>\ingroup Noah_LSM + +!> This module contains namelist options for Noah LSM module namelist_soilveg implicit none save diff --git a/physics/SFC_Models/Land/Noah/sflx.f b/physics/SFC_Models/Land/Noah/sflx.f index b2fb38ae1..5f0c6c747 100644 --- a/physics/SFC_Models/Land/Noah/sflx.f +++ b/physics/SFC_Models/Land/Noah/sflx.f @@ -1,5 +1,7 @@ !>\file sflx.f -!! This file is the entity of GFS Noah LSM Model(Version 2.7). +!! + +!> This module contains the entity of GFS Noah LSM Model(Version 2.7). module sflx contains !>\ingroup Noah_LSM diff --git a/physics/SFC_Models/Land/Noah/surface_perturbation.F90 b/physics/SFC_Models/Land/Noah/surface_perturbation.F90 index e0429a5fc..acf722754 100644 --- a/physics/SFC_Models/Land/Noah/surface_perturbation.F90 +++ b/physics/SFC_Models/Land/Noah/surface_perturbation.F90 @@ -3,6 +3,7 @@ !! albedo and vegetation fraction perturbations. !>\defgroup gfs_sfcpert GFS Surface Perturbation Module + !> This module contains routines used in the percentile matching algorithm for the !! albedo and vegetation fraction perturbations. module surface_perturbation diff --git a/physics/SFC_Models/Land/Noahmp/module_sf_noahmp_glacier.F90 b/physics/SFC_Models/Land/Noahmp/module_sf_noahmp_glacier.F90 index fcbe40a70..bcb157c54 100644 --- a/physics/SFC_Models/Land/Noahmp/module_sf_noahmp_glacier.F90 +++ b/physics/SFC_Models/Land/Noahmp/module_sf_noahmp_glacier.F90 @@ -3,6 +3,8 @@ !! This file contains the NoahMP Glacier scheme. !>\ingroup NoahMP_LSM + +!> This module contains the NoahMP Glacier scheme module noahmp_glacier_globals use machine , only : kind_phys @@ -77,6 +79,8 @@ end module noahmp_glacier_globals !------------------------------------------------------------------------------------------! !>\ingroup NoahMP_LSM + +!> This module contains NoahMP glacier routines module noahmp_glacier_routines use noahmp_glacier_globals #ifndef CCPP @@ -3489,6 +3493,7 @@ end subroutine noahmp_options_glacier end module noahmp_glacier_routines ! ================================================================================================== +!> This module contains the interface of noahmp_glacier_routines and noahmp_glacier_globals module module_sf_noahmp_glacier use noahmp_glacier_routines diff --git a/physics/SFC_Models/Land/Noahmp/noahmp_tables.f90 b/physics/SFC_Models/Land/Noahmp/noahmp_tables.f90 index 753c8ff24..d6e9963da 100644 --- a/physics/SFC_Models/Land/Noahmp/noahmp_tables.f90 +++ b/physics/SFC_Models/Land/Noahmp/noahmp_tables.f90 @@ -2,7 +2,8 @@ !! This file contains Fortran versions of the data tables included with NoahMP in mptable.tbl, soilparm.tbl, and genparm.tbl. !> \ingroup NoahMP_LSM -!! \brief Data from MPTABLE.TBL, SOILPARM.TBL, GENPARM.TBL for NoahMP + +!> brief Data from MPTABLE.TBL, SOILPARM.TBL, GENPARM.TBL for NoahMP !! !! Note that a subset of the data in the *.TBL files is represented in this file. For example, !! only the data in the noah_mp_modis_parameters section of MPTABLE.TBL and the STAS section of diff --git a/physics/SFC_Models/Land/RUC/lsm_ruc.F90 b/physics/SFC_Models/Land/RUC/lsm_ruc.F90 index 8df8cca24..9a41b066b 100644 --- a/physics/SFC_Models/Land/RUC/lsm_ruc.F90 +++ b/physics/SFC_Models/Land/RUC/lsm_ruc.F90 @@ -1,6 +1,7 @@ !>\file lsm_ruc.F90 !! This file contains the RUC land surface scheme driver. +!> This module contain the RUC land surface model driver module lsm_ruc use machine, only: kind_phys, kind_dbl_prec @@ -322,7 +323,7 @@ end subroutine lsm_ruc_finalize !> \section arg_table_lsm_ruc_run Argument Table !! \htmlinclude lsm_ruc_run.html !! -!>\section gen_lsmruc RUC LSM General Algorithm +!>\section gen_lsm_ruc_run RUC LSM General Algorithm subroutine lsm_ruc_run & ! inputs & ( iter, me, master, delt, kdt, im, nlev, lsm_ruc, lsm, & & imp_physics, imp_physics_gfdl, imp_physics_thompson, & diff --git a/physics/SFC_Models/Land/RUC/module_sf_ruclsm.F90 b/physics/SFC_Models/Land/RUC/module_sf_ruclsm.F90 index 2d01f96c9..66e5d7d1f 100644 --- a/physics/SFC_Models/Land/RUC/module_sf_ruclsm.F90 +++ b/physics/SFC_Models/Land/RUC/module_sf_ruclsm.F90 @@ -83,7 +83,7 @@ MODULE module_sf_ruclsm !>\ingroup lsm_ruc_group !> The RUN LSM model is described in Smirnova et al.(1997) !! \cite Smirnova_1997 and Smirnova et al.(2000) \cite Smirnova_2000 -!>\section gen_lsmruc GSD RUC LSM General Algorithm +!>\section gen_lsmruc RUC LSM General Algorithm !! @{ SUBROUTINE LSMRUC(xlat,xlon, & DT,init,lsm_cold_start,KTAU,iter,NSL, & diff --git a/physics/SFC_Models/Land/RUC/module_soil_pre.F90 b/physics/SFC_Models/Land/RUC/module_soil_pre.F90 index 8eb5a5775..d8cdf5b82 100644 --- a/physics/SFC_Models/Land/RUC/module_soil_pre.F90 +++ b/physics/SFC_Models/Land/RUC/module_soil_pre.F90 @@ -1,5 +1,6 @@ !>\file module_soil_pre.F90 -!! This file contains subroutines that initialize RUC LSM levels, soil + +!> This module contains subroutines that initialize RUC LSM levels, soil !! temperature/moisture. module module_soil_pre diff --git a/physics/SFC_Models/Land/RUC/namelist_soilveg_ruc.F90 b/physics/SFC_Models/Land/RUC/namelist_soilveg_ruc.F90 index d93dc5c64..f50a264cc 100644 --- a/physics/SFC_Models/Land/RUC/namelist_soilveg_ruc.F90 +++ b/physics/SFC_Models/Land/RUC/namelist_soilveg_ruc.F90 @@ -1,6 +1,7 @@ !>\file namelist_soilveg_ruc.F90 !>\ingroup RUC_lsm +!> This module contains the namelist options of soil/vegetation in RUC module namelist_soilveg_ruc use machine , only : kind_phys diff --git a/physics/SFC_Models/Land/RUC/set_soilveg_ruc.F90 b/physics/SFC_Models/Land/RUC/set_soilveg_ruc.F90 index 8ce6023ff..012c81323 100644 --- a/physics/SFC_Models/Land/RUC/set_soilveg_ruc.F90 +++ b/physics/SFC_Models/Land/RUC/set_soilveg_ruc.F90 @@ -1,7 +1,7 @@ !>\file set_soilveg_ruc.F90 -!! This file contains subroutine to specify vegetation and soil -!! parameters for a given soild and land-use classification. +!> This module contains subroutine to specify vegetation and soil +!! parameters for a given soild and land-use classification. module set_soilveg_ruc_mod use machine , only : kind_phys diff --git a/physics/SFC_Models/Land/sfc_land.F90 b/physics/SFC_Models/Land/sfc_land.F90 index a85e8b787..6f52452db 100644 --- a/physics/SFC_Models/Land/sfc_land.F90 +++ b/physics/SFC_Models/Land/sfc_land.F90 @@ -13,21 +13,10 @@ module sfc_land contains -!> \defgroup sfc_land for coupling to land -!! @{ -!! \section diagram Calling Hierarchy Diagram -!! \section intraphysics Intraphysics Communication -!! !> \brief Brief description of the subroutine -!! !! \section arg_table_sfc_land_run Arguments !! \htmlinclude sfc_land_run.html !! - -!! -!! \section general General Algorithm -!! \section detailed Detailed Algorithm -!! @{ subroutine sfc_land_run(im, cpllnd, cpllnd2atm, flag_iter, dry, & sncovr1_lnd, qsurf_lnd, evap_lnd, hflx_lnd, & ep_lnd, t2mmp_lnd, q2mp_lnd, gflux_lnd, & @@ -104,5 +93,4 @@ subroutine sfc_land_run(im, cpllnd, cpllnd2atm, flag_iter, dry, & end subroutine sfc_land_run -!> @} end module sfc_land diff --git a/physics/SFC_Models/SeaIce/CICE/sfc_cice.f b/physics/SFC_Models/SeaIce/CICE/sfc_cice.f index 0df1f67a5..369e24cf0 100644 --- a/physics/SFC_Models/SeaIce/CICE/sfc_cice.f +++ b/physics/SFC_Models/SeaIce/CICE/sfc_cice.f @@ -11,23 +11,11 @@ module sfc_cice contains -!> \defgroup sfc_sice for coupling to CICE -!! @{ -!! \section diagram Calling Hierarchy Diagram -!! \section intraphysics Intraphysics Communication -!! !> \brief Brief description of the subroutine -!! !! \section arg_table_sfc_cice_run Arguments !! \htmlinclude sfc_cice_run.html !! -!! -!! \section general General Algorithm -!! \section detailed Detailed Algorithm -!! @{ - - !! use physcons, only : hvap => con_hvap, cp => con_cp, & !! & rvrdm1 => con_fvirt, rd => con_rd ! @@ -163,5 +151,4 @@ subroutine sfc_cice_run & end subroutine sfc_cice_run !----------------------------------- -!> @} end module sfc_cice 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 @@ - - + + + + + + + + + + $projectname: $title $title + + + + + + - $treeview $search $mathjax @@ -24,6 +40,13 @@ $extrastylesheet + + + + + +
diff --git a/physics/docs/ccpp_dox_layout.xml b/physics/docs/ccpp_dox_layout.xml index 6242933b7..b844b5c1b 100644 --- a/physics/docs/ccpp_dox_layout.xml +++ b/physics/docs/ccpp_dox_layout.xml @@ -1,16 +1,16 @@ + - + - - + + - - - - + + + diff --git a/physics/docs/ccpp_doxyfile b/physics/docs/ccpp_doxyfile index b4ca66424..7e40361ae 100644 --- a/physics/docs/ccpp_doxyfile +++ b/physics/docs/ccpp_doxyfile @@ -1,556 +1,2919 @@ -# Doxyfile 1.9.3 +# Doxyfile 1.12.0 + +# This file describes the settings to be used by the documentation system +# Doxygen (www.doxygen.org) for a project. +# +# All text after a double hash (##) is considered a comment and is placed in +# front of the TAG it is preceding. +# +# All text after a single hash (#) is considered a comment and will be ignored. +# The format is: +# TAG = value [value, ...] +# For lists, items can also be appended using: +# TAG += value [value, ...] +# Values that contain spaces should be placed between quotes (\" \"). +# +# Note: +# +# Use Doxygen to compare the used configuration file with the template +# configuration file: +# doxygen -x [configFile] +# Use Doxygen to compare the used configuration file with the template +# configuration file without replacing the environment variables or CMake type +# replacement variables: +# doxygen -x_noenv [configFile] + +#--------------------------------------------------------------------------- +# Project related configuration options +#--------------------------------------------------------------------------- + +# This tag specifies the encoding used for all characters in the configuration +# file that follow. The default is UTF-8 which is also the encoding used for all +# text before the first occurrence of this tag. Doxygen uses libiconv (or the +# iconv built into libc) for the transcoding. See +# https://www.gnu.org/software/libiconv/ for the list of possible encodings. +# The default value is: UTF-8. DOXYFILE_ENCODING = UTF-8 -PROJECT_NAME = "CCPP SciDoc" -PROJECT_NUMBER = "v6.0.0" + +# The PROJECT_NAME tag is a single word (or a sequence of words surrounded by +# double-quotes, unless you are using Doxywizard) that should identify the +# project for which the documentation is generated. This name is used in the +# title of most generated pages and in a few other places. +# The default value is: My Project. + +PROJECT_NAME = "CCPP SciDoc v7.0.0" + +# The PROJECT_NUMBER tag can be used to enter a project or revision number. This +# could be handy for archiving the generated documentation or if some version +# control system is used. + +PROJECT_NUMBER = v7.0.0 + +# Using the PROJECT_BRIEF tag one can provide an optional one line description +# for a project that appears at the top of each page and should give viewer a +# quick idea about the purpose of the project. Keep the description short. + PROJECT_BRIEF = "Common Community Physics Package Developed at DTC" + +# With the PROJECT_LOGO tag one can specify a logo or an icon that is included +# in the documentation. The maximum height of the logo should not exceed 55 +# pixels and the maximum width should not exceed 200 pixels. Doxygen will copy +# the logo to the output directory. + PROJECT_LOGO = img/dtc_logo.png + +# With the PROJECT_ICON tag one can specify an icon that is included in the tabs +# when the HTML document is shown. Doxygen will copy the logo to the output +# directory. + +PROJECT_ICON = + +# The OUTPUT_DIRECTORY tag is used to specify the (relative or absolute) path +# into which the generated documentation will be written. If a relative path is +# entered, it will be relative to the location where Doxygen was started. If +# left blank the current directory will be used. + OUTPUT_DIRECTORY = doc + +# If the CREATE_SUBDIRS tag is set to YES then Doxygen will create up to 4096 +# sub-directories (in 2 levels) under the output directory of each output format +# and will distribute the generated files over these directories. Enabling this +# option can be useful when feeding Doxygen a huge amount of source files, where +# putting all generated files in the same directory would otherwise causes +# performance problems for the file system. Adapt CREATE_SUBDIRS_LEVEL to +# control the number of sub-directories. +# The default value is: NO. + CREATE_SUBDIRS = NO + +# Controls the number of sub-directories that will be created when +# CREATE_SUBDIRS tag is set to YES. Level 0 represents 16 directories, and every +# level increment doubles the number of directories, resulting in 4096 +# directories at level 8 which is the default and also the maximum value. The +# sub-directories are organized in 2 levels, the first level always has a fixed +# number of 16 directories. +# Minimum value: 0, maximum value: 8, default value: 8. +# This tag requires that the tag CREATE_SUBDIRS is set to YES. + +CREATE_SUBDIRS_LEVEL = 8 + +# If the ALLOW_UNICODE_NAMES tag is set to YES, Doxygen will allow non-ASCII +# characters to appear in the names of generated files. If set to NO, non-ASCII +# characters will be escaped, for example _xE3_x81_x84 will be used for Unicode +# U+3044. +# The default value is: NO. + ALLOW_UNICODE_NAMES = NO + +# The OUTPUT_LANGUAGE tag is used to specify the language in which all +# documentation generated by Doxygen is written. Doxygen will use this +# information to generate all constant output in the proper language. +# Possible values are: Afrikaans, Arabic, Armenian, Brazilian, Bulgarian, +# Catalan, Chinese, Chinese-Traditional, Croatian, Czech, Danish, Dutch, English +# (United States), Esperanto, Farsi (Persian), Finnish, French, German, Greek, +# Hindi, Hungarian, Indonesian, Italian, Japanese, Japanese-en (Japanese with +# English messages), Korean, Korean-en (Korean with English messages), Latvian, +# Lithuanian, Macedonian, Norwegian, Persian (Farsi), Polish, Portuguese, +# Romanian, Russian, Serbian, Serbian-Cyrillic, Slovak, Slovene, Spanish, +# Swedish, Turkish, Ukrainian and Vietnamese. +# The default value is: English. + OUTPUT_LANGUAGE = English + +# If the BRIEF_MEMBER_DESC tag is set to YES, Doxygen will include brief member +# descriptions after the members that are listed in the file and class +# documentation (similar to Javadoc). Set to NO to disable this. +# The default value is: YES. + BRIEF_MEMBER_DESC = YES + +# If the REPEAT_BRIEF tag is set to YES, Doxygen will prepend the brief +# description of a member or function before the detailed description +# +# Note: If both HIDE_UNDOC_MEMBERS and BRIEF_MEMBER_DESC are set to NO, the +# brief descriptions will be completely suppressed. +# The default value is: YES. + REPEAT_BRIEF = NO + +# This tag implements a quasi-intelligent brief description abbreviator that is +# used to form the text in various listings. Each string in this list, if found +# as the leading text of the brief description, will be stripped from the text +# and the result, after processing the whole list, is used as the annotated +# text. Otherwise, the brief description is used as-is. If left blank, the +# following values are used ($name is automatically replaced with the name of +# the entity):The $name class, The $name widget, The $name file, is, provides, +# specifies, contains, represents, a, an and the. + ABBREVIATE_BRIEF = + +# If the ALWAYS_DETAILED_SEC and REPEAT_BRIEF tags are both set to YES then +# Doxygen will generate a detailed section even if there is only a brief +# description. +# The default value is: NO. + ALWAYS_DETAILED_SEC = NO + +# If the INLINE_INHERITED_MEMB tag is set to YES, Doxygen will show all +# inherited members of a class in the documentation of that class as if those +# members were ordinary class members. Constructors, destructors and assignment +# operators of the base classes will not be shown. +# The default value is: NO. + INLINE_INHERITED_MEMB = NO -FULL_PATH_NAMES = NO + +# If the FULL_PATH_NAMES tag is set to YES, Doxygen will prepend the full path +# before files name in the file list and in the header files. If set to NO the +# shortest path that makes the file name unique will be used +# The default value is: YES. + +FULL_PATH_NAMES = YES + +# The STRIP_FROM_PATH tag can be used to strip a user-defined part of the path. +# Stripping is only done if one of the specified strings matches the left-hand +# part of the path. The tag can be used to show relative paths in the file list. +# If left blank the directory from which Doxygen is run is used as the path to +# strip. +# +# Note that you can specify absolute paths here, but also relative paths, which +# will be relative from the directory where Doxygen is started. +# This tag requires that the tag FULL_PATH_NAMES is set to YES. + STRIP_FROM_PATH = + +# The STRIP_FROM_INC_PATH tag can be used to strip a user-defined part of the +# path mentioned in the documentation of a class, which tells the reader which +# header file to include in order to use a class. If left blank only the name of +# the header file containing the class definition is used. Otherwise one should +# specify the list of include paths that are normally passed to the compiler +# using the -I flag. + STRIP_FROM_INC_PATH = + +# If the SHORT_NAMES tag is set to YES, Doxygen will generate much shorter (but +# less readable) file names. This can be useful is your file systems doesn't +# support long names like on DOS, Mac, or CD-ROM. +# The default value is: NO. + SHORT_NAMES = NO + +# If the JAVADOC_AUTOBRIEF tag is set to YES then Doxygen will interpret the +# first line (until the first dot) of a Javadoc-style comment as the brief +# description. If set to NO, the Javadoc-style will behave just like regular Qt- +# style comments (thus requiring an explicit @brief command for a brief +# description.) +# The default value is: NO. + JAVADOC_AUTOBRIEF = NO + +# If the JAVADOC_BANNER tag is set to YES then Doxygen will interpret a line +# such as +# /*************** +# as being the beginning of a Javadoc-style comment "banner". If set to NO, the +# Javadoc-style will behave just like regular comments and it will not be +# interpreted by Doxygen. +# The default value is: NO. + JAVADOC_BANNER = NO + +# If the QT_AUTOBRIEF tag is set to YES then Doxygen will interpret the first +# line (until the first dot) of a Qt-style comment as the brief description. If +# set to NO, the Qt-style will behave just like regular Qt-style comments (thus +# requiring an explicit \brief command for a brief description.) +# The default value is: NO. + QT_AUTOBRIEF = NO + +# The MULTILINE_CPP_IS_BRIEF tag can be set to YES to make Doxygen treat a +# multi-line C++ special comment block (i.e. a block of //! or /// comments) as +# a brief description. This used to be the default behavior. The new default is +# to treat a multi-line C++ comment block as a detailed description. Set this +# tag to YES if you prefer the old behavior instead. +# +# Note that setting this tag to YES also means that rational rose comments are +# not recognized any more. +# The default value is: NO. + MULTILINE_CPP_IS_BRIEF = NO + +# By default Python docstrings are displayed as preformatted text and Doxygen's +# special commands cannot be used. By setting PYTHON_DOCSTRING to NO the +# Doxygen's special commands can be used and the contents of the docstring +# documentation blocks is shown as Doxygen documentation. +# The default value is: YES. + PYTHON_DOCSTRING = YES + +# If the INHERIT_DOCS tag is set to YES then an undocumented member inherits the +# documentation from any documented member that it re-implements. +# The default value is: YES. + INHERIT_DOCS = YES + +# If the SEPARATE_MEMBER_PAGES tag is set to YES then Doxygen will produce a new +# page for each member. If set to NO, the documentation of a member will be part +# of the file/class/namespace that contains it. +# The default value is: NO. + SEPARATE_MEMBER_PAGES = YES + +# The TAB_SIZE tag can be used to set the number of spaces in a tab. Doxygen +# uses this value to replace tabs by spaces in code fragments. +# Minimum value: 1, maximum value: 16, default value: 4. + TAB_SIZE = 4 + +# This tag can be used to specify a number of aliases that act as commands in +# the documentation. An alias has the form: +# name=value +# For example adding +# "sideeffect=@par Side Effects:^^" +# will allow you to put the command \sideeffect (or @sideeffect) in the +# documentation, which will result in a user-defined paragraph with heading +# "Side Effects:". Note that you cannot put \n's in the value part of an alias +# to insert newlines (in the resulting output). You can put ^^ in the value part +# of an alias to insert a newline as if a physical newline was in the original +# file. When you need a literal { or } or , in the value part of an alias you +# have to escape them by means of a backslash (\), this can lead to conflicts +# with the commands \{ and \} for these it is advised to use the version @{ and +# @} or use a double escape (\\{ and \\}) + ALIASES = + +# Set the OPTIMIZE_OUTPUT_FOR_C tag to YES if your project consists of C sources +# only. Doxygen will then generate output that is more tailored for C. For +# instance, some of the names that are used will be different. The list of all +# members will be omitted, etc. +# The default value is: NO. + OPTIMIZE_OUTPUT_FOR_C = NO + +# Set the OPTIMIZE_OUTPUT_JAVA tag to YES if your project consists of Java or +# Python sources only. Doxygen will then generate output that is more tailored +# for that language. For instance, namespaces will be presented as packages, +# qualified scopes will look different, etc. +# The default value is: NO. + OPTIMIZE_OUTPUT_JAVA = NO + +# Set the OPTIMIZE_FOR_FORTRAN tag to YES if your project consists of Fortran +# sources. Doxygen will then generate output that is tailored for Fortran. +# The default value is: NO. + OPTIMIZE_FOR_FORTRAN = YES + +# Set the OPTIMIZE_OUTPUT_VHDL tag to YES if your project consists of VHDL +# sources. Doxygen will then generate output that is tailored for VHDL. +# The default value is: NO. + OPTIMIZE_OUTPUT_VHDL = NO + +# Set the OPTIMIZE_OUTPUT_SLICE tag to YES if your project consists of Slice +# sources only. Doxygen will then generate output that is more tailored for that +# language. For instance, namespaces will be presented as modules, types will be +# separated into more groups, etc. +# The default value is: NO. + OPTIMIZE_OUTPUT_SLICE = NO + +# Doxygen selects the parser to use depending on the extension of the files it +# parses. With this tag you can assign which parser to use for a given +# extension. Doxygen has a built-in mapping, but you can override or extend it +# using this tag. The format is ext=language, where ext is a file extension, and +# language is one of the parsers supported by Doxygen: IDL, Java, JavaScript, +# Csharp (C#), C, C++, Lex, D, PHP, md (Markdown), Objective-C, Python, Slice, +# VHDL, Fortran (fixed format Fortran: FortranFixed, free formatted Fortran: +# FortranFree, unknown formatted Fortran: Fortran. In the later case the parser +# tries to guess whether the code is fixed or free formatted code, this is the +# default for Fortran type files). For instance to make Doxygen treat .inc files +# as Fortran files (default is PHP), and .f files as C (default is Fortran), +# use: inc=Fortran f=C. +# +# Note: For files without extension you can use no_extension as a placeholder. +# +# Note that for custom extensions you also need to set FILE_PATTERNS otherwise +# the files are not read by Doxygen. When specifying no_extension you should add +# * to the FILE_PATTERNS. +# +# Note see also the list of default file extension mappings. + EXTENSION_MAPPING = .f=FortranFree \ .F=FortranFree \ .F90=FortranFree \ .f90=FortranFree + +# If the MARKDOWN_SUPPORT tag is enabled then Doxygen pre-processes all comments +# according to the Markdown format, which allows for more readable +# documentation. See https://daringfireball.net/projects/markdown/ for details. +# The output of markdown processing is further processed by Doxygen, so you can +# mix Doxygen, HTML, and XML commands with Markdown formatting. Disable only in +# case of backward compatibilities issues. +# The default value is: YES. + MARKDOWN_SUPPORT = YES + +# When the TOC_INCLUDE_HEADINGS tag is set to a non-zero value, all headings up +# to that level are automatically included in the table of contents, even if +# they do not have an id attribute. +# Note: This feature currently applies only to Markdown headings. +# Minimum value: 0, maximum value: 99, default value: 6. +# This tag requires that the tag MARKDOWN_SUPPORT is set to YES. + TOC_INCLUDE_HEADINGS = 5 + +# The MARKDOWN_ID_STYLE tag can be used to specify the algorithm used to +# generate identifiers for the Markdown headings. Note: Every identifier is +# unique. +# Possible values are: DOXYGEN use a fixed 'autotoc_md' string followed by a +# sequence number starting at 0 and GITHUB use the lower case version of title +# with any whitespace replaced by '-' and punctuation characters removed. +# The default value is: DOXYGEN. +# This tag requires that the tag MARKDOWN_SUPPORT is set to YES. + +MARKDOWN_ID_STYLE = DOXYGEN + +# When enabled Doxygen tries to link words that correspond to documented +# classes, or namespaces to their corresponding documentation. Such a link can +# be prevented in individual cases by putting a % sign in front of the word or +# globally by setting AUTOLINK_SUPPORT to NO. +# The default value is: YES. + AUTOLINK_SUPPORT = YES + +# If you use STL classes (i.e. std::string, std::vector, etc.) but do not want +# to include (a tag file for) the STL sources as input, then you should set this +# tag to YES in order to let Doxygen match functions declarations and +# definitions whose arguments contain STL classes (e.g. func(std::string); +# versus func(std::string) {}). This also makes the inheritance and +# collaboration diagrams that involve STL classes more complete and accurate. +# The default value is: NO. + BUILTIN_STL_SUPPORT = NO + +# If you use Microsoft's C++/CLI language, you should set this option to YES to +# enable parsing support. +# The default value is: NO. + CPP_CLI_SUPPORT = NO + +# Set the SIP_SUPPORT tag to YES if your project consists of sip (see: +# https://www.riverbankcomputing.com/software) sources only. Doxygen will parse +# them like normal C++ but will assume all classes use public instead of private +# inheritance when no explicit protection keyword is present. +# The default value is: NO. + SIP_SUPPORT = NO + +# For Microsoft's IDL there are propget and propput attributes to indicate +# getter and setter methods for a property. Setting this option to YES will make +# Doxygen to replace the get and set methods by a property in the documentation. +# This will only work if the methods are indeed getting or setting a simple +# type. If this is not the case, or you want to show the methods anyway, you +# should set this option to NO. +# The default value is: YES. + IDL_PROPERTY_SUPPORT = YES + +# If member grouping is used in the documentation and the DISTRIBUTE_GROUP_DOC +# tag is set to YES then Doxygen will reuse the documentation of the first +# member in the group (if any) for the other members of the group. By default +# all members of a group must be documented explicitly. +# The default value is: NO. + DISTRIBUTE_GROUP_DOC = YES + +# If one adds a struct or class to a group and this option is enabled, then also +# any nested class or struct is added to the same group. By default this option +# is disabled and one has to add nested compounds explicitly via \ingroup. +# The default value is: NO. + GROUP_NESTED_COMPOUNDS = NO + +# Set the SUBGROUPING tag to YES to allow class member groups of the same type +# (for instance a group of public functions) to be put as a subgroup of that +# type (e.g. under the Public Functions section). Set it to NO to prevent +# subgrouping. Alternatively, this can be done per class using the +# \nosubgrouping command. +# The default value is: YES. + SUBGROUPING = YES + +# When the INLINE_GROUPED_CLASSES tag is set to YES, classes, structs and unions +# are shown inside the group in which they are included (e.g. using \ingroup) +# instead of on a separate page (for HTML and Man pages) or section (for LaTeX +# and RTF). +# +# Note that this feature does not work in combination with +# SEPARATE_MEMBER_PAGES. +# The default value is: NO. + INLINE_GROUPED_CLASSES = NO + +# When the INLINE_SIMPLE_STRUCTS tag is set to YES, structs, classes, and unions +# with only public data fields or simple typedef fields will be shown inline in +# the documentation of the scope in which they are defined (i.e. file, +# namespace, or group documentation), provided this scope is documented. If set +# to NO, structs, classes, and unions are shown on a separate page (for HTML and +# Man pages) or section (for LaTeX and RTF). +# The default value is: NO. + INLINE_SIMPLE_STRUCTS = NO + +# When TYPEDEF_HIDES_STRUCT tag is enabled, a typedef of a struct, union, or +# enum is documented as struct, union, or enum with the name of the typedef. So +# typedef struct TypeS {} TypeT, will appear in the documentation as a struct +# with name TypeT. When disabled the typedef will appear as a member of a file, +# namespace, or class. And the struct will be named TypeS. This can typically be +# useful for C code in case the coding convention dictates that all compound +# types are typedef'ed and only the typedef is referenced, never the tag name. +# The default value is: NO. + TYPEDEF_HIDES_STRUCT = YES + +# The size of the symbol lookup cache can be set using LOOKUP_CACHE_SIZE. This +# cache is used to resolve symbols given their name and scope. Since this can be +# an expensive process and often the same symbol appears multiple times in the +# code, Doxygen keeps a cache of pre-resolved symbols. If the cache is too small +# Doxygen will become slower. If the cache is too large, memory is wasted. The +# cache size is given by this formula: 2^(16+LOOKUP_CACHE_SIZE). The valid range +# is 0..9, the default is 0, corresponding to a cache size of 2^16=65536 +# symbols. At the end of a run Doxygen will report the cache usage and suggest +# the optimal cache size from a speed point of view. +# Minimum value: 0, maximum value: 9, default value: 0. + LOOKUP_CACHE_SIZE = 0 + +# The NUM_PROC_THREADS specifies the number of threads Doxygen is allowed to use +# during processing. When set to 0 Doxygen will based this on the number of +# cores available in the system. You can set it explicitly to a value larger +# than 0 to get more control over the balance between CPU load and processing +# speed. At this moment only the input processing can be done using multiple +# threads. Since this is still an experimental feature the default is set to 1, +# which effectively disables parallel processing. Please report any issues you +# encounter. Generating dot graphs in parallel is controlled by the +# DOT_NUM_THREADS setting. +# Minimum value: 0, maximum value: 32, default value: 1. + NUM_PROC_THREADS = 1 +# If the TIMESTAMP tag is set different from NO then each generated page will +# contain the date or date and time when the page was generated. Setting this to +# NO can help when comparing the output of multiple runs. +# Possible values are: YES, NO, DATETIME and DATE. +# The default value is: NO. + +TIMESTAMP = NO + #--------------------------------------------------------------------------- # Build related configuration options #--------------------------------------------------------------------------- +# If the EXTRACT_ALL tag is set to YES, Doxygen will assume all entities in +# documentation are documented, even if no documentation was available. Private +# class members and static file members will be hidden unless the +# EXTRACT_PRIVATE respectively EXTRACT_STATIC tags are set to YES. +# Note: This will also disable the warnings about undocumented members that are +# normally produced when WARNINGS is set to YES. +# The default value is: NO. + EXTRACT_ALL = YES + +# If the EXTRACT_PRIVATE tag is set to YES, all private members of a class will +# be included in the documentation. +# The default value is: NO. + EXTRACT_PRIVATE = YES + +# If the EXTRACT_PRIV_VIRTUAL tag is set to YES, documented private virtual +# methods of a class will be included in the documentation. +# The default value is: NO. + EXTRACT_PRIV_VIRTUAL = NO + +# If the EXTRACT_PACKAGE tag is set to YES, all members with package or internal +# scope will be included in the documentation. +# The default value is: NO. + EXTRACT_PACKAGE = YES + +# If the EXTRACT_STATIC tag is set to YES, all static members of a file will be +# included in the documentation. +# The default value is: NO. + EXTRACT_STATIC = YES + +# If the EXTRACT_LOCAL_CLASSES tag is set to YES, classes (and structs) defined +# locally in source files will be included in the documentation. If set to NO, +# only classes defined in header files are included. Does not have any effect +# for Java sources. +# The default value is: YES. + EXTRACT_LOCAL_CLASSES = YES + +# This flag is only useful for Objective-C code. If set to YES, local methods, +# which are defined in the implementation section but not in the interface are +# included in the documentation. If set to NO, only methods in the interface are +# included. +# The default value is: NO. + EXTRACT_LOCAL_METHODS = YES + +# If this flag is set to YES, the members of anonymous namespaces will be +# extracted and appear in the documentation as a namespace called +# 'anonymous_namespace{file}', where file will be replaced with the base name of +# the file that contains the anonymous namespace. By default anonymous namespace +# are hidden. +# The default value is: NO. + EXTRACT_ANON_NSPACES = YES + +# If this flag is set to YES, the name of an unnamed parameter in a declaration +# will be determined by the corresponding definition. By default unnamed +# parameters remain unnamed in the output. +# The default value is: YES. + RESOLVE_UNNAMED_PARAMS = YES + +# If the HIDE_UNDOC_MEMBERS tag is set to YES, Doxygen will hide all +# undocumented members inside documented classes or files. If set to NO these +# members will be included in the various overviews, but no documentation +# section is generated. This option has no effect if EXTRACT_ALL is enabled. +# The default value is: NO. + HIDE_UNDOC_MEMBERS = NO + +# If the HIDE_UNDOC_CLASSES tag is set to YES, Doxygen will hide all +# undocumented classes that are normally visible in the class hierarchy. If set +# to NO, these classes will be included in the various overviews. This option +# will also hide undocumented C++ concepts if enabled. This option has no effect +# if EXTRACT_ALL is enabled. +# The default value is: NO. + HIDE_UNDOC_CLASSES = NO + +# If the HIDE_FRIEND_COMPOUNDS tag is set to YES, Doxygen will hide all friend +# declarations. If set to NO, these declarations will be included in the +# documentation. +# The default value is: NO. + HIDE_FRIEND_COMPOUNDS = NO + +# If the HIDE_IN_BODY_DOCS tag is set to YES, Doxygen will hide any +# documentation blocks found inside the body of a function. If set to NO, these +# blocks will be appended to the function's detailed documentation block. +# The default value is: NO. + HIDE_IN_BODY_DOCS = NO + +# The INTERNAL_DOCS tag determines if documentation that is typed after a +# \internal command is included. If the tag is set to NO then the documentation +# will be excluded. Set it to YES to include the internal documentation. +# The default value is: NO. + INTERNAL_DOCS = YES + +# With the correct setting of option CASE_SENSE_NAMES Doxygen will better be +# able to match the capabilities of the underlying filesystem. In case the +# filesystem is case sensitive (i.e. it supports files in the same directory +# whose names only differ in casing), the option must be set to YES to properly +# deal with such files in case they appear in the input. For filesystems that +# are not case sensitive the option should be set to NO to properly deal with +# output files written for symbols that only differ in casing, such as for two +# classes, one named CLASS and the other named Class, and to also support +# references to files without having to specify the exact matching casing. On +# Windows (including Cygwin) and macOS, users should typically set this option +# to NO, whereas on Linux or other Unix flavors it should typically be set to +# YES. +# Possible values are: SYSTEM, NO and YES. +# The default value is: SYSTEM. + CASE_SENSE_NAMES = NO + +# If the HIDE_SCOPE_NAMES tag is set to NO then Doxygen will show members with +# their full class and namespace scopes in the documentation. If set to YES, the +# scope will be hidden. +# The default value is: NO. + HIDE_SCOPE_NAMES = NO + +# If the HIDE_COMPOUND_REFERENCE tag is set to NO (default) then Doxygen will +# append additional text to a page's title, such as Class Reference. If set to +# YES the compound reference will be hidden. +# The default value is: NO. + HIDE_COMPOUND_REFERENCE= NO + +# If the SHOW_HEADERFILE tag is set to YES then the documentation for a class +# will show which file needs to be included to use the class. +# The default value is: YES. + SHOW_HEADERFILE = YES -SHOW_INCLUDE_FILES = NO + +# If the SHOW_INCLUDE_FILES tag is set to YES then Doxygen will put a list of +# the files that are included by a file in the documentation of that file. +# The default value is: YES. + +SHOW_INCLUDE_FILES = YES + +# If the SHOW_GROUPED_MEMB_INC tag is set to YES then Doxygen will add for each +# grouped member an include statement to the documentation, telling the reader +# which file to include in order to use the member. +# The default value is: NO. + SHOW_GROUPED_MEMB_INC = NO + +# If the FORCE_LOCAL_INCLUDES tag is set to YES then Doxygen will list include +# files with double quotes in the documentation rather than with sharp brackets. +# The default value is: NO. + FORCE_LOCAL_INCLUDES = NO + +# If the INLINE_INFO tag is set to YES then a tag [inline] is inserted in the +# documentation for inline members. +# The default value is: YES. + INLINE_INFO = YES + +# If the SORT_MEMBER_DOCS tag is set to YES then Doxygen will sort the +# (detailed) documentation of file and class members alphabetically by member +# name. If set to NO, the members will appear in declaration order. +# The default value is: YES. + SORT_MEMBER_DOCS = NO + +# If the SORT_BRIEF_DOCS tag is set to YES then Doxygen will sort the brief +# descriptions of file, namespace and class members alphabetically by member +# name. If set to NO, the members will appear in declaration order. Note that +# this will also influence the order of the classes in the class list. +# The default value is: NO. + SORT_BRIEF_DOCS = NO + +# If the SORT_MEMBERS_CTORS_1ST tag is set to YES then Doxygen will sort the +# (brief and detailed) documentation of class members so that constructors and +# destructors are listed first. If set to NO the constructors will appear in the +# respective orders defined by SORT_BRIEF_DOCS and SORT_MEMBER_DOCS. +# Note: If SORT_BRIEF_DOCS is set to NO this option is ignored for sorting brief +# member documentation. +# Note: If SORT_MEMBER_DOCS is set to NO this option is ignored for sorting +# detailed member documentation. +# The default value is: NO. + SORT_MEMBERS_CTORS_1ST = NO + +# If the SORT_GROUP_NAMES tag is set to YES then Doxygen will sort the hierarchy +# of group names into alphabetical order. If set to NO the group names will +# appear in their defined order. +# The default value is: NO. + SORT_GROUP_NAMES = NO + +# If the SORT_BY_SCOPE_NAME tag is set to YES, the class list will be sorted by +# fully-qualified names, including namespaces. If set to NO, the class list will +# be sorted only by class name, not including the namespace part. +# Note: This option is not very useful if HIDE_SCOPE_NAMES is set to YES. +# Note: This option applies only to the class list, not to the alphabetical +# list. +# The default value is: NO. + SORT_BY_SCOPE_NAME = NO + +# If the STRICT_PROTO_MATCHING option is enabled and Doxygen fails to do proper +# type resolution of all parameters of a function it will reject a match between +# the prototype and the implementation of a member function even if there is +# only one candidate or it is obvious which candidate to choose by doing a +# simple string match. By disabling STRICT_PROTO_MATCHING Doxygen will still +# accept a match between prototype and implementation in such cases. +# The default value is: NO. + STRICT_PROTO_MATCHING = NO + +# The GENERATE_TODOLIST tag can be used to enable (YES) or disable (NO) the todo +# list. This list is created by putting \todo commands in the documentation. +# The default value is: YES. + GENERATE_TODOLIST = YES + +# The GENERATE_TESTLIST tag can be used to enable (YES) or disable (NO) the test +# list. This list is created by putting \test commands in the documentation. +# The default value is: YES. + GENERATE_TESTLIST = YES + +# The GENERATE_BUGLIST tag can be used to enable (YES) or disable (NO) the bug +# list. This list is created by putting \bug commands in the documentation. +# The default value is: YES. + GENERATE_BUGLIST = YES + +# The GENERATE_DEPRECATEDLIST tag can be used to enable (YES) or disable (NO) +# the deprecated list. This list is created by putting \deprecated commands in +# the documentation. +# The default value is: YES. + GENERATE_DEPRECATEDLIST= YES + +# The ENABLED_SECTIONS tag can be used to enable conditional documentation +# sections, marked by \if ... \endif and \cond +# ... \endcond blocks. + ENABLED_SECTIONS = YES + +# The MAX_INITIALIZER_LINES tag determines the maximum number of lines that the +# initial value of a variable or macro / define can have for it to appear in the +# documentation. If the initializer consists of more lines than specified here +# it will be hidden. Use a value of 0 to hide initializers completely. The +# appearance of the value of individual variables and macros / defines can be +# controlled using \showinitializer or \hideinitializer command in the +# documentation regardless of this setting. +# Minimum value: 0, maximum value: 10000, default value: 30. + MAX_INITIALIZER_LINES = 30 + +# Set the SHOW_USED_FILES tag to NO to disable the list of files generated at +# the bottom of the documentation of classes and structs. If set to YES, the +# list will mention the files that were used to generate the documentation. +# The default value is: YES. + SHOW_USED_FILES = NO -SHOW_FILES = NO + +# Set the SHOW_FILES tag to NO to disable the generation of the Files page. This +# will remove the Files entry from the Quick Index and from the Folder Tree View +# (if specified). +# The default value is: YES. + +SHOW_FILES = NO + +# Set the SHOW_NAMESPACES tag to NO to disable the generation of the Namespaces +# page. This will remove the Namespaces entry from the Quick Index and from the +# Folder Tree View (if specified). +# The default value is: YES. + SHOW_NAMESPACES = YES + +# The FILE_VERSION_FILTER tag can be used to specify a program or script that +# Doxygen should invoke to get the current version for each file (typically from +# the version control system). Doxygen will invoke the program by executing (via +# popen()) the command command input-file, where command is the value of the +# FILE_VERSION_FILTER tag, and input-file is the name of an input file provided +# by Doxygen. Whatever the program writes to standard output is used as the file +# version. For an example see the documentation. + FILE_VERSION_FILTER = + +# The LAYOUT_FILE tag can be used to specify a layout file which will be parsed +# by Doxygen. The layout file controls the global structure of the generated +# output files in an output format independent way. To create the layout file +# that represents Doxygen's defaults, run Doxygen with the -l option. You can +# optionally specify a file name after the option, if omitted DoxygenLayout.xml +# will be used as the name of the layout file. See also section "Changing the +# layout of pages" for information. +# +# Note that if you run Doxygen from a directory containing a file called +# DoxygenLayout.xml, Doxygen will parse it automatically even if the LAYOUT_FILE +# tag is left empty. + LAYOUT_FILE = ccpp_dox_layout.xml + +# The CITE_BIB_FILES tag can be used to specify one or more bib files containing +# the reference definitions. This must be a list of .bib files. The .bib +# extension is automatically appended if omitted. This requires the bibtex tool +# to be installed. See also https://en.wikipedia.org/wiki/BibTeX for more info. +# For LaTeX the style of the bibliography can be controlled using +# LATEX_BIB_STYLE. To use this feature you need bibtex and perl available in the +# search path. See also \cite for info how to create references. + CITE_BIB_FILES = library.bib +# The EXTERNAL_TOOL_PATH tag can be used to extend the search path (PATH +# environment variable) so that external tools such as latex and gs can be +# found. +# Note: Directories specified with EXTERNAL_TOOL_PATH are added in front of the +# path already specified by the PATH variable, and are added in the order +# specified. +# Note: This option is particularly useful for macOS version 14 (Sonoma) and +# higher, when running Doxygen from Doxywizard, because in this case any user- +# defined changes to the PATH are ignored. A typical example on macOS is to set +# EXTERNAL_TOOL_PATH = /Library/TeX/texbin /usr/local/bin +# together with the standard path, the full search path used by doxygen when +# launching external tools will then become +# PATH=/Library/TeX/texbin:/usr/local/bin:/usr/bin:/bin:/usr/sbin:/sbin + +EXTERNAL_TOOL_PATH = + #--------------------------------------------------------------------------- # Configuration options related to warning and progress messages #--------------------------------------------------------------------------- + +# The QUIET tag can be used to turn on/off the messages that are generated to +# standard output by Doxygen. If QUIET is set to YES this implies that the +# messages are off. +# The default value is: NO. + QUIET = NO + +# The WARNINGS tag can be used to turn on/off the warning messages that are +# generated to standard error (stderr) by Doxygen. If WARNINGS is set to YES +# this implies that the warnings are on. +# +# Tip: Turn warnings on while writing the documentation. +# The default value is: YES. + WARNINGS = YES + +# If the WARN_IF_UNDOCUMENTED tag is set to YES then Doxygen will generate +# warnings for undocumented members. If EXTRACT_ALL is set to YES then this flag +# will automatically be disabled. +# The default value is: YES. + WARN_IF_UNDOCUMENTED = NO + +# If the WARN_IF_DOC_ERROR tag is set to YES, Doxygen will generate warnings for +# potential errors in the documentation, such as documenting some parameters in +# a documented function twice, or documenting parameters that don't exist or +# using markup commands wrongly. +# The default value is: YES. + WARN_IF_DOC_ERROR = YES + +# If WARN_IF_INCOMPLETE_DOC is set to YES, Doxygen will warn about incomplete +# function parameter documentation. If set to NO, Doxygen will accept that some +# parameters have no documentation without warning. +# The default value is: YES. + WARN_IF_INCOMPLETE_DOC = YES + +# This WARN_NO_PARAMDOC option can be enabled to get warnings for functions that +# are documented, but have no documentation for their parameters or return +# value. If set to NO, Doxygen will only warn about wrong parameter +# documentation, but not about the absence of documentation. If EXTRACT_ALL is +# set to YES then this flag will automatically be disabled. See also +# WARN_IF_INCOMPLETE_DOC +# The default value is: NO. + WARN_NO_PARAMDOC = NO + +# If WARN_IF_UNDOC_ENUM_VAL option is set to YES, Doxygen will warn about +# undocumented enumeration values. If set to NO, Doxygen will accept +# undocumented enumeration values. If EXTRACT_ALL is set to YES then this flag +# will automatically be disabled. +# The default value is: NO. + +WARN_IF_UNDOC_ENUM_VAL = NO + +# If the WARN_AS_ERROR tag is set to YES then Doxygen will immediately stop when +# a warning is encountered. If the WARN_AS_ERROR tag is set to FAIL_ON_WARNINGS +# then Doxygen will continue running as if WARN_AS_ERROR tag is set to NO, but +# at the end of the Doxygen process Doxygen will return with a non-zero status. +# If the WARN_AS_ERROR tag is set to FAIL_ON_WARNINGS_PRINT then Doxygen behaves +# like FAIL_ON_WARNINGS but in case no WARN_LOGFILE is defined Doxygen will not +# write the warning messages in between other messages but write them at the end +# of a run, in case a WARN_LOGFILE is defined the warning messages will be +# besides being in the defined file also be shown at the end of a run, unless +# the WARN_LOGFILE is defined as - i.e. standard output (stdout) in that case +# the behavior will remain as with the setting FAIL_ON_WARNINGS. +# Possible values are: NO, YES, FAIL_ON_WARNINGS and FAIL_ON_WARNINGS_PRINT. +# The default value is: NO. + WARN_AS_ERROR = NO + +# The WARN_FORMAT tag determines the format of the warning messages that Doxygen +# can produce. The string should contain the $file, $line, and $text tags, which +# will be replaced by the file and line number from which the warning originated +# and the warning text. Optionally the format may contain $version, which will +# be replaced by the version of the file (if it could be obtained via +# FILE_VERSION_FILTER) +# See also: WARN_LINE_FORMAT +# The default value is: $file:$line: $text. + WARN_FORMAT = -WARN_LOGFILE = + +# In the $text part of the WARN_FORMAT command it is possible that a reference +# to a more specific place is given. To make it easier to jump to this place +# (outside of Doxygen) the user can define a custom "cut" / "paste" string. +# Example: +# WARN_LINE_FORMAT = "'vi $file +$line'" +# See also: WARN_FORMAT +# The default value is: at line $line of file $file. + +WARN_LINE_FORMAT = "at line $line of file $file" + +# The WARN_LOGFILE tag can be used to specify a file to which warning and error +# messages should be written. If left blank the output is written to standard +# error (stderr). In case the file specified cannot be opened for writing the +# warning and error messages are written to standard error. When as file - is +# specified the warning and error messages are written to standard output +# (stdout). + +WARN_LOGFILE = #--------------------------------------------------------------------------- # Configuration options related to the input files #--------------------------------------------------------------------------- -INPUT = pdftxt/mainpage.txt \ - pdftxt/all_schemes_list.txt \ - pdftxt/GFS_v16_suite.txt \ - pdftxt/GFS_v17_p8_suite.txt \ - pdftxt/RAP_suite.txt \ - pdftxt/HRRR_suite.txt \ - pdftxt/RE6/FV3_HRRR_input.nml \ - pdftxt/RRFS_v1beta_suite.txt \ - pdftxt/WoFS_v0_suite.txt \ - pdftxt/RRFS_SGSCLOUD.txt \ - pdftxt/GFS_RRTMG.txt \ - pdftxt/GFS_SFCLYR.txt \ - pdftxt/MYNN_SFCLAYER.txt \ - pdftxt/GFS_NSST.txt \ - pdftxt/GFS_OCEAN.txt \ - pdftxt/GFS_NOAH.txt \ - pdftxt/GFS_SFCSICE.txt \ - pdftxt/GFS_SATMEDMFVDIFQ.txt \ - pdftxt/GFS_NOAHMP.txt \ - pdftxt/GFS_UGWPv0.txt \ - pdftxt/GFS_unified_ugwp.txt \ - pdftxt/GFS_drag_suite.txt \ - pdftxt/GFS_GWDPS.txt \ - pdftxt/GFS_OZPHYS.txt \ - pdftxt/GFS_H2OPHYS.txt \ - pdftxt/GFS_SAMFdeep.txt \ - pdftxt/GFS_SAMFshal.txt \ - pdftxt/GFDL_cloud.txt \ - pdftxt/NSSLMICRO.txt \ - pdftxt/MYNN_EDMF.txt \ - pdftxt/CU_GF_deep.txt \ - pdftxt/RUCLSM.txt \ - pdftxt/THOMPSON.txt \ - pdftxt/suite_input.nml.txt \ - pdftxt/GFS_SPP.txt \ - ../fv_sat_adj.F90 \ - ../GFS_time_vary_pre.fv3.F90 \ - ../GFS_rad_time_vary.fv3.F90 \ - ../GFS_phys_time_vary.fv3.F90 \ - ../get_prs_fv3.F90 \ - ../get_phi_fv3.F90 \ - ../ozne_def.f \ - ../ozinterp.f90 \ - ../h2o_def.f \ - ../h2ointerp.f90 \ - ../aerclm_def.F \ - ../aerinterp.F90 \ - ../iccn_def.F \ - ../iccninterp.F90 \ - ../sfcsub.F \ - ../gcycle.F90 \ - ../GFS_suite_interstitial_1.F90 \ - ../GFS_suite_interstitial_2.F90 \ - ../GFS_suite_interstitial_3.F90 \ - ../GFS_suite_interstitial_4.F90 \ - ../GFS_suite_interstitial_5.F90 \ - ../GFS_suite_interstitial_phys_reset.F90 \ - ../GFS_suite_interstitial_rad_reset.F90 \ - ../GFS_suite_stateout_reset.F90 \ - ../GFS_suite_stateout_update.F90 \ - ../GFS_surface_composites_inter.F90 \ - ../GFS_surface_composites_pre.F90 \ - ../GFS_surface_composites_post.F90 \ - ../GFS_surface_loop_control_part1.F90 \ - ../GFS_surface_loop_control_part2.F90 \ - ../GFS_radiation_surface.F90 \ - ../GFS_rrtmg_pre.F90 \ - ../GFS_rrtmg_post.F90 \ - ../GFS_rrtmg_setup.F90 \ - ../rad_sw_pre.F90 \ - ../sgscloud_radpre.F90 \ - ../sgscloud_radpost.F90 \ - ../radsw_main.F90 \ - ../rrtmg_sw_post.F90 \ - ../rrtmg_lw_pre.F90 \ - ../radlw_main.F90 \ - ../rrtmg_lw_post.F90 \ - ../radiation_aerosols.f \ - ../radiation_astronomy.f \ - ../radiation_clouds.f \ - ../radiation_cloud_overlap.F90 \ - ../radiation_gases.f \ - ../radiation_surface.f \ - ../radlw_param.f \ - ../radlw_datatb.f \ - ../radsw_param.f \ - ../radsw_datatb.f \ - ../GFS_cloud_diagnostics.F90 \ - ../dcyc2t3.f \ - ../sfc_diff.f \ - ../sfc_diag.f \ - ../sfc_diag_post.F90 \ - ../sfc_nst.f \ - ../sfc_nst_pre.f \ - ../sfc_nst_post.f \ - ../sfc_ocean.F \ - ../module_nst_model.f90 \ - ../module_nst_parameters.f90 \ - ../module_nst_water_prop.f90 \ - ../lsm_noah.f \ - ../sflx.f \ - ../namelist_soilveg.f \ - ../set_soilveg.f \ - ../noahmpdrv.F90 \ - ../module_sf_noahmplsm.f90 \ - ../module_sf_noahmp_glacier.f90 \ - ../noahmp_tables.f90 \ - ../GFS_surface_generic_pre.F90 \ - ../GFS_surface_generic_post.F90 \ - ../surface_perturbation.F90 \ - ../GFS_DCNV_generic_pre.F90 \ - ../GFS_DCNV_generic_post.F90 \ - ../GFS_SCNV_generic_pre.F90 \ - ../GFS_SCNV_generic_post.F90 \ - ../sfc_sice.f \ - ../satmedmfvdifq.F \ - ../mfpbltq.f \ - ../mfscuq.f \ - ../tridi.f \ - ../GFS_GWD_generic_pre.F90 \ - ../GFS_GWD_generic_post.F90 \ - ../unified_ugwp.F90 \ - ../drag_suite.F90 \ - ../cires_tauamf_data.F90 \ - ../cires_orowam2017.f \ - ../cires_ugwp.F90 \ - ../cires_ugwp_initialize.F90 \ - ../cires_ugwp_module.F90 \ - ../cires_ugwp_post.F90 \ - ../cires_ugwp_triggers.F90 \ - ../cires_ugwp_module.F90 \ - ../gwdps.f \ - ../ugwp_driver_v0.F \ - ../ozphys_2015.f \ - ../h2ophys.f \ - ../samfdeepcnv.f \ - ../samfshalcnv.f \ - ../cnvc90.f \ - ../module_bfmicrophysics.f \ - ../gfdl_cloud_microphys.F90 \ - ../module_gfdl_cloud_microphys.F90 \ - ../GFS_MP_generic_pre.F90 \ - ../GFS_MP_generic_post.F90 \ - ../GFS_PBL_generic_common.F90 \ - ../GFS_PBL_generic_pre.F90 \ - ../GFS_PBL_generic_post.F90 \ - ../calpreciptype.f90 \ - ../GFS_stochastics.F90 \ - ../cu_gf_driver.F90 \ - ../cu_gf_driver_pre.F90 \ - ../cu_gf_deep.F90 \ - ../cu_gf_sh.F90 \ - ../cu_gf_driver_post.F90 \ - ../mynnedmf_wrapper.F90 \ - ../module_bl_mynn.F90 \ - ../mynnsfc_wrapper.F90 \ - ../module_sf_mynn.F90 \ - ../lsm_ruc.F90 \ - ../module_sf_ruclsm.F90 \ - ../namelist_soilveg_ruc.F90 \ - ../set_soilveg_ruc.F90 \ - ../module_soil_pre.F90 \ - ../mp_thompson_pre.F90 \ - ../module_mp_thompson_make_number_concentrations.F90 \ - ../mp_thompson.F90 \ - ../module_mp_thompson.F90 \ - ../module_mp_radar.F90 \ - ../mp_thompson_post.F90 \ - ../mp_nssl.F90 \ - ../module_mp_nssl_2mom.F90 \ - ../funcphys.f90 \ - ../physparam.f \ - ../physcons.F90 \ - ../radcons.f90 \ - ../mersenne_twister.f \ - ../maximum_hourly_diagnostics.F90 \ - ../phys_tend.F90 +# The INPUT tag is used to specify the files and/or directories that contain +# documented source files. You may enter file names like myfile.cpp or +# directories like /usr/src/myproject. Separate the files or directories with +# spaces. See also FILE_PATTERNS and EXTENSION_MAPPING +# Note: If this tag is empty the current directory is searched. + +INPUT = pdftxt/mainpage.txt \ + pdftxt/ccppv7_phy_updates.txt \ + pdftxt/all_schemes_list.txt \ + pdftxt/GFS_v16_suite.txt \ + pdftxt/GFS_v16_RRTMGP_suite.txt \ + pdftxt/GFS_v17_p8_ugwpv1_suite.txt \ + pdftxt/HRRR_gf_suite.txt \ + pdftxt/WoFS_v0_suite.txt \ + pdftxt/RRFS_SGSCLOUD.txt \ + pdftxt/GFS_RRTMG.txt \ + pdftxt/GFS_RRTMGP.txt \ + pdftxt/GFS_SFCLYR.txt \ + pdftxt/MYNN_SFCLAYER.txt \ + pdftxt/GFS_NSST.txt \ + pdftxt/GFS_OCEAN.txt \ + pdftxt/NOAH_LSM.txt \ + pdftxt/GFS_SFCSICE.txt \ + pdftxt/GFS_SATMEDMFVDIFQ.txt \ + pdftxt/NOAHMP_LSM.txt \ + pdftxt/UGWPv0.txt \ + pdftxt/GFS_ugwpv1.txt \ + pdftxt/GFS_UGWPV1_ORO.txt \ + pdftxt/GFS_GWDPS.txt \ + pdftxt/GFS_OZPHYS.txt \ + pdftxt/GFS_H2OPHYS.txt \ + pdftxt/GFS_SAMFdeep.txt \ + pdftxt/GFS_SAMFshal.txt \ + pdftxt/GFDL_cloud.txt \ + pdftxt/NSSLMICRO.txt \ + pdftxt/MYNN_EDMF.txt \ + pdftxt/CU_GF_deep.txt \ + pdftxt/RUCLSM.txt \ + pdftxt/CLM_LAKE.txt \ + pdftxt/THOMPSON.txt \ + pdftxt/suite_input.nml.txt \ + pdftxt/acronyms.txt \ + ../MP \ + ../CONV \ + ../GWD \ + ../SFC_Layer \ + ../PBL \ + ../SFC_Models \ + ../photochem \ + ../Radiation + +# This tag can be used to specify the character encoding of the source files +# that Doxygen parses. Internally Doxygen uses the UTF-8 encoding. Doxygen uses +# libiconv (or the iconv built into libc) for the transcoding. See the libiconv +# documentation (see: +# https://www.gnu.org/software/libiconv/) for the list of possible encodings. +# See also: INPUT_FILE_ENCODING +# The default value is: UTF-8. INPUT_ENCODING = UTF-8 + +# This tag can be used to specify the character encoding of the source files +# that Doxygen parses The INPUT_FILE_ENCODING tag can be used to specify +# character encoding on a per file pattern basis. Doxygen will compare the file +# name with each pattern and apply the encoding instead of the default +# INPUT_ENCODING) if there is a match. The character encodings are a list of the +# form: pattern=encoding (like *.php=ISO-8859-1). +# See also: INPUT_ENCODING for further information on supported encodings. + +INPUT_FILE_ENCODING = + +# If the value of the INPUT tag contains directories, you can use the +# FILE_PATTERNS tag to specify one or more wildcard patterns (like *.cpp and +# *.h) to filter out the source-files in the directories. +# +# Note that for custom extensions or not directly supported extensions you also +# need to set EXTENSION_MAPPING for the extension otherwise the files are not +# read by Doxygen. +# +# Note the list of default checked file patterns might differ from the list of +# default file extension mappings. +# +# If left blank the following patterns are tested:*.c, *.cc, *.cxx, *.cxxm, +# *.cpp, *.cppm, *.ccm, *.c++, *.c++m, *.java, *.ii, *.ixx, *.ipp, *.i++, *.inl, +# *.idl, *.ddl, *.odl, *.h, *.hh, *.hxx, *.hpp, *.h++, *.ixx, *.l, *.cs, *.d, +# *.php, *.php4, *.php5, *.phtml, *.inc, *.m, *.markdown, *.md, *.mm, *.dox (to +# be provided as Doxygen C comment), *.py, *.pyw, *.f90, *.f95, *.f03, *.f08, +# *.f18, *.f, *.for, *.vhd, *.vhdl, *.ucf, *.qsf and *.ice. + FILE_PATTERNS = *.f \ *.F \ *.F90 \ *.f90 \ *.nml \ *.txt + +# The RECURSIVE tag can be used to specify whether or not subdirectories should +# be searched for input files as well. +# The default value is: NO. + RECURSIVE = YES -EXCLUDE = + +# The EXCLUDE tag can be used to specify files and/or directories that should be +# excluded from the INPUT source files. This way you can easily exclude a +# subdirectory from a directory tree whose root is specified with the INPUT tag. +# +# Note that relative paths are relative to the directory from which Doxygen is +# run. + +EXCLUDE = ../Radiation/RRTMGP/rte-rrtmgp \ + ../MP/Morrison_Gettelman \ + ../MP/Ferrier_Aligo \ + ../MP/Zhao_Carr \ + ../PBL/MYJ \ + ../MP/GFDL/GFDL_parse_tracers.F90 \ + ../PBL/HEDMF \ + ../PBL/SHOC \ + ../PBL/saYSU \ + ../PBL/YSU \ + ../PBL/SATMEDMF/mfscu.f \ + ../PBL/SATMEDMF/satmedmfvdif.F \ + ../SFC_Models/Lake/Flake \ + ../smoke_dust \ + ../SFC_Layer/GFDL \ + ../SFC_Layer/MYJ \ + ../tools \ + ../CONV/C3 \ + ../CONV/Chikira_Sugiyama \ + ../CONV/nTiedtke \ + ../CONV/RAS \ + ../CONV/SAS \ + ../CONV/SAMF/samfaerosols.F \ + ../SFC_Layer/UFS/date_def.f \ + ../GWD/cires_ugwpv1_module.F90 \ + ../GWD/cires_ugwpv1_initialize.F90 \ + ../GWD/cires_ugwpv1_oro.F90 \ + ../GWD/cires_ugwpv1_solv2.F90 \ + ../GWD/cires_ugwpv1_sporo.F90 \ + ../GWD/cires_ugwpv1_triggers.F90 \ + ../GWD/cires_tauamf_data.F90 \ + ../GWD/unified_ugwp.F90 \ + ../GWD/unified_ugwp_post.F90 \ + ../GWD/gwdc.f \ + ../GWD/gwdc_post.f \ + ../GWD/gwdc_pre.f \ + ../GWD/rayleigh_damp.f + +# The EXCLUDE_SYMLINKS tag can be used to select whether or not files or +# directories that are symbolic links (a Unix file system feature) are excluded +# from the input. +# The default value is: NO. + EXCLUDE_SYMLINKS = NO + +# If the value of the INPUT tag contains directories, you can use the +# EXCLUDE_PATTERNS tag to specify one or more wildcard patterns to exclude +# certain files from those directories. +# +# Note that the wildcards are matched against the file with absolute path, so to +# exclude all test directories for example use the pattern */test/* + EXCLUDE_PATTERNS = + +# The EXCLUDE_SYMBOLS tag can be used to specify one or more symbol names +# (namespaces, classes, functions, etc.) that should be excluded from the +# output. The symbol name can be a fully qualified name, a word, or if the +# wildcard * is used, a substring. Examples: ANamespace, AClass, +# ANamespace::AClass, ANamespace::*Test + EXCLUDE_SYMBOLS = -EXAMPLE_PATH = pdftxt/RE6 \ + +# The EXAMPLE_PATH tag can be used to specify one or more files or directories +# that contain example code fragments that are included (see the \include +# command). + +EXAMPLE_PATH = pdftxt/RE7 \ doc/html -EXAMPLE_PATTERNS = + +# If the value of the EXAMPLE_PATH tag contains directories, you can use the +# EXAMPLE_PATTERNS tag to specify one or more wildcard pattern (like *.cpp and +# *.h) to filter out the source-files in the directories. If left blank all +# files are included. + +EXAMPLE_PATTERNS = + +# If the EXAMPLE_RECURSIVE tag is set to YES then subdirectories will be +# searched for input files to be used with the \include or \dontinclude commands +# irrespective of the value of the RECURSIVE tag. +# The default value is: NO. + EXAMPLE_RECURSIVE = NO + +# The IMAGE_PATH tag can be used to specify one or more files or directories +# that contain images that are to be included in the documentation (see the +# \image command). + IMAGE_PATH = img + +# The INPUT_FILTER tag can be used to specify a program that Doxygen should +# invoke to filter for each input file. Doxygen will invoke the filter program +# by executing (via popen()) the command: +# +# +# +# where is the value of the INPUT_FILTER tag, and is the +# name of an input file. Doxygen will then use the output that the filter +# program writes to standard output. If FILTER_PATTERNS is specified, this tag +# will be ignored. +# +# Note that the filter must not add or remove lines; it is applied before the +# code is scanned, but not when the output code is generated. If lines are added +# or removed, the anchors will not be placed correctly. +# +# Note that Doxygen will use the data processed and written to standard output +# for further processing, therefore nothing else, like debug statements or used +# commands (so in case of a Windows batch file always use @echo OFF), should be +# written to standard output. +# +# Note that for custom extensions or not directly supported extensions you also +# need to set EXTENSION_MAPPING for the extension otherwise the files are not +# properly processed by Doxygen. + INPUT_FILTER = + +# The FILTER_PATTERNS tag can be used to specify filters on a per file pattern +# basis. Doxygen will compare the file name with each pattern and apply the +# filter if there is a match. The filters are a list of the form: pattern=filter +# (like *.cpp=my_cpp_filter). See INPUT_FILTER for further information on how +# filters are used. If the FILTER_PATTERNS tag is empty or if none of the +# patterns match the file name, INPUT_FILTER is applied. +# +# Note that for custom extensions or not directly supported extensions you also +# need to set EXTENSION_MAPPING for the extension otherwise the files are not +# properly processed by Doxygen. + FILTER_PATTERNS = + +# If the FILTER_SOURCE_FILES tag is set to YES, the input filter (if set using +# INPUT_FILTER) will also be used to filter the input files that are used for +# producing the source files to browse (i.e. when SOURCE_BROWSER is set to YES). +# The default value is: NO. + FILTER_SOURCE_FILES = NO + +# The FILTER_SOURCE_PATTERNS tag can be used to specify source filters per file +# pattern. A pattern will override the setting for FILTER_PATTERN (if any) and +# it is also possible to disable source filtering for a specific pattern using +# *.ext= (so without naming a filter). +# This tag requires that the tag FILTER_SOURCE_FILES is set to YES. + FILTER_SOURCE_PATTERNS = + +# If the USE_MDFILE_AS_MAINPAGE tag refers to the name of a markdown file that +# is part of the input, its contents will be placed on the main page +# (index.html). This can be useful if you have a project on for instance GitHub +# and want to reuse the introduction page also for the Doxygen output. + USE_MDFILE_AS_MAINPAGE = +# The Fortran standard specifies that for fixed formatted Fortran code all +# characters from position 72 are to be considered as comment. A common +# extension is to allow longer lines before the automatic comment starts. The +# setting FORTRAN_COMMENT_AFTER will also make it possible that longer lines can +# be processed before the automatic comment starts. +# Minimum value: 7, maximum value: 10000, default value: 72. + +FORTRAN_COMMENT_AFTER = 72 + #--------------------------------------------------------------------------- # Configuration options related to source browsing #--------------------------------------------------------------------------- -SOURCE_BROWSER = NO +# If the SOURCE_BROWSER tag is set to YES then a list of source files will be +# generated. Documented entities will be cross-referenced with these sources. +# +# Note: To get rid of all source code in the generated output, make sure that +# also VERBATIM_HEADERS is set to NO. +# The default value is: NO. + +SOURCE_BROWSER = YES + +# Setting the INLINE_SOURCES tag to YES will include the body of functions, +# multi-line macros, enums or list initialized variables directly into the +# documentation. +# The default value is: NO. + INLINE_SOURCES = NO + +# Setting the STRIP_CODE_COMMENTS tag to YES will instruct Doxygen to hide any +# special comment blocks from generated source code fragments. Normal C, C++ and +# Fortran comments will always remain visible. +# The default value is: YES. + STRIP_CODE_COMMENTS = YES + +# If the REFERENCED_BY_RELATION tag is set to YES then for each documented +# entity all documented functions referencing it will be listed. +# The default value is: NO. + REFERENCED_BY_RELATION = YES + +# If the REFERENCES_RELATION tag is set to YES then for each documented function +# all documented entities called/used by that function will be listed. +# The default value is: NO. + REFERENCES_RELATION = YES + +# If the REFERENCES_LINK_SOURCE tag is set to YES and SOURCE_BROWSER tag is set +# to YES then the hyperlinks from functions in REFERENCES_RELATION and +# REFERENCED_BY_RELATION lists will link to the source code. Otherwise they will +# link to the documentation. +# The default value is: YES. + REFERENCES_LINK_SOURCE = YES + +# If SOURCE_TOOLTIPS is enabled (the default) then hovering a hyperlink in the +# source code will show a tooltip with additional information such as prototype, +# brief description and links to the definition and documentation. Since this +# will make the HTML file larger and loading of large files a bit slower, you +# can opt to disable this feature. +# The default value is: YES. +# This tag requires that the tag SOURCE_BROWSER is set to YES. + SOURCE_TOOLTIPS = YES + +# If the USE_HTAGS tag is set to YES then the references to source code will +# point to the HTML generated by the htags(1) tool instead of Doxygen built-in +# source browser. The htags tool is part of GNU's global source tagging system +# (see https://www.gnu.org/software/global/global.html). You will need version +# 4.8.6 or higher. +# +# To use it do the following: +# - Install the latest version of global +# - Enable SOURCE_BROWSER and USE_HTAGS in the configuration file +# - Make sure the INPUT points to the root of the source tree +# - Run doxygen as normal +# +# Doxygen will invoke htags (and that will in turn invoke gtags), so these +# tools must be available from the command line (i.e. in the search path). +# +# The result: instead of the source browser generated by Doxygen, the links to +# source code will now point to the output of htags. +# The default value is: NO. +# This tag requires that the tag SOURCE_BROWSER is set to YES. + USE_HTAGS = NO + +# If the VERBATIM_HEADERS tag is set the YES then Doxygen will generate a +# verbatim copy of the header file for each class for which an include is +# specified. Set to NO to disable this. +# See also: Section \class. +# The default value is: YES. + VERBATIM_HEADERS = YES -CLANG_ASSISTED_PARSING = NO -CLANG_ADD_INC_PATHS = YES -CLANG_OPTIONS = -CLANG_DATABASE_PATH = #--------------------------------------------------------------------------- # Configuration options related to the alphabetical class index #--------------------------------------------------------------------------- -ALPHABETICAL_INDEX = NO +# If the ALPHABETICAL_INDEX tag is set to YES, an alphabetical index of all +# compounds will be generated. Enable this if the project contains a lot of +# classes, structs, unions or interfaces. +# The default value is: YES. + +ALPHABETICAL_INDEX = YES + +# The IGNORE_PREFIX tag can be used to specify a prefix (or a list of prefixes) +# that should be ignored while generating the index headers. The IGNORE_PREFIX +# tag works for classes, function and member names. The entity will be placed in +# the alphabetical list under the first letter of the entity name that remains +# after removing the prefix. +# This tag requires that the tag ALPHABETICAL_INDEX is set to YES. + IGNORE_PREFIX = #--------------------------------------------------------------------------- # Configuration options related to the HTML output #--------------------------------------------------------------------------- +# If the GENERATE_HTML tag is set to YES, Doxygen will generate HTML output +# The default value is: YES. + GENERATE_HTML = YES + +# The HTML_OUTPUT tag is used to specify where the HTML docs will be put. If a +# relative path is entered the value of OUTPUT_DIRECTORY will be put in front of +# it. +# The default directory is: html. +# This tag requires that the tag GENERATE_HTML is set to YES. + HTML_OUTPUT = html + +# The HTML_FILE_EXTENSION tag can be used to specify the file extension for each +# generated HTML page (for example: .htm, .php, .asp). +# The default value is: .html. +# This tag requires that the tag GENERATE_HTML is set to YES. + HTML_FILE_EXTENSION = .html + +# The HTML_HEADER tag can be used to specify a user-defined HTML header file for +# each generated HTML page. If the tag is left blank Doxygen will generate a +# standard header. +# +# To get valid HTML the header file that includes any scripts and style sheets +# that Doxygen needs, which is dependent on the configuration options used (e.g. +# the setting GENERATE_TREEVIEW). It is highly recommended to start with a +# default header using +# doxygen -w html new_header.html new_footer.html new_stylesheet.css +# YourConfigFile +# and then modify the file new_header.html. See also section "Doxygen usage" +# for information on how to generate the default header that Doxygen normally +# uses. +# Note: The header is subject to change so you typically have to regenerate the +# default header when upgrading to a newer version of Doxygen. For a description +# of the possible markers and block names see the documentation. +# This tag requires that the tag GENERATE_HTML is set to YES. + HTML_HEADER = _doxygen/header.html + +# The HTML_FOOTER tag can be used to specify a user-defined HTML footer for each +# generated HTML page. If the tag is left blank Doxygen will generate a standard +# footer. See HTML_HEADER for more information on how to generate a default +# footer and what special commands can be used inside the footer. See also +# section "Doxygen usage" for information on how to generate the default footer +# that Doxygen normally uses. +# This tag requires that the tag GENERATE_HTML is set to YES. + HTML_FOOTER = _doxygen/footer.html -HTML_STYLESHEET = -HTML_EXTRA_STYLESHEET = _doxygen/doxygen-awesome.css \ + +# The HTML_STYLESHEET tag can be used to specify a user-defined cascading style +# sheet that is used by each HTML page. It can be used to fine-tune the look of +# the HTML output. If left blank Doxygen will generate a default style sheet. +# See also section "Doxygen usage" for information on how to generate the style +# sheet that Doxygen normally uses. +# Note: It is recommended to use HTML_EXTRA_STYLESHEET instead of this tag, as +# it is more robust and this tag (HTML_STYLESHEET) will in the future become +# obsolete. +# This tag requires that the tag GENERATE_HTML is set to YES. + +HTML_STYLESHEET = + +# The HTML_EXTRA_STYLESHEET tag can be used to specify additional user-defined +# cascading style sheets that are included after the standard style sheets +# created by Doxygen. Using this option one can overrule certain style aspects. +# This is preferred over using HTML_STYLESHEET since it does not replace the +# standard style sheet and is therefore more robust against future updates. +# Doxygen will copy the style sheet files to the output directory. +# Note: The order of the extra style sheet files is of importance (e.g. the last +# style sheet in the list overrules the setting of the previous ones in the +# list). +# Note: Since the styling of scrollbars can currently not be overruled in +# Webkit/Chromium, the styling will be left out of the default doxygen.css if +# one or more extra stylesheets have been specified. So if scrollbar +# customization is desired it has to be added explicitly. For an example see the +# documentation. +# This tag requires that the tag GENERATE_HTML is set to YES. + +HTML_EXTRA_STYLESHEET = _doxygen/doxygen-awesome.css \ _doxygen/doxygen-awesome-sidebar-only.css \ - _doxygen/doxygen-awesome-sidebar-only-darkmode-toggle.css \ - _doxygen/doxygen-awesome-ccpp.css + _doxygen/doxygen-awesome-sidebar-only-darkmode-toggle.css \ + _doxygen/doxygen-awesome-ccpp.css \ + _doxygen/custom.css + +# The HTML_EXTRA_FILES tag can be used to specify one or more extra images or +# other source files which should be copied to the HTML output directory. Note +# that these files will be copied to the base HTML output directory. Use the +# $relpath^ marker in the HTML_HEADER and/or HTML_FOOTER files to load these +# files. In the HTML_STYLESHEET file, use the file name only. Also note that the +# files will be copied as-is; there are no commands or markers available. +# This tag requires that the tag GENERATE_HTML is set to YES. + HTML_EXTRA_FILES = _doxygen/doxygen-awesome-darkmode-toggle.js \ _doxygen/doxygen-awesome-ccpp.js + +# The HTML_COLORSTYLE tag can be used to specify if the generated HTML output +# should be rendered with a dark or light theme. +# Possible values are: LIGHT always generates light mode output, DARK always +# generates dark mode output, AUTO_LIGHT automatically sets the mode according +# to the user preference, uses light mode if no preference is set (the default), +# AUTO_DARK automatically sets the mode according to the user preference, uses +# dark mode if no preference is set and TOGGLE allows a user to switch between +# light and dark mode via a button. +# The default value is: AUTO_LIGHT. +# This tag requires that the tag GENERATE_HTML is set to YES. + +HTML_COLORSTYLE = LIGHT + +# The HTML_COLORSTYLE_HUE tag controls the color of the HTML output. Doxygen +# will adjust the colors in the style sheet and background images according to +# this color. Hue is specified as an angle on a color-wheel, see +# https://en.wikipedia.org/wiki/Hue for more information. For instance the value +# 0 represents red, 60 is yellow, 120 is green, 180 is cyan, 240 is blue, 300 +# purple, and 360 is red again. +# Minimum value: 0, maximum value: 359, default value: 220. +# This tag requires that the tag GENERATE_HTML is set to YES. + HTML_COLORSTYLE_HUE = 209 + +# The HTML_COLORSTYLE_SAT tag controls the purity (or saturation) of the colors +# in the HTML output. For a value of 0 the output will use gray-scales only. A +# value of 255 will produce the most vivid colors. +# Minimum value: 0, maximum value: 255, default value: 100. +# This tag requires that the tag GENERATE_HTML is set to YES. + HTML_COLORSTYLE_SAT = 255 + +# The HTML_COLORSTYLE_GAMMA tag controls the gamma correction applied to the +# luminance component of the colors in the HTML output. Values below 100 +# gradually make the output lighter, whereas values above 100 make the output +# darker. The value divided by 100 is the actual gamma applied, so 80 represents +# a gamma of 0.8, The value 220 represents a gamma of 2.2, and 100 does not +# change the gamma. +# Minimum value: 40, maximum value: 240, default value: 80. +# This tag requires that the tag GENERATE_HTML is set to YES. + HTML_COLORSTYLE_GAMMA = 113 -HTML_TIMESTAMP = NO + +# If the HTML_DYNAMIC_MENUS tag is set to YES then the generated HTML +# documentation will contain a main index with vertical navigation menus that +# are dynamically created via JavaScript. If disabled, the navigation index will +# consists of multiple levels of tabs that are statically embedded in every HTML +# page. Disable this option to support browsers that do not have JavaScript, +# like the Qt help browser. +# The default value is: YES. +# This tag requires that the tag GENERATE_HTML is set to YES. + HTML_DYNAMIC_MENUS = YES + +# If the HTML_DYNAMIC_SECTIONS tag is set to YES then the generated HTML +# documentation will contain sections that can be hidden and shown after the +# page has loaded. +# The default value is: NO. +# This tag requires that the tag GENERATE_HTML is set to YES. + HTML_DYNAMIC_SECTIONS = NO + +# If the HTML_CODE_FOLDING tag is set to YES then classes and functions can be +# dynamically folded and expanded in the generated HTML source code. +# The default value is: YES. +# This tag requires that the tag GENERATE_HTML is set to YES. + +HTML_CODE_FOLDING = YES + +# If the HTML_COPY_CLIPBOARD tag is set to YES then Doxygen will show an icon in +# the top right corner of code and text fragments that allows the user to copy +# its content to the clipboard. Note this only works if supported by the browser +# and the web page is served via a secure context (see: +# https://www.w3.org/TR/secure-contexts/), i.e. using the https: or file: +# protocol. +# The default value is: YES. +# This tag requires that the tag GENERATE_HTML is set to YES. + +HTML_COPY_CLIPBOARD = YES + +# Doxygen stores a couple of settings persistently in the browser (via e.g. +# cookies). By default these settings apply to all HTML pages generated by +# Doxygen across all projects. The HTML_PROJECT_COOKIE tag can be used to store +# the settings under a project specific key, such that the user preferences will +# be stored separately. +# This tag requires that the tag GENERATE_HTML is set to YES. + +HTML_PROJECT_COOKIE = + +# With HTML_INDEX_NUM_ENTRIES one can control the preferred number of entries +# shown in the various tree structured indices initially; the user can expand +# and collapse entries dynamically later on. Doxygen will expand the tree to +# such a level that at most the specified number of entries are visible (unless +# a fully collapsed tree already exceeds this amount). So setting the number of +# entries 1 will produce a full collapsed tree by default. 0 is a special value +# representing an infinite number of entries and will result in a full expanded +# tree by default. +# Minimum value: 0, maximum value: 9999, default value: 100. +# This tag requires that the tag GENERATE_HTML is set to YES. + HTML_INDEX_NUM_ENTRIES = 100 + +# If the GENERATE_DOCSET tag is set to YES, additional index files will be +# generated that can be used as input for Apple's Xcode 3 integrated development +# environment (see: +# https://developer.apple.com/xcode/), introduced with OSX 10.5 (Leopard). To +# create a documentation set, Doxygen will generate a Makefile in the HTML +# output directory. Running make will produce the docset in that directory and +# running make install will install the docset in +# ~/Library/Developer/Shared/Documentation/DocSets so that Xcode will find it at +# startup. See https://developer.apple.com/library/archive/featuredarticles/Doxy +# genXcode/_index.html for more information. +# The default value is: NO. +# This tag requires that the tag GENERATE_HTML is set to YES. + GENERATE_DOCSET = NO + +# This tag determines the name of the docset feed. A documentation feed provides +# an umbrella under which multiple documentation sets from a single provider +# (such as a company or product suite) can be grouped. +# The default value is: Doxygen generated docs. +# This tag requires that the tag GENERATE_DOCSET is set to YES. + DOCSET_FEEDNAME = "Doxygen generated docs" + +# This tag determines the URL of the docset feed. A documentation feed provides +# an umbrella under which multiple documentation sets from a single provider +# (such as a company or product suite) can be grouped. +# This tag requires that the tag GENERATE_DOCSET is set to YES. + DOCSET_FEEDURL = + +# This tag specifies a string that should uniquely identify the documentation +# set bundle. This should be a reverse domain-name style string, e.g. +# com.mycompany.MyDocSet. Doxygen will append .docset to the name. +# The default value is: org.doxygen.Project. +# This tag requires that the tag GENERATE_DOCSET is set to YES. + DOCSET_BUNDLE_ID = org.doxygen.Project + +# The DOCSET_PUBLISHER_ID tag specifies a string that should uniquely identify +# the documentation publisher. This should be a reverse domain-name style +# string, e.g. com.mycompany.MyDocSet.documentation. +# The default value is: org.doxygen.Publisher. +# This tag requires that the tag GENERATE_DOCSET is set to YES. + DOCSET_PUBLISHER_ID = org.doxygen.Publisher + +# The DOCSET_PUBLISHER_NAME tag identifies the documentation publisher. +# The default value is: Publisher. +# This tag requires that the tag GENERATE_DOCSET is set to YES. + DOCSET_PUBLISHER_NAME = Publisher + +# If the GENERATE_HTMLHELP tag is set to YES then Doxygen generates three +# additional HTML index files: index.hhp, index.hhc, and index.hhk. The +# index.hhp is a project file that can be read by Microsoft's HTML Help Workshop +# on Windows. In the beginning of 2021 Microsoft took the original page, with +# a.o. the download links, offline the HTML help workshop was already many years +# in maintenance mode). You can download the HTML help workshop from the web +# archives at Installation executable (see: +# http://web.archive.org/web/20160201063255/http://download.microsoft.com/downlo +# ad/0/A/9/0A939EF6-E31C-430F-A3DF-DFAE7960D564/htmlhelp.exe). +# +# The HTML Help Workshop contains a compiler that can convert all HTML output +# generated by Doxygen into a single compiled HTML file (.chm). Compiled HTML +# files are now used as the Windows 98 help format, and will replace the old +# Windows help format (.hlp) on all Windows platforms in the future. Compressed +# HTML files also contain an index, a table of contents, and you can search for +# words in the documentation. The HTML workshop also contains a viewer for +# compressed HTML files. +# The default value is: NO. +# This tag requires that the tag GENERATE_HTML is set to YES. + GENERATE_HTMLHELP = NO + +# The CHM_FILE tag can be used to specify the file name of the resulting .chm +# file. You can add a path in front of the file if the result should not be +# written to the html output directory. +# This tag requires that the tag GENERATE_HTMLHELP is set to YES. + CHM_FILE = + +# The HHC_LOCATION tag can be used to specify the location (absolute path +# including file name) of the HTML help compiler (hhc.exe). If non-empty, +# Doxygen will try to run the HTML help compiler on the generated index.hhp. +# The file has to be specified with full path. +# This tag requires that the tag GENERATE_HTMLHELP is set to YES. + HHC_LOCATION = + +# The GENERATE_CHI flag controls if a separate .chi index file is generated +# (YES) or that it should be included in the main .chm file (NO). +# The default value is: NO. +# This tag requires that the tag GENERATE_HTMLHELP is set to YES. + GENERATE_CHI = NO + +# The CHM_INDEX_ENCODING is used to encode HtmlHelp index (hhk), content (hhc) +# and project file content. +# This tag requires that the tag GENERATE_HTMLHELP is set to YES. + CHM_INDEX_ENCODING = + +# The BINARY_TOC flag controls whether a binary table of contents is generated +# (YES) or a normal table of contents (NO) in the .chm file. Furthermore it +# enables the Previous and Next buttons. +# The default value is: NO. +# This tag requires that the tag GENERATE_HTMLHELP is set to YES. + BINARY_TOC = NO + +# The TOC_EXPAND flag can be set to YES to add extra items for group members to +# the table of contents of the HTML help documentation and to the tree view. +# The default value is: NO. +# This tag requires that the tag GENERATE_HTMLHELP is set to YES. + TOC_EXPAND = NO + +# The SITEMAP_URL tag is used to specify the full URL of the place where the +# generated documentation will be placed on the server by the user during the +# deployment of the documentation. The generated sitemap is called sitemap.xml +# and placed on the directory specified by HTML_OUTPUT. In case no SITEMAP_URL +# is specified no sitemap is generated. For information about the sitemap +# protocol see https://www.sitemaps.org +# This tag requires that the tag GENERATE_HTML is set to YES. + +SITEMAP_URL = + +# If the GENERATE_QHP tag is set to YES and both QHP_NAMESPACE and +# QHP_VIRTUAL_FOLDER are set, an additional index file will be generated that +# can be used as input for Qt's qhelpgenerator to generate a Qt Compressed Help +# (.qch) of the generated HTML documentation. +# The default value is: NO. +# This tag requires that the tag GENERATE_HTML is set to YES. + GENERATE_QHP = NO + +# If the QHG_LOCATION tag is specified, the QCH_FILE tag can be used to specify +# the file name of the resulting .qch file. The path specified is relative to +# the HTML output folder. +# This tag requires that the tag GENERATE_QHP is set to YES. + QCH_FILE = + +# The QHP_NAMESPACE tag specifies the namespace to use when generating Qt Help +# Project output. For more information please see Qt Help Project / Namespace +# (see: +# https://doc.qt.io/archives/qt-4.8/qthelpproject.html#namespace). +# The default value is: org.doxygen.Project. +# This tag requires that the tag GENERATE_QHP is set to YES. + QHP_NAMESPACE = org.doxygen.Project + +# The QHP_VIRTUAL_FOLDER tag specifies the namespace to use when generating Qt +# Help Project output. For more information please see Qt Help Project / Virtual +# Folders (see: +# https://doc.qt.io/archives/qt-4.8/qthelpproject.html#virtual-folders). +# The default value is: doc. +# This tag requires that the tag GENERATE_QHP is set to YES. + QHP_VIRTUAL_FOLDER = doc + +# If the QHP_CUST_FILTER_NAME tag is set, it specifies the name of a custom +# filter to add. For more information please see Qt Help Project / Custom +# Filters (see: +# https://doc.qt.io/archives/qt-4.8/qthelpproject.html#custom-filters). +# This tag requires that the tag GENERATE_QHP is set to YES. + QHP_CUST_FILTER_NAME = + +# The QHP_CUST_FILTER_ATTRS tag specifies the list of the attributes of the +# custom filter to add. For more information please see Qt Help Project / Custom +# Filters (see: +# https://doc.qt.io/archives/qt-4.8/qthelpproject.html#custom-filters). +# This tag requires that the tag GENERATE_QHP is set to YES. + QHP_CUST_FILTER_ATTRS = + +# The QHP_SECT_FILTER_ATTRS tag specifies the list of the attributes this +# project's filter section matches. Qt Help Project / Filter Attributes (see: +# https://doc.qt.io/archives/qt-4.8/qthelpproject.html#filter-attributes). +# This tag requires that the tag GENERATE_QHP is set to YES. + QHP_SECT_FILTER_ATTRS = + +# The QHG_LOCATION tag can be used to specify the location (absolute path +# including file name) of Qt's qhelpgenerator. If non-empty Doxygen will try to +# run qhelpgenerator on the generated .qhp file. +# This tag requires that the tag GENERATE_QHP is set to YES. + QHG_LOCATION = + +# If the GENERATE_ECLIPSEHELP tag is set to YES, additional index files will be +# generated, together with the HTML files, they form an Eclipse help plugin. To +# install this plugin and make it available under the help contents menu in +# Eclipse, the contents of the directory containing the HTML and XML files needs +# to be copied into the plugins directory of eclipse. The name of the directory +# within the plugins directory should be the same as the ECLIPSE_DOC_ID value. +# After copying Eclipse needs to be restarted before the help appears. +# The default value is: NO. +# This tag requires that the tag GENERATE_HTML is set to YES. + GENERATE_ECLIPSEHELP = NO + +# A unique identifier for the Eclipse help plugin. When installing the plugin +# the directory name containing the HTML and XML files should also have this +# name. Each documentation set should have its own identifier. +# The default value is: org.doxygen.Project. +# This tag requires that the tag GENERATE_ECLIPSEHELP is set to YES. + ECLIPSE_DOC_ID = org.doxygen.Project + +# If you want full control over the layout of the generated HTML pages it might +# be necessary to disable the index and replace it with your own. The +# DISABLE_INDEX tag can be used to turn on/off the condensed index (tabs) at top +# of each HTML page. A value of NO enables the index and the value YES disables +# it. Since the tabs in the index contain the same information as the navigation +# tree, you can set this option to YES if you also set GENERATE_TREEVIEW to YES. +# The default value is: NO. +# This tag requires that the tag GENERATE_HTML is set to YES. + DISABLE_INDEX = YES + +# The GENERATE_TREEVIEW tag is used to specify whether a tree-like index +# structure should be generated to display hierarchical information. If the tag +# value is set to YES, a side panel will be generated containing a tree-like +# index structure (just like the one that is generated for HTML Help). For this +# to work a browser that supports JavaScript, DHTML, CSS and frames is required +# (i.e. any modern browser). Windows users are probably better off using the +# HTML help feature. Via custom style sheets (see HTML_EXTRA_STYLESHEET) one can +# further fine tune the look of the index (see "Fine-tuning the output"). As an +# example, the default style sheet generated by Doxygen has an example that +# shows how to put an image at the root of the tree instead of the PROJECT_NAME. +# Since the tree basically has the same information as the tab index, you could +# consider setting DISABLE_INDEX to YES when enabling this option. +# The default value is: NO. +# This tag requires that the tag GENERATE_HTML is set to YES. + GENERATE_TREEVIEW = YES + +# When both GENERATE_TREEVIEW and DISABLE_INDEX are set to YES, then the +# FULL_SIDEBAR option determines if the side bar is limited to only the treeview +# area (value NO) or if it should extend to the full height of the window (value +# YES). Setting this to YES gives a layout similar to +# https://docs.readthedocs.io with more room for contents, but less room for the +# project logo, title, and description. If either GENERATE_TREEVIEW or +# DISABLE_INDEX is set to NO, this option has no effect. +# The default value is: NO. +# This tag requires that the tag GENERATE_HTML is set to YES. + FULL_SIDEBAR = NO + +# The ENUM_VALUES_PER_LINE tag can be used to set the number of enum values that +# Doxygen will group on one line in the generated HTML documentation. +# +# Note that a value of 0 will completely suppress the enum values from appearing +# in the overview section. +# Minimum value: 0, maximum value: 20, default value: 4. +# This tag requires that the tag GENERATE_HTML is set to YES. + ENUM_VALUES_PER_LINE = 4 + +# When the SHOW_ENUM_VALUES tag is set doxygen will show the specified +# enumeration values besides the enumeration mnemonics. +# The default value is: NO. + +SHOW_ENUM_VALUES = NO + +# If the treeview is enabled (see GENERATE_TREEVIEW) then this tag can be used +# to set the initial width (in pixels) of the frame in which the tree is shown. +# Minimum value: 0, maximum value: 1500, default value: 250. +# This tag requires that the tag GENERATE_HTML is set to YES. + TREEVIEW_WIDTH = 335 + +# If the EXT_LINKS_IN_WINDOW option is set to YES, Doxygen will open links to +# external symbols imported via tag files in a separate window. +# The default value is: NO. +# This tag requires that the tag GENERATE_HTML is set to YES. + EXT_LINKS_IN_WINDOW = NO + +# If the OBFUSCATE_EMAILS tag is set to YES, Doxygen will obfuscate email +# addresses. +# The default value is: YES. +# This tag requires that the tag GENERATE_HTML is set to YES. + OBFUSCATE_EMAILS = YES + +# If the HTML_FORMULA_FORMAT option is set to svg, Doxygen will use the pdf2svg +# tool (see https://github.com/dawbarton/pdf2svg) or inkscape (see +# https://inkscape.org) to generate formulas as SVG images instead of PNGs for +# the HTML output. These images will generally look nicer at scaled resolutions. +# Possible values are: png (the default) and svg (looks nicer but requires the +# pdf2svg or inkscape tool). +# The default value is: png. +# This tag requires that the tag GENERATE_HTML is set to YES. + HTML_FORMULA_FORMAT = SVG + +# Use this tag to change the font size of LaTeX formulas included as images in +# the HTML documentation. When you change the font size after a successful +# Doxygen run you need to manually remove any form_*.png images from the HTML +# output directory to force them to be regenerated. +# Minimum value: 8, maximum value: 50, default value: 10. +# This tag requires that the tag GENERATE_HTML is set to YES. + FORMULA_FONTSIZE = 10 -FORMULA_TRANSPARENT = YES + +# The FORMULA_MACROFILE can contain LaTeX \newcommand and \renewcommand commands +# to create new LaTeX commands to be used in formulas as building blocks. See +# the section "Including formulas" for details. + FORMULA_MACROFILE = + +# Enable the USE_MATHJAX option to render LaTeX formulas using MathJax (see +# https://www.mathjax.org) which uses client side JavaScript for the rendering +# instead of using pre-rendered bitmaps. Use this if you do not have LaTeX +# installed or if you want to formulas look prettier in the HTML output. When +# enabled you may also need to install MathJax separately and configure the path +# to it using the MATHJAX_RELPATH option. +# The default value is: NO. +# This tag requires that the tag GENERATE_HTML is set to YES. + USE_MATHJAX = YES + +# With MATHJAX_VERSION it is possible to specify the MathJax version to be used. +# Note that the different versions of MathJax have different requirements with +# regards to the different settings, so it is possible that also other MathJax +# settings have to be changed when switching between the different MathJax +# versions. +# Possible values are: MathJax_2 and MathJax_3. +# The default value is: MathJax_2. +# This tag requires that the tag USE_MATHJAX is set to YES. + MATHJAX_VERSION = MathJax_2 + +# When MathJax is enabled you can set the default output format to be used for +# the MathJax output. For more details about the output format see MathJax +# version 2 (see: +# http://docs.mathjax.org/en/v2.7-latest/output.html) and MathJax version 3 +# (see: +# http://docs.mathjax.org/en/latest/web/components/output.html). +# Possible values are: HTML-CSS (which is slower, but has the best +# compatibility. This is the name for Mathjax version 2, for MathJax version 3 +# this will be translated into chtml), NativeMML (i.e. MathML. Only supported +# for MathJax 2. For MathJax version 3 chtml will be used instead.), chtml (This +# is the name for Mathjax version 3, for MathJax version 2 this will be +# translated into HTML-CSS) and SVG. +# The default value is: HTML-CSS. +# This tag requires that the tag USE_MATHJAX is set to YES. + MATHJAX_FORMAT = HTML-CSS + +# When MathJax is enabled you need to specify the location relative to the HTML +# output directory using the MATHJAX_RELPATH option. The destination directory +# should contain the MathJax.js script. For instance, if the mathjax directory +# is located at the same level as the HTML output directory, then +# MATHJAX_RELPATH should be ../mathjax. The default value points to the MathJax +# Content Delivery Network so you can quickly see the result without installing +# MathJax. However, it is strongly recommended to install a local copy of +# MathJax from https://www.mathjax.org before deployment. The default value is: +# - in case of MathJax version 2: https://cdn.jsdelivr.net/npm/mathjax@2 +# - in case of MathJax version 3: https://cdn.jsdelivr.net/npm/mathjax@3 +# This tag requires that the tag USE_MATHJAX is set to YES. + MATHJAX_RELPATH = https://cdn.jsdelivr.net/npm/mathjax@2 + +# The MATHJAX_EXTENSIONS tag can be used to specify one or more MathJax +# extension names that should be enabled during MathJax rendering. For example +# for MathJax version 2 (see +# https://docs.mathjax.org/en/v2.7-latest/tex.html#tex-and-latex-extensions): +# MATHJAX_EXTENSIONS = TeX/AMSmath TeX/AMSsymbols +# For example for MathJax version 3 (see +# http://docs.mathjax.org/en/latest/input/tex/extensions/index.html): +# MATHJAX_EXTENSIONS = ams +# This tag requires that the tag USE_MATHJAX is set to YES. + MATHJAX_EXTENSIONS = + +# The MATHJAX_CODEFILE tag can be used to specify a file with JavaScript pieces +# of code that will be used on startup of the MathJax code. See the MathJax site +# (see: +# http://docs.mathjax.org/en/v2.7-latest/output.html) for more details. For an +# example see the documentation. +# This tag requires that the tag USE_MATHJAX is set to YES. + MATHJAX_CODEFILE = + +# When the SEARCHENGINE tag is enabled Doxygen will generate a search box for +# the HTML output. The underlying search engine uses JavaScript and DHTML and +# should work on any modern browser. Note that when using HTML help +# (GENERATE_HTMLHELP), Qt help (GENERATE_QHP), or docsets (GENERATE_DOCSET) +# there is already a search function so this one should typically be disabled. +# For large projects the JavaScript based search engine can be slow, then +# enabling SERVER_BASED_SEARCH may provide a better solution. It is possible to +# search using the keyboard; to jump to the search box use + S +# (what the is depends on the OS and browser, but it is typically +# , /