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/tempo_mp
  • Loading branch information
dustinswales committed Nov 12, 2024
2 parents 6f8c3eb + 002a886 commit 5571bfa
Show file tree
Hide file tree
Showing 20 changed files with 262 additions and 236 deletions.
5 changes: 3 additions & 2 deletions CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -140,9 +140,10 @@ SET_PROPERTY(SOURCE ${SCHEMES} ${CAPS}
APPEND_STRING PROPERTY COMPILE_FLAGS " ${CMAKE_Fortran_FLAGS_PHYSICS} ${OpenMP_Fortran_FLAGS}")

# Lower optimization for certain schemes when compiling with Intel in Release mode
if(CMAKE_BUILD_TYPE STREQUAL "Release" AND ${CMAKE_Fortran_COMPILER_ID} STREQUAL "Intel")
if(CMAKE_BUILD_TYPE STREQUAL "Release" AND (${CMAKE_Fortran_COMPILER_ID} STREQUAL "Intel" OR ${CMAKE_Fortran_COMPILER_ID} STREQUAL "IntelLLVM"))
# Define a list of schemes that need lower optimization with Intel in Release mode
set(SCHEME_NAMES_LOWER_OPTIMIZATION module_sf_mynn.F90
module_mp_nssl_2mom.F90
mynnedmf_wrapper.F90
gcycle.F90)
foreach(SCHEME_NAME IN LISTS SCHEME_NAMES_LOWER_OPTIMIZATION)
Expand All @@ -156,7 +157,7 @@ if(CMAKE_BUILD_TYPE STREQUAL "Release" AND ${CMAKE_Fortran_COMPILER_ID} STREQUAL
endif()

# No optimization for certain schemes when compiling with Intel in Release mode
if(CMAKE_BUILD_TYPE STREQUAL "Release" AND ${CMAKE_Fortran_COMPILER_ID} STREQUAL "Intel")
if(CMAKE_BUILD_TYPE STREQUAL "Release" AND (${CMAKE_Fortran_COMPILER_ID} STREQUAL "Intel" OR ${CMAKE_Fortran_COMPILER_ID} STREQUAL "IntelLLVM"))
# Define a list of schemes that can't be optimized with Intel in Release mode
set(SCHEME_NAMES_NO_OPTIMIZATION GFS_typedefs.F90)
foreach(SCHEME_NAME IN LISTS SCHEME_NAMES_NO_OPTIMIZATION)
Expand Down
360 changes: 180 additions & 180 deletions CODEOWNERS

Large diffs are not rendered by default.

14 changes: 8 additions & 6 deletions physics/CONV/Grell_Freitas/cu_gf_deep.F90
Original file line number Diff line number Diff line change
Expand Up @@ -425,9 +425,9 @@ subroutine cu_gf_deep_run( &
integer :: turn,pmin_lev(its:ite),start_level(its:ite),ktopkeep(its:ite)
real(kind=kind_phys), dimension (its:ite,kts:kte) :: dtempdz
integer, dimension (its:ite,kts:kte) :: k_inv_layers
real(kind=kind_phys), dimension (its:ite) :: c0 ! HCB
real(kind=kind_phys), dimension (its:ite) :: c0, rrfs_factor ! HCB
real(kind=kind_phys), dimension (its:ite,kts:kte) :: c0t3d ! hli for smoke/dust wet scavenging
!$acc declare create(pmin_lev,start_level,ktopkeep,dtempdz,k_inv_layers,c0,c0t3d)
!$acc declare create(pmin_lev,start_level,ktopkeep,dtempdz,k_inv_layers,c0,rrfs_factor,c0t3d)

! rainevap from sas
real(kind=kind_phys) zuh2(40)
Expand Down Expand Up @@ -486,6 +486,7 @@ subroutine cu_gf_deep_run( &
! Set cloud water to rain water conversion rate (c0)
!$acc kernels
c0(:)=0.004
rrfs_factor(:)=1.
do i=its,itf
xland1(i)=int(xland(i)+.0001) ! 1.
if(xland(i).gt.1.5 .or. xland(i).lt.0.5)then
Expand All @@ -495,6 +496,7 @@ subroutine cu_gf_deep_run( &
if(imid.eq.1)then
c0(i)=0.002
endif
if(kdt.le.(4500./dtime))rrfs_factor(i)=1.-(float(kdt)/(4500./dtime)-1.)**2
enddo
!$acc end kernels

Expand Down Expand Up @@ -591,7 +593,6 @@ subroutine cu_gf_deep_run( &
sig(i)=(1.-frh)**2
!frh_out(i) = frh
if(forcing(i,7).eq.0.)sig(i)=1.
if(kdt.le.(3600./dtime))sig(i)=1.
frh_out(i) = frh*sig(i)
enddo
!$acc end kernels
Expand Down Expand Up @@ -2029,7 +2030,7 @@ subroutine cu_gf_deep_run( &
zuo,pre,pwo_ens,xmb,ktop, &
edto,pwdo,'deep',ierr2,ierr3, &
po_cup,pr_ens,maxens3, &
sig,closure_n,xland1,xmbm_in,xmbs_in, &
sig,closure_n,xland1,xmbm_in,xmbs_in,rrfs_factor, &
ichoice,imid,ipr,itf,ktf, &
its,ite, kts,kte, &
dicycle,xf_dicycle )
Expand Down Expand Up @@ -4056,7 +4057,7 @@ subroutine cup_output_ens_3d(xff_mid,xf_ens,ierr,dellat,dellaq,dellaqc, &
zu,pre,pw,xmb,ktop, &
edt,pwd,name,ierr2,ierr3,p_cup,pr_ens, &
maxens3, &
sig,closure_n,xland1,xmbm_in,xmbs_in, &
sig,closure_n,xland1,xmbm_in,xmbs_in,rrfs_factor, &
ichoice,imid,ipr,itf,ktf, &
its,ite, kts,kte, &
dicycle,xf_dicycle )
Expand Down Expand Up @@ -4118,7 +4119,7 @@ subroutine cup_output_ens_3d(xff_mid,xf_ens,ierr,dellat,dellaq,dellaqc, &
,intent (inout) :: &
ierr,ierr2,ierr3
integer, intent(in) :: dicycle
real(kind=kind_phys), intent(in), dimension (its:ite) :: xf_dicycle
real(kind=kind_phys), intent(in), dimension (its:ite) :: xf_dicycle, rrfs_factor
!$acc declare copyin(zu,pwd,p_cup,sig,xmbm_in,xmbs_in,edt,xff_mid,dellat,dellaqc,dellaq,pw,ktop,xland1,xf_dicycle)
!$acc declare copy(xf_ens,pr_ens,outtem,outq,outqc,pre,xmb,closure_n,ierr,ierr2,ierr3)
!
Expand Down Expand Up @@ -4198,6 +4199,7 @@ subroutine cup_output_ens_3d(xff_mid,xf_ens,ierr,dellat,dellaq,dellaqc, &
clos_wei=16./max(1.,closure_n(i))
xmb_ave(i)=min(xmb_ave(i),100.)
xmb(i)=clos_wei*sig(i)*xmb_ave(i)
if(dx(i)<dx_thresh) xmb(i)=rrfs_factor(i)*xmb(i)

if(xmb(i) < 1.e-16)then
ierr(i)=19
Expand Down
11 changes: 7 additions & 4 deletions physics/CONV/Grell_Freitas/cu_gf_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -883,6 +883,13 @@ subroutine cu_gf_driver_run(ntracer,garea,im,km,dt,flag_init,flag_restart,&
cutenm(i)=0.
endif ! pret > 0

maxupmf(i)=0.
if(forcing2(i,6).gt.0.)then
maxupmf(i)=maxval(xmb(i)*zu(i,kts:ktf)/forcing2(i,6))
endif
if (xland(i)==0)then ! cu precip rate (mm/h)
if((maxupmf(i).lt.0.1) .or. (pret(i)*3600.lt.0.05)) pret(i)=0.
endif
if(pret(i).gt.0.)then
cuten(i)=1.
cutenm(i)=0.
Expand Down Expand Up @@ -999,10 +1006,6 @@ subroutine cu_gf_driver_run(ntracer,garea,im,km,dt,flag_init,flag_restart,&
gdc(i,15,10)=qfx(i)
gdc(i,16,10)=pret(i)*3600.

maxupmf(i)=0.
if(forcing2(i,6).gt.0.)then
maxupmf(i)=maxval(xmb(i)*zu(i,kts:ktf)/forcing2(i,6))
endif

if(ktop(i).gt.2 .and.pret(i).gt.0.)dt_mf(i,ktop(i)-1)=ud_mf(i,ktop(i))
endif
Expand Down
2 changes: 1 addition & 1 deletion physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmg_pre.F90
Original file line number Diff line number Diff line change
Expand Up @@ -231,7 +231,7 @@ subroutine GFS_rrtmg_pre_run (im, levs, lm, lmk, lmp, n_var_lndp, lextop,&
real(kind=kind_phys), dimension(:,:,:), intent(out) :: faerlw1,&
faerlw2,&
faerlw3
real(kind=kind_phys), dimension(:,:), intent(out) :: alpha
real(kind=kind_phys), dimension(:,:), intent(out), optional :: alpha
character(len=*), intent(out) :: errmsg
integer, intent(out) :: errflg

Expand Down
1 change: 1 addition & 0 deletions physics/Interstitials/UFS_SCM_NEPTUNE/GFS_rrtmg_pre.meta
Original file line number Diff line number Diff line change
Expand Up @@ -1489,6 +1489,7 @@
type = real
kind = kind_phys
intent = out
optional = True
[top_at_1]
standard_name = flag_for_vertical_ordering_in_radiation
long_name = flag for vertical ordering in radiation
Expand Down
2 changes: 1 addition & 1 deletion physics/Interstitials/UFS_SCM_NEPTUNE/gcycle.F90
Original file line number Diff line number Diff line change
Expand Up @@ -107,7 +107,7 @@ subroutine gcycle (me, nthrds, nx, ny, isc, jsc, nsst, tile_num, nlunit, fn_nml,
real (kind=kind_io8) :: min_ice(nx*ny)
integer :: i_indx(nx*ny), j_indx(nx*ny)
character(len=6) :: tile_num_ch
real(kind=kind_phys) :: sig1t
real(kind=kind_phys) :: sig1t(nx*ny)
integer :: npts, nb, ix, jx, ls, ios, ll
logical :: exists

Expand Down
15 changes: 7 additions & 8 deletions physics/MP/Morrison_Gettelman/aerinterp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -282,7 +282,7 @@ SUBROUTINE aerinterpol( me,master,nthrds,npts,IDATE,FHOUR,iflip, jindx1,jindx2,
character(*), intent(inout) :: errmsg
integer, intent(in) :: iflip
integer i1,i2, iday,j,j1,j2,l,npts,nc,n1,n2,lev,k,i,ii, klev
real(kind=kind_phys) fhour,temj, tx1, tx2,temi, tem
real(kind=kind_phys) fhour,temj, tx1, tx2,temi, tem, tem1, tem2
real(kind=kind_phys), dimension(npts) :: temij,temiy,temjx,ddxy

!
Expand Down Expand Up @@ -363,10 +363,9 @@ SUBROUTINE aerinterpol( me,master,nthrds,npts,IDATE,FHOUR,iflip, jindx1,jindx2,
!$OMP parallel num_threads(nthrds) default(none) &
!$OMP shared(npts,ntrcaer,aerin,aer_pres,prsl) &
!$OMP shared(ddx,ddy,jindx1,jindx2,iindx1,iindx2) &
!$OMP shared(aerpm,aerpres,aerout,lev,nthrds) &
!$OMP shared(temij,temiy,temjx,ddxy) &
!$OMP private(l,j,k,ii,i1,i2,j1,j2,tem) &
!$OMP copyin(tx1,tx2) firstprivate(tx1,tx2)
!$OMP shared(aerpm,aerpres,aerout,lev,nthrds) &
!$OMP shared(temij,temiy,temjx,ddxy,tx1,tx2) &
!$OMP private(l,j,k,ii,i1,i2,j1,j2,tem,tem1,tem2)

!$OMP do
#endif
Expand Down Expand Up @@ -416,10 +415,10 @@ SUBROUTINE aerinterpol( me,master,nthrds,npts,IDATE,FHOUR,iflip, jindx1,jindx2,
ENDIF
ENDDO
tem = 1.0 / (aerpres(j,i1) - aerpres(j,i2))
tx1 = (prsl(j,L) - aerpres(j,i2)) * tem
tx2 = (aerpres(j,i1) - prsl(j,L)) * tem
tem1 = (prsl(j,L) - aerpres(j,i2)) * tem
tem2 = (aerpres(j,i1) - prsl(j,L)) * tem
DO ii = 1, ntrcaer
aerout(j,L,ii) = aerpm(j,i1,ii)*tx1 + aerpm(j,i2,ii)*tx2
aerout(j,L,ii) = aerpm(j,i1,ii)*tem1 + aerpm(j,i2,ii)*tem2
ENDDO
endif
ENDDO !L-loop
Expand Down
8 changes: 4 additions & 4 deletions physics/PBL/MYNN_EDMF/module_bl_mynn.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2005,7 +2005,7 @@ SUBROUTINE mym_length ( &
ugrid = sqrt(u1(kts)**2 + v1(kts)**2)
uonset= 15.
wt_u = (1.0 - min(max(ugrid - uonset, 0.0)/30.0, 0.5))
cns = 2.7 !was 3.5
cns = 3.5
alp1 = 0.23
alp2 = 0.3
alp3 = 2.5 * wt_u !taper off bouyancy enhancement in shear-driven pbls
Expand Down Expand Up @@ -2039,7 +2039,7 @@ SUBROUTINE mym_length ( &
zwk = zw(k)
DO WHILE (zwk .LE. zi2+h1)
dzk = 0.5*( dz(k)+dz(k-1) )
qdz = min(max( qkw(k)-qmin, 0.03 ), 30.0)*dzk
qdz = min(max( qkw(k)-qmin, 0.02 ), 30.0)*dzk
elt = elt +qdz*zwk
vsc = vsc +qdz
k = k+1
Expand Down Expand Up @@ -5036,7 +5036,7 @@ SUBROUTINE mynn_tendencies(kts,kte,i, &
IF (FLAG_QI) THEN
DO k=kts,kte
Dth(k)=(thl(k) + xlvcp/exner(k)*sqc2(k) &
& + xlscp/exner(k)*(sqi2(k)+sqs(k)) &
& + xlscp/exner(k)*(sqi2(k)) & !+sqs(k)) &
& - th(k))/delt
!Use form from Tripoli and Cotton (1981) with their
!suggested min temperature to improve accuracy:
Expand Down Expand Up @@ -6057,7 +6057,7 @@ SUBROUTINE DMP_mf( &
if ((landsea-1.5).LT.0) then !land
acfac = .5*tanh((fltv2 - 0.02)/0.05) + .5
else !water
acfac = .5*tanh((fltv2 - 0.01)/0.03) + .5
acfac = .5*tanh((fltv2 - 0.015)/0.04) + .5
endif
!add a windspeed-dependent adjustment to acfac that tapers off
!the mass-flux scheme linearly above sfc wind speeds of 10 m/s.
Expand Down
3 changes: 2 additions & 1 deletion physics/Radiation/RRTMG/radlw_main.F90
Original file line number Diff line number Diff line change
Expand Up @@ -630,7 +630,8 @@ subroutine rrtmg_lw_run &

real (kind=kind_phys), dimension(:), intent(in) :: sfemis, &
& sfgtmp, de_lgth
real (kind=kind_phys), dimension(npts,nlay), intent(in) :: alpha
real (kind=kind_phys), dimension(npts,nlay),intent(in),optional:: &
alpha

real (kind=kind_phys), dimension(:,:,:),intent(in):: &
& aeraod, aerssa
Expand Down
1 change: 1 addition & 0 deletions physics/Radiation/RRTMG/radlw_main.meta
Original file line number Diff line number Diff line change
Expand Up @@ -199,6 +199,7 @@
type = real
kind = kind_phys
intent = in
optional = True
[npts]
standard_name = horizontal_loop_extent
long_name = horizontal dimension
Expand Down
3 changes: 2 additions & 1 deletion physics/Radiation/RRTMG/radsw_main.F90
Original file line number Diff line number Diff line change
Expand Up @@ -726,7 +726,8 @@ subroutine rrtmg_sw_run &

real (kind=kind_phys), intent(in) :: cosz(npts), solcon, &
& de_lgth(npts)
real (kind=kind_phys), dimension(npts,nlay), intent(in) :: alpha
real (kind=kind_phys), dimension(npts,nlay),intent(in),optional:: &
alpha

! --- outputs:
real (kind=kind_phys), dimension(:,:), intent(inout) :: hswc
Expand Down
1 change: 1 addition & 0 deletions physics/Radiation/RRTMG/radsw_main.meta
Original file line number Diff line number Diff line change
Expand Up @@ -223,6 +223,7 @@
type = real
kind = kind_phys
intent = in
optional = True
[cosz]
standard_name = cosine_of_solar_zenith_angle_for_daytime_points_on_radiation_timestep
long_name = cosine of the solar zenit angle
Expand Down
10 changes: 5 additions & 5 deletions physics/SFC_Models/Land/RUC/lsm_ruc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -455,12 +455,13 @@ subroutine lsm_ruc_run & ! inputs
! for land
& sncovr1_lnd, qsurf_lnd, gflux_lnd, evap_lnd, &
& cmm_lnd, chh_lnd, hflx_lnd, sbsno, &
& acsnow_lnd, snowmt_lnd, snohf, &
& snowmt_lnd, snohf, &
! for ice
& sncovr1_ice, qsurf_ice, gflux_ice, evap_ice, ep1d_ice, &
& cmm_ice, chh_ice, hflx_ice, &
& acsnow_ice, snowmt_ice

& snowmt_ice
real (kind_phys), dimension(:), intent(inout), optional :: &
acsnow_lnd, acsnow_ice
real (kind_phys), dimension(:), intent( out) :: &
& albdvis_lnd, albdnir_lnd, albivis_lnd, albinir_lnd
real (kind_phys), dimension(:), intent( out), optional :: &
Expand Down Expand Up @@ -1312,8 +1313,7 @@ subroutine lsm_ruc_run & ! inputs

! --- ... accumulated total runoff and surface runoff
runoff(i) = runoff(i) + (drain(i)+runof(i)) * delt ! accum total kg m-2
!srunoff(i) = srunoff(i) + runof(i) * delt ! accum surface kg m-2
srunoff(i) = acrunoff(i,j) ! accum surface kg m-2
srunoff(i) = srunoff(i) + runof(i) * delt ! accum surface kg m-2

! --- ... accumulated frozen precipitation (accumulation in lsmruc)
snowfallac_lnd(i) = snfallac_lnd(i,j) ! accum kg m-2
Expand Down
2 changes: 2 additions & 0 deletions physics/SFC_Models/Land/RUC/lsm_ruc.meta
Original file line number Diff line number Diff line change
Expand Up @@ -1489,6 +1489,7 @@
type = real
kind = kind_phys
intent = inout
optional = True
[snowmt_lnd]
standard_name = surface_snow_melt_over_land
long_name = snow melt during timestep over land
Expand Down Expand Up @@ -1653,6 +1654,7 @@
type = real
kind = kind_phys
intent = inout
optional = True
[snowmt_ice]
standard_name = surface_snow_melt_over_ice
long_name = snow melt during timestep over ice
Expand Down
4 changes: 2 additions & 2 deletions physics/SFC_Models/Land/RUC/module_sf_ruclsm.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1740,7 +1740,7 @@ SUBROUTINE SFCTMP (debug_print, delt,ktau,conflx,i,j, & !--- input varia
!-- will reduce warm bias in western Canada
!-- and US West coast, where max snow albedo is low (0.3-0.5).
!print *,'ALB increase to 0.7',alb_snow,snhei,snhei_crit,albsn,i,j
!ALBsn = 0.7_kind_phys
ALBsn = 0.7_kind_phys
endif

Emiss= emissn
Expand All @@ -1753,7 +1753,7 @@ SUBROUTINE SFCTMP (debug_print, delt,ktau,conflx,i,j, & !--- input varia
!-- will reduce warm bias in western Canada
!-- and US West coast, where max snow albedo is low (0.3-0.5).
!print *,'ALB increase to 0.7',alb_snow,snhei,snhei_crit,albsn,i,j
!ALBsn = 0.7_kind_phys
ALBsn = 0.7_kind_phys
!print *,'NO mosaic ALB increase to 0.7',alb_snow,snhei,snhei_crit,alb,i,j
endif

Expand Down
6 changes: 4 additions & 2 deletions physics/SFC_Models/SeaIce/CICE/sfc_cice.f
Original file line number Diff line number Diff line change
Expand Up @@ -101,8 +101,10 @@ subroutine sfc_cice_run &

! real (kind=kind_phys), dimension(im), intent(in) :: u1, v1, &
real (kind=kind_phys), dimension(:), intent(in) :: &
& t1, q1, cm, ch, prsl1, wind, snowd

& t1, q1, cm, ch, prsl1, wind
real (kind=kind_phys), dimension(:), intent(in), optional :: &
& snowd

real (kind=kind_phys), dimension(:), intent(in), optional :: &
& dqsfc, dtsfc, dusfc, dvsfc
logical, dimension(:), intent(in) :: flag_cice, flag_iter
Expand Down
1 change: 1 addition & 0 deletions physics/SFC_Models/SeaIce/CICE/sfc_cice.meta
Original file line number Diff line number Diff line change
Expand Up @@ -160,6 +160,7 @@
type = real
kind = kind_phys
intent = in
optional = True
[qsurf]
standard_name = surface_specific_humidity_over_ice
long_name = surface air saturation specific humidity over ice
Expand Down
Loading

0 comments on commit 5571bfa

Please sign in to comment.