Skip to content

Commit

Permalink
Merge branch 'ufs/dev' of https://github.com/ufs-community/ccpp-physics
Browse files Browse the repository at this point in the history
… into feature_reorg_physics
  • Loading branch information
dustinswales committed Sep 1, 2023
2 parents c31f920 + 5b94685 commit f45f8ad
Show file tree
Hide file tree
Showing 42 changed files with 4,761 additions and 894 deletions.
1 change: 1 addition & 0 deletions physics/CONV/Grell_Freitas/cu_gf_deep.F90
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ module cu_gf_deep
integer, parameter :: autoconv=1 !2
integer, parameter :: aeroevap=1 !3
real(kind=kind_phys), parameter :: scav_factor = 0.5

real(kind=kind_phys), parameter :: dx_thresh = 6500.
!> still 16 ensembles for clousres
integer, parameter:: maxens3=16
Expand Down
1,424 changes: 767 additions & 657 deletions physics/Land/CLM_lake/clm_lake.f90

Large diffs are not rendered by default.

14 changes: 14 additions & 0 deletions physics/Land/CLM_lake/clm_lake.meta
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,13 @@
[ccpp-arg-table]
name = clm_lake_run
type = scheme
[flag_restart]
standard_name = flag_for_restart
long_name = flag for restart (warmstart) or coldstart
units = flag
dimensions = ()
type = logical
intent = in
[im]
standard_name = horizontal_loop_extent
long_name = horizontal loop extent
Expand Down Expand Up @@ -935,6 +942,13 @@
type = logical
active = (control_for_lake_model_selection == 3)
intent = in
[clm_debug_print]
standard_name = flag_for_printing_in_clm_lake_model
long_name = flag for printing in clm lake model
units = flag
dimensions = ()
type = logical
intent = in
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
Expand Down
2 changes: 2 additions & 0 deletions physics/Land/RUC/module_sf_ruclsm.F90
Original file line number Diff line number Diff line change
Expand Up @@ -991,10 +991,12 @@ SUBROUTINE LSMRUC(xlat,xlon, &
if(mosaic_lu == 1) then
! greenness factor: between 0 for min greenness and 1 for max greenness.
factor = max(zero,min(one,(vegfra(i,j)-shdmin(i,j))/max(one,(shdmax(i,j)-shdmin(i,j)))))
if (debug_print ) then
if (abs(xlat-testptlat).lt.0.1 .and. &
abs(xlon-testptlon).lt.0.1)then
print *,' lat,lon=',xlat,xlon,' factor=',factor
endif
endif

if((ivgtyp(i,j) == natural .or. ivgtyp(i,j) == crop) .and. factor > 0.75) then
! cropland or grassland, apply irrigation during the growing seaspon when fraction
Expand Down
46 changes: 22 additions & 24 deletions physics/MP/Thompson/module_mp_thompson.F90
Original file line number Diff line number Diff line change
Expand Up @@ -708,9 +708,9 @@ SUBROUTINE thompson_init(is_aerosol_aware_in, &
dtc(n) = (Dc(n) - Dc(n-1))
enddo

!> - Create bins of cloud ice (from min diameter up to 5x min snow size)
!> - Create bins of cloud ice (from min diameter up to 2x min snow size)
xDx(1) = D0i*1.0d0
xDx(nbi+1) = 5.0d0*D0s
xDx(nbi+1) = 2.0d0*D0s
do n = 2, nbi
xDx(n) = DEXP(DFLOAT(n-1)/DFLOAT(nbi) &
*DLOG(xDx(nbi+1)/xDx(1)) +DLOG(xDx(1)))
Expand Down Expand Up @@ -2822,7 +2822,7 @@ subroutine mp_thompson (qv1d, qc1d, qi1d, qr1d, qs1d, qg1d, ni1d, &
prr_rcg(k) = MIN(DBLE(rg(k)*odts), prr_rcg(k))
prg_rcg(k) = -prr_rcg(k)
!> - Put in explicit drop break-up due to collisions.
pnr_rcg(k) = -5.*tnr_gacr(idx_g1,idx_g,idx_r1,idx_r) ! RAIN2M
pnr_rcg(k) = -1.5*tnr_gacr(idx_g1,idx_g,idx_r1,idx_r) ! RAIN2M
endif
endif
endif
Expand Down Expand Up @@ -3053,34 +3053,32 @@ subroutine mp_thompson (qv1d, qc1d, qi1d, qr1d, qs1d, qg1d, ni1d, &
if (prr_sml(k) .gt. 0.) then
prr_sml(k) = prr_sml(k) + 4218.*olfus*tempc &
* (prr_rcs(k)+prs_scw(k))
endif
prr_sml(k) = MIN(DBLE(rs(k)*odts), MAX(0.D0, prr_sml(k)))
pnr_sml(k) = smo0(k)/rs(k)*prr_sml(k) * 10.0**(-0.25*tempc) ! RAIN2M
pnr_sml(k) = MIN(DBLE(smo0(k)*odts), pnr_sml(k))

if (ssati(k).lt. 0.) then
prs_sde(k) = C_cube*t1_subl*diffu(k)*ssati(k)*rvs &
* (t1_qs_sd*smo1(k) &
+ t2_qs_sd*rhof2(k)*vsc2(k)*smof(k))
prs_sde(k) = MAX(DBLE(-rs(k)*odts), prs_sde(k))
prr_sml(k) = MIN(DBLE(rs(k)*odts), prr_sml(k))
pnr_sml(k) = smo0(k)/rs(k)*prr_sml(k) * 10.0**(-0.25*tempc) ! RAIN2M
pnr_sml(k) = MIN(DBLE(smo0(k)*odts), pnr_sml(k))
elseif (ssati(k).lt. 0.) then
prr_sml(k) = 0.0
prs_sde(k) = C_cube*t1_subl*diffu(k)*ssati(k)*rvs &
* (t1_qs_sd*smo1(k) &
+ t2_qs_sd*rhof2(k)*vsc2(k)*smof(k))
prs_sde(k) = MAX(DBLE(-rs(k)*odts), prs_sde(k))
endif
endif

if (L_qg(k)) then
prr_gml(k) = (tempc*tcond(k)-lvap0*diffu(k)*delQvs(k)) &
* N0_g(k)*(t1_qg_me*ilamg(k)**cge(10) &
+ t2_qg_me*rhof2(k)*vsc2(k)*ilamg(k)**cge(11))
!-GT prr_gml(k) = prr_gml(k) + 4218.*olfus*tempc &
!-GT * (prr_rcg(k)+prg_gcw(k))
prr_gml(k) = MIN(DBLE(rg(k)*odts), MAX(0.D0, prr_gml(k)))
pnr_gml(k) = N0_g(k)*cgg(2)*ilamg(k)**cge(2) / rg(k) & ! RAIN2M
* prr_gml(k) * 10.0**(-0.5*tempc)

if (ssati(k).lt. 0.) then
prg_gde(k) = C_cube*t1_subl*diffu(k)*ssati(k)*rvs &
* N0_g(k) * (t1_qg_sd*ilamg(k)**cge(10) &
+ t2_qg_sd*vsc2(k)*rhof2(k)*ilamg(k)**cge(11))
prg_gde(k) = MAX(DBLE(-rg(k)*odts), prg_gde(k))
if (prr_gml(k) .gt. 0.) then
prr_gml(k) = MIN(DBLE(rg(k)*odts), prr_gml(k))
pnr_gml(k) = N0_g(k)*cgg(2)*ilamg(k)**cge(2) / rg(k) & ! RAIN2M
* prr_gml(k) * 10.0**(-0.5*tempc)
elseif (ssati(k).lt. 0.) then
prr_gml(k) = 0.0
prg_gde(k) = C_cube*t1_subl*diffu(k)*ssati(k)*rvs &
* N0_g(k) * (t1_qg_sd*ilamg(k)**cge(10) &
+ t2_qg_sd*vsc2(k)*rhof2(k)*ilamg(k)**cge(11))
prg_gde(k) = MAX(DBLE(-rg(k)*odts), prg_gde(k))
endif
endif

Expand Down
12 changes: 7 additions & 5 deletions physics/PBL/SATMEDMF/satmedmfvdifq.F
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ module satmedmfvdifq
!! and to reduce the negative wind speed bias in upper troposphere
!!
!! Incorporate the LES-based changes for TC simulation
!! (Chen et al.,2022, https://doi.org/10.1175/WAF-D-21-0168.1)
!! (Chen et al.,2022 \cite Chen_2022)
!! with additional improvements on MF working with Cu schemes
!! Xiaomin Chen, 5/2/2022
!!
Expand Down Expand Up @@ -443,7 +443,9 @@ subroutine satmedmfvdifq_run(im,km,ntrac,ntcw,ntrw, &
endif
enddo
!
! compute a function for green vegetation fraction and surface roughness
!> - Compute a function for green vegetation fraction and surface roughness.
!! Entrainment rate in updraft is a function of vegetation fraction and surface
!! roughness length
!
do i = 1,im
tem = (sigmaf(i) - vegflo) / (vegfup - vegflo)
Expand Down Expand Up @@ -745,7 +747,7 @@ subroutine satmedmfvdifq_run(im,km,ntrac,ntcw,ntrw, &
endif
enddo
!
! compute mean tke within pbl
!> - Compute mean tke within pbl
!
do i = 1, im
sumx(i) = 0.
Expand All @@ -766,8 +768,8 @@ subroutine satmedmfvdifq_run(im,km,ntrac,ntcw,ntrw, &
endif
enddo
!
! compute wind shear term as a sink term for updraft and downdraft
! velocity
!> - Compute wind shear term as a sink term for updraft and downdraft
!! velocity
!
kps = max(kmpbl, kmscu)
do k = 2, kps
Expand Down
2 changes: 1 addition & 1 deletion physics/docs/ccpp_doxyfile
Original file line number Diff line number Diff line change
Expand Up @@ -115,7 +115,7 @@ WARN_LOGFILE =
#---------------------------------------------------------------------------

INPUT = pdftxt/mainpage.txt \
pdftxt/all_shemes_list.txt \
pdftxt/all_schemes_list.txt \
pdftxt/GFS_v16_suite.txt \
pdftxt/GFS_v17_p8_suite.txt \
pdftxt/RAP_suite.txt \
Expand Down
14 changes: 8 additions & 6 deletions physics/docs/ccppsrw_doxyfile
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
# Doxyfile 1.9.3

DOXYFILE_ENCODING = UTF-8
PROJECT_NAME = "CCPP Scidoc for SRW v2.1.0"
PROJECT_NUMBER = "SRW v2.1.0"
PROJECT_NAME = "CCPP SciDoc for UFS-SRW v3.0.0"
PROJECT_NUMBER = "SRW v3.0.0"
PROJECT_BRIEF = "Common Community Physics Package Developed at DTC"
PROJECT_LOGO = img/dtc_logo.png
OUTPUT_DIRECTORY = doc
Expand Down Expand Up @@ -115,9 +115,10 @@ WARN_LOGFILE =
#---------------------------------------------------------------------------

INPUT = pdftxt/SRW_mainpage.txt \
pdftxt/SRW_all_shemes_list.txt \
pdftxt/SRW_all_schemes_list.txt \
pdftxt/GFS_v16_suite.txt \
pdftxt/HRRR_suite.txt \
pdftxt/RAP_suite.txt \
pdftxt/RRFS_v1beta_suite.txt \
pdftxt/WoFS_v0_suite.txt \
pdftxt/RRFS_SGSCLOUD.txt \
Expand All @@ -144,6 +145,7 @@ INPUT = pdftxt/SRW_mainpage.txt \
pdftxt/RUCLSM.txt \
pdftxt/THOMPSON.txt \
pdftxt/suite_input.nml.txt \
pdftxt/CLM_LAKE.txt \
pdftxt/GFS_SPP.txt \
../fv_sat_adj.F90 \
../GFS_time_vary_pre.fv3.F90 \
Expand Down Expand Up @@ -206,6 +208,7 @@ INPUT = pdftxt/SRW_mainpage.txt \
../sfc_nst_pre.f \
../sfc_nst_post.f \
../sfc_ocean.F \
../clm_lake.f90 \
../module_nst_model.f90 \
../module_nst_parameters.f90 \
../module_nst_water_prop.f90 \
Expand Down Expand Up @@ -283,7 +286,6 @@ INPUT = pdftxt/SRW_mainpage.txt \
../mp_nssl.F90 \
../module_mp_nssl_2mom.F90 \
../funcphys.f90 \
../physparam.f \
../physcons.F90 \
../radcons.f90 \
../mersenne_twister.f \
Expand All @@ -302,7 +304,7 @@ EXCLUDE =
EXCLUDE_SYMLINKS = NO
EXCLUDE_PATTERNS =
EXCLUDE_SYMBOLS =
EXAMPLE_PATH = pdftxt/RE210 \
EXAMPLE_PATH = pdftxt/RE300 \
doc/html
EXAMPLE_PATTERNS =
EXAMPLE_RECURSIVE = NO
Expand Down Expand Up @@ -540,7 +542,7 @@ DIRECTORY_GRAPH = YES
DIR_GRAPH_MAX_DEPTH = 1
DOT_IMAGE_FORMAT = SVG
INTERACTIVE_SVG = NO
DOT_PATH =
DOT_PATH =
DOTFILE_DIRS =
MSCFILE_DIRS =
DIAFILE_DIRS =
Expand Down
Loading

0 comments on commit f45f8ad

Please sign in to comment.