34 use fv_mp_nlm_mod,
only: is, ie, js, je, isd, ied, jsd, jed, isc, iec, jsc, jec
50 real,
allocatable ::
rf(:),
rw(:)
73 u, v, w, pt, delp, delz,q, uc, vc, pkz, &
74 nested, inline_q, make_nh, ng, &
75 gridstruct, flagstruct, neststruct, &
76 nest_timestep, tracer_nest_timestep, &
81 real,
intent(IN) :: zvir
83 integer,
intent(IN) :: npx, npy, npz
84 integer,
intent(IN) :: ncnst, ng, nwat
85 logical,
intent(IN) :: inline_q, make_nh,nested
87 real,
intent(inout),
dimension(bd%isd:bd%ied ,bd%jsd:bd%jed+1,npz) :: u
88 real,
intent(inout),
dimension(bd%isd:bd%ied+1,bd%jsd:bd%jed ,npz) :: v
89 real,
intent(inout) :: w( bd%isd: ,bd%jsd: ,1:)
90 real,
intent(inout) :: pt( bd%isd:bd%ied ,bd%jsd:bd%jed ,npz)
91 real,
intent(inout) :: delp(bd%isd:bd%ied ,bd%jsd:bd%jed ,npz)
92 real,
intent(inout) :: delz(bd%isd: ,bd%jsd: ,1:)
93 real,
intent(inout) :: q( bd%isd:bd%ied ,bd%jsd:bd%jed ,npz, ncnst)
94 real,
intent(inout) :: uc(bd%isd:bd%ied+1,bd%jsd:bd%jed ,npz)
95 real,
intent(inout) :: vc(bd%isd:bd%ied ,bd%jsd:bd%jed+1,npz)
96 real,
intent(inout) :: pkz (bd%is:bd%ie,bd%js:bd%je,npz)
97 integer,
intent(INOUT) :: nest_timestep, tracer_nest_timestep
102 type(
domain2d),
intent(INOUT) :: domain
103 real :: divg(bd%isd:bd%ied+1,bd%jsd:bd%jed+1, npz)
104 real :: ua(bd%isd:bd%ied,bd%jsd:bd%jed)
105 real :: va(bd%isd:bd%ied,bd%jsd:bd%jed)
107 real :: pkz_coarse( bd%isd:bd%ied ,bd%jsd:bd%jed ,npz)
108 integer :: i,j,k,n,p, sphum
114 logical,
pointer :: child_grids(:)
116 integer :: is, ie, js, je
117 integer :: isd, ied, jsd, jed
128 child_grids => neststruct%child_grids
135 if (.not. inline_q) tracer_nest_timestep = 0
138 if (neststruct%nested .and. (.not. (neststruct%first_step) .or. make_nh) )
then 140 call set_bcs_t0(ncnst, flagstruct%hydrostatic, neststruct)
148 if (any(neststruct%child_grids))
then 153 domain, gridtype=dgrid_ne, complete=.true.)
159 call d2c_setup(u(isd,jsd,k), v(isd,jsd,k), &
161 uc(isd,jsd,k), vc(isd,jsd,k), flagstruct%nord>0, &
162 isd,ied,jsd,jed, is,ie,js,je, npx,npy, &
163 gridstruct%grid_type, gridstruct%nested, &
164 gridstruct%se_corner, gridstruct%sw_corner, &
165 gridstruct%ne_corner, gridstruct%nw_corner, &
166 gridstruct%rsin_u, gridstruct%rsin_v, &
167 gridstruct%cosa_s, gridstruct%rsin2 )
169 call divergence_corner_nest(u(isd,jsd,k), v(isd,jsd,k), ua, va, divg(isd,jsd,k), gridstruct, flagstruct, bd)
171 call divergence_corner(u(isd,jsd,k), v(isd,jsd,k), ua, va, divg(isd,jsd,k), gridstruct, flagstruct, bd)
177 if (flagstruct%hydrostatic)
then 182 pkz_coarse(i,j,k) = pkz(i,j,k)
189 if (neststruct%nested)
then 190 if (.not.
allocated(
q_buf))
then 191 allocate(
q_buf(ncnst))
204 if (flagstruct%hydrostatic)
then 205 call allocate_fv_nest_bc_type(pkz_bc,is,ie,js,je,isd,ied,jsd,jed,npx,npy,npz,ng,0,0,0,.false.)
230 do p=1,
size(child_grids)
231 if (child_grids(p))
then 239 if (flagstruct%hydrostatic)
then 258 neststruct%ind_h, neststruct%wt_h, 0, 0, npx, npy, npz, bd, &
259 neststruct%delp_BC,
delp_buf, pd_in=do_pd)
262 neststruct%ind_h, neststruct%wt_h, 0, 0, npx, npy, npz, bd, &
263 neststruct%q_BC(n),
q_buf(n), pd_in=do_pd)
267 neststruct%ind_h, neststruct%wt_h, 0, 0, npx, npy, npz, bd, &
271 if (flagstruct%hydrostatic)
then 273 neststruct%ind_h, neststruct%wt_h, 0, 0, npx, npy, npz, bd, &
275 call setup_pt_bc(neststruct%pt_BC, pkz_bc, neststruct%q_BC(sphum), npx, npy, npz, zvir, bd)
278 neststruct%ind_h, neststruct%wt_h, 0, 0, npx, npy, npz, bd, &
279 neststruct%w_BC,
w_buf)
281 neststruct%ind_h, neststruct%wt_h, 0, 0, npx, npy, npz, bd, &
284 call setup_pt_nh_bc(neststruct%pt_BC, neststruct%delp_BC, neststruct%delz_BC, &
285 neststruct%q_BC(sphum), neststruct%q_BC, ncnst, &
287 neststruct%q_con_BC, &
289 neststruct%cappa_BC, &
292 npx, npy, npz, zvir, bd)
296 neststruct%ind_u, neststruct%wt_u, 0, 1, npx, npy, npz, bd, &
297 neststruct%u_BC,
u_buf)
299 neststruct%ind_u, neststruct%wt_u, 0, 1, npx, npy, npz, bd, &
302 neststruct%ind_v, neststruct%wt_v, 1, 0, npx, npy, npz, bd, &
303 neststruct%v_BC,
v_buf)
305 neststruct%ind_v, neststruct%wt_v, 1, 0, npx, npy, npz, bd, &
309 neststruct%ind_b, neststruct%wt_b, 1, 1, npx, npy, npz, bd, &
313 if (neststruct%first_step)
then 314 if (neststruct%nested)
call set_bcs_t0(ncnst, flagstruct%hydrostatic, neststruct)
315 neststruct%first_step = .false.
316 if (.not. flagstruct%hydrostatic) flagstruct%make_nh= .false.
317 else if (flagstruct%make_nh)
then 319 flagstruct%make_nh= .false.
336 subroutine setup_pt_bc(pt_BC, pkz_BC, sphum_BC, npx, npy, npz, zvir, bd)
338 type(fv_grid_bounds_type),
intent(IN) :: bd
339 type(fv_nest_BC_type_3d),
intent(IN),
target :: pkz_BC, sphum_BC
340 type(fv_nest_BC_type_3d),
intent(INOUT),
target :: pt_BC
341 integer,
intent(IN) :: npx, npy, npz
342 real,
intent(IN) :: zvir
344 real,
dimension(:,:,:),
pointer :: ptBC, pkzBC, sphumBC
346 integer :: i,j,k, istart, iend
348 integer :: is, ie, js, je
349 integer :: isd, ied, jsd, jed
361 ptbc => pt_bc%west_t1
362 pkzbc => pkz_bc%west_t1
363 sphumbc => sphum_bc%west_t1
368 ptbc(i,j,k) = ptbc(i,j,k)/pkzbc(i,j,k)*(1.+zvir*sphumbc(i,j,k))
375 ptbc => pt_bc%south_t1
376 pkzbc => pkz_bc%south_t1
377 sphumbc => sphum_bc%south_t1
383 if (ie == npx-1)
then 393 ptbc(i,j,k) = ptbc(i,j,k)/pkzbc(i,j,k) * &
394 (1.+zvir*sphumbc(i,j,k))
401 if (ie == npx-1)
then 402 ptbc => pt_bc%east_t1
403 pkzbc => pkz_bc%east_t1
404 sphumbc => sphum_bc%east_t1
409 ptbc(i,j,k) = ptbc(i,j,k)/pkzbc(i,j,k) * &
410 (1.+zvir*sphumbc(i,j,k))
416 if (je == npy-1)
then 417 ptbc => pt_bc%north_t1
418 pkzbc => pkz_bc%north_t1
419 sphumbc => sphum_bc%north_t1
425 if (ie == npx-1)
then 435 ptbc(i,j,k) = ptbc(i,j,k)/pkzbc(i,j,k) * &
436 (1.+zvir*sphumbc(i,j,k))
444 subroutine setup_pt_nh_bc(pt_BC, delp_BC, delz_BC, sphum_BC, q_BC, nq, &
451 npx, npy, npz, zvir, bd)
453 type(fv_grid_bounds_type),
intent(IN) :: bd
454 type(fv_nest_BC_type_3d),
intent(IN),
target :: delp_BC, delz_BC, sphum_BC
455 type(fv_nest_BC_type_3d),
intent(INOUT),
target :: pt_BC
456 integer,
intent(IN) :: nq
457 type(fv_nest_BC_type_3d),
intent(IN),
target :: q_BC(nq)
459 type(fv_nest_BC_type_3d),
intent(INOUT),
target :: q_con_BC
461 type(fv_nest_BC_type_3d),
intent(INOUT),
target :: cappa_BC
464 integer,
intent(IN) :: npx, npy, npz
465 real,
intent(IN) :: zvir
467 real,
parameter:: c_liq = 4185.5
468 real,
parameter:: c_ice = 1972.
471 real,
dimension(:,:,:),
pointer :: ptBC, sphumBC, qconBC, delpBC, delzBC, cappaBC
472 real,
dimension(:,:,:),
pointer :: liq_watBC_west, ice_watBC_west, rainwatBC_west, snowwatBC_west, graupelBC_west
473 real,
dimension(:,:,:),
pointer :: liq_watBC_east, ice_watBC_east, rainwatBC_east, snowwatBC_east, graupelBC_east
474 real,
dimension(:,:,:),
pointer :: liq_watBC_north, ice_watBC_north, rainwatBC_north, snowwatBC_north, graupelBC_north
475 real,
dimension(:,:,:),
pointer :: liq_watBC_south, ice_watBC_south, rainwatBC_south, snowwatBC_south, graupelBC_south
477 real :: dp1, q_liq, q_sol, q_con = 0., cvm, pkz, rdg, cv_air
479 integer :: i,j,k, istart, iend
480 integer :: liq_wat, ice_wat, rainwat, snowwat, graupel
481 real,
parameter:: tice = 273.16
482 real,
parameter:: t_i0 = 15.
484 integer :: is, ie, js, je
485 integer :: isd, ied, jsd, jed
507 allocate(
dum_west(isd:0,jsd:jed,npz))
531 if (ie == npx-1)
then 533 allocate(
dum_east(npx:ied,jsd:jed,npz))
544 if (je == npy-1)
then 558 if (liq_wat > 0)
then 559 liq_watbc_west => q_bc(liq_wat)%west_t1
560 liq_watbc_east => q_bc(liq_wat)%east_t1
561 liq_watbc_north => q_bc(liq_wat)%north_t1
562 liq_watbc_south => q_bc(liq_wat)%south_t1
569 if (ice_wat > 0)
then 570 ice_watbc_west => q_bc(ice_wat)%west_t1
571 ice_watbc_east => q_bc(ice_wat)%east_t1
572 ice_watbc_north => q_bc(ice_wat)%north_t1
573 ice_watbc_south => q_bc(ice_wat)%south_t1
580 if (rainwat > 0)
then 581 rainwatbc_west => q_bc(rainwat)%west_t1
582 rainwatbc_east => q_bc(rainwat)%east_t1
583 rainwatbc_north => q_bc(rainwat)%north_t1
584 rainwatbc_south => q_bc(rainwat)%south_t1
591 if (snowwat > 0)
then 592 snowwatbc_west => q_bc(snowwat)%west_t1
593 snowwatbc_east => q_bc(snowwat)%east_t1
594 snowwatbc_north => q_bc(snowwat)%north_t1
595 snowwatbc_south => q_bc(snowwat)%south_t1
602 if (graupel > 0)
then 603 graupelbc_west => q_bc(graupel)%west_t1
604 graupelbc_east => q_bc(graupel)%east_t1
605 graupelbc_north => q_bc(graupel)%north_t1
606 graupelbc_south => q_bc(graupel)%south_t1
615 ptbc => pt_bc%west_t1
616 sphumbc => sphum_bc%west_t1
618 qconbc => q_con_bc%west_t1
620 cappabc => cappa_bc%west_t1
623 delpbc => delp_bc%west_t1
624 delzbc => delz_bc%west_t1
632 dp1 = zvir*sphumbc(i,j,k)
635 q_con = liq_watbc_west(i,j,k)
636 q_sol = q_con*
max(
min((tice-ptbc(i,j,k))/t_i0,1.),0.)
637 q_liq = q_con - q_sol
639 q_liq = liq_watbc_west(i,j,k) + rainwatbc_west(i,j,k)
640 q_sol = ice_watbc_west(i,j,k) + snowwatbc_west(i,j,k) + graupelbc_west(i,j,k)
641 q_con = q_liq + q_sol
643 qconbc(i,j,k) = q_con
645 cvm = (1.-(sphumbc(i,j,k)+q_con))*cv_air+sphumbc(i,j,k)*cv_vap+q_liq*c_liq+q_sol*c_ice
647 pkz = exp( cappabc(i,j,k)*log(rdg*delpbc(i,j,k)*ptbc(i,j,k) * &
648 (1.+dp1)*(1.-q_con)/delzbc(i,j,k)))
650 pkz = exp(
kappa*log(rdg*delpbc(i,j,k)*ptbc(i,j,k) * &
651 (1.+dp1)*(1.-q_con)/delzbc(i,j,k)))
653 ptbc(i,j,k) = ptbc(i,j,k)*(1.+dp1)*(1.-q_con)/pkz
655 pkz = exp(
kappa*log(rdg*delpbc(i,j,k)*ptbc(i,j,k) * &
656 (1.+dp1)/delzbc(i,j,k)))
657 ptbc(i,j,k) = ptbc(i,j,k)*(1.+dp1)/pkz
666 ptbc => pt_bc%south_t1
667 sphumbc => sphum_bc%south_t1
669 qconbc => q_con_bc%south_t1
671 cappabc => cappa_bc%south_t1
674 delpbc => delp_bc%south_t1
675 delzbc => delz_bc%south_t1
681 if (ie == npx-1)
then 695 dp1 = zvir*sphumbc(i,j,k)
698 q_con = liq_watbc_south(i,j,k)
699 q_sol = q_con*
max(
min((tice-ptbc(i,j,k))/t_i0,1.),0.)
700 q_liq = q_con - q_sol
702 q_liq = liq_watbc_south(i,j,k) + rainwatbc_south(i,j,k)
703 q_sol = ice_watbc_south(i,j,k) + snowwatbc_south(i,j,k) + graupelbc_south(i,j,k)
704 q_con = q_liq + q_sol
706 qconbc(i,j,k) = q_con
708 cvm = (1.-(sphumbc(i,j,k)+q_con))*cv_air+sphumbc(i,j,k)*cv_vap+q_liq*c_liq+q_sol*c_ice
710 pkz = exp( cappabc(i,j,k)*log(rdg*delpbc(i,j,k)*ptbc(i,j,k) * &
711 (1.+dp1)*(1.-q_con)/delzbc(i,j,k)))
713 pkz = exp(
kappa*log(rdg*delpbc(i,j,k)*ptbc(i,j,k) * &
714 (1.+dp1)*(1.-q_con)/delzbc(i,j,k)))
716 ptbc(i,j,k) = ptbc(i,j,k)*(1.+dp1)*(1.-q_con)/pkz
718 pkz = exp(
kappa*log(rdg*delpbc(i,j,k)*ptbc(i,j,k) * &
719 (1.+dp1)/delzbc(i,j,k)))
720 ptbc(i,j,k) = ptbc(i,j,k)*(1.+dp1)/pkz
728 if (ie == npx-1)
then 729 ptbc => pt_bc%east_t1
730 sphumbc => sphum_bc%east_t1
732 qconbc => q_con_bc%east_t1
734 cappabc => cappa_bc%east_t1
737 delpbc => delp_bc%east_t1
738 delzbc => delz_bc%east_t1
746 dp1 = zvir*sphumbc(i,j,k)
749 q_con = liq_watbc_east(i,j,k)
750 q_sol = q_con*
max(
min((tice-ptbc(i,j,k))/t_i0,1.),0.)
751 q_liq = q_con - q_sol
753 q_liq = liq_watbc_east(i,j,k) + rainwatbc_east(i,j,k)
754 q_sol = ice_watbc_east(i,j,k) + snowwatbc_east(i,j,k) + graupelbc_east(i,j,k)
755 q_con = q_liq + q_sol
757 qconbc(i,j,k) = q_con
759 cvm = (1.-(sphumbc(i,j,k)+q_con))*cv_air+sphumbc(i,j,k)*cv_vap+q_liq*c_liq+q_sol*c_ice
761 pkz = exp( cappabc(i,j,k)*log(rdg*delpbc(i,j,k)*ptbc(i,j,k) * &
762 (1.+dp1)*(1.-q_con)/delzbc(i,j,k)))
764 pkz = exp(
kappa*log(rdg*delpbc(i,j,k)*ptbc(i,j,k) * &
765 (1.+dp1)*(1.-q_con)/delzbc(i,j,k)))
767 ptbc(i,j,k) = ptbc(i,j,k)*(1.+dp1)*(1.-q_con)/pkz
769 pkz = exp(
kappa*log(rdg*delpbc(i,j,k)*ptbc(i,j,k) * &
770 (1.+dp1)/delzbc(i,j,k)))
771 ptbc(i,j,k) = ptbc(i,j,k)*(1.+dp1)/pkz
778 if (je == npy-1)
then 779 ptbc => pt_bc%north_t1
780 sphumbc => sphum_bc%north_t1
782 qconbc => q_con_bc%north_t1
784 cappabc => cappa_bc%north_t1
787 delpbc => delp_bc%north_t1
788 delzbc => delz_bc%north_t1
794 if (ie == npx-1)
then 807 dp1 = zvir*sphumbc(i,j,k)
810 q_con = liq_watbc_north(i,j,k)
811 q_sol = q_con*
max(
min((tice-ptbc(i,j,k))/t_i0,1.),0.)
812 q_liq = q_con - q_sol
814 q_liq = liq_watbc_north(i,j,k) + rainwatbc_north(i,j,k)
815 q_sol = ice_watbc_north(i,j,k) + snowwatbc_north(i,j,k) + graupelbc_north(i,j,k)
816 q_con = q_liq + q_sol
818 qconbc(i,j,k) = q_con
820 cvm = (1.-(sphumbc(i,j,k)+q_con))*cv_air+sphumbc(i,j,k)*cv_vap+q_liq*c_liq+q_sol*c_ice
822 pkz = exp( cappabc(i,j,k)*log(rdg*delpbc(i,j,k)*ptbc(i,j,k) * &
823 (1.+dp1)*(1.-q_con)/delzbc(i,j,k)))
825 pkz = exp(
kappa*log(rdg*delpbc(i,j,k)*ptbc(i,j,k) * &
826 (1.+dp1)*(1.-q_con)/delzbc(i,j,k)))
828 ptbc(i,j,k) = ptbc(i,j,k)*(1.+dp1)*(1.-q_con)/pkz
830 pkz = exp(
kappa*log(rdg*delpbc(i,j,k)*ptbc(i,j,k) * &
831 (1.+dp1)/delzbc(i,j,k)))
832 ptbc(i,j,k) = ptbc(i,j,k)*(1.+dp1)/pkz
846 type(fv_nest_type),
intent(INOUT) :: neststruct
849 neststruct%delz_BC%east_t0 = neststruct%delz_BC%east_t1
850 neststruct%delz_BC%west_t0 = neststruct%delz_BC%west_t1
851 neststruct%delz_BC%north_t0 = neststruct%delz_BC%north_t1
852 neststruct%delz_BC%south_t0 = neststruct%delz_BC%south_t1
854 neststruct%w_BC%east_t0 = neststruct%w_BC%east_t1
855 neststruct%w_BC%west_t0 = neststruct%w_BC%west_t1
856 neststruct%w_BC%north_t0 = neststruct%w_BC%north_t1
857 neststruct%w_BC%south_t0 = neststruct%w_BC%south_t1
862 subroutine set_bcs_t0(ncnst, hydrostatic, neststruct)
864 integer,
intent(IN) :: ncnst
865 logical,
intent(IN) :: hydrostatic
866 type(fv_nest_type),
intent(INOUT) :: neststruct
870 neststruct%delp_BC%east_t0 = neststruct%delp_BC%east_t1
871 neststruct%delp_BC%west_t0 = neststruct%delp_BC%west_t1
872 neststruct%delp_BC%north_t0 = neststruct%delp_BC%north_t1
873 neststruct%delp_BC%south_t0 = neststruct%delp_BC%south_t1
875 neststruct%q_BC(n)%east_t0 = neststruct%q_BC(n)%east_t1
876 neststruct%q_BC(n)%west_t0 = neststruct%q_BC(n)%west_t1
877 neststruct%q_BC(n)%north_t0 = neststruct%q_BC(n)%north_t1
878 neststruct%q_BC(n)%south_t0 = neststruct%q_BC(n)%south_t1
881 neststruct%pt_BC%east_t0 = neststruct%pt_BC%east_t1
882 neststruct%pt_BC%west_t0 = neststruct%pt_BC%west_t1
883 neststruct%pt_BC%north_t0 = neststruct%pt_BC%north_t1
884 neststruct%pt_BC%south_t0 = neststruct%pt_BC%south_t1
885 neststruct%pt_BC%east_t0 = neststruct%pt_BC%east_t1
886 neststruct%pt_BC%west_t0 = neststruct%pt_BC%west_t1
887 neststruct%pt_BC%north_t0 = neststruct%pt_BC%north_t1
888 neststruct%pt_BC%south_t0 = neststruct%pt_BC%south_t1
891 neststruct%q_con_BC%east_t0 = neststruct%q_con_BC%east_t1
892 neststruct%q_con_BC%west_t0 = neststruct%q_con_BC%west_t1
893 neststruct%q_con_BC%north_t0 = neststruct%q_con_BC%north_t1
894 neststruct%q_con_BC%south_t0 = neststruct%q_con_BC%south_t1
896 neststruct%cappa_BC%east_t0 = neststruct%cappa_BC%east_t1
897 neststruct%cappa_BC%west_t0 = neststruct%cappa_BC%west_t1
898 neststruct%cappa_BC%north_t0 = neststruct%cappa_BC%north_t1
899 neststruct%cappa_BC%south_t0 = neststruct%cappa_BC%south_t1
903 if (.not. hydrostatic)
then 907 neststruct%u_BC%east_t0 = neststruct%u_BC%east_t1
908 neststruct%u_BC%west_t0 = neststruct%u_BC%west_t1
909 neststruct%u_BC%north_t0 = neststruct%u_BC%north_t1
910 neststruct%u_BC%south_t0 = neststruct%u_BC%south_t1
911 neststruct%v_BC%east_t0 = neststruct%v_BC%east_t1
912 neststruct%v_BC%west_t0 = neststruct%v_BC%west_t1
913 neststruct%v_BC%north_t0 = neststruct%v_BC%north_t1
914 neststruct%v_BC%south_t0 = neststruct%v_BC%south_t1
917 neststruct%vc_BC%east_t0 = neststruct%vc_BC%east_t1
918 neststruct%vc_BC%west_t0 = neststruct%vc_BC%west_t1
919 neststruct%vc_BC%north_t0 = neststruct%vc_BC%north_t1
920 neststruct%vc_BC%south_t0 = neststruct%vc_BC%south_t1
921 neststruct%uc_BC%east_t0 = neststruct%uc_BC%east_t1
922 neststruct%uc_BC%west_t0 = neststruct%uc_BC%west_t1
923 neststruct%uc_BC%north_t0 = neststruct%uc_BC%north_t1
924 neststruct%uc_BC%south_t0 = neststruct%uc_BC%south_t1
926 neststruct%divg_BC%east_t0 = neststruct%divg_BC%east_t1
927 neststruct%divg_BC%west_t0 = neststruct%divg_BC%west_t1
928 neststruct%divg_BC%north_t0 = neststruct%divg_BC%north_t1
929 neststruct%divg_BC%south_t0 = neststruct%divg_BC%south_t1
960 integer,
intent(IN) :: ngrids
961 logical,
intent(IN) :: grids_on_this_pe(ngrids)
962 real,
intent(IN) :: zvir
964 integer :: n, p, sphum
972 if (atm(n)%neststruct%twowaynest )
then 973 if (grids_on_this_pe(n) .or. grids_on_this_pe(atm(n)%parent_grid%grid_number))
then 976 atm(n)%ncnst, sphum, atm(n)%u, atm(n)%v, atm(n)%w, atm(n)%omga, &
977 atm(n)%pt, atm(n)%delp, atm(n)%q, atm(n)%uc, atm(n)%vc, &
978 atm(n)%pkz, atm(n)%delz, atm(n)%ps, atm(n)%ptop, &
979 atm(n)%gridstruct, atm(n)%flagstruct, atm(n)%neststruct, atm(n)%parent_grid, atm(n)%bd, .false.)
987 if (atm(n)%neststruct%parent_of_twoway .and. grids_on_this_pe(n))
then 989 atm(n)%u, atm(n)%v, atm(n)%w, atm(n)%delz, &
990 atm(n)%pt, atm(n)%delp, atm(n)%q, &
991 atm(n)%ps, atm(n)%pe, atm(n)%pk, atm(n)%peln, atm(n)%pkz, &
992 atm(n)%phis, atm(n)%ua, atm(n)%va, &
993 atm(n)%ptop, atm(n)%gridstruct, atm(n)%flagstruct, &
994 atm(n)%domain, atm(n)%bd)
1008 u, v, w, omga, pt, delp, q, &
1009 uc, vc, pkz, delz, ps, ptop, &
1010 gridstruct, flagstruct, neststruct, &
1011 parent_grid, bd, conv_theta_in)
1013 real,
intent(IN) :: zvir, ptop
1015 integer,
intent(IN) :: npx, npy, npz
1016 integer,
intent(IN) :: ncnst, sphum
1017 logical,
intent(IN),
OPTIONAL :: conv_theta_in
1019 type(fv_grid_bounds_type),
intent(IN) :: bd
1020 real,
intent(inout),
dimension(bd%isd:bd%ied ,bd%jsd:bd%jed+1,npz) :: u
1021 real,
intent(inout),
dimension(bd%isd:bd%ied+1,bd%jsd:bd%jed ,npz) :: v
1022 real,
intent(inout) :: w( bd%isd: ,bd%jsd: ,1: )
1023 real,
intent(inout) :: omga(bd%isd:bd%ied,bd%jsd:bd%jed,npz)
1024 real,
intent(inout) :: pt( bd%isd:bd%ied ,bd%jsd:bd%jed ,npz)
1025 real,
intent(inout) :: delp(bd%isd:bd%ied ,bd%jsd:bd%jed ,npz)
1026 real,
intent(inout) :: q( bd%isd:bd%ied ,bd%jsd:bd%jed ,npz, ncnst)
1027 real,
intent(inout) :: uc(bd%isd:bd%ied+1,bd%jsd:bd%jed ,npz)
1028 real,
intent(inout) :: vc(bd%isd:bd%ied ,bd%jsd:bd%jed+1,npz)
1030 real,
intent(inout) :: pkz (bd%is:bd%ie,bd%js:bd%je,npz)
1031 real,
intent(inout) :: delz(bd%isd: ,bd%jsd: ,1: )
1032 real,
intent(inout) :: ps (bd%isd:bd%ied ,bd%jsd:bd%jed)
1034 type(fv_grid_type),
intent(INOUT) :: gridstruct
1035 type(fv_flags_type),
intent(INOUT) :: flagstruct
1036 type(fv_nest_type),
intent(INOUT) :: neststruct
1038 type(fv_atmos_type),
intent(INOUT) :: parent_grid
1040 real,
allocatable :: t_nest(:,:,:), ps0(:,:)
1042 integer :: isd_p, ied_p, jsd_p, jed_p, isc_p, iec_p, jsc_p, jec_p
1043 integer :: isg, ieg, jsg,jeg, npx_p, npy_p
1044 integer :: istart, iend
1045 real :: qmass_b, qmass_a, fix = 1.
1046 logical :: used, conv_theta=.true.
1048 real :: qdp( bd%isd:bd%ied ,bd%jsd:bd%jed ,npz)
1049 real,
allocatable :: qdp_coarse(:,:,:)
1050 real(kind=f_p),
allocatable :: q_diff(:,:,:)
1051 real :: L_sum_b(npz), L_sum_a(npz)
1054 integer :: is, ie, js, je
1055 integer :: isd, ied, jsd, jed
1056 integer :: isu, ieu, jsu, jeu
1066 isu = neststruct%isu
1067 ieu = neststruct%ieu
1068 jsu = neststruct%jsu
1069 jeu = neststruct%jeu
1071 upoff = neststruct%upoff
1075 if (
present(conv_theta_in)) conv_theta = conv_theta_in
1077 if ((.not. neststruct%parent_proc) .and. (.not. neststruct%child_proc))
return 1080 isd_p, ied_p, jsd_p, jed_p )
1082 isc_p, iec_p, jsc_p, jec_p )
1087 if (neststruct%nestupdate < 3)
then 1090 neststruct%ind_update_h, gridstruct%dx, gridstruct%dy, gridstruct%area, &
1091 isd_p, ied_p, jsd_p, jed_p, isd, ied, jsd, jed, &
1092 neststruct%isu, neststruct%ieu, neststruct%jsu, neststruct%jeu, &
1093 npx, npy, npz, 0, 0, &
1094 neststruct%refinement, neststruct%nestupdate, upoff, 0, &
1095 neststruct%parent_proc, neststruct%child_proc, parent_grid)
1100 if (neststruct%parent_proc)
then 1104 parent_grid%ps(i,j) = &
1105 parent_grid%delp(i,j,1)/
grav 1115 if (neststruct%nestupdate /= 3 .and. neststruct%nestupdate /= 7 .and. neststruct%nestupdate /= 8)
then 1117 allocate(qdp_coarse(isd_p:ied_p,jsd_p:jed_p,npz))
1118 if (parent_grid%flagstruct%nwat > 0)
then 1119 allocate(q_diff(isd_p:ied_p,jsd_p:jed_p,npz))
1123 do n=1,parent_grid%flagstruct%nwat
1126 if (neststruct%child_proc)
then 1130 qdp(i,j,k) = q(i,j,k,n)*delp(i,j,k)
1138 if (neststruct%parent_proc)
then 1143 qdp_coarse(i,j,k) = parent_grid%q(i,j,k,n)*parent_grid%delp(i,j,k)
1147 call level_sum(qdp_coarse, parent_grid%gridstruct%area, parent_grid%domain, &
1148 parent_grid%bd, npz, l_sum_b)
1152 if (neststruct%parent_proc)
then 1153 if (n <= parent_grid%flagstruct%nwat)
then 1157 q_diff(i,j,k) = q_diff(i,j,k) - qdp_coarse(i,j,k)
1165 neststruct%ind_update_h, gridstruct%dx, gridstruct%dy, gridstruct%area, &
1166 isd_p, ied_p, jsd_p, jed_p, isd, ied, jsd, jed, &
1167 neststruct%isu, neststruct%ieu, neststruct%jsu, neststruct%jeu, &
1168 npx, npy, npz, 0, 0, &
1169 neststruct%refinement, neststruct%nestupdate, upoff, 0, neststruct%parent_proc, neststruct%child_proc, parent_grid)
1173 if (neststruct%parent_proc)
then 1174 call level_sum(qdp_coarse, parent_grid%gridstruct%area, parent_grid%domain, &
1175 parent_grid%bd, npz, l_sum_a)
1177 if (l_sum_a(k) > 0.)
then 1178 fix = l_sum_b(k)/l_sum_a(k)
1182 parent_grid%q(i,j,k,n) = qdp_coarse(i,j,k)*fix
1189 if (neststruct%parent_proc)
then 1190 if (n <= parent_grid%flagstruct%nwat)
then 1194 q_diff(i,j,k) = q_diff(i,j,k) + parent_grid%q(i,j,k,n)
1203 if (neststruct%parent_proc)
then 1204 if (parent_grid%flagstruct%nwat > 0)
then 1208 parent_grid%delp(i,j,k) = parent_grid%delp(i,j,k) + q_diff(i,j,k)
1214 do n=1,parent_grid%flagstruct%nwat
1218 parent_grid%q(i,j,k,n) = parent_grid%q(i,j,k,n)/parent_grid%delp(i,j,k)
1225 deallocate(qdp_coarse)
1226 if (
allocated(q_diff))
deallocate(q_diff)
1231 if (neststruct%nestupdate /= 3 .and. neststruct%nestupdate /= 8)
then 1233 if (conv_theta)
then 1235 if (neststruct%child_proc)
then 1239 allocate(t_nest(isd:ied,jsd:jed,1:npz))
1244 t_nest(i,j,k) = pt(i,j,k)*pkz(i,j,k)/(1.+zvir*q(i,j,k,sphum))
1252 t_nest, neststruct%nest_domain, &
1253 neststruct%ind_update_h, gridstruct%dx, gridstruct%dy, gridstruct%area, &
1254 isd_p, ied_p, jsd_p, jed_p, isd, ied, jsd, jed, &
1255 neststruct%isu, neststruct%ieu, neststruct%jsu, neststruct%jeu, &
1256 npx, npy, npz, 0, 0, &
1257 neststruct%refinement, neststruct%nestupdate, upoff, 0, neststruct%parent_proc, neststruct%child_proc, parent_grid)
1261 pt, neststruct%nest_domain, &
1262 neststruct%ind_update_h, gridstruct%dx, gridstruct%dy, gridstruct%area, &
1263 isd_p, ied_p, jsd_p, jed_p, isd, ied, jsd, jed, &
1264 neststruct%isu, neststruct%ieu, neststruct%jsu, neststruct%jeu, &
1265 npx, npy, npz, 0, 0, &
1266 neststruct%refinement, neststruct%nestupdate, upoff, 0, neststruct%parent_proc, neststruct%child_proc, parent_grid)
1272 if (.not. flagstruct%hydrostatic)
then 1275 neststruct%ind_update_h, gridstruct%dx, gridstruct%dy, gridstruct%area, &
1276 isd_p, ied_p, jsd_p, jed_p, isd, ied, jsd, jed, &
1277 neststruct%isu, neststruct%ieu, neststruct%jsu, neststruct%jeu, &
1278 npx, npy, npz, 0, 0, &
1279 neststruct%refinement, neststruct%nestupdate, upoff, 0, neststruct%parent_proc, neststruct%child_proc, parent_grid)
1295 neststruct%ind_update_h, gridstruct%dx, gridstruct%dy, gridstruct%area, &
1296 isd_p, ied_p, jsd_p, jed_p, isd, ied, jsd, jed, &
1297 neststruct%isu, neststruct%ieu, neststruct%jsu, neststruct%jeu, &
1298 npx, npy, npz, 0, 1, &
1299 neststruct%refinement, neststruct%nestupdate, upoff, 0, neststruct%parent_proc, neststruct%child_proc, parent_grid)
1302 neststruct%ind_update_h, gridstruct%dx, gridstruct%dy, gridstruct%area, &
1303 isd_p, ied_p, jsd_p, jed_p, isd, ied, jsd, jed, &
1304 neststruct%isu, neststruct%ieu, neststruct%jsu, neststruct%jeu, &
1305 npx, npy, npz, 1, 0, &
1306 neststruct%refinement, neststruct%nestupdate, upoff, 0, neststruct%parent_proc, neststruct%child_proc, parent_grid)
1312 if (neststruct%nestupdate >= 5 .and. npz > 4)
then 1319 allocate(ps0(isd_p:ied_p,jsd_p:jed_p))
1320 if (neststruct%parent_proc)
then 1322 parent_grid%ps = parent_grid%ptop
1328 parent_grid%ps(i,j) = parent_grid%ps(i,j) + &
1329 parent_grid%delp(i,j,k)
1334 ps0 = parent_grid%ps
1337 if (neststruct%child_proc)
then 1344 ps(i,j) = ps(i,j) + delp(i,j,k)
1351 neststruct%ind_update_h, gridstruct%dx, gridstruct%dy, gridstruct%area, &
1352 isd_p, ied_p, jsd_p, jed_p, isd, ied, jsd, jed, &
1353 neststruct%isu, neststruct%ieu, neststruct%jsu, neststruct%jeu, &
1355 neststruct%refinement, neststruct%nestupdate, upoff, 0, neststruct%parent_proc, neststruct%child_proc, parent_grid)
1361 if (neststruct%parent_proc)
then 1369 if (parent_grid%tile == neststruct%parent_tile)
then 1371 if (neststruct%parent_proc)
then 1377 if (parent_grid%flagstruct%remap_option /= 0)
then 1382 parent_grid%pt(i,j,k) = &
1383 parent_grid%pt(i,j,k)/parent_grid%pkz(i,j,k)*&
1384 (1.+zvir*parent_grid%q(i,j,k,sphum))
1390 parent_grid%ps, parent_grid%delp, &
1391 parent_grid%pt, parent_grid%q, parent_grid%w, &
1392 parent_grid%flagstruct%hydrostatic, &
1393 npz, ps0, zvir, parent_grid%ptop, ncnst, &
1394 parent_grid%flagstruct%kord_tm, parent_grid%flagstruct%kord_tr, &
1395 parent_grid%flagstruct%kord_wz, &
1396 isc_p, iec_p, jsc_p, jec_p, isd_p, ied_p, jsd_p, jed_p, .false. )
1397 if (parent_grid%flagstruct%remap_option /= 0)
then 1402 parent_grid%pt(i,j,k) = &
1403 parent_grid%pt(i,j,k)*parent_grid%pkz(i,j,k) / &
1404 (1.+zvir*parent_grid%q(i,j,k,sphum))
1413 parent_grid%v, npz, ps0, parent_grid%flagstruct%kord_mt, &
1414 isc_p, iec_p, jsc_p, jec_p, isd_p, ied_p, jsd_p, jed_p, parent_grid%ptop)
1420 if (
allocated(ps0))
deallocate(ps0)
1428 subroutine level_sum(q, area, domain, bd, npz, L_sum)
1430 integer,
intent(IN) :: npz
1431 type(fv_grid_bounds_type),
intent(IN) :: bd
1432 real,
intent(in) :: area( bd%isd:bd%ied ,bd%jsd:bd%jed)
1433 real,
intent(in) :: q( bd%isd:bd%ied ,bd%jsd:bd%jed ,npz)
1434 real,
intent(OUT) :: L_sum( npz )
1435 type(domain2d),
intent(IN) :: domain
1437 integer :: i, j, k, n
1445 qa = qa + q(i,j,k)*area(i,j)
1448 call mp_reduce_sum(qa)
1458 u, v, w, delz, pt, delp, q, &
1459 ps, pe, pk, peln, pkz, phis, ua, va, &
1460 ptop, gridstruct, flagstruct, &
1463 type(fv_grid_bounds_type),
intent(IN) :: bd
1464 real,
intent(IN) :: ptop
1466 integer,
intent(IN) :: ng, npx, npy, npz
1467 integer,
intent(IN) :: ncnst
1469 real,
intent(inout),
dimension(bd%isd:bd%ied ,bd%jsd:bd%jed+1,npz) :: u
1470 real,
intent(inout),
dimension(bd%isd:bd%ied+1,bd%jsd:bd%jed ,npz) :: v
1471 real,
intent(inout) :: w( bd%isd: ,bd%jsd: ,1: )
1472 real,
intent(inout) :: pt( bd%isd:bd%ied ,bd%jsd:bd%jed ,npz)
1473 real,
intent(inout) :: delp(bd%isd:bd%ied ,bd%jsd:bd%jed ,npz)
1474 real,
intent(inout) :: q( bd%isd:bd%ied ,bd%jsd:bd%jed ,npz, ncnst)
1475 real,
intent(inout) :: delz(bd%isd: ,bd%jsd: ,1: )
1482 real,
intent(inout) :: ps (bd%isd:bd%ied ,bd%jsd:bd%jed)
1483 real,
intent(inout) :: pe (bd%is-1:bd%ie+1, npz+1,bd%js-1:bd%je+1)
1484 real,
intent(inout) :: pk (bd%is:bd%ie,bd%js:bd%je, npz+1)
1485 real,
intent(inout) :: peln(bd%is:bd%ie,npz+1,bd%js:bd%je)
1486 real,
intent(inout) :: pkz (bd%is:bd%ie,bd%js:bd%je,npz)
1491 real,
intent(inout) :: phis(bd%isd:bd%ied,bd%jsd:bd%jed)
1493 real,
intent(inout),
dimension(bd%isd:bd%ied ,bd%jsd:bd%jed ,npz):: ua, va
1494 type(fv_grid_type),
intent(IN) :: gridstruct
1495 type(fv_flags_type),
intent(IN) :: flagstruct
1496 type(domain2d),
intent(INOUT) :: domain
1498 logical :: bad_range
1500 integer :: is, ie, js, je
1501 integer :: isd, ied, jsd, jed
1513 gridstruct, npx, npy, npz, &
1514 1, gridstruct%grid_type, domain, &
1515 gridstruct%nested, flagstruct%c2l_ord, bd)
1529 q, ng, flagstruct%ncnst, gridstruct%area_64, 0., &
1531 flagstruct%moist_phys, flagstruct%hydrostatic, &
1532 flagstruct%nwat, domain, .false.)
1536 if (flagstruct%range_warn)
then 1537 call range_check(
'TA update', pt, is, ie, js, je, ng, npz, gridstruct%agrid, 130., 350., bad_range)
1538 call range_check(
'UA update', ua, is, ie, js, je, ng, npz, gridstruct%agrid, -220., 250., bad_range)
1539 call range_check(
'VA update', va, is, ie, js, je, ng, npz, gridstruct%agrid, -220., 220., bad_range)
1540 if (.not. flagstruct%hydrostatic)
then 1541 call range_check(
'W update', w, is, ie, js, je, ng, npz, gridstruct%agrid, -50., 100., bad_range)
1552 subroutine update_remap_tqw( npz, ak, bk, ps, delp, t, q, w, hydrostatic, &
1553 kmd, ps0, zvir, ptop, nq, kord_tm, kord_tr, kord_wz, &
1554 is, ie, js, je, isd, ied, jsd, jed, do_q)
1555 integer,
intent(in):: npz, kmd, nq, kord_tm, kord_tr, kord_wz
1556 real,
intent(in):: zvir, ptop
1557 real,
intent(in):: ak(npz+1), bk(npz+1)
1558 real,
intent(in),
dimension(isd:ied,jsd:jed):: ps0
1559 real,
intent(in),
dimension(isd:ied,jsd:jed):: ps
1560 real,
intent(in),
dimension(isd:ied,jsd:jed,npz):: delp
1561 real,
intent(inout),
dimension(isd:ied,jsd:jed,npz):: t, w
1562 real,
intent(inout),
dimension(isd:ied,jsd:jed,npz,nq):: q
1563 integer,
intent(in) :: is, ie, js, je, isd, ied, jsd, jed
1564 logical,
intent(in) :: hydrostatic, do_q
1566 real,
dimension(is:ie,kmd):: tp, qp
1567 real,
dimension(is:ie,kmd+1):: pe0, pn0
1568 real,
dimension(is:ie,npz):: qn1
1569 real,
dimension(is:ie,npz+1):: pe1, pn1
1579 pe0(i,k) = ak(k) + bk(k)*ps0(i,j)
1580 pn0(i,k) = log(pe0(i,k))
1585 pe1(i,k) = ak(k) + bk(k)*ps(i,j)
1586 pn1(i,k) = log(pe1(i,k))
1593 qp(i,k) = q(i,j,k,iq)
1596 call mappm(kmd, pe0, qp, npz, pe1, qn1, is,ie, 0, kord_tr, ptop)
1599 q(i,j,k,iq) = qn1(i,k)
1611 call mappm(kmd, pn0, tp, npz, pn1, qn1, is,ie, 1, abs(kord_tm), ptop)
1619 if (.not. hydrostatic)
then 1627 call mappm(kmd, pe0, tp, npz, pe1, qn1, is,ie, -1, kord_wz, ptop)
1641 subroutine update_remap_uv(npz, ak, bk, ps, u, v, kmd, ps0, kord_mt, &
1642 is, ie, js, je, isd, ied, jsd, jed, ptop)
1643 integer,
intent(in):: npz
1644 real,
intent(in):: ak(npz+1), bk(npz+1)
1645 real,
intent(in):: ps(isd:ied,jsd:jed)
1646 real,
intent(inout),
dimension(isd:ied,jsd:jed+1,npz):: u
1647 real,
intent(inout),
dimension(isd:ied+1,jsd:jed,npz):: v
1649 integer,
intent(in):: kmd, kord_mt
1650 real,
intent(IN) :: ptop
1651 real,
intent(in):: ps0(isd:ied,jsd:jed)
1652 integer,
intent(in) :: is, ie, js, je, isd, ied, jsd, jed
1655 real,
dimension(is:ie+1,kmd+1):: pe0
1656 real,
dimension(is:ie+1,npz+1):: pe1
1657 real,
dimension(is:ie+1,kmd):: qt
1658 real,
dimension(is:ie+1,npz):: qn1
1672 pe0(i,k) = ak(k) + bk(k)*0.5*(ps0(i,j)+ps0(i,j-1))
1680 pe1(i,k) = ak(k) + bk(k)*0.5*(ps(i,j)+ps(i,j-1))
1693 call mappm(kmd, pe0(is:ie,:), qt(is:ie,:), npz, pe1(is:ie,:), qn1(is:ie,:), is,ie, -1, kord_mt, ptop)
1713 pe0(i,k) = ak(k) + bk(k)*0.5*(ps0(i,j)+ps0(i-1,j))
1721 pe1(i,k) = ak(k) + bk(k)*0.5*(ps(i,j)+ps(i-1,j))
1734 call mappm(kmd, pe0(is:ie+1,:), qt(is:ie+1,:), npz, pe1(is:ie+1,:), qn1(is:ie+1,:), is,ie+1, -1, 8, ptop)
real, parameter, public radius
Radius of the Earth [m].
integer, parameter, public model_atmos
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, public twoway_nesting(Atm, ngrids, grids_on_this_pe, zvir)
type(fv_nest_bc_type_3d) delz_buf
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
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)
real, dimension(:,:,:), allocatable, target dum_north
type(fv_nest_bc_type_3d) delp_buf
real(kind=8), parameter, public pi_8
Ratio of circle circumference to diameter [N/A].
real, dimension(:,:,:), allocatable, target dum_south
real, parameter, public hlv
Latent heat of evaporation [J/kg].
real, parameter, public rdgas
Gas constant for dry air [J/kg/deg].
real, public sphum_ll_fix
real, parameter, public cp_vapor
Specific heat capacity of water vapor at constant pressure [J/kg/deg].
real, dimension(:,:,:), allocatable, target dum_west
subroutine, public cubed_to_latlon(u, v, ua, va, gridstruct, npx, npy, km, mode, grid_type, domain, nested, c2l_ord, bd)
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)
type(fv_nest_bc_type_3d) pt_buf
type(fv_nest_bc_type_3d) vc_buf
type(fv_nest_bc_type_3d) pkz_buf
subroutine, public nested_grid_bc_recv(nest_domain, istag, jstag, npz, bd, nest_BC_buffers)
integer, parameter, public f_p
real, parameter, public rvgas
Gas constant for water vapor [J/kg/deg].
subroutine timing_on(blk_name)
type(fv_nest_bc_type_3d) uc_buf
subroutine setup_pt_bc(pt_BC, pkz_BC, sphum_BC, npx, npy, npz, zvir, bd)
real, parameter, public cp_air
Specific heat capacity of dry air at constant pressure [J/kg/deg].
subroutine, public divergence_corner(u, v, ua, va, divg_d, gridstruct, flagstruct, bd)
real, dimension(:,:,:), allocatable dp1_coarse
real, dimension(:,:), allocatable te_2d_coarse
subroutine set_bcs_t0(ncnst, hydrostatic, neststruct)
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)
type(fv_nest_bc_type_3d) v_buf
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)
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)
type(fv_nest_bc_type_3d), dimension(:), allocatable q_buf
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 level_sum(q, area, domain, bd, npz, L_sum)
subroutine, public divergence_corner_nest(u, v, ua, va, divg_d, gridstruct, flagstruct, bd)
type(fv_nest_bc_type_3d) divg_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)
subroutine set_nh_bcs_t0(neststruct)
type(fv_nest_bc_type_3d) w_buf
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)
real, dimension(:,:,:), allocatable, target dum_east
real, dimension(:), allocatable rw
real, parameter, public kappa
RDGAS / CP_AIR [dimensionless].
subroutine update_remap_uv(npz, ak, bk, ps, u, v, kmd, ps0, kord_mt, is, ie, js, je, isd, ied, jsd, jed, ptop)
subroutine, public range_check(qname, q, is, ie, js, je, n_g, km, pos, q_low, q_hi, bad_range)
type(fv_nest_bc_type_3d) u_buf
subroutine setup_pt_nh_bc(pt_BC, delp_BC, delz_BC, sphum_BC, q_BC, nq, ifdef USE_COND
real(fp), parameter, public pi
subroutine timing_off(blk_name)