Skip to content

Commit

Permalink
Merge pull request #11 from climbfuji/dtc_develop_udpate_from_emc_201…
Browse files Browse the repository at this point in the history
…91127

dtc/develop: update from EMC 2019/11/27
  • Loading branch information
climbfuji authored Dec 3, 2019
2 parents bc31689 + eae6786 commit 88e87e9
Show file tree
Hide file tree
Showing 14 changed files with 468 additions and 119 deletions.
2 changes: 1 addition & 1 deletion atmos_cubed_sphere
4 changes: 3 additions & 1 deletion ccpp/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -89,8 +89,10 @@ if (${CMAKE_Fortran_COMPILER_ID} MATCHES "GNU")
set (CMAKE_Fortran_FLAGS "${CMAKE_Fortran_FLAGS} -fcray-pointer -ffree-line-length-none -fno-range-check")
set (CMAKE_Fortran_FLAGS "${CMAKE_Fortran_FLAGS} -fbacktrace -cpp")
if (${CMAKE_BUILD_TYPE} MATCHES "Debug")
set (CMAKE_C_FLAGS "${CMAKE_C_FLAGS} -Wall")
set (CMAKE_CXX_FLAGS "${CMAKE_CXX_FLAGS} -Wall")
set (CMAKE_Fortran_FLAGS "${CMAKE_Fortran_FLAGS} -fno-unsafe-math-optimizations -frounding-math -fsignaling-nans")
set (CMAKE_Fortran_FLAGS "${CMAKE_Fortran_FLAGS} -ffpe-trap=invalid,zero,overflow -fcheck=bounds -fbacktrace -fno-range-check")
set (CMAKE_Fortran_FLAGS "${CMAKE_Fortran_FLAGS} -ffpe-trap=invalid,zero,overflow -fcheck=bounds -fbacktrace -fno-range-check -Wall")
elseif (${CMAKE_BUILD_TYPE} MATCHES "Bitforbit")
set (CMAKE_Fortran_FLAGS "${CMAKE_Fortran_FLAGS}")
endif (${CMAKE_BUILD_TYPE} MATCHES "Debug")
Expand Down
2 changes: 1 addition & 1 deletion ccpp/framework
7 changes: 6 additions & 1 deletion fv3_cap.F90
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ module fv3gfs_cap_mod
cplprint_flag,output_1st_tstep_rst, &
first_kdt

use module_fv3_io_def, only: num_pes_fcst,write_groups, &
use module_fv3_io_def, only: num_pes_fcst,write_groups,app_domain, &
num_files, filename_base, &
wrttasks_per_group, n_group, &
lead_wrttask, last_wrttask, &
Expand Down Expand Up @@ -322,6 +322,10 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
label ='write_tasks_per_group:',rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

