195 subroutine cires_ugwp_run(do_ugwp, me, master, im, levs, ntrac, dtp, kdt, lonr, &
196 oro, oro_uf, hprime, nmtvr, oc, theta, sigma, gamma, elvmax, clx, oa4, &
197 do_tofd, ldiag_ugwp, cdmbgwd, xlat, xlat_d, sinlat, coslat, &
198 area, ugrs, vgrs, tgrs, qgrs, prsi, prsl, prslk, phii, phil, &
199 del, kpbl, dusfcg, dvsfcg, gw_dudt, gw_dvdt, gw_dtdt, gw_kdis, &
200 tau_tofd, tau_mtb, tau_ogw, tau_ngw, zmtb, zlwb, zogw, &
201 dusfc_ms, dvsfc_ms, dusfc_bl, dvsfc_bl, &
202 dudt_ogw, dtauy2d_ms, dtaux2d_bl, dtauy2d_bl, &
203 dudt_mtb, dudt_tms, du3dt_mtb, du3dt_ogw, du3dt_tms, &
204 dudt, dvdt, dtdt, rdxzb, con_g, con_pi, con_cp, con_rd, con_rv, con_fvirt, &
205 con_omega, rain, ntke, q_tke, dqdt_tke, lprnt, ipr, &
206 dtend, dtidx, index_of_x_wind, index_of_y_wind, index_of_temperature, &
207 index_of_process_orographic_gwd, index_of_process_nonorographic_gwd, &
208 ldiag3d, lssav, flag_for_gwd_generic_tend, errmsg, errflg)
213 integer,
intent(in) :: me, master, im, levs, ntrac, kdt, lonr, nmtvr
214 integer,
intent(in),
dimension(:) :: kpbl
215 real(kind=kind_phys),
intent(in),
dimension(:) :: oro, oro_uf, hprime, oc, theta, sigma, gamma
216 logical,
intent(in) :: flag_for_gwd_generic_tend
218 real(kind=kind_phys),
intent(inout),
dimension(:) :: elvmax
219 real(kind=kind_phys),
intent(in),
dimension(:, :) :: clx, oa4
220 real(kind=kind_phys),
intent(in),
dimension(:) :: xlat, xlat_d, sinlat, coslat, area
221 real(kind=kind_phys),
intent(in),
dimension(:, :) :: del, ugrs, vgrs, tgrs, prsl, prslk, phil
222 real(kind=kind_phys),
intent(in),
dimension(:, :) :: prsi, phii
223 real(kind=kind_phys),
intent(in),
dimension(:,:,:):: qgrs
224 real(kind=kind_phys),
intent(in) :: dtp, cdmbgwd(:)
225 logical,
intent(in) :: do_ugwp, do_tofd, ldiag_ugwp
227 real(kind=kind_phys),
intent(out),
dimension(:) :: dusfcg, dvsfcg
228 real(kind=kind_phys),
intent(out),
dimension(:) :: zmtb, zlwb, zogw, rdxzb
229 real(kind=kind_phys),
intent(out),
dimension(:) :: tau_mtb, tau_ogw, tau_tofd, tau_ngw
230 real(kind=kind_phys),
intent(out),
dimension(:, :):: gw_dudt, gw_dvdt, gw_dtdt, gw_kdis
231 real(kind=kind_phys),
intent(out),
dimension(:, :):: dudt_mtb, dudt_tms
232 real(kind=kind_phys),
intent(out),
dimension(:, :),
optional :: dudt_ogw
233 real(kind=kind_phys),
intent(out),
dimension(:),
optional :: dusfc_ms, dvsfc_ms, dusfc_bl, dvsfc_bl
234 real(kind=kind_phys),
intent(out),
dimension(:, :),
optional :: dtauy2d_ms
235 real(kind=kind_phys),
intent(out),
dimension(:, :),
optional :: dtaux2d_bl, dtauy2d_bl
238 real(kind=kind_phys),
optional,
intent(inout) :: dtend(:,:,:)
239 integer,
intent(in) :: dtidx(:,:), &
240 index_of_x_wind, index_of_y_wind, index_of_temperature, &
241 index_of_process_orographic_gwd, index_of_process_nonorographic_gwd
243 logical,
intent(in) :: ldiag3d, lssav
246 real(kind=kind_phys),
intent(inout),
dimension(:,:),
optional :: du3dt_mtb, du3dt_ogw, du3dt_tms
248 real(kind=kind_phys),
intent(inout),
dimension(:, :):: dudt, dvdt, dtdt
250 real(kind=kind_phys),
intent(in) :: con_g, con_pi, con_cp, con_rd, con_rv, con_fvirt, con_omega
252 real(kind=kind_phys),
intent(in),
dimension(:) :: rain
254 integer,
intent(in) :: ntke
255 real(kind=kind_phys),
intent(in),
dimension(:,:) :: q_tke, dqdt_tke
257 logical,
intent(in) :: lprnt
258 integer,
intent(in) :: ipr
260 character(len=*),
intent(out) :: errmsg
261 integer,
intent(out) :: errflg
264 integer :: i, k, idtend
265 real(kind=kind_phys),
dimension(im) :: sgh30
266 real(kind=kind_phys),
dimension(im, levs) :: pdvdt, pdudt
267 real(kind=kind_phys),
dimension(im, levs) :: pdtdt, pkdis
268 real(kind=kind_phys),
dimension(im, levs) :: ed_dudt, ed_dvdt, ed_dtdt
270 real(kind=kind_phys),
parameter :: tamp_mpa=30.e-3
272 real(kind=kind_phys),
parameter :: pogw=1., pngw=1., pked=1.
274 real(kind=kind_phys),
dimension(:,:),
allocatable :: tke
275 real(kind=kind_phys),
dimension(:),
allocatable :: turb_fac, tem
276 real(kind=kind_phys) :: rfac, tx1
291 sgh30 = abs(oro - oro_uf)
299 call gwdps_v0(im, levs, lonr, do_tofd, pdvdt, pdudt, pdtdt, pkdis, &
300 ugrs, vgrs, tgrs, qgrs(:,:,1), kpbl, prsi,del,prsl, prslk, phii, phil, &
301 dtp, kdt, sgh30, hprime, oc, oa4, clx, theta, sigma, gamma, elvmax, &
302 dusfcg, dvsfcg, xlat_d, sinlat, coslat, area, cdmbgwd(1:2), &
303 me, master, rdxzb, con_g, con_omega, zmtb, zogw, tau_mtb, tau_ogw, &
304 tau_tofd, dudt_mtb, dudt_ogw, dudt_tms)
317 if (cdmbgwd(1) > 0.0 .or. cdmbgwd(2) > 0.0)
then
318 call gwdps_run(im, levs, pdvdt, pdudt, pdtdt, &
319 ugrs, vgrs, tgrs, qgrs(:,:,1), &
320 kpbl, prsi, del, prsl, prslk, phii, phil, dtp, kdt, &
321 hprime, oc, oa4, clx, theta, sigma, gamma, &
322 elvmax, dusfcg, dvsfcg, dudt_ogw, dtauy2d_ms, &
323 dtaux2d_bl, dtauy2d_bl, dusfc_ms, dvsfc_ms, &
324 dusfc_bl, dvsfc_bl, &
325 con_g, con_cp, con_rd, con_rv, lonr, &
326 nmtvr, cdmbgwd, me, lprnt, ipr, rdxzb, ldiag_ugwp, &
328 if (errflg/=0)
return
331 tau_mtb = 0.0 ; tau_ogw = 0.0 ; tau_tofd = 0.0
333 du3dt_mtb = 0.0 ; du3dt_ogw = 0.0 ; du3dt_tms= 0.0
339 if(ldiag3d .and. lssav .and. .not. flag_for_gwd_generic_tend)
then
340 idtend = dtidx(index_of_x_wind,index_of_process_orographic_gwd)
342 dtend(:,:,idtend) = dtend(:,:,idtend) + pdudt*dtp
344 idtend = dtidx(index_of_y_wind,index_of_process_orographic_gwd)
346 dtend(:,:,idtend) = dtend(:,:,idtend) + pdvdt*dtp
348 idtend = dtidx(index_of_temperature,index_of_process_orographic_gwd)
350 dtend(:,:,idtend) = dtend(:,:,idtend) + pdtdt*dtp
355 if (cdmbgwd(3) > 0.0)
then
358 call slat_geos5_tamp_v0(im, tamp_mpa, xlat_d, tau_ngw)
360 if (abs(1.0-cdmbgwd(3)) > 1.0e-6)
then
361 if (cdmbgwd(4) > 0.0)
then
362 allocate(turb_fac(im))
367 allocate(tke(im,levs))
369 tke(:,:) = q_tke(:,:) + dqdt_tke(:,:) * dtp
373 turb_fac(i) = turb_fac(i) + del(i,k) * tke(i,k)
374 tem(i) = tem(i) + del(i,k)
378 turb_fac(i) = turb_fac(i) / tem(i)
383 rfac = 86400000 / dtp
385 tx1 = cdmbgwd(4)*min(10.0, max(turb_fac(i),rain(i)*rfac))
386 tau_ngw(i) = tau_ngw(i) * max(0.1, min(5.0, tx1))
391 tau_ngw(i) = tau_ngw(i) * cdmbgwd(3)
395 call fv3_ugwp_solv2_v0(im, levs, dtp, tgrs, ugrs, vgrs,qgrs(:,:,1), &
396 prsl, prsi, phil, xlat_d, sinlat, coslat, &
397 gw_dudt, gw_dvdt, gw_dtdt, gw_kdis, tau_ngw, &
402 gw_dtdt(i,k) = pngw*gw_dtdt(i,k) + pogw*pdtdt(i,k)
403 gw_dudt(i,k) = pngw*gw_dudt(i,k) + pogw*pdudt(i,k)
404 gw_dvdt(i,k) = pngw*gw_dvdt(i,k) + pogw*pdvdt(i,k)
405 gw_kdis(i,k) = pngw*gw_kdis(i,k) + pogw*pkdis(i,k)
417 gw_dtdt(i,k) = pdtdt(i,k)
418 gw_dudt(i,k) = pdudt(i,k)
419 gw_dvdt(i,k) = pdvdt(i,k)
420 gw_kdis(i,k) = pkdis(i,k)
426 if (pogw == 0.0)
then
427 tau_mtb = 0. ; tau_ogw = 0. ; tau_tofd = 0.
428 dudt_mtb = 0. ; dudt_ogw = 0. ; dudt_tms = 0.
431 if(ldiag3d .and. lssav .and. .not. flag_for_gwd_generic_tend)
then
432 idtend = dtidx(index_of_x_wind,index_of_process_nonorographic_gwd)
434 dtend(:,:,idtend) = dtend(:,:,idtend) + (gw_dudt - pdudt)*dtp
436 idtend = dtidx(index_of_y_wind,index_of_process_nonorographic_gwd)
438 dtend(:,:,idtend) = dtend(:,:,idtend) + (gw_dvdt - pdvdt)*dtp
440 idtend = dtidx(index_of_temperature,index_of_process_nonorographic_gwd)
442 dtend(:,:,idtend) = dtend(:,:,idtend) + (gw_dtdt - pdtdt)*dtp