35 use fv_mp_nlm_mod,
only: is, ie, js, je, isd, ied, jsd, jed, isc, iec, jsc, jec
54 real,
allocatable ::
rf(:),
rw(:)
96 & u_ad, v, v_ad, w, pt, delp, delz, q, uc, uc_ad, vc, vc_ad, pkz, &
97 & nested, inline_q, make_nh, ng, gridstruct, flagstruct, neststruct, &
98 & nest_timestep, tracer_nest_timestep, domain, bd, nwat)
101 REAL,
INTENT(IN) :: zvir
102 INTEGER,
INTENT(IN) :: npx, npy, npz
103 INTEGER,
INTENT(IN) :: ncnst, ng, nwat
104 LOGICAL,
INTENT(IN) :: inline_q, make_nh, nested
106 REAL,
DIMENSION(bd%isd:bd%ied, bd%jsd:bd%jed+1, npz),
INTENT(INOUT) &
108 REAL,
DIMENSION(bd%isd:bd%ied, bd%jsd:bd%jed+1, npz),
INTENT(INOUT) &
111 REAL,
DIMENSION(bd%isd:bd%ied+1, bd%jsd:bd%jed, npz),
INTENT(INOUT) &
113 REAL,
DIMENSION(bd%isd:bd%ied+1, bd%jsd:bd%jed, npz),
INTENT(INOUT) &
116 REAL,
INTENT(INOUT) :: w(bd%isd:, bd%jsd:, :)
118 REAL,
INTENT(INOUT) :: pt(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
120 REAL,
INTENT(INOUT) :: delp(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
122 REAL,
INTENT(INOUT) :: delz(bd%isd:, bd%jsd:, :)
124 REAL,
INTENT(INOUT) :: q(bd%isd:bd%ied, bd%jsd:bd%jed, npz, ncnst)
126 REAL,
INTENT(INOUT) :: uc(bd%isd:bd%ied+1, bd%jsd:bd%jed, npz)
127 REAL,
INTENT(INOUT) :: uc_ad(bd%isd:bd%ied+1, bd%jsd:bd%jed, npz)
128 REAL,
INTENT(INOUT) :: vc(bd%isd:bd%ied, bd%jsd:bd%jed+1, npz)
129 REAL,
INTENT(INOUT) :: vc_ad(bd%isd:bd%ied, bd%jsd:bd%jed+1, npz)
131 REAL,
INTENT(INOUT) :: pkz(bd%is:bd%ie, bd%js:bd%je, npz)
132 INTEGER,
INTENT(INOUT) :: nest_timestep, tracer_nest_timestep
136 TYPE(
domain2d),
INTENT(INOUT) :: domain
137 REAL :: divg(bd%isd:bd%ied+1, bd%jsd:bd%jed+1, npz)
138 REAL :: ua(bd%isd:bd%ied, bd%jsd:bd%jed)
139 REAL :: va(bd%isd:bd%ied, bd%jsd:bd%jed)
140 REAL :: pkz_coarse(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
141 INTEGER :: i, j, k, n, p, sphum
145 LOGICAL,
POINTER :: child_grids(:)
146 INTEGER :: is, ie, js, je
147 INTEGER :: isd, ied, jsd, jed
165 IF (any(neststruct%child_grids))
THEN 170 CALL d2c_setup_fwd(u(isd, jsd, k), v(isd, jsd, k), ua, va, uc(&
171 & isd, jsd, k), vc(isd, jsd, k), arg1, isd, ied, jsd&
172 & , jed, is, ie, js, je, npx, npy, gridstruct%&
173 &
grid_type, gridstruct%nested, gridstruct%se_corner&
174 & , gridstruct%sw_corner, gridstruct%ne_corner, &
175 & gridstruct%nw_corner, gridstruct%rsin_u, gridstruct&
176 & %rsin_v, gridstruct%cosa_s, gridstruct%rsin2)
183 IF (neststruct%nested)
THEN 184 IF (.NOT.
ALLOCATED(
q_buf))
THEN 185 ALLOCATE(
q_buf(ncnst))
190 IF (branch .EQ. 0)
THEN 192 CALL d2c_setup_bwd(u(isd, jsd, k), u_ad(isd, jsd, k), v(isd, jsd&
193 & , k), v_ad(isd, jsd, k), ua, va, uc(isd, jsd, k), &
194 & uc_ad(isd, jsd, k), vc(isd, jsd, k), vc_ad(isd, jsd&
195 & , k), arg1, isd, ied, jsd, jed, is, ie, js, je, npx&
196 & , npy, gridstruct%grid_type, gridstruct%nested, &
197 & gridstruct%se_corner, gridstruct%sw_corner, &
198 & gridstruct%ne_corner, gridstruct%nw_corner, &
199 & gridstruct%rsin_u, gridstruct%rsin_v, gridstruct%&
200 & cosa_s, gridstruct%rsin2)
203 & dgrid_ne, complete=.true.)
209 & pt, delp, delz, q, uc, vc, pkz, nested, inline_q, make_nh, ng, &
210 & gridstruct, flagstruct, neststruct, nest_timestep, &
211 & tracer_nest_timestep, domain, bd, nwat)
214 REAL,
INTENT(IN) :: zvir
215 INTEGER,
INTENT(IN) :: npx, npy, npz
216 INTEGER,
INTENT(IN) :: ncnst, ng, nwat
217 LOGICAL,
INTENT(IN) :: inline_q, make_nh, nested
219 REAL,
DIMENSION(bd%isd:bd%ied, bd%jsd:bd%jed+1, npz),
INTENT(INOUT) &
222 REAL,
DIMENSION(bd%isd:bd%ied+1, bd%jsd:bd%jed, npz),
INTENT(INOUT) &
225 REAL,
INTENT(INOUT) :: w(bd%isd:, bd%jsd:, :)
227 REAL,
INTENT(INOUT) :: pt(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
229 REAL,
INTENT(INOUT) :: delp(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
231 REAL,
INTENT(INOUT) :: delz(bd%isd:, bd%jsd:, :)
233 REAL,
INTENT(INOUT) :: q(bd%isd:bd%ied, bd%jsd:bd%jed, npz, ncnst)
235 REAL,
INTENT(INOUT) :: uc(bd%isd:bd%ied+1, bd%jsd:bd%jed, npz)
236 REAL,
INTENT(INOUT) :: vc(bd%isd:bd%ied, bd%jsd:bd%jed+1, npz)
238 REAL,
INTENT(INOUT) :: pkz(bd%is:bd%ie, bd%js:bd%je, npz)
239 INTEGER,
INTENT(INOUT) :: nest_timestep, tracer_nest_timestep
243 TYPE(
domain2d),
INTENT(INOUT) :: domain
244 REAL :: divg(bd%isd:bd%ied+1, bd%jsd:bd%jed+1, npz)
245 REAL :: ua(bd%isd:bd%ied, bd%jsd:bd%jed)
246 REAL :: va(bd%isd:bd%ied, bd%jsd:bd%jed)
247 REAL :: pkz_coarse(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
248 INTEGER :: i, j, k, n, p, sphum
252 LOGICAL,
POINTER :: child_grids(:)
253 INTEGER :: is, ie, js, je
254 INTEGER :: isd, ied, jsd, jed
267 child_grids => neststruct%child_grids
271 IF (.NOT.inline_q) tracer_nest_timestep = 0
272 IF (neststruct%nested .AND. ((.NOT.neststruct%first_step) .OR. &
275 CALL set_bcs_t0(ncnst, flagstruct%hydrostatic, neststruct)
282 IF (any(neststruct%child_grids))
THEN 293 arg1 = flagstruct%nord .GT. 0
294 CALL d2c_setup(u(isd, jsd, k), v(isd, jsd, k), ua, va, uc(isd, &
295 & jsd, k), vc(isd, jsd, k), arg1, isd, ied, jsd, jed, is&
296 & , ie, js, je, npx, npy, gridstruct%grid_type, &
297 & gridstruct%nested, gridstruct%se_corner, gridstruct%&
298 & sw_corner, gridstruct%ne_corner, gridstruct%nw_corner, &
299 & gridstruct%rsin_u, gridstruct%rsin_v, gridstruct%cosa_s&
300 & , gridstruct%rsin2)
303 & , va, divg(isd, jsd, k), gridstruct, &
307 & , divg(isd, jsd, k), gridstruct, flagstruct, &
312 IF (flagstruct%hydrostatic)
THEN 317 pkz_coarse(i, j, k) = pkz(i, j, k)
323 IF (neststruct%nested)
THEN 324 IF (.NOT.
ALLOCATED(
q_buf))
THEN 325 ALLOCATE(
q_buf(ncnst))
335 IF (flagstruct%hydrostatic)
THEN 337 & jsd, jed, npx, npy, npz, ng, 0, 0, 0, &
359 DO p=1,
SIZE(child_grids)
360 IF (child_grids(p))
THEN 365 & nest_domain_all(p), 0, 0)
369 IF (flagstruct%hydrostatic)
THEN 372 & nest_domain_all(p), 0, 0)
392 & ind_h, neststruct%wt_h, 0, 0, npx, npy, &
393 & npz, bd, neststruct%delp_bc,
delp_buf, &
397 & %ind_h, neststruct%wt_h, 0, 0, npx, npy&
398 & , npz, bd, neststruct%q_bc(n),
q_buf(n)&
402 & ind_h, neststruct%wt_h, 0, 0, npx, npy, &
403 & npz, bd, neststruct%pt_bc,
pt_buf)
405 IF (flagstruct%hydrostatic)
THEN 407 & %ind_h, neststruct%wt_h, 0, 0, npx, npy&
409 CALL setup_pt_bc(neststruct%pt_bc, pkz_bc, neststruct%q_bc(sphum&
410 & ), npx, npy, npz, zvir, bd)
413 & %ind_h, neststruct%wt_h, 0, 0, npx, npy&
414 & , npz, bd, neststruct%w_bc,
w_buf)
416 & %ind_h, neststruct%wt_h, 0, 0, npx, npy&
417 & , npz, bd, neststruct%delz_bc,
delz_buf)
420 & neststruct%delz_bc, neststruct%q_bc(sphum), &
421 & neststruct%q_bc, ncnst, npx, npy, npz, zvir, bd)
424 & ind_u, neststruct%wt_u, 0, 1, npx, npy, &
425 & npz, bd, neststruct%u_bc,
u_buf)
427 & ind_u, neststruct%wt_u, 0, 1, npx, npy, &
428 & npz, bd, neststruct%vc_bc,
vc_buf)
430 & ind_v, neststruct%wt_v, 1, 0, npx, npy, &
431 & npz, bd, neststruct%v_bc,
v_buf)
433 & ind_v, neststruct%wt_v, 1, 0, npx, npy, &
434 & npz, bd, neststruct%uc_bc,
uc_buf)
436 & ind_b, neststruct%wt_b, 1, 1, npx, npy, &
437 & npz, bd, neststruct%divg_bc,
divg_buf)
439 IF (neststruct%first_step)
THEN 440 IF (neststruct%nested)
CALL set_bcs_t0(ncnst, flagstruct%&
441 & hydrostatic, neststruct)
442 neststruct%first_step = .false.
443 IF (.NOT.flagstruct%hydrostatic) flagstruct%make_nh = .false.
444 ELSE IF (flagstruct%make_nh)
THEN 446 flagstruct%make_nh = .false.
458 SUBROUTINE setup_pt_bc(pt_bc, pkz_bc, sphum_bc, npx, npy, npz, zvir, &
461 TYPE(FV_GRID_BOUNDS_TYPE),
INTENT(IN) :: bd
462 TYPE(FV_NEST_BC_TYPE_3D),
INTENT(IN),
TARGET :: pkz_bc, sphum_bc
463 TYPE(FV_NEST_BC_TYPE_3D),
INTENT(INOUT),
TARGET :: pt_bc
464 INTEGER,
INTENT(IN) :: npx, npy, npz
465 REAL,
INTENT(IN) :: zvir
466 REAL,
DIMENSION(:, :, :),
POINTER :: ptbc, pkzbc, sphumbc
467 INTEGER :: i, j, k, istart, iend
468 INTEGER :: is, ie, js, je
469 INTEGER :: isd, ied, jsd, jed
479 ptbc => pt_bc%west_t1
480 pkzbc => pkz_bc%west_t1
481 sphumbc => sphum_bc%west_t1
486 ptbc(i, j, k) = ptbc(i, j, k)/pkzbc(i, j, k)*(1.+zvir*&
493 ptbc => pt_bc%south_t1
494 pkzbc => pkz_bc%south_t1
495 sphumbc => sphum_bc%south_t1
501 IF (ie .EQ. npx - 1)
THEN 510 ptbc(i, j, k) = ptbc(i, j, k)/pkzbc(i, j, k)*(1.+zvir*&
516 IF (ie .EQ. npx - 1)
THEN 517 ptbc => pt_bc%east_t1
518 pkzbc => pkz_bc%east_t1
519 sphumbc => sphum_bc%east_t1
524 ptbc(i, j, k) = ptbc(i, j, k)/pkzbc(i, j, k)*(1.+zvir*&
530 IF (je .EQ. npy - 1)
THEN 531 ptbc => pt_bc%north_t1
532 pkzbc => pkz_bc%north_t1
533 sphumbc => sphum_bc%north_t1
539 IF (ie .EQ. npx - 1)
THEN 548 ptbc(i, j, k) = ptbc(i, j, k)/pkzbc(i, j, k)*(1.+zvir*&
555 SUBROUTINE setup_pt_nh_bc(pt_bc, delp_bc, delz_bc, sphum_bc, q_bc, nq&
556 & , npx, npy, npz, zvir, bd)
558 TYPE(FV_GRID_BOUNDS_TYPE),
INTENT(IN) :: bd
559 TYPE(FV_NEST_BC_TYPE_3D),
INTENT(IN),
TARGET :: delp_bc, delz_bc, &
561 TYPE(FV_NEST_BC_TYPE_3D),
INTENT(INOUT),
TARGET :: pt_bc
562 INTEGER,
INTENT(IN) :: nq
563 TYPE(FV_NEST_BC_TYPE_3D),
INTENT(IN),
TARGET :: q_bc(nq)
564 INTEGER,
INTENT(IN) :: npx, npy, npz
565 REAL,
INTENT(IN) :: zvir
567 REAL,
PARAMETER :: c_liq=4185.5
569 REAL,
PARAMETER :: c_ice=1972.
572 REAL,
DIMENSION(:, :, :),
POINTER :: ptbc, sphumbc, qconbc, delpbc, &
574 REAL,
DIMENSION(:, :, :),
POINTER :: liq_watbc_west, ice_watbc_west&
575 & , rainwatbc_west, snowwatbc_west, graupelbc_west
576 REAL,
DIMENSION(:, :, :),
POINTER :: liq_watbc_east, ice_watbc_east&
577 & , rainwatbc_east, snowwatbc_east, graupelbc_east
578 REAL,
DIMENSION(:, :, :),
POINTER :: liq_watbc_north, &
579 & ice_watbc_north, rainwatbc_north, snowwatbc_north, graupelbc_north
580 REAL,
DIMENSION(:, :, :),
POINTER :: liq_watbc_south, &
581 & ice_watbc_south, rainwatbc_south, snowwatbc_south, graupelbc_south
582 REAL :: dp1, q_liq, q_sol
583 REAL,
SAVE :: q_con=0.
588 INTEGER :: i, j, k, istart, iend
589 INTEGER :: liq_wat, ice_wat, rainwat, snowwat, graupel
591 REAL,
PARAMETER :: tice=273.16
592 REAL,
PARAMETER :: t_i0=15.
593 INTEGER :: is, ie, js, je
594 INTEGER :: isd, ied, jsd, jed
615 ALLOCATE(
dum_west(isd:0, jsd:jed, npz))
639 IF (ie .EQ. npx - 1)
THEN 641 ALLOCATE(
dum_east(npx:ied, jsd:jed, npz))
652 IF (je .EQ. npy - 1)
THEN 654 ALLOCATE(
dum_north(isd:ied, npy:jed, npz))
665 IF (liq_wat .GT. 0)
THEN 666 liq_watbc_west => q_bc(liq_wat)%west_t1
667 liq_watbc_east => q_bc(liq_wat)%east_t1
668 liq_watbc_north => q_bc(liq_wat)%north_t1
669 liq_watbc_south => q_bc(liq_wat)%south_t1
676 IF (ice_wat .GT. 0)
THEN 677 ice_watbc_west => q_bc(ice_wat)%west_t1
678 ice_watbc_east => q_bc(ice_wat)%east_t1
679 ice_watbc_north => q_bc(ice_wat)%north_t1
680 ice_watbc_south => q_bc(ice_wat)%south_t1
687 IF (rainwat .GT. 0)
THEN 688 rainwatbc_west => q_bc(rainwat)%west_t1
689 rainwatbc_east => q_bc(rainwat)%east_t1
690 rainwatbc_north => q_bc(rainwat)%north_t1
691 rainwatbc_south => q_bc(rainwat)%south_t1
698 IF (snowwat .GT. 0)
THEN 699 snowwatbc_west => q_bc(snowwat)%west_t1
700 snowwatbc_east => q_bc(snowwat)%east_t1
701 snowwatbc_north => q_bc(snowwat)%north_t1
702 snowwatbc_south => q_bc(snowwat)%south_t1
709 IF (graupel .GT. 0)
THEN 710 graupelbc_west => q_bc(graupel)%west_t1
711 graupelbc_east => q_bc(graupel)%east_t1
712 graupelbc_north => q_bc(graupel)%north_t1
713 graupelbc_south => q_bc(graupel)%south_t1
721 ptbc => pt_bc%west_t1
722 sphumbc => sphum_bc%west_t1
723 delpbc => delp_bc%west_t1
724 delzbc => delz_bc%west_t1
732 dp1 = zvir*sphumbc(i, j, k)
733 pkz = exp(
kappa*log(rdg*delpbc(i, j, k)*ptbc(i, j, k)*(1.+&
734 & dp1)/delzbc(i, j, k)))
735 ptbc(i, j, k) = ptbc(i, j, k)*(1.+dp1)/pkz
741 ptbc => pt_bc%south_t1
742 sphumbc => sphum_bc%south_t1
743 delpbc => delp_bc%south_t1
744 delzbc => delz_bc%south_t1
750 IF (ie .EQ. npx - 1)
THEN 763 dp1 = zvir*sphumbc(i, j, k)
764 pkz = exp(
kappa*log(rdg*delpbc(i, j, k)*ptbc(i, j, k)*(1.+&
765 & dp1)/delzbc(i, j, k)))
766 ptbc(i, j, k) = ptbc(i, j, k)*(1.+dp1)/pkz
771 IF (ie .EQ. npx - 1)
THEN 772 ptbc => pt_bc%east_t1
773 sphumbc => sphum_bc%east_t1
774 delpbc => delp_bc%east_t1
775 delzbc => delz_bc%east_t1
783 dp1 = zvir*sphumbc(i, j, k)
784 pkz = exp(
kappa*log(rdg*delpbc(i, j, k)*ptbc(i, j, k)*(1.+&
785 & dp1)/delzbc(i, j, k)))
786 ptbc(i, j, k) = ptbc(i, j, k)*(1.+dp1)/pkz
791 IF (je .EQ. npy - 1)
THEN 792 ptbc => pt_bc%north_t1
793 sphumbc => sphum_bc%north_t1
794 delpbc => delp_bc%north_t1
795 delzbc => delz_bc%north_t1
801 IF (ie .EQ. npx - 1)
THEN 813 dp1 = zvir*sphumbc(i, j, k)
814 pkz = exp(
kappa*log(rdg*delpbc(i, j, k)*ptbc(i, j, k)*(1.+&
815 & dp1)/delzbc(i, j, k)))
816 ptbc(i, j, k) = ptbc(i, j, k)*(1.+dp1)/pkz
822 SUBROUTINE set_bcs_t0(ncnst, hydrostatic, neststruct)
824 INTEGER,
INTENT(IN) :: ncnst
825 LOGICAL,
INTENT(IN) :: hydrostatic
826 TYPE(FV_NEST_TYPE),
INTENT(INOUT) :: neststruct
828 neststruct%delp_bc%east_t0 = neststruct%delp_bc%east_t1
829 neststruct%delp_bc%west_t0 = neststruct%delp_bc%west_t1
830 neststruct%delp_bc%north_t0 = neststruct%delp_bc%north_t1
831 neststruct%delp_bc%south_t0 = neststruct%delp_bc%south_t1
833 neststruct%q_bc(n)%east_t0 = neststruct%q_bc(n)%east_t1
834 neststruct%q_bc(n)%west_t0 = neststruct%q_bc(n)%west_t1
835 neststruct%q_bc(n)%north_t0 = neststruct%q_bc(n)%north_t1
836 neststruct%q_bc(n)%south_t0 = neststruct%q_bc(n)%south_t1
838 neststruct%pt_bc%east_t0 = neststruct%pt_bc%east_t1
839 neststruct%pt_bc%west_t0 = neststruct%pt_bc%west_t1
840 neststruct%pt_bc%north_t0 = neststruct%pt_bc%north_t1
841 neststruct%pt_bc%south_t0 = neststruct%pt_bc%south_t1
842 neststruct%pt_bc%east_t0 = neststruct%pt_bc%east_t1
843 neststruct%pt_bc%west_t0 = neststruct%pt_bc%west_t1
844 neststruct%pt_bc%north_t0 = neststruct%pt_bc%north_t1
845 neststruct%pt_bc%south_t0 = neststruct%pt_bc%south_t1
847 neststruct%u_bc%east_t0 = neststruct%u_bc%east_t1
848 neststruct%u_bc%west_t0 = neststruct%u_bc%west_t1
849 neststruct%u_bc%north_t0 = neststruct%u_bc%north_t1
850 neststruct%u_bc%south_t0 = neststruct%u_bc%south_t1
851 neststruct%v_bc%east_t0 = neststruct%v_bc%east_t1
852 neststruct%v_bc%west_t0 = neststruct%v_bc%west_t1
853 neststruct%v_bc%north_t0 = neststruct%v_bc%north_t1
854 neststruct%v_bc%south_t0 = neststruct%v_bc%south_t1
855 neststruct%vc_bc%east_t0 = neststruct%vc_bc%east_t1
856 neststruct%vc_bc%west_t0 = neststruct%vc_bc%west_t1
857 neststruct%vc_bc%north_t0 = neststruct%vc_bc%north_t1
858 neststruct%vc_bc%south_t0 = neststruct%vc_bc%south_t1
859 neststruct%uc_bc%east_t0 = neststruct%uc_bc%east_t1
860 neststruct%uc_bc%west_t0 = neststruct%uc_bc%west_t1
861 neststruct%uc_bc%north_t0 = neststruct%uc_bc%north_t1
862 neststruct%uc_bc%south_t0 = neststruct%uc_bc%south_t1
863 neststruct%divg_bc%east_t0 = neststruct%divg_bc%east_t1
864 neststruct%divg_bc%west_t0 = neststruct%divg_bc%west_t1
865 neststruct%divg_bc%north_t0 = neststruct%divg_bc%north_t1
866 neststruct%divg_bc%south_t0 = neststruct%divg_bc%south_t1
870 TYPE(FV_NEST_TYPE),
INTENT(INOUT) :: neststruct
871 neststruct%delz_bc%east_t0 = neststruct%delz_bc%east_t1
872 neststruct%delz_bc%west_t0 = neststruct%delz_bc%west_t1
873 neststruct%delz_bc%north_t0 = neststruct%delz_bc%north_t1
874 neststruct%delz_bc%south_t0 = neststruct%delz_bc%south_t1
875 neststruct%w_bc%east_t0 = neststruct%w_bc%east_t1
876 neststruct%w_bc%west_t0 = neststruct%w_bc%west_t1
877 neststruct%w_bc%north_t0 = neststruct%w_bc%north_t1
878 neststruct%w_bc%south_t0 = neststruct%w_bc%south_t1
901 INTEGER,
INTENT(IN) :: ngrids
903 LOGICAL,
INTENT(IN) :: grids_on_this_pe(ngrids)
904 REAL,
INTENT(IN) :: zvir
905 INTEGER :: n, p, sphum
907 IF (ngrids .GT. 1)
THEN 911 IF (atm(n)%neststruct%twowaynest)
THEN 912 IF (grids_on_this_pe(n) .OR. grids_on_this_pe(atm(n)%&
913 & parent_grid%grid_number))
THEN 916 & zvir, atm(n)%ncnst, sphum, atm(n)%u, atm(n&
917 & )%v, atm(n)%w, atm(n)%omga, atm(n)%pt, atm&
918 & (n)%delp, atm(n)%q, atm(n)%uc, atm(n)%vc, &
919 & atm(n)%pkz, atm(n)%delz, atm(n)%ps, atm(n)&
920 & %ptop, atm(n)%gridstruct, atm(n)%&
921 & flagstruct, atm(n)%neststruct, atm(n)%&
922 & parent_grid, atm(n)%bd, .false.)
928 IF (atm(n)%neststruct%parent_of_twoway .AND. grids_on_this_pe(n)&
930 & npz, atm(n)%ng, atm(n)%ncnst, atm(n)%u&
931 & , atm(n)%v, atm(n)%w, atm(n)%delz, atm&
932 & (n)%pt, atm(n)%delp, atm(n)%q, atm(n)%&
933 & ps, atm(n)%pe, atm(n)%pk, atm(n)%peln&
934 & , atm(n)%pkz, atm(n)%phis, atm(n)%ua, &
935 & atm(n)%va, atm(n)%ptop, atm(n)%&
936 & gridstruct, atm(n)%flagstruct, atm(n)%&
944 & , w, omga, pt, delp, q, uc, vc, pkz, delz, ps, ptop, gridstruct, &
945 & flagstruct, neststruct, parent_grid, bd, conv_theta_in)
947 REAL,
INTENT(IN) :: zvir, ptop
948 INTEGER,
INTENT(IN) :: npx, npy, npz
949 INTEGER,
INTENT(IN) :: ncnst, sphum
950 LOGICAL,
INTENT(IN),
OPTIONAL :: conv_theta_in
951 TYPE(FV_GRID_BOUNDS_TYPE),
INTENT(IN) :: bd
953 REAL,
DIMENSION(bd%isd:bd%ied, bd%jsd:bd%jed+1, npz),
INTENT(INOUT) &
956 REAL,
DIMENSION(bd%isd:bd%ied+1, bd%jsd:bd%jed, npz),
INTENT(INOUT) &
959 REAL,
INTENT(INOUT) :: w(bd%isd:, bd%jsd:, :)
961 REAL,
INTENT(INOUT) :: omga(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
963 REAL,
INTENT(INOUT) :: pt(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
965 REAL,
INTENT(INOUT) :: delp(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
967 REAL,
INTENT(INOUT) :: q(bd%isd:bd%ied, bd%jsd:bd%jed, npz, ncnst)
969 REAL,
INTENT(INOUT) :: uc(bd%isd:bd%ied+1, bd%jsd:bd%jed, npz)
970 REAL,
INTENT(INOUT) :: vc(bd%isd:bd%ied, bd%jsd:bd%jed+1, npz)
972 REAL,
INTENT(INOUT) :: pkz(bd%is:bd%ie, bd%js:bd%je, npz)
974 REAL,
INTENT(INOUT) :: delz(bd%isd:, bd%jsd:, :)
976 REAL,
INTENT(INOUT) :: ps(bd%isd:bd%ied, bd%jsd:bd%jed)
977 TYPE(FV_GRID_TYPE),
INTENT(INOUT) :: gridstruct
978 TYPE(FV_FLAGS_TYPE),
INTENT(INOUT) :: flagstruct
979 TYPE(FV_NEST_TYPE),
INTENT(INOUT) :: neststruct
980 TYPE(FV_ATMOS_TYPE),
INTENT(INOUT) :: parent_grid
981 REAL,
ALLOCATABLE :: t_nest(:, :, :), ps0(:, :)
982 INTEGER :: i, j, k, n
983 INTEGER :: isd_p, ied_p, jsd_p, jed_p, isc_p, iec_p, jsc_p, jec_p
984 INTEGER :: isg, ieg, jsg, jeg, npx_p, npy_p
985 INTEGER :: istart, iend
986 REAL :: qmass_b, qmass_a
989 LOGICAL,
SAVE :: conv_theta=.true.
990 REAL :: qdp(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
991 REAL,
ALLOCATABLE :: qdp_coarse(:, :, :)
992 REAL(kind=f_p),
ALLOCATABLE :: q_diff(:, :, :)
993 REAL :: l_sum_b(npz), l_sum_a(npz)
995 INTEGER :: is, ie, js, je
996 INTEGER :: isd, ied, jsd, jed
997 INTEGER :: isu, ieu, jsu, jeu
1008 isu = neststruct%isu
1009 ieu = neststruct%ieu
1010 jsu = neststruct%jsu
1011 jeu = neststruct%jeu
1012 upoff = neststruct%upoff
1015 IF (
PRESENT(conv_theta_in)) conv_theta = conv_theta_in
1016 IF (.NOT.neststruct%parent_proc .AND. (.NOT.neststruct%child_proc)) &
1025 IF (neststruct%nestupdate .LT. 3)
THEN 1027 & nest_domain, neststruct%ind_update_h, &
1028 & gridstruct%dx, gridstruct%dy, gridstruct%area&
1029 & , isd_p, ied_p, jsd_p, jed_p, isd, ied, jsd, &
1030 & jed, neststruct%isu, neststruct%ieu, &
1031 & neststruct%jsu, neststruct%jeu, npx, npy, npz&
1032 & , 0, 0, neststruct%refinement, neststruct%&
1033 & nestupdate, upoff, 0, neststruct%parent_proc, &
1034 & neststruct%child_proc, parent_grid)
1039 IF (neststruct%nestupdate .NE. 3 .AND. neststruct%nestupdate .NE. &
1040 & 7 .AND. neststruct%nestupdate .NE. 8)
THEN 1041 ALLOCATE(qdp_coarse(isd_p:ied_p, jsd_p:jed_p, npz))
1042 IF (parent_grid%flagstruct%nwat .GT. 0)
THEN 1043 ALLOCATE(q_diff(isd_p:ied_p, jsd_p:jed_p, npz))
1046 DO n=1,parent_grid%flagstruct%nwat
1048 IF (neststruct%child_proc)
THEN 1052 qdp(i, j, k) = q(i, j, k, n)*delp(i, j, k)
1059 IF (neststruct%parent_proc)
THEN 1064 qdp_coarse(i, j, k) = parent_grid%q(i, j, k, n)*&
1065 & parent_grid%delp(i, j, k)
1069 CALL level_sum(qdp_coarse, parent_grid%gridstruct%area, &
1070 & parent_grid%domain, parent_grid%bd, npz, l_sum_b)
1074 IF (neststruct%parent_proc)
THEN 1075 IF (n .LE. parent_grid%flagstruct%nwat)
THEN 1079 q_diff(i, j, k) = q_diff(i, j, k) - qdp_coarse(i, j&
1087 & nest_domain, neststruct%ind_update_h, &
1088 & gridstruct%dx, gridstruct%dy, gridstruct%&
1089 & area, isd_p, ied_p, jsd_p, jed_p, isd, ied, &
1090 & jsd, jed, neststruct%isu, neststruct%ieu, &
1091 & neststruct%jsu, neststruct%jeu, npx, npy, &
1092 & npz, 0, 0, neststruct%refinement, neststruct&
1093 & %nestupdate, upoff, 0, neststruct%&
1094 & parent_proc, neststruct%child_proc, &
1098 IF (neststruct%parent_proc)
THEN 1099 CALL level_sum(qdp_coarse, parent_grid%gridstruct%area, &
1100 & parent_grid%domain, parent_grid%bd, npz, l_sum_a)
1102 IF (l_sum_a(k) .GT. 0.)
THEN 1103 fix = l_sum_b(k)/l_sum_a(k)
1107 parent_grid%q(i, j, k, n) = qdp_coarse(i, j, k)*fix
1114 IF (neststruct%parent_proc)
THEN 1115 IF (n .LE. parent_grid%flagstruct%nwat)
THEN 1119 q_diff(i, j, k) = q_diff(i, j, k) + parent_grid%q(i&
1127 IF (neststruct%parent_proc)
THEN 1128 IF (parent_grid%flagstruct%nwat .GT. 0)
THEN 1132 parent_grid%delp(i, j, k) = parent_grid%delp(i, j, k) &
1138 DO n=1,parent_grid%flagstruct%nwat
1142 parent_grid%q(i, j, k, n) = parent_grid%q(i, j, k, n)/&
1143 & parent_grid%delp(i, j, k)
1149 DEALLOCATE(qdp_coarse)
1150 IF (
ALLOCATED(q_diff))
THEN 1155 IF (neststruct%nestupdate .NE. 3 .AND. neststruct%nestupdate .NE. &
1158 IF (conv_theta)
THEN 1159 IF (neststruct%child_proc)
THEN 1163 ALLOCATE(t_nest(isd:ied, jsd:jed, 1:npz))
1168 t_nest(i, j, k) = pt(i, j, k)*pkz(i, j, k)/(1.+zvir*q(&
1176 & nest_domain, neststruct%ind_update_h, &
1177 & gridstruct%dx, gridstruct%dy, gridstruct%&
1178 & area, isd_p, ied_p, jsd_p, jed_p, isd, ied, &
1179 & jsd, jed, neststruct%isu, neststruct%ieu, &
1180 & neststruct%jsu, neststruct%jeu, npx, npy, &
1181 & npz, 0, 0, neststruct%refinement, neststruct&
1182 & %nestupdate, upoff, 0, neststruct%&
1183 & parent_proc, neststruct%child_proc, &
1187 & nest_domain, neststruct%ind_update_h, &
1188 & gridstruct%dx, gridstruct%dy, gridstruct%&
1189 & area, isd_p, ied_p, jsd_p, jed_p, isd, ied, &
1190 & jsd, jed, neststruct%isu, neststruct%ieu, &
1191 & neststruct%jsu, neststruct%jeu, npx, npy, &
1192 & npz, 0, 0, neststruct%refinement, neststruct&
1193 & %nestupdate, upoff, 0, neststruct%&
1194 & parent_proc, neststruct%child_proc, &
1199 IF (.NOT.flagstruct%hydrostatic)
THEN 1201 & nest_domain, neststruct%ind_update_h, &
1202 & gridstruct%dx, gridstruct%dy, gridstruct%&
1203 & area, isd_p, ied_p, jsd_p, jed_p, isd, ied, &
1204 & jsd, jed, neststruct%isu, neststruct%ieu, &
1205 & neststruct%jsu, neststruct%jeu, npx, npy, &
1206 & npz, 0, 0, neststruct%refinement, neststruct&
1207 & %nestupdate, upoff, 0, neststruct%&
1208 & parent_proc, neststruct%child_proc, &
1220 & neststruct%ind_update_h, gridstruct%dx, &
1221 & gridstruct%dy, gridstruct%area, isd_p, ied_p, &
1222 & jsd_p, jed_p, isd, ied, jsd, jed, neststruct%isu&
1223 & , neststruct%ieu, neststruct%jsu, neststruct%jeu&
1224 & , npx, npy, npz, 0, 1, neststruct%refinement, &
1225 & neststruct%nestupdate, upoff, 0, neststruct%&
1226 & parent_proc, neststruct%child_proc, parent_grid)
1228 & neststruct%ind_update_h, gridstruct%dx, &
1229 & gridstruct%dy, gridstruct%area, isd_p, ied_p, &
1230 & jsd_p, jed_p, isd, ied, jsd, jed, neststruct%isu&
1231 & , neststruct%ieu, neststruct%jsu, neststruct%jeu&
1232 & , npx, npy, npz, 1, 0, neststruct%refinement, &
1233 & neststruct%nestupdate, upoff, 0, neststruct%&
1234 & parent_proc, neststruct%child_proc, parent_grid)
1237 IF (neststruct%nestupdate .GE. 5 .AND. npz .GT. 4)
THEN 1241 ALLOCATE(ps0(isd_p:ied_p, jsd_p:jed_p))
1242 IF (neststruct%parent_proc)
THEN 1243 parent_grid%ps = parent_grid%ptop
1249 parent_grid%ps(i, j) = parent_grid%ps(i, j) + &
1250 & parent_grid%delp(i, j, k)
1254 ps0 = parent_grid%ps
1256 IF (neststruct%child_proc)
THEN 1262 ps(i, j) = ps(i, j) + delp(i, j, k)
1268 & neststruct%ind_update_h, gridstruct%dx, &
1269 & gridstruct%dy, gridstruct%area, isd_p, ied_p, &
1270 & jsd_p, jed_p, isd, ied, jsd, jed, neststruct%&
1271 & isu, neststruct%ieu, neststruct%jsu, &
1272 & neststruct%jeu, npx, npy, 0, 0, neststruct%&
1273 & refinement, neststruct%nestupdate, upoff, 0, &
1274 & neststruct%parent_proc, neststruct%child_proc&
1279 IF (neststruct%parent_proc)
THEN 1287 IF (parent_grid%tile .EQ. neststruct%parent_tile)
THEN 1289 IF (neststruct%parent_proc)
THEN 1294 IF (parent_grid%flagstruct%remap_option .NE. 0)
THEN 1299 parent_grid%pt(i, j, k) = parent_grid%pt(i, j, k)/&
1300 & parent_grid%pkz(i, j, k)*(1.+zvir*parent_grid%q(i&
1307 & parent_grid%ps, parent_grid%delp, &
1308 & parent_grid%pt, parent_grid%q, parent_grid%w&
1309 & , parent_grid%flagstruct%hydrostatic, npz, &
1310 & ps0, zvir, parent_grid%ptop, ncnst, &
1311 & parent_grid%flagstruct%kord_tm, parent_grid%&
1312 & flagstruct%kord_tr, parent_grid%flagstruct%&
1313 & kord_wz, isc_p, iec_p, jsc_p, jec_p, isd_p, &
1314 & ied_p, jsd_p, jed_p, .false.)
1316 IF (parent_grid%flagstruct%remap_option .NE. 0)
THEN 1321 parent_grid%pt(i, j, k) = parent_grid%pt(i, j, k)*&
1322 & parent_grid%pkz(i, j, k)/(1.+zvir*parent_grid%q(i&
1329 & parent_grid%ps, parent_grid%u, parent_grid%v&
1330 & , npz, ps0, parent_grid%flagstruct%kord_mt, &
1331 & isc_p, iec_p, jsc_p, jec_p, isd_p, ied_p, &
1332 & jsd_p, jed_p, parent_grid%ptop)
1335 IF (
ALLOCATED(ps0))
THEN 1341 SUBROUTINE level_sum(q, area, domain, bd, npz, l_sum)
1345 INTEGER,
INTENT(IN) :: npz
1346 TYPE(FV_GRID_BOUNDS_TYPE),
INTENT(IN) :: bd
1347 REAL,
INTENT(IN) :: area(bd%isd:bd%ied, bd%jsd:bd%jed)
1348 REAL,
INTENT(IN) :: q(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
1349 REAL,
INTENT(OUT) :: l_sum(npz)
1350 TYPE(DOMAIN2D),
INTENT(IN) :: domain
1351 INTEGER :: i, j, k, n
1359 qa = qa + q(i, j, k)*area(i, j)
1362 CALL mp_reduce_sum(qa)
1367 & , delz, pt, delp, q, ps, pe, pk, peln, pkz, phis, ua, va, ptop, &
1368 & gridstruct, flagstruct, domain, bd)
1370 TYPE(FV_GRID_BOUNDS_TYPE),
INTENT(IN) :: bd
1371 REAL,
INTENT(IN) :: ptop
1372 INTEGER,
INTENT(IN) :: ng, npx, npy, npz
1373 INTEGER,
INTENT(IN) :: ncnst
1375 REAL,
DIMENSION(bd%isd:bd%ied, bd%jsd:bd%jed+1, npz),
INTENT(INOUT) &
1378 REAL,
DIMENSION(bd%isd:bd%ied+1, bd%jsd:bd%jed, npz),
INTENT(INOUT) &
1381 REAL,
INTENT(INOUT) :: w(bd%isd:, bd%jsd:, :)
1383 REAL,
INTENT(INOUT) :: pt(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
1385 REAL,
INTENT(INOUT) :: delp(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
1387 REAL,
INTENT(INOUT) :: q(bd%isd:bd%ied, bd%jsd:bd%jed, npz, ncnst)
1389 REAL,
INTENT(INOUT) :: delz(bd%isd:, bd%jsd:, :)
1396 REAL,
INTENT(INOUT) :: ps(bd%isd:bd%ied, bd%jsd:bd%jed)
1398 REAL,
INTENT(INOUT) :: pe(bd%is-1:bd%ie+1, npz+1, bd%js-1:bd%je+1)
1400 REAL,
INTENT(INOUT) :: pk(bd%is:bd%ie, bd%js:bd%je, npz+1)
1402 REAL,
INTENT(INOUT) :: peln(bd%is:bd%ie, npz+1, bd%js:bd%je)
1404 REAL,
INTENT(INOUT) :: pkz(bd%is:bd%ie, bd%js:bd%je, npz)
1409 REAL,
INTENT(INOUT) :: phis(bd%isd:bd%ied, bd%jsd:bd%jed)
1410 REAL,
DIMENSION(bd%isd:bd%ied, bd%jsd:bd%jed, npz),
INTENT(INOUT) ::&
1412 TYPE(FV_GRID_TYPE),
INTENT(IN) :: gridstruct
1413 TYPE(FV_FLAGS_TYPE),
INTENT(IN) :: flagstruct
1414 TYPE(DOMAIN2D),
INTENT(INOUT) :: domain
1415 LOGICAL :: bad_range
1416 INTEGER :: is, ie, js, je
1417 INTEGER :: isd, ied, jsd, jed
1427 & gridstruct%grid_type, domain, gridstruct%nested, &
1428 & flagstruct%c2l_ord, bd)
1434 CALL p_var(npz, is, ie, js, je, ptop,
ptop_min, delp, delz, pt, ps, &
1435 & pe, peln, pk, pkz,
kappa, q, ng, flagstruct%ncnst, gridstruct%&
1436 & area_64, 0., .false., .false., flagstruct%moist_phys, &
1437 & flagstruct%hydrostatic, flagstruct%nwat, domain, .false.)
1438 IF (flagstruct%range_warn)
THEN 1439 CALL range_check(
'TA update', pt, is, ie, js, je, ng, npz, &
1440 & gridstruct%agrid, 130., 350., bad_range)
1441 CALL range_check(
'UA update', ua, is, ie, js, je, ng, npz, &
1442 & gridstruct%agrid, -220., 250., bad_range)
1443 CALL range_check(
'VA update', va, is, ie, js, je, ng, npz, &
1444 & gridstruct%agrid, -220., 220., bad_range)
1445 IF (.NOT.flagstruct%hydrostatic)
CALL range_check(
'W update', w, &
1446 & is, ie, js, je, ng, &
1447 & npz, gridstruct%agrid&
1455 & hydrostatic, kmd, ps0, zvir, ptop, nq, kord_tm, kord_tr, kord_wz, is&
1456 & , ie, js, je, isd, ied, jsd, jed, do_q)
1458 INTEGER,
INTENT(IN) :: npz, kmd, nq, kord_tm, kord_tr, kord_wz
1459 REAL,
INTENT(IN) :: zvir, ptop
1460 REAL,
INTENT(IN) :: ak(npz+1), bk(npz+1)
1461 INTEGER,
INTENT(IN) :: is, ie, js, je, isd, ied, jsd, jed
1462 REAL,
DIMENSION(isd:ied, jsd:jed),
INTENT(IN) :: ps0
1463 REAL,
DIMENSION(isd:ied, jsd:jed),
INTENT(IN) :: ps
1464 REAL,
DIMENSION(isd:ied, jsd:jed, npz),
INTENT(IN) :: delp
1465 REAL,
DIMENSION(isd:ied, jsd:jed, npz),
INTENT(INOUT) :: t, w
1466 REAL,
DIMENSION(isd:ied, jsd:jed, npz, nq),
INTENT(INOUT) :: q
1467 LOGICAL,
INTENT(IN) :: hydrostatic, do_q
1469 REAL,
DIMENSION(is:ie, kmd) :: tp, qp
1470 REAL,
DIMENSION(is:ie, kmd+1) :: pe0, pn0
1471 REAL,
DIMENSION(is:ie, npz) :: qn1
1472 REAL,
DIMENSION(is:ie, npz+1) :: pe1, pn1
1473 INTEGER :: i, j, k, iq
1483 pe0(i, k) = ak(k) + bk(k)*ps0(i, j)
1484 pn0(i, k) = log(pe0(i, k))
1489 pe1(i, k) = ak(k) + bk(k)*ps(i, j)
1490 pn1(i, k) = log(pe1(i, k))
1497 qp(i, k) = q(i, j, k, iq)
1500 CALL mappm(kmd, pe0, qp, npz, pe1, qn1, is, ie, 0, kord_tr, &
1504 q(i, j, k, iq) = qn1(i, k)
1511 tp(i, k) = t(i, j, k)
1514 IF (kord_tm .GE. 0.)
THEN 1520 CALL mappm(kmd, pn0, tp, npz, pn1, qn1, is, ie, 1, abs0, ptop)
1523 t(i, j, k) = qn1(i, k)
1526 IF (.NOT.hydrostatic)
THEN 1529 tp(i, k) = w(i, j, k)
1534 CALL mappm(kmd, pe0, tp, npz, pe1, qn1, is, ie, -1, kord_wz, &
1538 w(i, j, k) = qn1(i, k)
1545 SUBROUTINE update_remap_uv(npz, ak, bk, ps, u, v, kmd, ps0, kord_mt, &
1546 & is, ie, js, je, isd, ied, jsd, jed, ptop)
1548 INTEGER,
INTENT(IN) :: npz
1549 REAL,
INTENT(IN) :: ak(npz+1), bk(npz+1)
1550 INTEGER,
INTENT(IN) :: is, ie, js, je, isd, ied, jsd, jed
1551 REAL,
INTENT(IN) :: ps(isd:ied, jsd:jed)
1552 REAL,
DIMENSION(isd:ied, jsd:jed+1, npz),
INTENT(INOUT) :: u
1553 REAL,
DIMENSION(isd:ied+1, jsd:jed, npz),
INTENT(INOUT) :: v
1555 INTEGER,
INTENT(IN) :: kmd, kord_mt
1556 REAL,
INTENT(IN) :: ptop
1557 REAL,
INTENT(IN) :: ps0(isd:ied, jsd:jed)
1560 REAL,
DIMENSION(is:ie+1, kmd+1) :: pe0
1561 REAL,
DIMENSION(is:ie+1, npz+1) :: pe1
1562 REAL,
DIMENSION(is:ie+1, kmd) :: qt
1563 REAL,
DIMENSION(is:ie+1, npz) :: qn1
1577 pe0(i, k) = ak(k) + bk(k)*0.5*(ps0(i, j)+ps0(i, j-1))
1585 pe1(i, k) = ak(k) + bk(k)*0.5*(ps(i, j)+ps(i, j-1))
1594 qt(i, k) = u(i, j, k)
1598 CALL mappm(kmd, pe0(is:ie, :), qt(is:ie, :), npz, pe1(is:ie, :), &
1599 & qn1(is:ie, :), is, ie, -1, kord_mt, ptop)
1602 u(i, j, k) = qn1(i, k)
1617 pe0(i, k) = ak(k) + bk(k)*0.5*(ps0(i, j)+ps0(i-1, j))
1625 pe1(i, k) = ak(k) + bk(k)*0.5*(ps(i, j)+ps(i-1, j))
1634 qt(i, k) = v(i, j, k)
1639 CALL mappm(kmd, pe0(is:ie+1, :), qt(is:ie+1, :), npz, pe1(is:ie+1&
1640 & , :), qn1(is:ie+1, :), is, arg1, -1, 8, ptop)
1643 v(i, j, k) = qn1(i, k)
type(fv_nest_bc_type_3d), dimension(:), allocatable q_buf
real, parameter, public radius
Radius of the Earth [m].
integer, parameter, public model_atmos
type(fv_nest_bc_type_3d) divg_buf
subroutine twoway_nest_update(npx, npy, npz, zvir, ncnst, sphum, u, v, w, omga, pt, delp, q, uc, vc, pkz, delz, ps, ptop, gridstruct, flagstruct, neststruct, parent_grid, bd, conv_theta_in)
subroutine, public p_var(km, ifirst, ilast, jfirst, jlast, ptop, ptop_min, delp, delz, pt, ps, pe, peln, pk, pkz, cappa, q, ng, nq, area, dry_mass, adjust_dry_mass, mountain, moist_phys, hydrostatic, nwat, domain, make_nh)
subroutine set_bcs_t0(ncnst, hydrostatic, neststruct)
real, dimension(:), allocatable rf
subroutine, public d2c_setup(u, v, ua, va, uc, vc, dord4, isd, ied, jsd, jed, is, ie, js, je, npx, npy, grid_type, nested, se_corner, sw_corner, ne_corner, nw_corner, rsin_u, rsin_v, cosa_s, rsin2)
real, parameter, public ptop_min
real(kind=8), parameter, public pi_8
Ratio of circle circumference to diameter [N/A].
real, parameter, public hlv
Latent heat of evaporation [J/kg].
subroutine, public pushcontrol(ctype, field)
type(fv_nest_bc_type_3d) uc_buf
type(fv_nest_bc_type_3d) delz_buf
real, parameter, public rdgas
Gas constant for dry air [J/kg/deg].
real, public sphum_ll_fix
subroutine update_remap_uv(npz, ak, bk, ps, u, v, kmd, ps0, kord_mt, is, ie, js, je, isd, ied, jsd, jed, ptop)
real, parameter, public cp_vapor
Specific heat capacity of water vapor at constant pressure [J/kg/deg].
subroutine pushcontrol1b(cc)
subroutine, public cubed_to_latlon(u, v, ua, va, gridstruct, npx, npy, km, mode, grid_type, domain, nested, c2l_ord, bd)
type(fv_nest_bc_type_3d) u_buf
real, dimension(:,:,:), allocatable, target dum_west
subroutine after_twoway_nest_update(npx, npy, npz, ng, ncnst, u, v, w, delz, pt, delp, q, ps, pe, pk, peln, pkz, phis, ua, va, ptop, gridstruct, flagstruct, domain, bd)
type(fv_nest_bc_type_3d) pt_buf
subroutine, public nested_grid_bc_recv(nest_domain, istag, jstag, npz, bd, nest_BC_buffers)
integer, parameter, public f_p
type(fv_nest_bc_type_3d) pkz_buf
subroutine, public setup_nested_grid_bcs_adm(npx, npy, npz, zvir, ncnst, u, u_ad, v, v_ad, w, pt, delp, delz, q, uc, uc_ad, vc, vc_ad, pkz, nested, inline_q, make_nh, ng, gridstruct, flagstruct, neststruct, nest_timestep, tracer_nest_timestep, domain, bd, nwat)
real, parameter, public rvgas
Gas constant for water vapor [J/kg/deg].
subroutine timing_on(blk_name)
real, dimension(:,:,:), allocatable, target dum_north
real, parameter, public cp_air
Specific heat capacity of dry air at constant pressure [J/kg/deg].
real, dimension(:), allocatable rw
real, dimension(:,:,:), allocatable dp1_coarse
subroutine, public divergence_corner(u, v, ua, va, divg_d, gridstruct, flagstruct, bd)
subroutine, public setup_nested_grid_bcs(npx, npy, npz, zvir, ncnst, u, v, w, pt, delp, delz, q, uc, vc, pkz, nested, inline_q, make_nh, ng, gridstruct, flagstruct, neststruct, nest_timestep, tracer_nest_timestep, domain, bd, nwat)
subroutine setup_pt_nh_bc(pt_bc, delp_bc, delz_bc, sphum_bc, q_bc, nq, npx, npy, npz, zvir, bd)
subroutine level_sum(q, area, domain, bd, npz, l_sum)
real, dimension(:,:,:), allocatable, target dum_south
subroutine update_remap_tqw(npz, ak, bk, ps, delp, t, q, w, hydrostatic, kmd, ps0, zvir, ptop, nq, kord_tm, kord_tr, kord_wz, is, ie, js, je, isd, ied, jsd, jed, do_q)
subroutine, public d2c_setup_fwd(u, v, ua, va, uc, vc, dord4, isd, ied, jsd, jed, is, ie, js, je, npx, npy, grid_type, nested, se_corner, sw_corner, ne_corner, nw_corner, rsin_u, rsin_v, cosa_s, rsin2)
real, dimension(:,:), allocatable te_2d_coarse
subroutine, public d2c_setup_bwd(u, u_ad, v, v_ad, ua, va, uc, uc_ad, vc, vc_ad, dord4, isd, ied, jsd, jed, is, ie, js, je, npx, npy, grid_type, nested, se_corner, sw_corner, ne_corner, nw_corner, rsin_u, rsin_v, cosa_s, rsin2)
subroutine set_nh_bcs_t0(neststruct)
subroutine setup_pt_bc(pt_bc, pkz_bc, sphum_bc, npx, npy, npz, zvir, bd)
subroutine, public nested_grid_bc_send(var_coarse, nest_domain, istag, jstag)
real, parameter, public grav
Acceleration due to gravity [m/s^2].
real function, public g_sum(domain, p, ifirst, ilast, jfirst, jlast, ngc, area, mode, reproduce)
subroutine, public mappm(km, pe1, q1, kn, pe2, q2, i1, i2, iv, kord, ptop)
subroutine, public neg_adj3(is, ie, js, je, ng, kbot, hydrostatic, peln, delz, pt, dp, qv, ql, qr, qi, qs, qg, qa, check_negative)
subroutine popcontrol1b(cc)
subroutine, public divergence_corner_nest(u, v, ua, va, divg_d, gridstruct, flagstruct, bd)
type(fv_nest_bc_type_3d) delp_buf
subroutine, public nested_grid_bc_save_proc(nest_domain, ind, wt, istag, jstag, npx, npy, npz, bd, nest_BC, nest_BC_buffers, pd_in)
type(fv_nest_bc_type_3d) vc_buf
subroutine, public twoway_nesting(atm, ngrids, grids_on_this_pe, zvir)
real, dimension(:,:,:), allocatable, target dum_east
type(fv_nest_bc_type_3d) w_buf
real, parameter, public kappa
RDGAS / CP_AIR [dimensionless].
subroutine, public popcontrol(ctype, field)
subroutine, public range_check(qname, q, is, ie, js, je, n_g, km, pos, q_low, q_hi, bad_range)
Derived type containing the data.
subroutine, public d2a_setup(u, v, ua, va, dord4, isd, ied, jsd, jed, is, ie, js, je, npx, npy, grid_type, nested, cosa_s, rsin2)
type(fv_nest_bc_type_3d) v_buf
real(fp), parameter, public pi
subroutine timing_off(blk_name)