CALL ESMF_ConfigGetAttribute(config=CF,value=app_domain, default="global", &
label ='app_domain:',rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

if(mype == 0) print *,'af nems config,restart_interval=',restart_interval, &
'quilting=',quilting,'write_groups=',write_groups,wrttasks_per_group, &
'calendar=',trim(calendar),'calendar_type=',calendar_type
Expand Down Expand Up @@ -692,6 +696,7 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
isrctermprocessing = 1
call ESMF_FieldBundleRegridStore(fcstFB(j), wrtFB(j,i), &
regridMethod=regridmethod, routehandle=routehandle(j,i), &
unmappedaction=ESMF_UNMAPPEDACTION_IGNORE, &
srcTermProcessing=isrctermprocessing, rc=rc)

! if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
Expand Down
2 changes: 1 addition & 1 deletion gfsphysics/GFS_layer/GFS_physics_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1206,7 +1206,7 @@ subroutine GFS_physics_driver &
if (fice(i) < one) then
wet(i) = .true.
! Sfcprop%tsfco(i) = tgice
Sfcprop%tsfco(i) = max(Sfcprop%tisfc(i), tgice)
if (.not. Model%cplflx) Sfcprop%tsfco(i) = max(Sfcprop%tisfc(i), tgice)
! Sfcprop%tsfco(i) = max((Sfcprop%tsfc(i) - fice(i)*sfcprop%tisfc(i)) &
! / (one - fice(i)), tgice)
endif
Expand Down
11 changes: 10 additions & 1 deletion gfsphysics/GFS_layer/GFS_restart.F90
Original file line number Diff line number Diff line change
Expand Up @@ -117,6 +117,9 @@ subroutine GFS_restart_populate (Restart, Model, Statein, Stateout, Sfcprop, &
#endif

Restart%num3d = Model%ntot3d
if(Model%lrefres) then
Restart%num3d = Model%ntot3d+1
endif
#ifdef CCPP
! GF
if (Model%imfdeepcnv == 3) then
Expand Down Expand Up @@ -252,7 +255,13 @@ subroutine GFS_restart_populate (Restart, Model, Statein, Stateout, Sfcprop, &
Restart%data(nb,num)%var3p => Tbd(nb)%phy_f3d(:,:,num)
enddo
enddo

if (Model%lrefres) then
num = Model%ntot3d+1
restart%name3d(num) = 'ref_f3d'
do nb = 1,nblks
Restart%data(nb,num)%var3p => IntDiag(nb)%refl_10cm(:,:)
enddo
endif
#ifdef CCPP
!--- RAP/HRRR-specific variables, 3D
num = Model%ntot3d
Expand Down
12 changes: 11 additions & 1 deletion gfsphysics/GFS_layer/GFS_typedefs.F90
Original file line number Diff line number Diff line change
Expand Up @@ -702,6 +702,9 @@ module GFS_typedefs
!--- GFDL microphysical paramters
logical :: lgfdlmprad !< flag for GFDL mp scheme and radiation consistency

!--- Thompson,GFDL mp parameter
logical :: lrefres !< flag for radar reflectivity in restart file

!--- land/surface model parameters
integer :: lsm !< flag for land surface model lsm=1 for noah lsm
integer :: lsm_noah=1 !< flag for NOAH land surface model
Expand Down Expand Up @@ -2796,6 +2799,9 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
!--- GFDL microphysical parameters
logical :: lgfdlmprad = .false. !< flag for GFDLMP radiation interaction

!--- Thompson,GFDL microphysical parameter
logical :: lrefres = .false. !< flag for radar reflectivity in restart file

!--- land/surface model parameters
integer :: lsm = 1 !< flag for land surface model to use =0 for osu lsm; =1 for noah lsm; =2 for noah mp lsm; =3 for RUC lsm
integer :: lsoil = 4 !< number of soil layers
Expand Down Expand Up @@ -3080,7 +3086,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
mg_do_graupel, mg_do_hail, mg_nccons, mg_nicons, mg_ngcons, &
mg_ncnst, mg_ninst, mg_ngnst, sed_supersat, do_sb_physics, &
mg_alf, mg_qcmin, mg_do_ice_gmao, mg_do_liq_liu, &
ltaerosol, lradar, ttendlim, lgfdlmprad, &
ltaerosol, lradar, lrefres, ttendlim, lgfdlmprad, &
!--- max hourly
avg_max_length, &
!--- land/surface model control
Expand Down Expand Up @@ -3380,6 +3386,8 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &

!--- gfdl MP parameters
Model%lgfdlmprad = lgfdlmprad
!--- Thompson,GFDL MP parameter
Model%lrefres = lrefres

!--- land/surface model parameters
Model%lsm = lsm
Expand Down Expand Up @@ -4420,6 +4428,7 @@ subroutine control_print(Model)
print *, ' Thompson microphysical parameters'
print *, ' ltaerosol : ', Model%ltaerosol
print *, ' lradar : ', Model%lradar
print *, ' lrefres : ', Model%lrefres
print *, ' ttendlim : ', Model%ttendlim
print *, ' '
endif
Expand All @@ -4437,6 +4446,7 @@ subroutine control_print(Model)
if (Model%imp_physics == Model%imp_physics_gfdl) then
print *, ' GFDL microphysical parameters'
print *, ' GFDL MP radiation inter: ', Model%lgfdlmprad
print *, ' lrefres : ', Model%lrefres
print *, ' '
endif
#ifdef CCPP
Expand Down
8 changes: 4 additions & 4 deletions gfsphysics/physics/gfdl_cloud_microphys.F90
Original file line number Diff line number Diff line change
Expand Up @@ -4688,7 +4688,7 @@ subroutine cloud_diagnosis (is, ie, ks, ke, den, delp, lsm, qmw, qmi, qmr, qms,
real :: n0r = 8.0e6, n0s = 3.0e6, n0g = 4.0e6
real :: alphar = 0.8, alphas = 0.25, alphag = 0.5
real :: gammar = 17.837789, gammas = 8.2850630, gammag = 11.631769
real :: qmin = 1.0e-12, beta = 1.22
real :: qmin = 1.0e-12, beta = 1.22, qmin1 = 9.e-6

do k = ks, ke
do i = is, ie
Expand Down Expand Up @@ -4718,7 +4718,7 @@ subroutine cloud_diagnosis (is, ie, ks, ke, den, delp, lsm, qmw, qmi, qmr, qms,
! cloud ice (Heymsfield and Mcfarquhar, 1996)
! -----------------------------------------------------------------------

if (qmi (i, k) .gt. qmin) then
if (qmi (i, k) .gt. qmin1) then
qci (i, k) = dpg * qmi (i, k) * 1.0e3
rei_fac = log (1.0e3 * qmi (i, k) * den (i, k))
if (t (i, k) - tice .lt. - 50) then
Expand All @@ -4744,7 +4744,7 @@ subroutine cloud_diagnosis (is, ie, ks, ke, den, delp, lsm, qmw, qmi, qmr, qms,
! cloud ice (Wyser, 1998)
! -----------------------------------------------------------------------

if (qmi (i, k) .gt. qmin) then
if (qmi (i, k) .gt. qmin1) then
qci (i, k) = dpg * qmi (i, k) * 1.0e3
bw = - 2. + 1.e-3 * log10 (den (i, k) * qmi (i, k) / rho_0) * max (0.0, tice - t (i, k)) ** 1.5
rei (i, k) = 377.4 + bw * (203.3 + bw * (37.91 + 2.3696 * bw))
Expand Down Expand Up @@ -4774,7 +4774,7 @@ subroutine cloud_diagnosis (is, ie, ks, ke, den, delp, lsm, qmw, qmi, qmr, qms,
! snow (Lin et al., 1983)
! -----------------------------------------------------------------------

if (qms (i, k) .gt. qmin) then
if (qms (i, k) .gt. qmin1) then
qcs (i, k) = dpg * qms (i, k) * 1.0e3
lambdas = exp (0.25 * log (pi * rhos * n0s / qms (i, k) / den (i, k)))
res (i, k) = 0.5 * exp (log (gammas / 6) / alphas) / lambdas * 1.0e6
Expand Down
53 changes: 27 additions & 26 deletions gfsphysics/physics/satmedmfvdifq.f
Original file line number Diff line number Diff line change
Expand Up @@ -151,7 +151,7 @@ subroutine satmedmfvdifq(ix,im,km,ntrac,ntcw,ntiw,ntke,
& rlmn, rlmn1, rlmx, elmx,
& ttend, utend, vtend, qtend,
& zfac, zfmin, vk, spdk2,
& tkmin, xkzinv, xkgdx,
& tkmin, tkminx, xkzinv, xkgdx,
& zlup, zldn, bsum,
& tem, tem1, tem2,
& ptem, ptem0, ptem1, ptem2
Expand All @@ -176,11 +176,11 @@ subroutine satmedmfvdifq(ix,im,km,ntrac,ntcw,ntiw,ntke,
parameter(prmin=0.25,prmax=4.0)
parameter(pr0=1.0,prtke=1.0,prscu=0.67)
parameter(f0=1.e-4,crbmin=0.15,crbmax=0.35)
parameter(tkmin=1.e-9,dspmax=10.0)
parameter(tkmin=1.e-9,tkminx=0.2,dspmax=10.0)
parameter(qmin=1.e-8,qlmin=1.e-12,zfmin=1.e-8)
parameter(aphi5=5.,aphi16=16.)
parameter(elmfac=1.0,elefac=1.0,cql=100.)
parameter(dw2min=1.e-4,dkmax=1000.,xkgdx=25000.)
parameter(dw2min=1.e-4,dkmax=1000.,xkgdx=5000.)
parameter(qlcr=3.5e-5,zstblmax=2500.,xkzinv=0.1)
parameter(h1=0.33333333)
parameter(ck0=0.4,ck1=0.15,ch0=0.4,ch1=0.15)
Expand Down Expand Up @@ -273,20 +273,20 @@ subroutine satmedmfvdifq(ix,im,km,ntrac,ntcw,ntiw,ntke,
xkzo(i,k) = 0.0
xkzmo(i,k) = 0.0
if (k < kinver(i)) then
! vertical background diffusivity
ptem = prsi(i,k+1) * tx1(i)
tem1 = 1.0 - ptem
tem2 = tem1 * tem1 * 10.0
tem2 = min(1.0, exp(-tem2))
xkzo(i,k) = xkzm_hx(i) * tem2
!
! minimum turbulent mixing length
ptem = prsl(i,k) * tx1(i)
tem1 = 1.0 - ptem
tem2 = tem1 * tem1 * 2.5
tem2 = min(1.0, exp(-tem2))
rlmnz(i,k)= rlmn * tem2
rlmnz(i,k)= max(rlmnz(i,k), rlmn1)
! vertical background diffusivity for momentum
! vertical background diffusivity
ptem = prsi(i,k+1) * tx1(i)
tem1 = 1.0 - ptem
tem2 = tem1 * tem1 * 10.0
tem2 = min(1.0, exp(-tem2))
xkzo(i,k) = xkzm_hx(i) * tem2
! vertical background diffusivity for momentum
if (ptem >= xkzm_s) then
xkzmo(i,k) = xkzm_mx(i)
kx1(i) = k + 1
Expand Down Expand Up @@ -674,20 +674,20 @@ subroutine satmedmfvdifq(ix,im,km,ntrac,ntcw,ntiw,ntke,
!
! background diffusivity decreasing with increasing surface layer stability
!
do i = 1, im
if(.not.sfcflg(i)) then
tem = (1. + 5. * rbsoil(i))**2.
! tem = (1. + 5. * zol(i))**2.
frik(i) = 0.1 + 0.9 / tem
endif
enddo
!
do k = 1,km1
do i=1,im
xkzo(i,k) = frik(i) * xkzo(i,k)
xkzmo(i,k)= frik(i) * xkzmo(i,k)
enddo
enddo
! do i = 1, im
! if(.not.sfcflg(i)) then
! tem = (1. + 5. * rbsoil(i))**2.
!! tem = (1. + 5. * zol(i))**2.
! frik(i) = 0.1 + 0.9 / tem
! endif
! enddo
!
! do k = 1,km1
! do i=1,im
! xkzo(i,k) = frik(i) * xkzo(i,k)
! xkzmo(i,k)= frik(i) * xkzmo(i,k)
! enddo
! enddo
!
! The background vertical diffusivities in the inversion layers are limited
! to be less than or equal to xkzminv
Expand Down Expand Up @@ -867,13 +867,14 @@ subroutine satmedmfvdifq(ix,im,km,ntrac,ntcw,ntiw,ntke,
do i = 1, im
if(k == 1) then
tem = ckz(i,1)
tem1 = xkzmo(i,1)
tem1 = 0.5 * xkzmo(i,1)
else
tem = 0.5 * (ckz(i,k-1) + ckz(i,k))
tem1 = 0.5 * (xkzmo(i,k-1) + xkzmo(i,k))
endif
ptem = tem1 / (tem * elm(i,k))
tkmnz(i,k) = ptem * ptem
tkmnz(i,k) = min(tkmnz(i,k), tkminx)
tkmnz(i,k) = max(tkmnz(i,k), tkmin)
enddo
enddo
Expand Down
12 changes: 3 additions & 9 deletions io/FV3GFS_io.F90
Original file line number Diff line number Diff line change
Expand Up @@ -101,8 +101,7 @@ module FV3GFS_io_mod
logical :: uwork_set = .false.
character(128) :: uwindname
integer, parameter, public :: DIAG_SIZE = 500
! real(kind=kind_phys), parameter :: missing_value = 1.d30
real(kind=kind_phys), parameter :: missing_value = 9.99e20
real, parameter :: missing_value = 9.99e20
real, parameter:: stndrd_atmos_ps = 101325.
real, parameter:: stndrd_atmos_lapse = 0.0065

Expand Down Expand Up @@ -1137,15 +1136,10 @@ subroutine sfc_prop_restart_read (Sfcprop, Atm_block, Model, fv_domain)
Sfcprop(nb)%zorll(ix) = Sfcprop(nb)%zorlo(ix)
Sfcprop(nb)%zorl(ix) = Sfcprop(nb)%zorlo(ix)
Sfcprop(nb)%tsfc(ix) = Sfcprop(nb)%tsfco(ix)
if (Sfcprop(nb)%slmsk(ix) < 0.1 .or. Sfcprop(nb)%slmsk(ix) > 1.9) then
if (Sfcprop(nb)%slmsk(ix) > 1.9) then
Sfcprop(nb)%landfrac(ix) = 0.0
if (Sfcprop(nb)%oro_uf(ix) > 0.01) then
Sfcprop(nb)%lakefrac(ix) = 1.0 ! lake
else
Sfcprop(nb)%lakefrac(ix) = 0.0 ! ocean
endif
else
Sfcprop(nb)%landfrac(ix) = 1.0 ! land
Sfcprop(nb)%landfrac(ix) = Sfcprop(nb)%slmsk(ix)
endif
enddo
enddo
Expand Down
1 change: 1 addition & 0 deletions io/module_fv3_io_def.F90
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ module module_fv3_io_def
logical :: write_nemsioflip
logical :: write_fsyncflag
integer :: num_files
character(255) :: app_domain
character(255) :: output_grid
character(255) :: output_file
integer :: imo,jmo
Expand Down
Loading

0 comments on commit 88e87e9

Please sign in to comment.