Skip to content

Commit

Permalink
Merge pull request NCAR#36 from joeolson42/gsd/develop
Browse files Browse the repository at this point in the history
MYNN PBL and SFC updates for ocean coupling, ...
  • Loading branch information
DomHeinzeller authored Jun 9, 2020
2 parents 3b0f7c2 + 43821e3 commit 84047fe
Show file tree
Hide file tree
Showing 6 changed files with 930 additions and 195 deletions.
66 changes: 53 additions & 13 deletions physics/module_MYNNPBL_wrapper.F90
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,8 @@ end subroutine mynnedmf_wrapper_finalize
SUBROUTINE mynnedmf_wrapper_run( &
& im,levs, &
& flag_init,flag_restart,cycling, &
& lssav, ldiag3d, qdiag3d, lsidea,&
& lssav, ldiag3d, qdiag3d, &
& lsidea, cplflx, &
& delt,dtf,dx,zorl, &
& phii,u,v,omega,t3d, &
& qgrs_water_vapor, &
Expand All @@ -52,10 +53,17 @@ SUBROUTINE mynnedmf_wrapper_run( &
& qgrs_ice_aer_num_conc, &
& prsl,exner, &
& slmsk,tsurf,qsfc,ps, &
& ust,ch,hflx,qflx, &
& wspd,rb,dtsfc1,dqsfc1, &
& ust,ch,hflx,qflx,wspd,rb, &
& dtsfc1,dqsfc1, &
& dusfc1,dvsfc1, &
& dusfci_diag,dvsfci_diag, &
& dtsfci_diag,dqsfci_diag, &
& dusfc_diag,dvsfc_diag, &
& dtsfc_diag,dqsfc_diag, &
& dusfci_cpl,dvsfci_cpl, &
& dtsfci_cpl,dqsfci_cpl, &
& dusfc_cpl,dvsfc_cpl, &
& dtsfc_cpl,dqsfc_cpl, &
& recmol, &
& qke,qke_adv,Tsq,Qsq,Cov, &
& el_pbl,sh3d,exch_h,exch_m, &
Expand Down Expand Up @@ -171,6 +179,8 @@ SUBROUTINE mynnedmf_wrapper_run( &
integer, intent(out) :: errflg

LOGICAL, INTENT(IN) :: lssav, ldiag3d, lsidea, qdiag3d
LOGICAL, INTENT(IN) :: cplflx

! NAMELIST OPTIONS (INPUT):
LOGICAL, INTENT(IN) :: bl_mynn_tkeadvect, ltaerosol, &
lprnt, do_mynnsfclay, cycling
Expand Down Expand Up @@ -272,17 +282,25 @@ SUBROUTINE mynnedmf_wrapper_run( &
real(kind=kind_phys), dimension(im), intent(inout) :: &
& pblh
real(kind=kind_phys), dimension(im), intent(out) :: &
& ch,dtsfc1,dqsfc1, &
& ch,dtsfc1,dqsfc1,dusfc1,dvsfc1, &
& dtsfci_diag,dqsfci_diag,dtsfc_diag,dqsfc_diag, &
& dusfci_diag,dvsfci_diag,dusfc_diag,dvsfc_diag, &
& maxMF
integer, dimension(im), intent(inout) :: &
& kpbl,nupdraft,ktop_plume
integer, dimension(im), intent(inout) :: &
& kpbl,nupdraft,ktop_plume

real(kind=kind_phys), dimension(:), intent(inout) :: &
& dusfc_cpl,dvsfc_cpl,dtsfc_cpl,dqsfc_cpl
real(kind=kind_phys), dimension(:), intent(inout) :: &
& dusfci_cpl,dvsfci_cpl,dtsfci_cpl,dqsfci_cpl

!LOCAL
real, dimension(im) :: &
& WSTAR,DELTA,qcg,hfx,qfx,rmol,xland, &
& uoce,voce,vdfg,znt,ts

real, dimension(im) :: dusfci1,dvsfci1,dtsfci1,dqsfci1

! Initialize CCPP error handling variables
errmsg = ''
errflg = 0
Expand Down Expand Up @@ -474,12 +492,33 @@ SUBROUTINE mynnedmf_wrapper_run( &
delta(i)=0.0
qcg(i)=0.0

dtsfc1(i)=hfx(i)
dqsfc1(i)=qfx(i)*XLV
dtsfci_diag(i)=dtsfc1(i)
dqsfci_diag(i)=dqsfc1(i)
dtsfc_diag(i)=dtsfc_diag(i) + dtsfc1(i)*delt
dqsfc_diag(i)=dqsfc_diag(i) + dqsfc1(i)*delt
dtsfc1(i) = hfx(i)
dqsfc1(i) = qfx(i)*XLV
dusfc1(i) = -1.*rho(i,1)*ust(i)*ust(i)*u(i,1)/wspd(i)
dvsfc1(i) = -1.*rho(i,1)*ust(i)*ust(i)*v(i,1)/wspd(i)

!BWG: diagnostic surface fluxes for scalars & momentum
dtsfci_diag(i) = dtsfc1(i)
dqsfci_diag(i) = dqsfc1(i)
dtsfc_diag(i) = dtsfc_diag(i) + dtsfc1(i)*delt
dqsfc_diag(i) = dqsfc_diag(i) + dqsfc1(i)*delt
dusfci_diag(i) = dusfc1(i)
dvsfci_diag(i) = dvsfc1(i)
dusfc_diag(i) = dusfc_diag(i) + dusfci_diag(i)*delt
dvsfc_diag(i) = dvsfc_diag(i) + dvsfci_diag(i)*delt

! BWG: Coupling insertion
if(cplflx) then
dusfci_cpl(i) = dusfci_diag(i)
dvsfci_cpl(i) = dvsfci_diag(i)
dtsfci_cpl(i) = dtsfci_diag(i)
dqsfci_cpl(i) = dqsfci_diag(i)

dusfc_cpl(i) = dusfc_cpl(i) + dusfci_cpl(i)*delt
dvsfc_cpl(i) = dvsfc_cpl(i) + dvsfci_cpl(i)*delt
dtsfc_cpl(i) = dtsfc_cpl(i) + dtsfci_cpl(i)*delt
dqsfc_cpl(i) = dqsfc_cpl(i) + dqsfci_cpl(i)*delt
endif

znt(i)=zorl(i)*0.01 !cm -> m?
if (do_mynnsfclay) then
Expand Down Expand Up @@ -782,7 +821,8 @@ SUBROUTINE mynnedmf_wrapper_run( &
enddo
endif
endif



if (lprnt) then
print*
print*,"===Finished with mynn_bl_driver; output:"
Expand Down
138 changes: 136 additions & 2 deletions physics/module_MYNNPBL_wrapper.meta
Original file line number Diff line number Diff line change
Expand Up @@ -101,6 +101,14 @@
type = logical
intent = in
optional = F
[cplflx]
standard_name = flag_for_flux_coupling
long_name = flag controlling cplflx collection (default off)
units = flag
dimensions = ()
type = logical
intent = in
optional = F
[delt]
standard_name = time_step_for_physics
long_name = time step for physics
Expand Down Expand Up @@ -380,6 +388,42 @@
kind = kind_phys
intent = out
optional = F
[dusfc1]
standard_name = instantaneous_surface_x_momentum_flux
long_name = surface momentum flux in the x-direction valid for current call
units = Pa
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = out
optional = F
[dvsfc1]
standard_name = instantaneous_surface_y_momentum_flux
long_name = surface momentum flux in the y-direction valid for current call
units = Pa
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = out
optional = F
[dusfci_diag]
standard_name = instantaneous_surface_x_momentum_flux_for_diag
long_name = instantaneous sfc x momentum flux multiplied by timestep
units = Pa
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = out
optional = F
[dvsfci_diag]
standard_name = instantaneous_surface_y_momentum_flux_for_diag
long_name = instantaneous sfc y momentum flux multiplied by timestep
units = Pa
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = out
optional = F
[dtsfci_diag]
standard_name = instantaneous_surface_upward_sensible_heat_flux_for_diag
long_name = instantaneous sfc sensible heat flux multiplied by timestep
Expand All @@ -398,14 +442,32 @@
kind = kind_phys
intent = out
optional = F
[dusfc_diag]
standard_name = cumulative_surface_x_momentum_flux_for_diag_multiplied_by_timestep
long_name = cumulative sfc x momentum flux multiplied by timestep
units = Pa s
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[dvsfc_diag]
standard_name = cumulative_surface_y_momentum_flux_for_diag_multiplied_by_timestep
long_name = cumulative sfc y momentum flux multiplied by timestep
units = Pa s
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[dtsfc_diag]
standard_name = cumulative_surface_upward_sensible_heat_flux_for_diag_multiplied_by_timestep
long_name = cumulative sfc sensible heat flux multiplied by timestep
units = W m-2 s
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = out
intent = inout
optional = F
[dqsfc_diag]
standard_name = cumulative_surface_upward_latent_heat_flux_for_diag_multiplied_by_timestep
Expand All @@ -414,7 +476,79 @@
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = out
intent = inout
optional = F
[dusfci_cpl]
standard_name = instantaneous_surface_x_momentum_flux_for_coupling
long_name = instantaneous sfc u momentum flux
units = Pa
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[dvsfci_cpl]
standard_name = instantaneous_surface_y_momentum_flux_for_coupling
long_name = instantaneous sfc v momentum flux
units = Pa
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[dtsfci_cpl]
standard_name = instantaneous_surface_upward_sensible_heat_flux_for_coupling
long_name = instantaneous sfc sensible heat flux
units = W m-2
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[dqsfci_cpl]
standard_name = instantaneous_surface_upward_latent_heat_flux_for_coupling
long_name = instantaneous sfc latent heat flux
units = W m-2
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[dusfc_cpl]
standard_name = cumulative_surface_x_momentum_flux_for_coupling_multiplied_by_timestep
long_name = cumulative sfc u momentum flux multiplied by timestep
units = Pa s
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[dvsfc_cpl]
standard_name = cumulative_surface_y_momentum_flux_for_coupling_multiplied_by_timestep
long_name = cumulative sfc v momentum flux multiplied by timestep
units = Pa s
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[dtsfc_cpl]
standard_name = cumulative_surface_upward_sensible_heat_flux_for_coupling_multiplied_by_timestep
long_name = cumulative sfc sensible heat flux multiplied by timestep
units = W m-2 s
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[dqsfc_cpl]
standard_name = cumulative_surface_upward_latent_heat_flux_for_coupling_multiplied_by_timestep
long_name = cumulative sfc latent heat flux multiplied by timestep
units = W m-2 s
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[recmol]
standard_name = reciprocal_of_obukhov_length
Expand Down
19 changes: 17 additions & 2 deletions physics/module_MYNNSFC_wrapper.F90
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,9 @@ SUBROUTINE mynnsfc_wrapper_run( &
& im,levs, &
& itimestep,iter, &
& flag_init,flag_restart,lsm, &
& sigmaf,vegtype,shdmax,ivegsrc, & !intent(in)
& z0pert,ztpert, & !intent(in)
& redrag,sfc_z0_type, & !intent(in)
& delt,dx, &
& u, v, t3d, qvsh, qc, prsl, phii, &
& exner, ps, PBLH, slmsk, &
Expand Down Expand Up @@ -101,6 +104,15 @@ SUBROUTINE mynnsfc_wrapper_run( &
& iz0tlnd = 0, &
& isfflx = 1

integer, intent(in) :: ivegsrc
integer, intent(in) :: sfc_z0_type ! option for calculating surface roughness length over ocean
logical, intent(in) :: redrag ! reduced drag coeff. flag for high wind over sea (j.han)

!Input data
integer, dimension(im), intent(in) :: vegtype
real(kind=kind_phys), dimension(im), intent(in) :: &
& sigmaf,shdmax,z0pert,ztpert

!MYNN-1D
REAL :: delt
INTEGER :: im, levs
Expand Down Expand Up @@ -235,8 +247,11 @@ SUBROUTINE mynnsfc_wrapper_run( &
CP=cp,G=g,ROVCP=rcp,R=r_d,XLV=xlv, &
SVP1=svp1,SVP2=svp2,SVP3=svp3,SVPT0=svpt0, &
EP1=ep_1,EP2=ep_2,KARMAN=karman, &
ISFFLX=isfflx,isftcflx=isftcflx,LSM=lsm, &
iz0tlnd=iz0tlnd,itimestep=itimestep,iter=iter, &
ISFFLX=isfflx,isftcflx=isftcflx,LSM=lsm,iz0tlnd=iz0tlnd, &
& sigmaf=sigmaf,vegtype=vegtype,shdmax=shdmax,ivegsrc=ivegsrc, & !intent(in)
& z0pert=z0pert,ztpert=ztpert, & !intent(in)
& redrag=redrag,sfc_z0_type=sfc_z0_type, & !intent(in)
itimestep=itimestep,iter=iter, &
wet=wet, dry=dry, icy=icy, & !intent(in)
tskin_ocn=tskin_ocn, tskin_lnd=tskin_lnd, tskin_ice=tskin_ice, & !intent(in)
tsurf_ocn=tsurf_ocn, tsurf_lnd=tsurf_lnd, tsurf_ice=tsurf_ice, & !intent(in)
Expand Down
Loading

0 comments on commit 84047fe

Please sign in to comment.