Skip to content

Commit

Permalink
address review and fix bugs
Browse files Browse the repository at this point in the history
  • Loading branch information
mzhangw committed Aug 1, 2024
1 parent 1dff883 commit b62597b
Show file tree
Hide file tree
Showing 18 changed files with 242 additions and 227 deletions.
2 changes: 0 additions & 2 deletions physics/CONV/progsigma_calc.f90
Original file line number Diff line number Diff line change
Expand Up @@ -11,8 +11,6 @@ module progsigma

contains

!>\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
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -232,7 +232,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
Expand Down
3 changes: 3 additions & 0 deletions physics/Interstitials/UFS_SCM_NEPTUNE/iccninterp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ module iccninterp

contains

!>
SUBROUTINE read_cidata (me, master)
use machine, only: kind_phys
use iccn_def
Expand Down Expand Up @@ -65,6 +66,7 @@ END SUBROUTINE read_cidata
!
!**********************************************************************
!
!>
SUBROUTINE setindxci(npts,dlat,jindx1,jindx2,ddy,dlon, &
iindx1,iindx2,ddx)
!
Expand Down Expand Up @@ -126,6 +128,7 @@ END SUBROUTINE setindxci
!**********************************************************************
!**********************************************************************
!
!>
SUBROUTINE ciinterpol(me,npts,IDATE,FHOUR,jindx1,jindx2,ddy, &
iindx1,iindx2,ddx,lev, prsl, ciplout,ccnout)
!
Expand Down
17 changes: 6 additions & 11 deletions physics/MP/Morrison_Gettelman/micro_mg3_0.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2,11 +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
Expand Down Expand Up @@ -247,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( &
Expand Down Expand Up @@ -432,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: [email protected], [email protected]
!!\section mg3_micro_mg_tend MG3 micro_mg_tend General Algorithm
Expand Down Expand Up @@ -4483,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)
Expand Down
13 changes: 3 additions & 10 deletions physics/MP/calpreciptype.f90
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,7 @@

module calpreciptype_mod
contains
!>\ingroup gfs_calpreciptype
!! Foure algorithms are called to calculate dominant precipitation type, and the
!> Foure algorithms are called to calculate dominant precipitation type, and the
!!tallies are sumed in calwxt_dominant().
!!
!>\section gen_calp GFS calpreciptype General Algorithm
Expand Down Expand Up @@ -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, &
Expand Down Expand Up @@ -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)
Expand Down Expand Up @@ -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.
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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.
!!
Expand Down
64 changes: 32 additions & 32 deletions physics/Radiation/RRTMGP/rrtmgp_aerosol_optics.F90
Original file line number Diff line number Diff line change
Expand Up @@ -25,54 +25,54 @@ subroutine rrtmgp_aerosol_optics_run(doSWrad, doLWrad, nCol, nLev, nDay, idxday,

! Inputs
logical, intent(in) :: &
doSWrad, & !< Logical flag for shortwave radiation call
doLWrad, & !< Logical flag for longwave radiation call
top_at_1 !< Logical flag for vertical grid direcetion
doSWrad, & ! Logical flag for shortwave radiation call
doLWrad, & ! Logical flag for longwave radiation call
top_at_1 ! Logical flag for vertical grid direcetion
integer, intent(in) :: &
nCol, & !< Number of horizontal grid points
nDay, & !< Number of daylit points
nLev, & !< Number of vertical layers
iaermdl, & !< Aerosol model scheme flag
iaerflg !< Aerosol effects to include
nCol, & ! Number of horizontal grid points
nDay, & ! Number of daylit points
nLev, & ! Number of vertical layers
iaermdl, & ! Aerosol model scheme flag
iaerflg ! Aerosol effects to include
integer,intent(in),dimension(:) :: &
idxday !< Indices for daylit points.
idxday ! Indices for daylit points.
real(kind_phys),intent(in) :: &
con_pi, & !< Physical constant (pi)
con_rd, & !< Physical constant (gas constant for dry-air)
con_g !< Physical constant (gravitational constant)
con_pi, & ! Physical constant (pi)
con_rd, & ! Physical constant (gas constant for dry-air)
con_g ! Physical constant (gravitational constant)
real(kind_phys), dimension(:), intent(in) :: &
lon, & !< Longitude
lat, & !< Latitude
lsmask !< Land/sea/sea-ice mask
lon, & ! Longitude
lat, & ! Latitude
lsmask ! Land/sea/sea-ice mask
real(kind_phys), dimension(:,:),intent(in), optional :: &
p_lay, & !< Pressure @ layer-centers (Pa)
tv_lay, & !< Virtual-temperature @ layer-centers (K)
relhum !< Relative-humidity @ layer-centers
p_lay, & ! Pressure @ layer-centers (Pa)
tv_lay, & ! Virtual-temperature @ layer-centers (K)
relhum ! Relative-humidity @ layer-centers
real(kind_phys), dimension(:,:),intent(in) :: &
p_lk !< Exner function @ layer-centers (1)
p_lk ! Exner function @ layer-centers (1)
real(kind_phys), dimension(:, :,:),intent(in) :: &
tracer !< trace gas concentrations
tracer ! trace gas concentrations
real(kind_phys), dimension(:, :,:),intent(in) :: &
aerfld !< aerosol input concentrations
aerfld ! aerosol input concentrations
real(kind_phys), dimension(:,:),intent(in), optional :: &
p_lev !< Pressure @ layer-interfaces (Pa)
p_lev ! Pressure @ layer-interfaces (Pa)
real (kind=kind_phys), dimension(:,:), intent(out) :: &
ext550 !< 3d optical extinction for total aerosol species
ext550 ! 3d optical extinction for total aerosol species

! Outputs
real(kind_phys), dimension(:,:), intent(out) :: &
aerodp !< Vertical integrated optical depth for various aerosol species
aerodp ! Vertical integrated optical depth for various aerosol species
real(kind_phys), dimension(:,:,:), intent(out) :: &
aerlw_tau, & !< Longwave aerosol optical depth
aerlw_ssa, & !< Longwave aerosol single scattering albedo
aerlw_g, & !< Longwave aerosol asymmetry parameter
aersw_tau, & !< Shortwave aerosol optical depth
aersw_ssa, & !< Shortwave aerosol single scattering albedo
aersw_g !< Shortwave aerosol asymmetry parameter
aerlw_tau, & ! Longwave aerosol optical depth
aerlw_ssa, & ! Longwave aerosol single scattering albedo
aerlw_g, & ! Longwave aerosol asymmetry parameter
aersw_tau, & ! Shortwave aerosol optical depth
aersw_ssa, & ! Shortwave aerosol single scattering albedo
aersw_g ! Shortwave aerosol asymmetry parameter
integer, intent(out) :: &
errflg !< CCPP error flag
errflg ! CCPP error flag
character(len=*), intent(out) :: &
errmsg !< CCPP error message
errmsg ! CCPP error message

! Local variables
real(kind_phys), dimension(nCol, nLev, lw_gas_props%get_nband(), 3) :: &
Expand Down
Loading

0 comments on commit b62597b

Please sign in to comment.