Skip to content

Commit

Permalink
save scidoc
Browse files Browse the repository at this point in the history
  • Loading branch information
mzhangw committed Jun 24, 2024
1 parent 1be281d commit 8525a7e
Show file tree
Hide file tree
Showing 20 changed files with 429 additions and 352 deletions.
Original file line number Diff line number Diff line change
@@ -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.
Expand All @@ -22,7 +25,7 @@ module GFS_ccpp_suite_sim_pre
! SUBROUTINE GFS_ccpp_suite_sim_pre_run
!
! ######################################################################################
!! \section arg_table_GFS_ccpp_suite_sim_pre_run
!> \section arg_table_GFS_ccpp_suite_sim_pre_run
!! \htmlinclude GFS_ccpp_suite_sim_pre_run.html
!!
subroutine GFS_ccpp_suite_sim_pre_run(do_ccpp_suite_sim, dtend, ntqv, dtidx, dtp, &
Expand Down Expand Up @@ -110,6 +113,7 @@ subroutine GFS_ccpp_suite_sim_pre_run(do_ccpp_suite_sim, dtend, ntqv, dtidx, dtp
end subroutine GFS_ccpp_suite_sim_pre_run

! ######################################################################################
!>
subroutine load_ccpp_suite_sim(nlunit, nml_file, physics_process, iactive_T, &
iactive_u, iactive_v, iactive_q, errmsg, errflg)

Expand Down
33 changes: 16 additions & 17 deletions physics/Interstitials/UFS_SCM_NEPTUNE/ccpp_suite_simulator.F90
Original file line number Diff line number Diff line change
@@ -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
Expand Down
101 changes: 38 additions & 63 deletions physics/Interstitials/UFS_SCM_NEPTUNE/module_ccpp_suite_simulator.F90
Original file line number Diff line number Diff line change
@@ -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
Expand All @@ -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
Expand All @@ -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
Expand All @@ -56,24 +52,20 @@ module module_ccpp_suite_simulator
real(kind_phys), dimension(:,:,:,:), allocatable :: q
end type phys_tend_4d

! This type contains the meta information and data for each physics process.

!> \section arg_table_base_physics_process Argument Table
!! \htmlinclude base_physics_process.html
!!
!> This type contains the meta information and data for each physics process.
type base_physics_process
character(len=16) :: name ! Physics process name
logical :: time_split = .false. ! Is process time-split?
logical :: use_sim = .false. ! Is process "active"?
integer :: order ! Order of process in process-loop
type(phys_tend_1d) :: tend1d ! Instantaneous data
type(phys_tend_2d) :: tend2d ! 2-dimensional data
type(phys_tend_3d) :: tend3d ! Not used. Placeholder for 3-dimensional spatial data.
type(phys_tend_4d) :: tend4d ! Not used. Placeholder for 4-dimensional spatio-tempo data.
character(len=16) :: active_name ! "Active" scheme: Physics process name
integer :: iactive_scheme ! "Active" scheme: Order of process in process-loop
logical :: active_tsp ! "Active" scheme: Is process time-split?
integer :: nprg_active ! "Active" scheme: Number of prognostic variables
character(len=16) :: name !< Physics process name
logical :: time_split = .false. !< Is process time-split?
logical :: use_sim = .false. !< Is process "active"?
integer :: order !< Order of process in process-loop
type(phys_tend_1d) :: tend1d !< Instantaneous data
type(phys_tend_2d) :: tend2d !< 2-dimensional data
type(phys_tend_3d) :: tend3d !< Not used. Placeholder for 3-dimensional spatial data.
type(phys_tend_4d) :: tend4d !< Not used. Placeholder for 4-dimensional spatio-tempo data.
character(len=16) :: active_name !< "Active" scheme: Physics process name
integer :: iactive_scheme !< "Active" scheme: Order of process in process-loop
logical :: active_tsp !< "Active" scheme: Is process time-split?
integer :: nprg_active !< "Active" scheme: Number of prognostic variables
contains
generic, public :: linterp => linterp_1D, linterp_2D
procedure, private :: linterp_1D
Expand All @@ -84,11 +76,8 @@ module module_ccpp_suite_simulator

contains

! ####################################################################################
! Type-bound procedure to compute tendency profile for time-of-day.
!
! For use with 1D data (level, time) tendencies with diurnal (24-hr) forcing.
! ####################################################################################
!> Type-bound procedure to compute tendency profile for time-of-day.
!! For use with 1D data (level, time) tendencies with diurnal (24-hr) forcing.
function linterp_1D(this, var_name, year, month, day, hour, min, sec) result(err_message)
class(base_physics_process), intent(inout) :: this
character(len=*), intent(in) :: var_name
Expand Down Expand Up @@ -131,13 +120,10 @@ function linterp_1D(this, var_name, year, month, day, hour, min, sec) result(err

end function linterp_1D

! ####################################################################################
! Type-bound procedure to compute tendency profile for time-of-day.
!
! For use with 2D data (location, level, time) tendencies with diurnal (24-hr) forcing.
! This assumes that the location dimension has a [longitude, latitude] allocated with
! each location.
! ####################################################################################
!> Type-bound procedure to compute tendency profile for time-of-day.
!! For use with 2D data (location, level, time) tendencies with diurnal (24-hr) forcing.
!! This assumes that the location dimension has a [longitude, latitude] allocated with
!! each location.
function linterp_2D(this, var_name, lon, lat, year, month, day, hour, min, sec) result(err_message)
class(base_physics_process), intent(inout) :: this
character(len=*), intent(in) :: var_name
Expand Down Expand Up @@ -165,10 +151,8 @@ function linterp_2D(this, var_name, lon, lat, year, month, day, hour, min, sec)
end select
end function linterp_2D

! ####################################################################################
! Type-bound procedure to find nearest location.
! For use with linterp_2D, NOT YET IMPLEMENTED.
! ####################################################################################
!> Type-bound procedure to find nearest location.
!! For use with linterp_2D, NOT YET IMPLEMENTED.
pure function find_nearest_loc_2d_1d(this, lon, lat)
class(base_physics_process), intent(in) :: this
real(kind_phys), intent(in) :: lon, lat
Expand All @@ -177,10 +161,8 @@ pure function find_nearest_loc_2d_1d(this, lon, lat)
find_nearest_loc_2d_1d = 1
end function find_nearest_loc_2d_1d

! ####################################################################################
! Type-bound procedure to compute linear interpolation weights for a diurnal (24-hour)
! forcing.
! ####################################################################################
!> Type-bound procedure to compute linear interpolation weights for a diurnal (24-hour)
!! forcing.
subroutine cmp_time_wts(this, year, month, day, hour, minute, sec, w1, w2, ti, tf)
! Inputs
class(base_physics_process), intent(in) :: this
Expand All @@ -199,8 +181,7 @@ subroutine cmp_time_wts(this, year, month, day, hour, minute, sec, w1, w2, ti, t

end subroutine cmp_time_wts

! ####################################################################################
! ####################################################################################
!>
subroutine sim_LWRAD( year, month, day, hour, min, sec, process)
type(base_physics_process), intent(inout) :: process
integer, intent(in) :: year, month, day, hour, min, sec
Expand All @@ -212,8 +193,7 @@ subroutine sim_LWRAD( year, month, day, hour, min, sec, process)

end subroutine sim_LWRAD

! ####################################################################################
! ####################################################################################
!>
subroutine sim_SWRAD( year, month, day, hour, min, sec, process)
type(base_physics_process), intent(inout) :: process
integer, intent(in) :: year, month, day, hour, min, sec
Expand All @@ -225,8 +205,7 @@ subroutine sim_SWRAD( year, month, day, hour, min, sec, process)

end subroutine sim_SWRAD

! ####################################################################################
! ####################################################################################
!>
subroutine sim_GWD( year, month, day, hour, min, sec, process)
type(base_physics_process), intent(inout) :: process
integer, intent(in) :: year, month, day, hour, min, sec
Expand All @@ -244,8 +223,7 @@ subroutine sim_GWD( year, month, day, hour, min, sec, process)

end subroutine sim_GWD

! ####################################################################################
! ####################################################################################
!>
subroutine sim_PBL( year, month, day, hour, min, sec, process)
type(base_physics_process), intent(inout) :: process
integer, intent(in) :: year, month, day, hour, min, sec
Expand All @@ -266,8 +244,7 @@ subroutine sim_PBL( year, month, day, hour, min, sec, process)

end subroutine sim_PBL

! ####################################################################################
! ####################################################################################
!>
subroutine sim_DCNV( year, month, day, hour, min, sec, process)
type(base_physics_process), intent(inout) :: process
integer, intent(in) :: year, month, day, hour, min, sec
Expand All @@ -288,8 +265,7 @@ subroutine sim_DCNV( year, month, day, hour, min, sec, process)

end subroutine sim_DCNV

! ####################################################################################
! ####################################################################################
!>
subroutine sim_SCNV( year, month, day, hour, min, sec, process)
type(base_physics_process), intent(inout) :: process
integer, intent(in) :: year, month, day, hour, min, sec
Expand All @@ -310,8 +286,7 @@ subroutine sim_SCNV( year, month, day, hour, min, sec, process)

end subroutine sim_SCNV

! ####################################################################################
! ####################################################################################
!>
subroutine sim_cldMP( year, month, day, hour, min, sec, process)
type(base_physics_process), intent(inout) :: process
integer, intent(in) :: year, month, day, hour, min, sec
Expand Down
4 changes: 4 additions & 0 deletions physics/Radiation/RRTMG/iounitdef.f
Original file line number Diff line number Diff line change
@@ -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 !!!!!
!!!!! ========================================================== !!!!!
Expand Down
4 changes: 2 additions & 2 deletions physics/Radiation/RRTMG/module_bfmicrophysics.f
Original file line number Diff line number Diff line change
@@ -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
Expand Down
6 changes: 2 additions & 4 deletions physics/Radiation/RRTMG/rad_sw_pre.F90
Original file line number Diff line number Diff line change
@@ -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
!!
Expand Down Expand Up @@ -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
4 changes: 0 additions & 4 deletions physics/Radiation/RRTMG/radcons.f90
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
3 changes: 3 additions & 0 deletions physics/Radiation/RRTMG/rrtmg_lw_cloud_optics.F90
Original file line number Diff line number Diff line change
@@ -1,3 +1,6 @@
!>\file rrtmg_lw_cloud_optics.F90
!!

module mo_rrtmg_lw_cloud_optics
use machine, only: kind_phys
use mersenne_twister, only: random_setseed, random_number, random_stat
Expand Down
Loading

0 comments on commit 8525a7e

Please sign in to comment.