FV3 Bundle
fv_nesting_adm.F90
Go to the documentation of this file.
1 !***********************************************************************
2 !* GNU General Public License *
3 !* This file is a part of fvGFS. *
4 !* *
5 !* fvGFS is free software; you can redistribute it and/or modify it *
6 !* and are expected to follow the terms of the GNU General Public *
7 !* License as published by the Free Software Foundation; either *
8 !* version 2 of the License, or (at your option) any later version. *
9 !* *
10 !* fvGFS is distributed in the hope that it will be useful, but *
11 !* WITHOUT ANY WARRANTY; without even the implied warranty of *
12 !* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU *
13 !* General Public License for more details. *
14 !* *
15 !* For the full text of the GNU General Public License, *
16 !* write to: Free Software Foundation, Inc., *
17 !* 675 Mass Ave, Cambridge, MA 02139, USA. *
18 !* or see: http://www.gnu.org/licenses/gpl.html *
19 !***********************************************************************
21 
26  use fv_sg_nlm_mod, only: neg_adj3
28  use mpp_domains_mod, only: dgrid_ne, domain2d
31  use mpp_mod, only: mpp_sync_self, mpp_sync, mpp_send, mpp_recv, mpp_error, fatal
32  use mpp_domains_mod, only: mpp_global_sum, bitwise_efp_sum, bitwise_exact_sum
35  use fv_mp_nlm_mod, only: is, ie, js, je, isd, ied, jsd, jed, isc, iec, jsc, jec
39  use init_hydro_nlm_mod, only: p_var
41  use fv_mapz_nlm_mod, only: mappm
43  use fv_mp_nlm_mod, only: is_master
44  use fv_mp_nlm_mod, only: mp_reduce_sum
47 
50 
51 implicit none
52  logical :: rf_initialized = .false.
53  logical :: bad_range
54  real, allocatable :: rf(:), rw(:)
55  integer :: kmax=1
56  !Arrays for global grid total energy, used for grid nesting
57  real, allocatable :: te_2d_coarse(:,:)
58  real, allocatable :: dp1_coarse(:,:,:)
59 
60  !For nested grid buffers
61  !Individual structures are allocated by nested_grid_BC_recv
63  type(fv_nest_bc_type_3d), allocatable:: q_buf(:)
64 !#ifdef USE_COND
65  real, dimension(:,:,:), allocatable, target :: dum_west, dum_east, dum_north, dum_south
66 !#endif
67 
68 private
71 
72 CONTAINS
73 ! Differentiation of setup_nested_grid_bcs in reverse (adjoint) mode (with options split(a2b_edge_mod.a2b_ord4 a2b_edge_mod.a
74 !2b_ord2 dyn_core_mod.dyn_core dyn_core_mod.pk3_halo dyn_core_mod.pln_halo dyn_core_mod.pe_halo dyn_core_mod.adv_pe dyn_core_mod.
75 !p_grad_c dyn_core_mod.nh_p_grad dyn_core_mod.split_p_grad dyn_core_mod.one_grad_p dyn_core_mod.grad1_p_update dyn_core_mod.mix_d
76 !p dyn_core_mod.geopk dyn_core_mod.del2_cubed dyn_core_mod.Rayleigh_fast fv_dynamics_mod.fv_dynamics fv_dynamics_mod.Rayleigh_Sup
77 !er fv_dynamics_mod.Rayleigh_Friction fv_dynamics_mod.compute_aam fv_grid_utils_mod.cubed_to_latlon fv_grid_utils_mod.c2l_ord4 fv
78 !_grid_utils_mod.c2l_ord2 fv_mapz_mod.Lagrangian_to_Eulerian fv_mapz_mod.compute_total_energy fv_mapz_mod.pkez fv_mapz_mod.remap_
79 !z fv_mapz_mod.map_scalar fv_mapz_mod.map1_ppm fv_mapz_mod.mapn_tracer fv_mapz_mod.map1_q2 fv_mapz_mod.remap_2d fv_ma
80 !pz_mod.scalar_profile fv_mapz_mod.cs_profile fv_mapz_mod.cs_limiters fv_mapz_mod.ppm_profile fv_mapz_mod.ppm_limiters fv_m
81 !apz_mod.steepz fv_mapz_mod.rst_remap fv_mapz_mod.mappm fv_mapz_mod.moist_cv fv_mapz_mod.moist_cp fv_mapz_mod.map1_cubic fv_resta
82 !rt_mod.d2c_setup fv_tracer2d_mod.tracer_2d_1L fv_tracer2d_mod.tracer_2d fv_tracer2d_mod.tracer_2d_nested fv_sg_mod.fv_subgrid_z
83 !main_mod.compute_pressures main_mod.run nh_core_mod.Riem_Solver3 nh_utils_mod.update_dz_c nh_utils_mod.update_dz_d nh_utils_mod.
84 !Riem_Solver_c nh_utils_mod.Riem_Solver3test nh_utils_mod.imp_diff_w nh_utils_mod.RIM_2D nh_utils_mod.SIM3_solver nh_utils_mod.SI
85 !M3p0_solver nh_utils_mod.SIM1_solver nh_utils_mod.SIM_solver nh_utils_mod.edge_scalar nh_utils_mod.edge_profile nh_utils_mod.nes
86 !t_halo_nh sw_core_mod.c_sw sw_core_mod.d_sw sw_core_mod.divergence_corner sw_core_mod.divergence_corner_nest sw_core_mod.d2a2c_
87 !vect sw_core_mod.fill3_4corners sw_core_mod.fill2_4corners sw_core_mod.fill_4corners sw_core_mod.xtp_u sw_core_mod.ytp_v s
88 !w_core_mod.compute_divergence_damping sw_core_mod.smag_corner tp_core_mod.mp_ghost_ew tp_core_mod.fv_tp_2d tp_core_mod.
89 !copy_corners tp_core_mod.xppm tp_core_mod.yppm tp_core_mod.deln_flux a2b_edge_mod.extrap_corner fv_grid_utils_mod
90 !.great_circle_dist sw_core_mod.edge_interpolate4)):
91 ! gradient of useful results: u v uc vc
92 ! with respect to varying inputs: u v
93 !!!! NOTE: Many of the routines here and in boundary.F90 have a lot of
94 !!!! redundant code, which could be cleaned up and simplified.
95  SUBROUTINE setup_nested_grid_bcs_adm(npx, npy, npz, zvir, ncnst, u, &
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)
99  IMPLICIT NONE
100  TYPE(fv_grid_bounds_type), INTENT(IN) :: bd
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
105 ! D grid zonal wind (m/s)
106  REAL, DIMENSION(bd%isd:bd%ied, bd%jsd:bd%jed+1, npz), INTENT(INOUT) &
107 & :: u
108  REAL, DIMENSION(bd%isd:bd%ied, bd%jsd:bd%jed+1, npz), INTENT(INOUT) &
109 & :: u_ad
110 ! D grid meridional wind (m/s)
111  REAL, DIMENSION(bd%isd:bd%ied+1, bd%jsd:bd%jed, npz), INTENT(INOUT) &
112 & :: v
113  REAL, DIMENSION(bd%isd:bd%ied+1, bd%jsd:bd%jed, npz), INTENT(INOUT) &
114 & :: v_ad
115 ! W (m/s)
116  REAL, INTENT(INOUT) :: w(bd%isd:, bd%jsd:, :)
117 ! temperature (K)
118  REAL, INTENT(INOUT) :: pt(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
119 ! pressure thickness (pascal)
120  REAL, INTENT(INOUT) :: delp(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
121 ! height thickness (m)
122  REAL, INTENT(INOUT) :: delz(bd%isd:, bd%jsd:, :)
123 ! specific humidity and constituents
124  REAL, INTENT(INOUT) :: q(bd%isd:bd%ied, bd%jsd:bd%jed, npz, ncnst)
125 ! (uc,vc) mostly used as the C grid winds
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)
130 ! finite-volume mean pk
131  REAL, INTENT(INOUT) :: pkz(bd%is:bd%ie, bd%js:bd%je, npz)
132  INTEGER, INTENT(INOUT) :: nest_timestep, tracer_nest_timestep
133  TYPE(fv_grid_type), INTENT(INOUT) :: gridstruct
134  TYPE(fv_flags_type), INTENT(INOUT) :: flagstruct
135  TYPE(fv_nest_type), INTENT(INOUT), TARGET :: neststruct
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
142  LOGICAL :: do_pd
143  TYPE(fv_nest_bc_type_3d) :: pkz_bc
144 !local pointers
145  LOGICAL, POINTER :: child_grids(:)
146  INTEGER :: is, ie, js, je
147  INTEGER :: isd, ied, jsd, jed
148  INTRINSIC any
149  INTRINSIC ALLOCATED
150  INTRINSIC SIZE
151  LOGICAL :: arg1
152  INTEGER :: branch
153  is = bd%is
154  ie = bd%ie
155  js = bd%js
156  je = bd%je
157  isd = bd%isd
158  ied = bd%ied
159  jsd = bd%jsd
160  jed = bd%jed
161 !IF nested, set up nested grid BCs for time-interpolation
162 !(actually applying the BCs is done in dyn_core
163 !compute uc/vc for nested-grid BCs
164 !!! CLEANUP: if we compute uc/vc here we don't need to do on the first call of c_sw, right?
165  IF (any(neststruct%child_grids)) THEN
166 !$OMP parallel do default(none) shared(isd,jsd,ied,jed,is,ie,js,je,npx,npy,npz, &
167 !$OMP gridstruct,flagstruct,bd,u,v,uc,vc,nested,divg) &
168 !$OMP private(ua,va)
169  DO k=1,npz
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)
177  END DO
178  CALL pushcontrol1b(0)
179  ELSE
180  CALL pushcontrol1b(1)
181  END IF
182 !! Nested grid: receive from parent grid
183  IF (neststruct%nested) THEN
184  IF (.NOT.ALLOCATED(q_buf)) THEN
185  ALLOCATE(q_buf(ncnst))
186  DEALLOCATE(q_buf)
187  END IF
188  END IF
189  CALL popcontrol1b(branch)
190  IF (branch .EQ. 0) THEN
191  DO k=npz,1,-1
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)
201  END DO
202  CALL mpp_update_domains_adm(u, u_ad, v, v_ad, domain, gridtype=&
203 & dgrid_ne, complete=.true.)
204  END IF
205  END SUBROUTINE setup_nested_grid_bcs_adm
206 !!!! NOTE: Many of the routines here and in boundary.F90 have a lot of
207 !!!! redundant code, which could be cleaned up and simplified.
208  SUBROUTINE setup_nested_grid_bcs(npx, npy, npz, zvir, ncnst, u, v, w, &
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)
212  IMPLICIT NONE
213  TYPE(fv_grid_bounds_type), INTENT(IN) :: bd
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
218 ! D grid zonal wind (m/s)
219  REAL, DIMENSION(bd%isd:bd%ied, bd%jsd:bd%jed+1, npz), INTENT(INOUT) &
220 & :: u
221 ! D grid meridional wind (m/s)
222  REAL, DIMENSION(bd%isd:bd%ied+1, bd%jsd:bd%jed, npz), INTENT(INOUT) &
223 & :: v
224 ! W (m/s)
225  REAL, INTENT(INOUT) :: w(bd%isd:, bd%jsd:, :)
226 ! temperature (K)
227  REAL, INTENT(INOUT) :: pt(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
228 ! pressure thickness (pascal)
229  REAL, INTENT(INOUT) :: delp(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
230 ! height thickness (m)
231  REAL, INTENT(INOUT) :: delz(bd%isd:, bd%jsd:, :)
232 ! specific humidity and constituents
233  REAL, INTENT(INOUT) :: q(bd%isd:bd%ied, bd%jsd:bd%jed, npz, ncnst)
234 ! (uc,vc) mostly used as the C grid winds
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)
237 ! finite-volume mean pk
238  REAL, INTENT(INOUT) :: pkz(bd%is:bd%ie, bd%js:bd%je, npz)
239  INTEGER, INTENT(INOUT) :: nest_timestep, tracer_nest_timestep
240  TYPE(fv_grid_type), INTENT(INOUT) :: gridstruct
241  TYPE(fv_flags_type), INTENT(INOUT) :: flagstruct
242  TYPE(fv_nest_type), INTENT(INOUT), TARGET :: neststruct
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
249  LOGICAL :: do_pd
250  TYPE(fv_nest_bc_type_3d) :: pkz_bc
251 !local pointers
252  LOGICAL, POINTER :: child_grids(:)
253  INTEGER :: is, ie, js, je
254  INTEGER :: isd, ied, jsd, jed
255  INTRINSIC any
256  INTRINSIC ALLOCATED
257  INTRINSIC SIZE
258  LOGICAL :: arg1
259  is = bd%is
260  ie = bd%ie
261  js = bd%js
262  je = bd%je
263  isd = bd%isd
264  ied = bd%ied
265  jsd = bd%jsd
266  jed = bd%jed
267  child_grids => neststruct%child_grids
268 !IF nested, set up nested grid BCs for time-interpolation
269 !(actually applying the BCs is done in dyn_core
270  nest_timestep = 0
271  IF (.NOT.inline_q) tracer_nest_timestep = 0
272  IF (neststruct%nested .AND. ((.NOT.neststruct%first_step) .OR. &
273 & make_nh)) THEN
274  do_pd = .true.
275  CALL set_bcs_t0(ncnst, flagstruct%hydrostatic, neststruct)
276  ELSE
277 !On first timestep the t0 BCs are not initialized and may contain garbage
278  do_pd = .false.
279  END IF
280 !compute uc/vc for nested-grid BCs
281 !!! CLEANUP: if we compute uc/vc here we don't need to do on the first call of c_sw, right?
282  IF (any(neststruct%child_grids)) THEN
283  CALL timing_on('COMM_TOTAL')
284 !!! CLEANUP: could we make this a non-blocking operation?
285 !!! Is this needed? it is on the initialization step.
286  CALL mpp_update_domains(u, v, domain, gridtype=dgrid_ne, complete=&
287 & .true.)
288  CALL timing_off('COMM_TOTAL')
289 !$OMP parallel do default(none) shared(isd,jsd,ied,jed,is,ie,js,je,npx,npy,npz, &
290 !$OMP gridstruct,flagstruct,bd,u,v,uc,vc,nested,divg) &
291 !$OMP private(ua,va)
292  DO k=1,npz
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)
301  IF (nested) THEN
302  CALL divergence_corner_nest(u(isd, jsd, k), v(isd, jsd, k), ua&
303 & , va, divg(isd, jsd, k), gridstruct, &
304 & flagstruct, bd)
305  ELSE
306  CALL divergence_corner(u(isd, jsd, k), v(isd, jsd, k), ua, va&
307 & , divg(isd, jsd, k), gridstruct, flagstruct, &
308 & bd)
309  END IF
310  END DO
311  END IF
312  IF (flagstruct%hydrostatic) THEN
313 !$OMP parallel do default(none) shared(npz,is,ie,js,je,pkz,pkz_coarse)
314  DO k=1,npz
315  DO j=js,je
316  DO i=is,ie
317  pkz_coarse(i, j, k) = pkz(i, j, k)
318  END DO
319  END DO
320  END DO
321  END IF
322 !! Nested grid: receive from parent grid
323  IF (neststruct%nested) THEN
324  IF (.NOT.ALLOCATED(q_buf)) THEN
325  ALLOCATE(q_buf(ncnst))
326  END IF
327  CALL nested_grid_bc_recv(neststruct%nest_domain, 0, 0, npz, bd, &
328 & delp_buf)
329  DO n=1,ncnst
330  CALL nested_grid_bc_recv(neststruct%nest_domain, 0, 0, npz, bd, &
331 & q_buf(n))
332  END DO
333  CALL nested_grid_bc_recv(neststruct%nest_domain, 0, 0, npz, bd, &
334 & pt_buf)
335  IF (flagstruct%hydrostatic) THEN
336  CALL allocate_fv_nest_bc_type(pkz_bc, is, ie, js, je, isd, ied, &
337 & jsd, jed, npx, npy, npz, ng, 0, 0, 0, &
338 & .false.)
339  CALL nested_grid_bc_recv(neststruct%nest_domain, 0, 0, npz, bd, &
340 & pkz_buf)
341  ELSE
342  CALL nested_grid_bc_recv(neststruct%nest_domain, 0, 0, npz, bd, &
343 & w_buf)
344  CALL nested_grid_bc_recv(neststruct%nest_domain, 0, 0, npz, bd, &
345 & delz_buf)
346  END IF
347  CALL nested_grid_bc_recv(neststruct%nest_domain, 0, 1, npz, bd, &
348 & u_buf)
349  CALL nested_grid_bc_recv(neststruct%nest_domain, 0, 1, npz, bd, &
350 & vc_buf)
351  CALL nested_grid_bc_recv(neststruct%nest_domain, 1, 0, npz, bd, &
352 & v_buf)
353  CALL nested_grid_bc_recv(neststruct%nest_domain, 1, 0, npz, bd, &
354 & uc_buf)
355  CALL nested_grid_bc_recv(neststruct%nest_domain, 1, 1, npz, bd, &
356 & divg_buf)
357  END IF
358 !! Coarse grid: send to child grids
359  DO p=1,SIZE(child_grids)
360  IF (child_grids(p)) THEN
361  CALL nested_grid_bc_send(delp, neststruct%nest_domain_all(p), 0&
362 & , 0)
363  DO n=1,ncnst
364  CALL nested_grid_bc_send(q(:, :, :, n), neststruct%&
365 & nest_domain_all(p), 0, 0)
366  END DO
367  CALL nested_grid_bc_send(pt, neststruct%nest_domain_all(p), 0, 0&
368 & )
369  IF (flagstruct%hydrostatic) THEN
370 !Working with PKZ is more complicated since it is only defined on the interior of the grid.
371  CALL nested_grid_bc_send(pkz_coarse, neststruct%&
372 & nest_domain_all(p), 0, 0)
373  ELSE
374  CALL nested_grid_bc_send(w, neststruct%nest_domain_all(p), 0, &
375 & 0)
376  CALL nested_grid_bc_send(delz, neststruct%nest_domain_all(p), &
377 & 0, 0)
378  END IF
379  CALL nested_grid_bc_send(u, neststruct%nest_domain_all(p), 0, 1)
380  CALL nested_grid_bc_send(vc, neststruct%nest_domain_all(p), 0, 1&
381 & )
382  CALL nested_grid_bc_send(v, neststruct%nest_domain_all(p), 1, 0)
383  CALL nested_grid_bc_send(uc, neststruct%nest_domain_all(p), 1, 0&
384 & )
385  CALL nested_grid_bc_send(divg, neststruct%nest_domain_all(p), 1&
386 & , 1)
387  END IF
388  END DO
389 !Nested grid: do computations
390  IF (nested) THEN
391  CALL nested_grid_bc_save_proc(neststruct%nest_domain, neststruct%&
392 & ind_h, neststruct%wt_h, 0, 0, npx, npy, &
393 & npz, bd, neststruct%delp_bc, delp_buf, &
394 & do_pd)
395  DO n=1,ncnst
396  CALL nested_grid_bc_save_proc(neststruct%nest_domain, neststruct&
397 & %ind_h, neststruct%wt_h, 0, 0, npx, npy&
398 & , npz, bd, neststruct%q_bc(n), q_buf(n)&
399 & , do_pd)
400  END DO
401  CALL nested_grid_bc_save_proc(neststruct%nest_domain, neststruct%&
402 & ind_h, neststruct%wt_h, 0, 0, npx, npy, &
403 & npz, bd, neststruct%pt_bc, pt_buf)
404  sphum = get_tracer_index(model_atmos, 'sphum')
405  IF (flagstruct%hydrostatic) THEN
406  CALL nested_grid_bc_save_proc(neststruct%nest_domain, neststruct&
407 & %ind_h, neststruct%wt_h, 0, 0, npx, npy&
408 & , npz, bd, pkz_bc, pkz_buf)
409  CALL setup_pt_bc(neststruct%pt_bc, pkz_bc, neststruct%q_bc(sphum&
410 & ), npx, npy, npz, zvir, bd)
411  ELSE
412  CALL nested_grid_bc_save_proc(neststruct%nest_domain, neststruct&
413 & %ind_h, neststruct%wt_h, 0, 0, npx, npy&
414 & , npz, bd, neststruct%w_bc, w_buf)
415  CALL nested_grid_bc_save_proc(neststruct%nest_domain, neststruct&
416 & %ind_h, neststruct%wt_h, 0, 0, npx, npy&
417 & , npz, bd, neststruct%delz_bc, delz_buf)
418 !Need a negative-definite method?
419  CALL setup_pt_nh_bc(neststruct%pt_bc, neststruct%delp_bc, &
420 & neststruct%delz_bc, neststruct%q_bc(sphum), &
421 & neststruct%q_bc, ncnst, npx, npy, npz, zvir, bd)
422  END IF
423  CALL nested_grid_bc_save_proc(neststruct%nest_domain, neststruct%&
424 & ind_u, neststruct%wt_u, 0, 1, npx, npy, &
425 & npz, bd, neststruct%u_bc, u_buf)
426  CALL nested_grid_bc_save_proc(neststruct%nest_domain, neststruct%&
427 & ind_u, neststruct%wt_u, 0, 1, npx, npy, &
428 & npz, bd, neststruct%vc_bc, vc_buf)
429  CALL nested_grid_bc_save_proc(neststruct%nest_domain, neststruct%&
430 & ind_v, neststruct%wt_v, 1, 0, npx, npy, &
431 & npz, bd, neststruct%v_bc, v_buf)
432  CALL nested_grid_bc_save_proc(neststruct%nest_domain, neststruct%&
433 & ind_v, neststruct%wt_v, 1, 0, npx, npy, &
434 & npz, bd, neststruct%uc_bc, uc_buf)
435  CALL nested_grid_bc_save_proc(neststruct%nest_domain, neststruct%&
436 & ind_b, neststruct%wt_b, 1, 1, npx, npy, &
437 & npz, bd, neststruct%divg_bc, divg_buf)
438  END IF
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
445  IF (neststruct%nested) CALL set_nh_bcs_t0(neststruct)
446  flagstruct%make_nh = .false.
447  END IF
448 !Unnecessary?
449 !!$ if ( neststruct%nested .and. .not. neststruct%divg_BC%initialized) then
450 !!$ neststruct%divg_BC%east_t0 = neststruct%divg_BC%east_t1
451 !!$ neststruct%divg_BC%west_t0 = neststruct%divg_BC%west_t1
452 !!$ neststruct%divg_BC%north_t0 = neststruct%divg_BC%north_t1
453 !!$ neststruct%divg_BC%south_t0 = neststruct%divg_BC%south_t1
454 !!$ neststruct%divg_BC%initialized = .true.
455 !!$ endif
456  CALL mpp_sync_self()
457  END SUBROUTINE setup_nested_grid_bcs
458  SUBROUTINE setup_pt_bc(pt_bc, pkz_bc, sphum_bc, npx, npy, npz, zvir, &
459 & bd)
460  IMPLICIT NONE
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
470  is = bd%is
471  ie = bd%ie
472  js = bd%js
473  je = bd%je
474  isd = bd%isd
475  ied = bd%ied
476  jsd = bd%jsd
477  jed = bd%jed
478  IF (is .EQ. 1) THEN
479  ptbc => pt_bc%west_t1
480  pkzbc => pkz_bc%west_t1
481  sphumbc => sphum_bc%west_t1
482 !$OMP parallel do default(none) shared(npz,jsd,jed,isd,ptBC,pkzBC,zvir,sphumBC)
483  DO k=1,npz
484  DO j=jsd,jed
485  DO i=isd,0
486  ptbc(i, j, k) = ptbc(i, j, k)/pkzbc(i, j, k)*(1.+zvir*&
487 & sphumbc(i, j, k))
488  END DO
489  END DO
490  END DO
491  END IF
492  IF (js .EQ. 1) THEN
493  ptbc => pt_bc%south_t1
494  pkzbc => pkz_bc%south_t1
495  sphumbc => sphum_bc%south_t1
496  IF (is .EQ. 1) THEN
497  istart = is
498  ELSE
499  istart = isd
500  END IF
501  IF (ie .EQ. npx - 1) THEN
502  iend = ie
503  ELSE
504  iend = ied
505  END IF
506 !$OMP parallel do default(none) shared(npz,jsd,istart,iend,ptBC,pkzBC,zvir,sphumBC)
507  DO k=1,npz
508  DO j=jsd,0
509  DO i=istart,iend
510  ptbc(i, j, k) = ptbc(i, j, k)/pkzbc(i, j, k)*(1.+zvir*&
511 & sphumbc(i, j, k))
512  END DO
513  END DO
514  END DO
515  END IF
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
520 !$OMP parallel do default(none) shared(npz,jsd,jed,npx,ied,ptBC,pkzBC,zvir,sphumBC)
521  DO k=1,npz
522  DO j=jsd,jed
523  DO i=npx,ied
524  ptbc(i, j, k) = ptbc(i, j, k)/pkzbc(i, j, k)*(1.+zvir*&
525 & sphumbc(i, j, k))
526  END DO
527  END DO
528  END DO
529  END IF
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
534  IF (is .EQ. 1) THEN
535  istart = is
536  ELSE
537  istart = isd
538  END IF
539  IF (ie .EQ. npx - 1) THEN
540  iend = ie
541  ELSE
542  iend = ied
543  END IF
544 !$OMP parallel do default(none) shared(npz,npy,jed,npx,istart,iend,ptBC,pkzBC,zvir,sphumBC)
545  DO k=1,npz
546  DO j=npy,jed
547  DO i=istart,iend
548  ptbc(i, j, k) = ptbc(i, j, k)/pkzbc(i, j, k)*(1.+zvir*&
549 & sphumbc(i, j, k))
550  END DO
551  END DO
552  END DO
553  END IF
554  END SUBROUTINE setup_pt_bc
555  SUBROUTINE setup_pt_nh_bc(pt_bc, delp_bc, delz_bc, sphum_bc, q_bc, nq&
556 & , npx, npy, npz, zvir, bd)
557  IMPLICIT NONE
558  TYPE(FV_GRID_BOUNDS_TYPE), INTENT(IN) :: bd
559  TYPE(FV_NEST_BC_TYPE_3D), INTENT(IN), TARGET :: delp_bc, delz_bc, &
560 & sphum_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
566 ! heat capacity of water at 0C
567  REAL, PARAMETER :: c_liq=4185.5
568 ! heat capacity of ice at 0C: c=c_ice+7.3*(T-Tice)
569  REAL, PARAMETER :: c_ice=1972.
570 ! 1384.5
571  REAL, PARAMETER :: cv_vap=cp_vapor-rvgas
572  REAL, DIMENSION(:, :, :), POINTER :: ptbc, sphumbc, qconbc, delpbc, &
573 & delzbc, cappabc
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.
584  REAL :: cvm
585  REAL :: pkz
586  REAL :: rdg
587  REAL :: cv_air
588  INTEGER :: i, j, k, istart, iend
589  INTEGER :: liq_wat, ice_wat, rainwat, snowwat, graupel
590 ! For GFS Partitioning
591  REAL, PARAMETER :: tice=273.16
592  REAL, PARAMETER :: t_i0=15.
593  INTEGER :: is, ie, js, je
594  INTEGER :: isd, ied, jsd, jed
595  INTRINSIC ALLOCATED
596  INTRINSIC log
597  INTRINSIC exp
598  is = bd%is
599  ie = bd%ie
600  js = bd%js
601  je = bd%je
602  isd = bd%isd
603  ied = bd%ied
604  jsd = bd%jsd
605  jed = bd%jed
606  rdg = -(rdgas/grav)
607  cv_air = cp_air - rdgas
608  liq_wat = get_tracer_index(model_atmos, 'liq_wat')
609  ice_wat = get_tracer_index(model_atmos, 'ice_wat')
610  rainwat = get_tracer_index(model_atmos, 'rainwat')
611  snowwat = get_tracer_index(model_atmos, 'snowwat')
612  graupel = get_tracer_index(model_atmos, 'graupel')
613  IF (is .EQ. 1) THEN
614  IF (.NOT.ALLOCATED(dum_west)) THEN
615  ALLOCATE(dum_west(isd:0, jsd:jed, npz))
616 !$OMP parallel do default(none) shared(npz,isd,jsd,jed,dum_West)
617  DO k=1,npz
618  DO j=jsd,jed
619  DO i=isd,0
620  dum_west(i, j, k) = 0.
621  END DO
622  END DO
623  END DO
624  END IF
625  END IF
626  IF (js .EQ. 1) THEN
627  IF (.NOT.ALLOCATED(dum_south)) THEN
628  ALLOCATE(dum_south(isd:ied, jsd:0, npz))
629 !$OMP parallel do default(none) shared(npz,isd,ied,jsd,dum_South)
630  DO k=1,npz
631  DO j=jsd,0
632  DO i=isd,ied
633  dum_south(i, j, k) = 0.
634  END DO
635  END DO
636  END DO
637  END IF
638  END IF
639  IF (ie .EQ. npx - 1) THEN
640  IF (.NOT.ALLOCATED(dum_east)) THEN
641  ALLOCATE(dum_east(npx:ied, jsd:jed, npz))
642 !$OMP parallel do default(none) shared(npx,npz,ied,jsd,jed,dum_East)
643  DO k=1,npz
644  DO j=jsd,jed
645  DO i=npx,ied
646  dum_east(i, j, k) = 0.
647  END DO
648  END DO
649  END DO
650  END IF
651  END IF
652  IF (je .EQ. npy - 1) THEN
653  IF (.NOT.ALLOCATED(dum_north)) THEN
654  ALLOCATE(dum_north(isd:ied, npy:jed, npz))
655 !$OMP parallel do default(none) shared(npy,npz,isd,ied,jed,dum_North)
656  DO k=1,npz
657  DO j=npy,jed
658  DO i=isd,ied
659  dum_north(i, j, k) = 0.
660  END DO
661  END DO
662  END DO
663  END IF
664  END IF
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
670  ELSE
671  liq_watbc_west => dum_west
672  liq_watbc_east => dum_east
673  liq_watbc_north => dum_north
674  liq_watbc_south => dum_south
675  END IF
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
681  ELSE
682  ice_watbc_west => dum_west
683  ice_watbc_east => dum_east
684  ice_watbc_north => dum_north
685  ice_watbc_south => dum_south
686  END IF
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
692  ELSE
693  rainwatbc_west => dum_west
694  rainwatbc_east => dum_east
695  rainwatbc_north => dum_north
696  rainwatbc_south => dum_south
697  END IF
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
703  ELSE
704  snowwatbc_west => dum_west
705  snowwatbc_east => dum_east
706  snowwatbc_north => dum_north
707  snowwatbc_south => dum_south
708  END IF
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
714  ELSE
715  graupelbc_west => dum_west
716  graupelbc_east => dum_east
717  graupelbc_north => dum_north
718  graupelbc_south => dum_south
719  END IF
720  IF (is .EQ. 1) THEN
721  ptbc => pt_bc%west_t1
722  sphumbc => sphum_bc%west_t1
723  delpbc => delp_bc%west_t1
724  delzbc => delz_bc%west_t1
725 !$OMP parallel do default(none) shared(npz,jsd,jed,isd,zvir,sphumBC,liq_watBC_west,rainwatBC_west,ice_watBC_west,snowwatBC_west,g
726 !raupelBC_west,qconBC,cappaBC, &
727 !$OMP rdg,cv_air,delpBC,delzBC,ptBC) &
728 !$OMP private(dp1,q_con,q_liq,q_sol,cvm,pkz)
729  DO k=1,npz
730  DO j=jsd,jed
731  DO i=isd,0
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
736  END DO
737  END DO
738  END DO
739  END IF
740  IF (js .EQ. 1) THEN
741  ptbc => pt_bc%south_t1
742  sphumbc => sphum_bc%south_t1
743  delpbc => delp_bc%south_t1
744  delzbc => delz_bc%south_t1
745  IF (is .EQ. 1) THEN
746  istart = is
747  ELSE
748  istart = isd
749  END IF
750  IF (ie .EQ. npx - 1) THEN
751  iend = ie
752  ELSE
753  iend = ied
754  END IF
755 !$OMP parallel do default(none) shared(npz,jsd,istart,iend,zvir,sphumBC, &
756 !$OMP liq_watBC_south,rainwatBC_south,ice_watBC_south,&
757 !$OMP snowwatBC_south,graupelBC_south,qconBC,cappaBC, &
758 !$OMP rdg,cv_air,delpBC,delzBC,ptBC) &
759 !$OMP private(dp1,q_con,q_liq,q_sol,cvm,pkz)
760  DO k=1,npz
761  DO j=jsd,0
762  DO i=istart,iend
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
767  END DO
768  END DO
769  END DO
770  END IF
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
776 !$OMP parallel do default(none) shared(npz,jsd,jed,npx,ied,zvir,sphumBC, &
777 !$OMP liq_watBC_east,rainwatBC_east,ice_watBC_east,snowwatBC_east,graupelBC_east,qconBC,cappaBC, &
778 !$OMP rdg,cv_air,delpBC,delzBC,ptBC) &
779 !$OMP private(dp1,q_con,q_liq,q_sol,cvm,pkz)
780  DO k=1,npz
781  DO j=jsd,jed
782  DO i=npx,ied
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
787  END DO
788  END DO
789  END DO
790  END IF
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
796  IF (is .EQ. 1) THEN
797  istart = is
798  ELSE
799  istart = isd
800  END IF
801  IF (ie .EQ. npx - 1) THEN
802  iend = ie
803  ELSE
804  iend = ied
805  END IF
806 !$OMP parallel do default(none) shared(npz,npy,jed,istart,iend,zvir, &
807 !$OMP sphumBC,liq_watBC_north,rainwatBC_north,ice_watBC_north,snowwatBC_north,graupelBC_north,qconBC,cappaBC, &
808 !$OMP rdg,cv_air,delpBC,delzBC,ptBC) &
809 !$OMP private(dp1,q_con,q_liq,q_sol,cvm,pkz)
810  DO k=1,npz
811  DO j=npy,jed
812  DO i=istart,iend
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
817  END DO
818  END DO
819  END DO
820  END IF
821  END SUBROUTINE setup_pt_nh_bc
822  SUBROUTINE set_bcs_t0(ncnst, hydrostatic, neststruct)
823  IMPLICIT NONE
824  INTEGER, INTENT(IN) :: ncnst
825  LOGICAL, INTENT(IN) :: hydrostatic
826  TYPE(FV_NEST_TYPE), INTENT(INOUT) :: neststruct
827  INTEGER :: n
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
832  DO n=1,ncnst
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
837  END DO
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
846  IF (.NOT.hydrostatic) CALL set_nh_bcs_t0(neststruct)
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
867  END SUBROUTINE set_bcs_t0
868  SUBROUTINE set_nh_bcs_t0(neststruct)
869  IMPLICIT NONE
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
879  END SUBROUTINE set_nh_bcs_t0
880 !! nestupdate types
881 !! 1 - Interpolation update on all variables
882 !! 2 - Conserving update (over areas on cell-
883 !! centered variables, over faces on winds) on all variables
884 !! 3 - Interpolation update on winds only
885 !! 4 - Interpolation update on all variables except delp (mass conserving)
886 !! 5 - Remap interpolating update, delp not updated
887 !! 6 - Remap conserving update, delp not updated
888 !! 7 - Remap conserving update, delp and q not updated
889 !! 8 - Remap conserving update, only winds updated
890 !! Note that nestupdate > 3 will not update delp.
891 !! "Remap update" remaps updated variables from the nested grid's
892 !! vertical coordinate to that of the coarse grid. When delp is not
893 !! updated (nestbctype >= 3) the vertical coordinates differ on
894 !! the two grids, because the surface pressure will be different
895 !! on the two grids.
896 !! Note: "conserving updates" do not guarantee global conservation
897 !! unless flux nested grid BCs are specified, or if a quantity is
898 !! not updated at all. This ability has not been implemented.
899  SUBROUTINE twoway_nesting(atm, ngrids, grids_on_this_pe, zvir)
900  IMPLICIT NONE
901  INTEGER, INTENT(IN) :: ngrids
902  TYPE(fv_atmos_type), INTENT(INOUT) :: atm(ngrids)
903  LOGICAL, INTENT(IN) :: grids_on_this_pe(ngrids)
904  REAL, INTENT(IN) :: zvir
905  INTEGER :: n, p, sphum
906 ! ngrids > 1
907  IF (ngrids .GT. 1) THEN
908 !loop backwards to allow information to propagate from finest to coarsest grids
909  DO n=ngrids,2,-1
910 !two-way updating
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
914  sphum = get_tracer_index(model_atmos, 'sphum')
915  CALL twoway_nest_update(atm(n)%npx, atm(n)%npy, atm(n)%npz, &
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.)
923  END IF
924  END IF
925  END DO
926 !NOTE: these routines need to be used with any grid which has been updated to, not just the coarsest grid.
927  DO n=1,ngrids
928  IF (atm(n)%neststruct%parent_of_twoway .AND. grids_on_this_pe(n)&
929 & ) CALL after_twoway_nest_update(atm(n)%npx, atm(n)%npy, atm(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)%&
937 & domain, atm(n)%bd)
938  END DO
939  END IF
940  END SUBROUTINE twoway_nesting
941 !!!CLEANUP: this routine assumes that the PARENT GRID has pt = (regular) temperature,
942 !!!not potential temperature; which may cause problems when updating if this is not the case.
943  SUBROUTINE twoway_nest_update(npx, npy, npz, zvir, ncnst, sphum, u, v&
944 & , w, omga, pt, delp, q, uc, vc, pkz, delz, ps, ptop, gridstruct, &
945 & flagstruct, neststruct, parent_grid, bd, conv_theta_in)
946  IMPLICIT NONE
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
952 ! D grid zonal wind (m/s)
953  REAL, DIMENSION(bd%isd:bd%ied, bd%jsd:bd%jed+1, npz), INTENT(INOUT) &
954 & :: u
955 ! D grid meridional wind (m/s)
956  REAL, DIMENSION(bd%isd:bd%ied+1, bd%jsd:bd%jed, npz), INTENT(INOUT) &
957 & :: v
958 ! W (m/s)
959  REAL, INTENT(INOUT) :: w(bd%isd:, bd%jsd:, :)
960 ! Vertical pressure velocity (pa/s)
961  REAL, INTENT(INOUT) :: omga(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
962 ! temperature (K)
963  REAL, INTENT(INOUT) :: pt(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
964 ! pressure thickness (pascal)
965  REAL, INTENT(INOUT) :: delp(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
966 ! specific humidity and constituents
967  REAL, INTENT(INOUT) :: q(bd%isd:bd%ied, bd%jsd:bd%jed, npz, ncnst)
968 ! (uc,vc) C grid winds
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)
971 ! finite-volume mean pk
972  REAL, INTENT(INOUT) :: pkz(bd%is:bd%ie, bd%js:bd%je, npz)
973 ! delta-height (m); non-hydrostatic only
974  REAL, INTENT(INOUT) :: delz(bd%isd:, bd%jsd:, :)
975 ! Surface pressure (pascal)
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
987  REAL, SAVE :: fix=1.
988  LOGICAL :: used
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)
994  INTEGER :: upoff
995  INTEGER :: is, ie, js, je
996  INTEGER :: isd, ied, jsd, jed
997  INTEGER :: isu, ieu, jsu, jeu
998  INTRINSIC PRESENT
999  INTRINSIC ALLOCATED
1000  is = bd%is
1001  ie = bd%ie
1002  js = bd%js
1003  je = bd%je
1004  isd = bd%isd
1005  ied = bd%ied
1006  jsd = bd%jsd
1007  jed = bd%jed
1008  isu = neststruct%isu
1009  ieu = neststruct%ieu
1010  jsu = neststruct%jsu
1011  jeu = neststruct%jeu
1012  upoff = neststruct%upoff
1013 !We update actual temperature, not theta.
1014 !If pt is actual temperature, set conv_theta to .false.
1015  IF (PRESENT(conv_theta_in)) conv_theta = conv_theta_in
1016  IF (.NOT.neststruct%parent_proc .AND. (.NOT.neststruct%child_proc)) &
1017 & THEN
1018  RETURN
1019  ELSE
1020  CALL mpp_get_data_domain(parent_grid%domain, isd_p, ied_p, jsd_p, &
1021 & jed_p)
1022  CALL mpp_get_compute_domain(parent_grid%domain, isc_p, iec_p, &
1023 & jsc_p, jec_p)
1024 !delp/ps
1025  IF (neststruct%nestupdate .LT. 3) THEN
1026  CALL update_coarse_grid(parent_grid%delp, delp, neststruct%&
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)
1035 !self
1036  CALL mpp_sync()
1037  END IF
1038 !if (neststruct%nestupdate /= 3 .and. neststruct%nestbctype /= 3) then
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))
1044  q_diff = 0.
1045  END IF
1046  DO n=1,parent_grid%flagstruct%nwat
1047  qdp_coarse = 0.
1048  IF (neststruct%child_proc) THEN
1049  DO k=1,npz
1050  DO j=jsd,jed
1051  DO i=isd,ied
1052  qdp(i, j, k) = q(i, j, k, n)*delp(i, j, k)
1053  END DO
1054  END DO
1055  END DO
1056  ELSE
1057  qdp = 0.
1058  END IF
1059  IF (neststruct%parent_proc) THEN
1060 !Add up ONLY region being replaced by nested grid
1061  DO k=1,npz
1062  DO j=jsu,jeu
1063  DO i=isu,ieu
1064  qdp_coarse(i, j, k) = parent_grid%q(i, j, k, n)*&
1065 & parent_grid%delp(i, j, k)
1066  END DO
1067  END DO
1068  END DO
1069  CALL level_sum(qdp_coarse, parent_grid%gridstruct%area, &
1070 & parent_grid%domain, parent_grid%bd, npz, l_sum_b)
1071  ELSE
1072  qdp_coarse = 0.
1073  END IF
1074  IF (neststruct%parent_proc) THEN
1075  IF (n .LE. parent_grid%flagstruct%nwat) THEN
1076  DO k=1,npz
1077  DO j=jsu,jeu
1078  DO i=isu,ieu
1079  q_diff(i, j, k) = q_diff(i, j, k) - qdp_coarse(i, j&
1080 & , k)
1081  END DO
1082  END DO
1083  END DO
1084  END IF
1085  END IF
1086  CALL update_coarse_grid(qdp_coarse, qdp, neststruct%&
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, &
1095 & parent_grid)
1096 !self
1097  CALL mpp_sync()
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)
1101  DO k=1,npz
1102  IF (l_sum_a(k) .GT. 0.) THEN
1103  fix = l_sum_b(k)/l_sum_a(k)
1104  DO j=jsu,jeu
1105  DO i=isu,ieu
1106 !Normalization mass fixer
1107  parent_grid%q(i, j, k, n) = qdp_coarse(i, j, k)*fix
1108  END DO
1109  END DO
1110  END IF
1111  END DO
1112  IF (n .EQ. 1) sphum_ll_fix = 1. - fix
1113  END IF
1114  IF (neststruct%parent_proc) THEN
1115  IF (n .LE. parent_grid%flagstruct%nwat) THEN
1116  DO k=1,npz
1117  DO j=jsu,jeu
1118  DO i=isu,ieu
1119  q_diff(i, j, k) = q_diff(i, j, k) + parent_grid%q(i&
1120 & , j, k, n)
1121  END DO
1122  END DO
1123  END DO
1124  END IF
1125  END IF
1126  END DO
1127  IF (neststruct%parent_proc) THEN
1128  IF (parent_grid%flagstruct%nwat .GT. 0) THEN
1129  DO k=1,npz
1130  DO j=jsu,jeu
1131  DO i=isu,ieu
1132  parent_grid%delp(i, j, k) = parent_grid%delp(i, j, k) &
1133 & + q_diff(i, j, k)
1134  END DO
1135  END DO
1136  END DO
1137  END IF
1138  DO n=1,parent_grid%flagstruct%nwat
1139  DO k=1,npz
1140  DO j=jsu,jeu
1141  DO i=isu,ieu
1142  parent_grid%q(i, j, k, n) = parent_grid%q(i, j, k, n)/&
1143 & parent_grid%delp(i, j, k)
1144  END DO
1145  END DO
1146  END DO
1147  END DO
1148  END IF
1149  DEALLOCATE(qdp_coarse)
1150  IF (ALLOCATED(q_diff)) THEN
1151  DEALLOCATE(q_diff)
1152  END IF
1153  END IF
1154 !Neststruct%nestupdate /= 3
1155  IF (neststruct%nestupdate .NE. 3 .AND. neststruct%nestupdate .NE. &
1156 & 8) THEN
1157 !conv_theta
1158  IF (conv_theta) THEN
1159  IF (neststruct%child_proc) THEN
1160 !pt is potential temperature on the nested grid, but actual
1161 !temperature on the coarse grid. Compute actual temperature
1162 !on the nested grid, then gather.
1163  ALLOCATE(t_nest(isd:ied, jsd:jed, 1:npz))
1164 !$OMP parallel do default(none) shared(npz,js,je,is,ie,t_nest,pt,pkz,zvir,q,sphum)
1165  DO k=1,npz
1166  DO j=js,je
1167  DO i=is,ie
1168  t_nest(i, j, k) = pt(i, j, k)*pkz(i, j, k)/(1.+zvir*q(&
1169 & i, j, k, sphum))
1170  END DO
1171  END DO
1172  END DO
1173  DEALLOCATE(t_nest)
1174  END IF
1175  CALL update_coarse_grid(parent_grid%pt, t_nest, neststruct%&
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, &
1184 & parent_grid)
1185  ELSE
1186  CALL update_coarse_grid(parent_grid%pt, pt, neststruct%&
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, &
1195 & parent_grid)
1196  END IF
1197 !self
1198  CALL mpp_sync()
1199  IF (.NOT.flagstruct%hydrostatic) THEN
1200  CALL update_coarse_grid(parent_grid%w, w, neststruct%&
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, &
1209 & parent_grid)
1210 !Updating for delz not yet implemented; may be problematic
1211 !!$ call update_coarse_grid(parent_grid%delz, delz, neststruct%nest_domain, &
1212 !!$ neststruct%ind_update_h, &
1213 !!$ isd_p, ied_p, jsd_p, jed_p, isd, ied, jsd, jed, npz, 0, 0, &
1214 !!$ neststruct%refinement, neststruct%nestupdate, upoff, 0, neststruct%parent_proc, neststruct%child_proc)
1215 !self
1216  CALL mpp_sync()
1217  END IF
1218  END IF
1219  CALL update_coarse_grid(parent_grid%u, u, neststruct%nest_domain, &
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)
1227  CALL update_coarse_grid(parent_grid%v, v, neststruct%nest_domain, &
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)
1235 !self
1236  CALL mpp_sync()
1237  IF (neststruct%nestupdate .GE. 5 .AND. npz .GT. 4) THEN
1238 !Use PS0 from nested grid, NOT the full delp. Also we assume the same number of levels on both grids.
1239 !PS0 should be initially set to be ps so that this routine does NOTHING outside of the update region
1240 !Re-compute nested (AND COARSE) grid ps
1241  ALLOCATE(ps0(isd_p:ied_p, jsd_p:jed_p))
1242  IF (neststruct%parent_proc) THEN
1243  parent_grid%ps = parent_grid%ptop
1244 !This loop appears to cause problems with OMP
1245 !$OMP parallel do default(none) shared(npz,jsd_p,jed_p,isd_p,ied_p,parent_grid)
1246  DO j=jsd_p,jed_p
1247  DO k=1,npz
1248  DO i=isd_p,ied_p
1249  parent_grid%ps(i, j) = parent_grid%ps(i, j) + &
1250 & parent_grid%delp(i, j, k)
1251  END DO
1252  END DO
1253  END DO
1254  ps0 = parent_grid%ps
1255  END IF
1256  IF (neststruct%child_proc) THEN
1257  ps = ptop
1258 !$OMP parallel do default(none) shared(npz,jsd,jed,isd,ied,ps,delp)
1259  DO j=jsd,jed
1260  DO k=1,npz
1261  DO i=isd,ied
1262  ps(i, j) = ps(i, j) + delp(i, j, k)
1263  END DO
1264  END DO
1265  END DO
1266  END IF
1267  CALL update_coarse_grid(ps0, ps, neststruct%nest_domain, &
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&
1275 & , parent_grid)
1276 !!! The mpp version of update_coarse_grid does not return a consistent value of ps
1277 !!! across PEs, as it does not go into the haloes of a given coarse-grid PE. This
1278 !!! update_domains call takes care of the problem.
1279  IF (neststruct%parent_proc) THEN
1280  CALL mpp_update_domains(parent_grid%ps, parent_grid%domain, &
1281 & complete=.true.)
1282  CALL mpp_update_domains(ps0, parent_grid%domain, complete=&
1283 & .true.)
1284  END IF
1285 !self
1286  CALL mpp_sync()
1287  IF (parent_grid%tile .EQ. neststruct%parent_tile) THEN
1288 !neststruct%parent_proc
1289  IF (neststruct%parent_proc) THEN
1290 !comment out if statement to always remap theta instead of t in the remap-update.
1291 !(In LtE typically we use remap_t = .true.: remapping t is better (except in
1292 !idealized simulations with a background uniform theta) since near the top
1293 !boundary theta is exponential, which is hard to accurately interpolate with a spline
1294  IF (parent_grid%flagstruct%remap_option .NE. 0) THEN
1295 !$OMP parallel do default(none) shared(npz,jsc_p,jec_p,isc_p,iec_p,parent_grid,zvir,sphum)
1296  DO k=1,npz
1297  DO j=jsc_p,jec_p
1298  DO i=isc_p,iec_p
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&
1301 & , j, k, sphum))
1302  END DO
1303  END DO
1304  END DO
1305  END IF
1306  CALL update_remap_tqw(npz, parent_grid%ak, parent_grid%bk, &
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.)
1315 !neststruct%nestupdate < 7)
1316  IF (parent_grid%flagstruct%remap_option .NE. 0) THEN
1317 !$OMP parallel do default(none) shared(npz,jsc_p,jec_p,isc_p,iec_p,parent_grid,zvir,sphum)
1318  DO k=1,npz
1319  DO j=jsc_p,jec_p
1320  DO i=isc_p,iec_p
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&
1323 & , j, k, sphum))
1324  END DO
1325  END DO
1326  END DO
1327  END IF
1328  CALL update_remap_uv(npz, parent_grid%ak, parent_grid%bk, &
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)
1333  END IF
1334  END IF
1335  IF (ALLOCATED(ps0)) THEN
1336  DEALLOCATE(ps0)
1337  END IF
1338  END IF
1339  END IF
1340  END SUBROUTINE twoway_nest_update
1341  SUBROUTINE level_sum(q, area, domain, bd, npz, l_sum)
1342  IMPLICIT NONE
1343 ! L_sum(k) = mpp_global_sum(domain, qA, flags=BITWISE_EXACT_SUM)
1344 ! L_sum(k) = mpp_global_sum(domain, qA, flags=BITWISE_EFP_SUM) ! doesn't work??
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
1352 !(bd%is:bd%ie, bd%js:bd%je)
1353  REAL :: qa
1354  DO k=1,npz
1355  qa = 0.
1356  DO j=bd%js,bd%je
1357  DO i=bd%is,bd%ie
1358 !qA(i,j) = q(i,j,k)*area(i,j)
1359  qa = qa + q(i, j, k)*area(i, j)
1360  END DO
1361  END DO
1362  CALL mp_reduce_sum(qa)
1363  l_sum(k) = qa
1364  END DO
1365  END SUBROUTINE level_sum
1366  SUBROUTINE after_twoway_nest_update(npx, npy, npz, ng, ncnst, u, v, w&
1367 & , delz, pt, delp, q, ps, pe, pk, peln, pkz, phis, ua, va, ptop, &
1368 & gridstruct, flagstruct, domain, bd)
1369  IMPLICIT NONE
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
1374 ! D grid zonal wind (m/s)
1375  REAL, DIMENSION(bd%isd:bd%ied, bd%jsd:bd%jed+1, npz), INTENT(INOUT) &
1376 & :: u
1377 ! D grid meridional wind (m/s)
1378  REAL, DIMENSION(bd%isd:bd%ied+1, bd%jsd:bd%jed, npz), INTENT(INOUT) &
1379 & :: v
1380 ! W (m/s)
1381  REAL, INTENT(INOUT) :: w(bd%isd:, bd%jsd:, :)
1382 ! temperature (K)
1383  REAL, INTENT(INOUT) :: pt(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
1384 ! pressure thickness (pascal)
1385  REAL, INTENT(INOUT) :: delp(bd%isd:bd%ied, bd%jsd:bd%jed, npz)
1386 ! specific humidity and constituents
1387  REAL, INTENT(INOUT) :: q(bd%isd:bd%ied, bd%jsd:bd%jed, npz, ncnst)
1388 ! delta-height (m); non-hydrostatic only
1389  REAL, INTENT(INOUT) :: delz(bd%isd:, bd%jsd:, :)
1390 !-----------------------------------------------------------------------
1391 ! Auxilliary pressure arrays:
1392 ! The 5 vars below can be re-computed from delp and ptop.
1393 !-----------------------------------------------------------------------
1394 ! dyn_aux:
1395 ! Surface pressure (pascal)
1396  REAL, INTENT(INOUT) :: ps(bd%isd:bd%ied, bd%jsd:bd%jed)
1397 ! edge pressure (pascal)
1398  REAL, INTENT(INOUT) :: pe(bd%is-1:bd%ie+1, npz+1, bd%js-1:bd%je+1)
1399 ! pe**cappa
1400  REAL, INTENT(INOUT) :: pk(bd%is:bd%ie, bd%js:bd%je, npz+1)
1401 ! ln(pe)
1402  REAL, INTENT(INOUT) :: peln(bd%is:bd%ie, npz+1, bd%js:bd%je)
1403 ! finite-volume mean pk
1404  REAL, INTENT(INOUT) :: pkz(bd%is:bd%ie, bd%js:bd%je, npz)
1405 !-----------------------------------------------------------------------
1406 ! Others:
1407 !-----------------------------------------------------------------------
1408 ! Surface geopotential (g*Z_surf)
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) ::&
1411 & ua, va
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
1418  is = bd%is
1419  ie = bd%ie
1420  js = bd%js
1421  je = bd%je
1422  isd = bd%isd
1423  ied = bd%ied
1424  jsd = bd%jsd
1425  jed = bd%jed
1426  CALL cubed_to_latlon(u, v, ua, va, gridstruct, npx, npy, npz, 1, &
1427 & gridstruct%grid_type, domain, gridstruct%nested, &
1428 & flagstruct%c2l_ord, bd)
1429 !To get coarse grid pkz, etc right after a two-way update so
1430 !that it is consistent across a restart:
1431 !(should only be called after doing such an update)
1432 !! CLEANUP: move to twoway_nest_update??
1433 !mountain argument not used
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&
1448 & , -50., 100., &
1449 & bad_range)
1450  END IF
1451  END SUBROUTINE after_twoway_nest_update
1452 !Routines for remapping (interpolated) nested-grid data to the coarse-grid's vertical coordinate.
1453 !This does not yet do anything for the tracers
1454  SUBROUTINE update_remap_tqw(npz, ak, bk, ps, delp, t, q, w, &
1455 & hydrostatic, kmd, ps0, zvir, ptop, nq, kord_tm, kord_tr, kord_wz, is&
1456 & , ie, js, je, isd, ied, jsd, jed, do_q)
1457  IMPLICIT NONE
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
1468 ! local:
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
1474  INTRINSIC log
1475  INTRINSIC abs
1476  INTEGER :: abs0
1477 !$OMP parallel do default(none) shared(js,je,kmd,is,ie,ak,bk,ps0,q,npz,ptop,do_q,&
1478 !$OMP t,w,ps,nq,hydrostatic,kord_tm,kord_tr,kord_wz) &
1479 !$OMP private(pe0,pn0,pe1,pn1,qp,tp,qn1)
1480  DO j=js,je
1481  DO k=1,kmd+1
1482  DO i=is,ie
1483  pe0(i, k) = ak(k) + bk(k)*ps0(i, j)
1484  pn0(i, k) = log(pe0(i, k))
1485  END DO
1486  END DO
1487  DO k=1,kmd+1
1488  DO i=is,ie
1489  pe1(i, k) = ak(k) + bk(k)*ps(i, j)
1490  pn1(i, k) = log(pe1(i, k))
1491  END DO
1492  END DO
1493  IF (do_q) THEN
1494  DO iq=1,nq
1495  DO k=1,kmd
1496  DO i=is,ie
1497  qp(i, k) = q(i, j, k, iq)
1498  END DO
1499  END DO
1500  CALL mappm(kmd, pe0, qp, npz, pe1, qn1, is, ie, 0, kord_tr, &
1501 & ptop)
1502  DO k=1,npz
1503  DO i=is,ie
1504  q(i, j, k, iq) = qn1(i, k)
1505  END DO
1506  END DO
1507  END DO
1508  END IF
1509  DO k=1,kmd
1510  DO i=is,ie
1511  tp(i, k) = t(i, j, k)
1512  END DO
1513  END DO
1514  IF (kord_tm .GE. 0.) THEN
1515  abs0 = kord_tm
1516  ELSE
1517  abs0 = -kord_tm
1518  END IF
1519 !Remap T using logp
1520  CALL mappm(kmd, pn0, tp, npz, pn1, qn1, is, ie, 1, abs0, ptop)
1521  DO k=1,npz
1522  DO i=is,ie
1523  t(i, j, k) = qn1(i, k)
1524  END DO
1525  END DO
1526  IF (.NOT.hydrostatic) THEN
1527  DO k=1,kmd
1528  DO i=is,ie
1529  tp(i, k) = w(i, j, k)
1530  END DO
1531  END DO
1532 !Remap w using p
1533 !Using iv == -1 instead of -2
1534  CALL mappm(kmd, pe0, tp, npz, pe1, qn1, is, ie, -1, kord_wz, &
1535 & ptop)
1536  DO k=1,npz
1537  DO i=is,ie
1538  w(i, j, k) = qn1(i, k)
1539  END DO
1540  END DO
1541  END IF
1542  END DO
1543  END SUBROUTINE update_remap_tqw
1544 !remap_uv as-is remaps only a-grid velocities. A new routine has been written to handle staggered grids.
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)
1547  IMPLICIT NONE
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
1554 !
1555  INTEGER, INTENT(IN) :: kmd, kord_mt
1556  REAL, INTENT(IN) :: ptop
1557  REAL, INTENT(IN) :: ps0(isd:ied, jsd:jed)
1558 !
1559 ! local:
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
1564  INTEGER :: i, j, k
1565  INTEGER :: arg1
1566 !------
1567 ! map u
1568 !------
1569 !$OMP parallel do default(none) shared(js,je,kmd,is,ie,ak,bk,ps,ps0,npz,u,ptop,kord_mt) &
1570 !$OMP private(pe0,pe1,qt,qn1)
1571  DO j=js,je+1
1572 !------
1573 ! Data
1574 !------
1575  DO k=1,kmd+1
1576  DO i=is,ie
1577  pe0(i, k) = ak(k) + bk(k)*0.5*(ps0(i, j)+ps0(i, j-1))
1578  END DO
1579  END DO
1580 !------
1581 ! Model
1582 !------
1583  DO k=1,kmd+1
1584  DO i=is,ie
1585  pe1(i, k) = ak(k) + bk(k)*0.5*(ps(i, j)+ps(i, j-1))
1586  END DO
1587  END DO
1588 !------
1589 !Do map
1590 !------
1591  qt = 0.
1592  DO k=1,kmd
1593  DO i=is,ie
1594  qt(i, k) = u(i, j, k)
1595  END DO
1596  END DO
1597  qn1 = 0.
1598  CALL mappm(kmd, pe0(is:ie, :), qt(is:ie, :), npz, pe1(is:ie, :), &
1599 & qn1(is:ie, :), is, ie, -1, kord_mt, ptop)
1600  DO k=1,npz
1601  DO i=is,ie
1602  u(i, j, k) = qn1(i, k)
1603  END DO
1604  END DO
1605  END DO
1606 !------
1607 ! map v
1608 !------
1609 !$OMP parallel do default(none) shared(js,je,kmd,is,ie,ak,bk,ps,ps0,npz,v,ptop) &
1610 !$OMP private(pe0,pe1,qt,qn1)
1611  DO j=js,je
1612 !------
1613 ! Data
1614 !------
1615  DO k=1,kmd+1
1616  DO i=is,ie+1
1617  pe0(i, k) = ak(k) + bk(k)*0.5*(ps0(i, j)+ps0(i-1, j))
1618  END DO
1619  END DO
1620 !------
1621 ! Model
1622 !------
1623  DO k=1,kmd+1
1624  DO i=is,ie+1
1625  pe1(i, k) = ak(k) + bk(k)*0.5*(ps(i, j)+ps(i-1, j))
1626  END DO
1627  END DO
1628 !------
1629 !Do map
1630 !------
1631  qt = 0.
1632  DO k=1,kmd
1633  DO i=is,ie+1
1634  qt(i, k) = v(i, j, k)
1635  END DO
1636  END DO
1637  qn1 = 0.
1638  arg1 = ie + 1
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)
1641  DO k=1,npz
1642  DO i=is,ie+1
1643  v(i, j, k) = qn1(i, k)
1644  END DO
1645  END DO
1646  END DO
1647  END SUBROUTINE update_remap_uv
1648 end module fv_nesting_adm_mod
type(fv_nest_bc_type_3d), dimension(:), allocatable q_buf
real, parameter, public radius
Radius of the Earth [m].
Definition: constants.F90:72
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].
Definition: constants.F90:73
real, parameter, public hlv
Latent heat of evaporation [J/kg].
Definition: constants.F90:80
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].
Definition: constants.F90:77
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].
Definition: constants.F90:89
subroutine pushcontrol1b(cc)
Definition: adBuffer.f:115
subroutine, public cubed_to_latlon(u, v, ua, va, gridstruct, npx, npy, km, mode, grid_type, domain, nested, c2l_ord, bd)
Definition: mpp.F90:39
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].
Definition: constants.F90:78
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].
Definition: constants.F90:83
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].
Definition: constants.F90:76
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)
Definition: fv_sg_nlm.F90:1132
subroutine popcontrol1b(cc)
Definition: adBuffer.f:120
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].
Definition: constants.F90:82
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)