FV3 Bundle
fv_nesting_nlm.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, mpp_update_domains, domain2d
30  use mpp_mod, only: mpp_sync_self, mpp_sync, mpp_send, mpp_recv, mpp_error, fatal
31  use mpp_domains_mod, only: mpp_global_sum, bitwise_efp_sum, bitwise_exact_sum
34  use fv_mp_nlm_mod, only: is, ie, js, je, isd, ied, jsd, jed, isc, iec, jsc, jec
38  use init_hydro_nlm_mod, only: p_var
40  use fv_mapz_nlm_mod, only: mappm
42  use fv_mp_nlm_mod, only: is_master
43  use fv_mp_nlm_mod, only: mp_reduce_sum
46 
47 implicit none
48  logical :: rf_initialized = .false.
49  logical :: bad_range
50  real, allocatable :: rf(:), rw(:)
51  integer :: kmax=1
52  !Arrays for global grid total energy, used for grid nesting
53  real, allocatable :: te_2d_coarse(:,:)
54  real, allocatable :: dp1_coarse(:,:,:)
55 
56  !For nested grid buffers
57  !Individual structures are allocated by nested_grid_BC_recv
59  type(fv_nest_bc_type_3d), allocatable:: q_buf(:)
60 !#ifdef USE_COND
61  real, dimension(:,:,:), allocatable, target :: dum_west, dum_east, dum_north, dum_south
62 !#endif
63 
64 private
66 
67 contains
68 
69 !!!! NOTE: Many of the routines here and in boundary_nlm.F90 have a lot of
70 !!!! redundant code, which could be cleaned up and simplified.
71 
72  subroutine setup_nested_grid_bcs(npx, npy, npz, zvir, ncnst, &
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, &
77  domain, bd, nwat)
78 
79 
80  type(fv_grid_bounds_type), intent(IN) :: bd
81  real, intent(IN) :: zvir
82 
83  integer, intent(IN) :: npx, npy, npz
84  integer, intent(IN) :: ncnst, ng, nwat
85  logical, intent(IN) :: inline_q, make_nh,nested
86 
87  real, intent(inout), dimension(bd%isd:bd%ied ,bd%jsd:bd%jed+1,npz) :: u ! D grid zonal wind (m/s)
88  real, intent(inout), dimension(bd%isd:bd%ied+1,bd%jsd:bd%jed ,npz) :: v ! D grid meridional wind (m/s)
89  real, intent(inout) :: w( bd%isd: ,bd%jsd: ,1:) ! W (m/s)
90  real, intent(inout) :: pt( bd%isd:bd%ied ,bd%jsd:bd%jed ,npz) ! temperature (K)
91  real, intent(inout) :: delp(bd%isd:bd%ied ,bd%jsd:bd%jed ,npz) ! pressure thickness (pascal)
92  real, intent(inout) :: delz(bd%isd: ,bd%jsd: ,1:) ! height thickness (m)
93  real, intent(inout) :: q( bd%isd:bd%ied ,bd%jsd:bd%jed ,npz, ncnst) ! specific humidity and constituents
94  real, intent(inout) :: uc(bd%isd:bd%ied+1,bd%jsd:bd%jed ,npz) ! (uc,vc) mostly used as the C grid winds
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) ! finite-volume mean pk
97  integer, intent(INOUT) :: nest_timestep, tracer_nest_timestep
98 
99  type(fv_grid_type), intent(INOUT) :: gridstruct
100  type(fv_flags_type), intent(INOUT) :: flagstruct
101  type(fv_nest_type), intent(INOUT), target :: neststruct
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)
106 
107  real :: pkz_coarse( bd%isd:bd%ied ,bd%jsd:bd%jed ,npz)
108  integer :: i,j,k,n,p, sphum
109  logical :: do_pd
110 
111  type(fv_nest_bc_type_3d) :: pkz_bc
112 
113  !local pointers
114  logical, pointer :: child_grids(:)
115 
116  integer :: is, ie, js, je
117  integer :: isd, ied, jsd, jed
118 
119  is = bd%is
120  ie = bd%ie
121  js = bd%js
122  je = bd%je
123  isd = bd%isd
124  ied = bd%ied
125  jsd = bd%jsd
126  jed = bd%jed
127 
128  child_grids => neststruct%child_grids
129 
130 
131  !IF nested, set up nested grid BCs for time-interpolation
132  !(actually applying the BCs is done in dyn_core
133 
134  nest_timestep = 0
135  if (.not. inline_q) tracer_nest_timestep = 0
136 
137 
138  if (neststruct%nested .and. (.not. (neststruct%first_step) .or. make_nh) ) then
139  do_pd = .true.
140  call set_bcs_t0(ncnst, flagstruct%hydrostatic, neststruct)
141  else
142  !On first timestep the t0 BCs are not initialized and may contain garbage
143  do_pd = .false.
144  end if
145 
146  !compute uc/vc for nested-grid BCs
147  !!! CLEANUP: if we compute uc/vc here we don't need to do on the first call of c_sw, right?
148  if (any(neststruct%child_grids)) then
149  call timing_on('COMM_TOTAL')
150  !!! CLEANUP: could we make this a non-blocking operation?
151  !!! Is this needed? it is on the initialization step.
152  call mpp_update_domains(u, v, &
153  domain, gridtype=dgrid_ne, complete=.true.)
154  call timing_off('COMM_TOTAL')
155 !$OMP parallel do default(none) shared(isd,jsd,ied,jed,is,ie,js,je,npx,npy,npz, &
156 !$OMP gridstruct,flagstruct,bd,u,v,uc,vc,nested,divg) &
157 !$OMP private(ua,va)
158  do k=1,npz
159  call d2c_setup(u(isd,jsd,k), v(isd,jsd,k), &
160  ua, va, &
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 )
168  if (nested) then
169  call divergence_corner_nest(u(isd,jsd,k), v(isd,jsd,k), ua, va, divg(isd,jsd,k), gridstruct, flagstruct, bd)
170  else
171  call divergence_corner(u(isd,jsd,k), v(isd,jsd,k), ua, va, divg(isd,jsd,k), gridstruct, flagstruct, bd)
172  endif
173  end do
174  endif
175 
176 #ifndef SW_DYNAMICS
177  if (flagstruct%hydrostatic) then
178 !$OMP parallel do default(none) shared(npz,is,ie,js,je,pkz,pkz_coarse)
179  do k=1,npz
180  do j=js,je
181  do i=is,ie
182  pkz_coarse(i,j,k) = pkz(i,j,k)
183  enddo
184  enddo
185  enddo
186  endif
187 #endif
188 !! Nested grid: receive from parent grid
189  if (neststruct%nested) then
190  if (.not. allocated(q_buf)) then
191  allocate(q_buf(ncnst))
192  endif
193 
194  call nested_grid_bc_recv(neststruct%nest_domain, 0, 0, npz, bd, &
195  delp_buf)
196  do n=1,ncnst
197  call nested_grid_bc_recv(neststruct%nest_domain, 0, 0, npz, bd, &
198  q_buf(n))
199  enddo
200 #ifndef SW_DYNAMICS
201  call nested_grid_bc_recv(neststruct%nest_domain, 0, 0, npz, bd, &
202  pt_buf)
203 
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.)
206  call nested_grid_bc_recv(neststruct%nest_domain, 0, 0, npz, bd, &
207  pkz_buf)
208  else
209  call nested_grid_bc_recv(neststruct%nest_domain, 0, 0, npz, bd, &
210  w_buf)
211  call nested_grid_bc_recv(neststruct%nest_domain, 0, 0, npz, bd, &
212  delz_buf)
213  endif
214 #endif
215  call nested_grid_bc_recv(neststruct%nest_domain, 0, 1, npz, bd, &
216  u_buf)
217  call nested_grid_bc_recv(neststruct%nest_domain, 0, 1, npz, bd, &
218  vc_buf)
219  call nested_grid_bc_recv(neststruct%nest_domain, 1, 0, npz, bd, &
220  v_buf)
221  call nested_grid_bc_recv(neststruct%nest_domain, 1, 0, npz, bd, &
222  uc_buf)
223  call nested_grid_bc_recv(neststruct%nest_domain, 1, 1, npz, bd, &
224  divg_buf)
225  endif
226 
227 
228 !! Coarse grid: send to child grids
229 
230  do p=1,size(child_grids)
231  if (child_grids(p)) then
232  call nested_grid_bc_send(delp, neststruct%nest_domain_all(p), 0, 0)
233  do n=1,ncnst
234  call nested_grid_bc_send(q(:,:,:,n), neststruct%nest_domain_all(p), 0, 0)
235  enddo
236 #ifndef SW_DYNAMICS
237  call nested_grid_bc_send(pt, neststruct%nest_domain_all(p), 0, 0)
238 
239  if (flagstruct%hydrostatic) then
240  !Working with PKZ is more complicated since it is only defined on the interior of the grid.
241  call nested_grid_bc_send(pkz_coarse, neststruct%nest_domain_all(p), 0, 0)
242  else
243  call nested_grid_bc_send(w, neststruct%nest_domain_all(p), 0, 0)
244  call nested_grid_bc_send(delz, neststruct%nest_domain_all(p), 0, 0)
245  endif
246 #endif
247  call nested_grid_bc_send(u, neststruct%nest_domain_all(p), 0, 1)
248  call nested_grid_bc_send(vc, neststruct%nest_domain_all(p), 0, 1)
249  call nested_grid_bc_send(v, neststruct%nest_domain_all(p), 1, 0)
250  call nested_grid_bc_send(uc, neststruct%nest_domain_all(p), 1, 0)
251  call nested_grid_bc_send(divg, neststruct%nest_domain_all(p), 1, 1)
252  endif
253  enddo
254 
255  !Nested grid: do computations
256  if (nested) then
257  call nested_grid_bc_save_proc(neststruct%nest_domain, &
258  neststruct%ind_h, neststruct%wt_h, 0, 0, npx, npy, npz, bd, &
259  neststruct%delp_BC, delp_buf, pd_in=do_pd)
260  do n=1,ncnst
261  call nested_grid_bc_save_proc(neststruct%nest_domain, &
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)
264  enddo
265 #ifndef SW_DYNAMICS
266  call nested_grid_bc_save_proc(neststruct%nest_domain, &
267  neststruct%ind_h, neststruct%wt_h, 0, 0, npx, npy, npz, bd, &
268  neststruct%pt_BC, pt_buf)
269 
270  sphum = get_tracer_index(model_atmos, 'sphum')
271  if (flagstruct%hydrostatic) then
272  call nested_grid_bc_save_proc(neststruct%nest_domain, &
273  neststruct%ind_h, neststruct%wt_h, 0, 0, npx, npy, npz, bd, &
274  pkz_bc, pkz_buf)
275  call setup_pt_bc(neststruct%pt_BC, pkz_bc, neststruct%q_BC(sphum), npx, npy, npz, zvir, bd)
276  else
277  call nested_grid_bc_save_proc(neststruct%nest_domain, &
278  neststruct%ind_h, neststruct%wt_h, 0, 0, npx, npy, npz, bd, &
279  neststruct%w_BC, w_buf)
280  call nested_grid_bc_save_proc(neststruct%nest_domain, &
281  neststruct%ind_h, neststruct%wt_h, 0, 0, npx, npy, npz, bd, &
282  neststruct%delz_BC, delz_buf) !Need a negative-definite method?
283 
284  call setup_pt_nh_bc(neststruct%pt_BC, neststruct%delp_BC, neststruct%delz_BC, &
285  neststruct%q_BC(sphum), neststruct%q_BC, ncnst, &
286 #ifdef USE_COND
287  neststruct%q_con_BC, &
288 #ifdef MOIST_CAPPA
289  neststruct%cappa_BC, &
290 #endif
291 #endif
292  npx, npy, npz, zvir, bd)
293  endif
294 #endif
295  call nested_grid_bc_save_proc(neststruct%nest_domain, &
296  neststruct%ind_u, neststruct%wt_u, 0, 1, npx, npy, npz, bd, &
297  neststruct%u_BC, u_buf)
298  call nested_grid_bc_save_proc(neststruct%nest_domain, &
299  neststruct%ind_u, neststruct%wt_u, 0, 1, npx, npy, npz, bd, &
300  neststruct%vc_BC, vc_buf)
301  call nested_grid_bc_save_proc(neststruct%nest_domain, &
302  neststruct%ind_v, neststruct%wt_v, 1, 0, npx, npy, npz, bd, &
303  neststruct%v_BC, v_buf)
304  call nested_grid_bc_save_proc(neststruct%nest_domain, &
305  neststruct%ind_v, neststruct%wt_v, 1, 0, npx, npy, npz, bd, &
306  neststruct%uc_BC, uc_buf)
307 
308  call nested_grid_bc_save_proc(neststruct%nest_domain, &
309  neststruct%ind_b, neststruct%wt_b, 1, 1, npx, npy, npz, bd, &
310  neststruct%divg_BC, divg_buf)
311  endif
312 
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
318  if (neststruct%nested) call set_nh_bcs_t0(neststruct)
319  flagstruct%make_nh= .false.
320  endif
321 
322  !Unnecessary?
323 !!$ if ( neststruct%nested .and. .not. neststruct%divg_BC%initialized) then
324 !!$ neststruct%divg_BC%east_t0 = neststruct%divg_BC%east_t1
325 !!$ neststruct%divg_BC%west_t0 = neststruct%divg_BC%west_t1
326 !!$ neststruct%divg_BC%north_t0 = neststruct%divg_BC%north_t1
327 !!$ neststruct%divg_BC%south_t0 = neststruct%divg_BC%south_t1
328 !!$ neststruct%divg_BC%initialized = .true.
329 !!$ endif
330 
331 
332  call mpp_sync_self
333 
334  end subroutine setup_nested_grid_bcs
335 
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
343 
344  real, dimension(:,:,:), pointer :: ptBC, pkzBC, sphumBC
345 
346  integer :: i,j,k, istart, iend
347 
348  integer :: is, ie, js, je
349  integer :: isd, ied, jsd, jed
350 
351  is = bd%is
352  ie = bd%ie
353  js = bd%js
354  je = bd%je
355  isd = bd%isd
356  ied = bd%ied
357  jsd = bd%jsd
358  jed = bd%jed
359 
360  if (is == 1) then
361  ptbc => pt_bc%west_t1
362  pkzbc => pkz_bc%west_t1
363  sphumbc => sphum_bc%west_t1
364 !$OMP parallel do default(none) shared(npz,jsd,jed,isd,ptBC,pkzBC,zvir,sphumBC)
365  do k=1,npz
366  do j=jsd,jed
367  do i=isd,0
368  ptbc(i,j,k) = ptbc(i,j,k)/pkzbc(i,j,k)*(1.+zvir*sphumbc(i,j,k))
369  end do
370  end do
371  end do
372  end if
373 
374  if (js == 1) then
375  ptbc => pt_bc%south_t1
376  pkzbc => pkz_bc%south_t1
377  sphumbc => sphum_bc%south_t1
378  if (is == 1) then
379  istart = is
380  else
381  istart = isd
382  end if
383  if (ie == npx-1) then
384  iend = ie
385  else
386  iend = ied
387  end if
388 
389 !$OMP parallel do default(none) shared(npz,jsd,istart,iend,ptBC,pkzBC,zvir,sphumBC)
390  do k=1,npz
391  do j=jsd,0
392  do i=istart,iend
393  ptbc(i,j,k) = ptbc(i,j,k)/pkzbc(i,j,k) * &
394  (1.+zvir*sphumbc(i,j,k))
395  end do
396  end do
397  end do
398  end if
399 
400 
401  if (ie == npx-1) then
402  ptbc => pt_bc%east_t1
403  pkzbc => pkz_bc%east_t1
404  sphumbc => sphum_bc%east_t1
405 !$OMP parallel do default(none) shared(npz,jsd,jed,npx,ied,ptBC,pkzBC,zvir,sphumBC)
406  do k=1,npz
407  do j=jsd,jed
408  do i=npx,ied
409  ptbc(i,j,k) = ptbc(i,j,k)/pkzbc(i,j,k) * &
410  (1.+zvir*sphumbc(i,j,k))
411  end do
412  end do
413  end do
414  end if
415 
416  if (je == npy-1) then
417  ptbc => pt_bc%north_t1
418  pkzbc => pkz_bc%north_t1
419  sphumbc => sphum_bc%north_t1
420  if (is == 1) then
421  istart = is
422  else
423  istart = isd
424  end if
425  if (ie == npx-1) then
426  iend = ie
427  else
428  iend = ied
429  end if
430 
431 !$OMP parallel do default(none) shared(npz,npy,jed,npx,istart,iend,ptBC,pkzBC,zvir,sphumBC)
432  do k=1,npz
433  do j=npy,jed
434  do i=istart,iend
435  ptbc(i,j,k) = ptbc(i,j,k)/pkzbc(i,j,k) * &
436  (1.+zvir*sphumbc(i,j,k))
437  end do
438  end do
439  end do
440  end if
441 
442  end subroutine setup_pt_bc
443 
444  subroutine setup_pt_nh_bc(pt_BC, delp_BC, delz_BC, sphum_BC, q_BC, nq, &
445 #ifdef USE_COND
446  q_con_BC, &
447 #ifdef MOIST_CAPPA
448  cappa_BC, &
449 #endif
450 #endif
451  npx, npy, npz, zvir, bd)
452 
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)
458 #ifdef USE_COND
459  type(fv_nest_BC_type_3d), intent(INOUT), target :: q_con_BC
460 #ifdef MOIST_CAPPA
461  type(fv_nest_BC_type_3d), intent(INOUT), target :: cappa_BC
462 #endif
463 #endif
464  integer, intent(IN) :: npx, npy, npz
465  real, intent(IN) :: zvir
466 
467  real, parameter:: c_liq = 4185.5 ! heat capacity of water at 0C
468  real, parameter:: c_ice = 1972. ! heat capacity of ice at 0C: c=c_ice+7.3*(T-Tice)
469  real, parameter:: cv_vap = cp_vapor - rvgas ! 1384.5
470 
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
476 
477  real :: dp1, q_liq, q_sol, q_con = 0., cvm, pkz, rdg, cv_air
478 
479  integer :: i,j,k, istart, iend
480  integer :: liq_wat, ice_wat, rainwat, snowwat, graupel
481  real, parameter:: tice = 273.16 ! For GFS Partitioning
482  real, parameter:: t_i0 = 15.
483 
484  integer :: is, ie, js, je
485  integer :: isd, ied, jsd, jed
486 
487  is = bd%is
488  ie = bd%ie
489  js = bd%js
490  je = bd%je
491  isd = bd%isd
492  ied = bd%ied
493  jsd = bd%jsd
494  jed = bd%jed
495 
496  rdg = -rdgas / grav
497  cv_air = cp_air - rdgas
498 
499  liq_wat = get_tracer_index(model_atmos, 'liq_wat')
500  ice_wat = get_tracer_index(model_atmos, 'ice_wat')
501  rainwat = get_tracer_index(model_atmos, 'rainwat')
502  snowwat = get_tracer_index(model_atmos, 'snowwat')
503  graupel = get_tracer_index(model_atmos, 'graupel')
504 
505  if (is == 1) then
506  if (.not. allocated(dum_west)) then
507  allocate(dum_west(isd:0,jsd:jed,npz))
508 !$OMP parallel do default(none) shared(npz,isd,jsd,jed,dum_West)
509  do k=1,npz
510  do j=jsd,jed
511  do i=isd,0
512  dum_west(i,j,k) = 0.
513  enddo
514  enddo
515  enddo
516  endif
517  endif
518  if (js == 1) then
519  if (.not. allocated(dum_south)) then
520  allocate(dum_south(isd:ied,jsd:0,npz))
521 !$OMP parallel do default(none) shared(npz,isd,ied,jsd,dum_South)
522  do k=1,npz
523  do j=jsd,0
524  do i=isd,ied
525  dum_south(i,j,k) = 0.
526  enddo
527  enddo
528  enddo
529  endif
530  endif
531  if (ie == npx-1) then
532  if (.not. allocated(dum_east)) then
533  allocate(dum_east(npx:ied,jsd:jed,npz))
534 !$OMP parallel do default(none) shared(npx,npz,ied,jsd,jed,dum_East)
535  do k=1,npz
536  do j=jsd,jed
537  do i=npx,ied
538  dum_east(i,j,k) = 0.
539  enddo
540  enddo
541  enddo
542  endif
543  endif
544  if (je == npy-1) then
545  if (.not. allocated(dum_north)) then
546  allocate(dum_north(isd:ied,npy:jed,npz))
547 !$OMP parallel do default(none) shared(npy,npz,isd,ied,jed,dum_North)
548  do k=1,npz
549  do j=npy,jed
550  do i=isd,ied
551  dum_north(i,j,k) = 0.
552  enddo
553  enddo
554  enddo
555  endif
556  endif
557 
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
563  else
564  liq_watbc_west => dum_west
565  liq_watbc_east => dum_east
566  liq_watbc_north => dum_north
567  liq_watbc_south => dum_south
568  endif
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
574  else
575  ice_watbc_west => dum_west
576  ice_watbc_east => dum_east
577  ice_watbc_north => dum_north
578  ice_watbc_south => dum_south
579  endif
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
585  else
586  rainwatbc_west => dum_west
587  rainwatbc_east => dum_east
588  rainwatbc_north => dum_north
589  rainwatbc_south => dum_south
590  endif
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
596  else
597  snowwatbc_west => dum_west
598  snowwatbc_east => dum_east
599  snowwatbc_north => dum_north
600  snowwatbc_south => dum_south
601  endif
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
607  else
608  graupelbc_west => dum_west
609  graupelbc_east => dum_east
610  graupelbc_north => dum_north
611  graupelbc_south => dum_south
612  endif
613 
614  if (is == 1) then
615  ptbc => pt_bc%west_t1
616  sphumbc => sphum_bc%west_t1
617 #ifdef USE_COND
618  qconbc => q_con_bc%west_t1
619 #ifdef MOIST_CAPPA
620  cappabc => cappa_bc%west_t1
621 #endif
622 #endif
623  delpbc => delp_bc%west_t1
624  delzbc => delz_bc%west_t1
625 
626 !$OMP parallel do default(none) shared(npz,jsd,jed,isd,zvir,sphumBC,liq_watBC_west,rainwatBC_west,ice_watBC_west,snowwatBC_west,graupelBC_west,qconBC,cappaBC, &
627 !$OMP rdg,cv_air,delpBC,delzBC,ptBC) &
628 !$OMP private(dp1,q_con,q_liq,q_sol,cvm,pkz)
629  do k=1,npz
630  do j=jsd,jed
631  do i=isd,0
632  dp1 = zvir*sphumbc(i,j,k)
633 #ifdef USE_COND
634 #ifdef GFS_PHYS
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
638 #else
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
642 #endif
643  qconbc(i,j,k) = q_con
644 #ifdef MOIST_CAPPA
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
646  cappabc(i,j,k) = rdgas/(rdgas + cvm/(1.+dp1))
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)))
649 #else
650  pkz = exp( kappa*log(rdg*delpbc(i,j,k)*ptbc(i,j,k) * &
651  (1.+dp1)*(1.-q_con)/delzbc(i,j,k)))
652 #endif
653  ptbc(i,j,k) = ptbc(i,j,k)*(1.+dp1)*(1.-q_con)/pkz
654 #else
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
658 #endif
659  end do
660  end do
661  end do
662  end if
663 
664 
665  if (js == 1) then
666  ptbc => pt_bc%south_t1
667  sphumbc => sphum_bc%south_t1
668 #ifdef USE_COND
669  qconbc => q_con_bc%south_t1
670 #ifdef MOIST_CAPPA
671  cappabc => cappa_bc%south_t1
672 #endif
673 #endif
674  delpbc => delp_bc%south_t1
675  delzbc => delz_bc%south_t1
676  if (is == 1) then
677  istart = is
678  else
679  istart = isd
680  end if
681  if (ie == npx-1) then
682  iend = ie
683  else
684  iend = ied
685  end if
686 
687 !$OMP parallel do default(none) shared(npz,jsd,istart,iend,zvir,sphumBC, &
688 !$OMP liq_watBC_south,rainwatBC_south,ice_watBC_south,&
689 !$OMP snowwatBC_south,graupelBC_south,qconBC,cappaBC, &
690 !$OMP rdg,cv_air,delpBC,delzBC,ptBC) &
691 !$OMP private(dp1,q_con,q_liq,q_sol,cvm,pkz)
692  do k=1,npz
693  do j=jsd,0
694  do i=istart,iend
695  dp1 = zvir*sphumbc(i,j,k)
696 #ifdef USE_COND
697 #ifdef GFS_PHYS
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
701 #else
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
705 #endif
706  qconbc(i,j,k) = q_con
707 #ifdef MOIST_CAPPA
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
709  cappabc(i,j,k) = rdgas/(rdgas + cvm/(1.+dp1))
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)))
712 #else
713  pkz = exp( kappa*log(rdg*delpbc(i,j,k)*ptbc(i,j,k) * &
714  (1.+dp1)*(1.-q_con)/delzbc(i,j,k)))
715 #endif
716  ptbc(i,j,k) = ptbc(i,j,k)*(1.+dp1)*(1.-q_con)/pkz
717 #else
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
721 #endif
722  end do
723  end do
724  end do
725  end if
726 
727 
728  if (ie == npx-1) then
729  ptbc => pt_bc%east_t1
730  sphumbc => sphum_bc%east_t1
731 #ifdef USE_COND
732  qconbc => q_con_bc%east_t1
733 #ifdef MOIST_CAPPA
734  cappabc => cappa_bc%east_t1
735 #endif
736 #endif
737  delpbc => delp_bc%east_t1
738  delzbc => delz_bc%east_t1
739 !$OMP parallel do default(none) shared(npz,jsd,jed,npx,ied,zvir,sphumBC, &
740 !$OMP liq_watBC_east,rainwatBC_east,ice_watBC_east,snowwatBC_east,graupelBC_east,qconBC,cappaBC, &
741 !$OMP rdg,cv_air,delpBC,delzBC,ptBC) &
742 !$OMP private(dp1,q_con,q_liq,q_sol,cvm,pkz)
743  do k=1,npz
744  do j=jsd,jed
745  do i=npx,ied
746  dp1 = zvir*sphumbc(i,j,k)
747 #ifdef USE_COND
748 #ifdef GFS_PHYS
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
752 #else
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
756 #endif
757  qconbc(i,j,k) = q_con
758 #ifdef MOIST_CAPPA
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
760  cappabc(i,j,k) = rdgas/(rdgas + cvm/(1.+dp1))
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)))
763 #else
764  pkz = exp( kappa*log(rdg*delpbc(i,j,k)*ptbc(i,j,k) * &
765  (1.+dp1)*(1.-q_con)/delzbc(i,j,k)))
766 #endif
767  ptbc(i,j,k) = ptbc(i,j,k)*(1.+dp1)*(1.-q_con)/pkz
768 #else
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
772 #endif
773  end do
774  end do
775  end do
776  end if
777 
778  if (je == npy-1) then
779  ptbc => pt_bc%north_t1
780  sphumbc => sphum_bc%north_t1
781 #ifdef USE_COND
782  qconbc => q_con_bc%north_t1
783 #ifdef MOIST_CAPPA
784  cappabc => cappa_bc%north_t1
785 #endif
786 #endif
787  delpbc => delp_bc%north_t1
788  delzbc => delz_bc%north_t1
789  if (is == 1) then
790  istart = is
791  else
792  istart = isd
793  end if
794  if (ie == npx-1) then
795  iend = ie
796  else
797  iend = ied
798  end if
799 
800 !$OMP parallel do default(none) shared(npz,npy,jed,istart,iend,zvir, &
801 !$OMP sphumBC,liq_watBC_north,rainwatBC_north,ice_watBC_north,snowwatBC_north,graupelBC_north,qconBC,cappaBC, &
802 !$OMP rdg,cv_air,delpBC,delzBC,ptBC) &
803 !$OMP private(dp1,q_con,q_liq,q_sol,cvm,pkz)
804  do k=1,npz
805  do j=npy,jed
806  do i=istart,iend
807  dp1 = zvir*sphumbc(i,j,k)
808 #ifdef USE_COND
809 #ifdef GFS_PHYS
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
813 #else
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
817 #endif
818  qconbc(i,j,k) = q_con
819 #ifdef MOIST_CAPPA
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
821  cappabc(i,j,k) = rdgas/(rdgas + cvm/(1.+dp1))
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)))
824 #else
825  pkz = exp( kappa*log(rdg*delpbc(i,j,k)*ptbc(i,j,k) * &
826  (1.+dp1)*(1.-q_con)/delzbc(i,j,k)))
827 #endif
828  ptbc(i,j,k) = ptbc(i,j,k)*(1.+dp1)*(1.-q_con)/pkz
829 #else
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
833 #endif
834  end do
835  end do
836  end do
837  end if
838 
839 
840 
841  end subroutine setup_pt_nh_bc
842 
843 
844  subroutine set_nh_bcs_t0(neststruct)
846  type(fv_nest_type), intent(INOUT) :: neststruct
847 
848 #ifndef SW_DYNAMICS
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
853 
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
858 #endif
859 
860  end subroutine set_nh_bcs_t0
861 
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
867 
868  integer :: n
869 
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
874  do n=1,ncnst
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
879  enddo
880 #ifndef SW_DYNAMICS
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
889 
890 #ifdef USE_COND
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
895 #ifdef MOIST_CAPPA
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
900 #endif
901 #endif
902 
903  if (.not. hydrostatic) then
904  call set_nh_bcs_t0(neststruct)
905  endif
906 #endif
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
915 
916 
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
925 
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
930 
931 
932  end subroutine set_bcs_t0
933 
934 
935 !! nestupdate types
936 !! 1 - Interpolation update on all variables
937 !! 2 - Conserving update (over areas on cell-
938 !! centered variables, over faces on winds) on all variables
939 !! 3 - Interpolation update on winds only
940 !! 4 - Interpolation update on all variables except delp (mass conserving)
941 !! 5 - Remap interpolating update, delp not updated
942 !! 6 - Remap conserving update, delp not updated
943 !! 7 - Remap conserving update, delp and q not updated
944 !! 8 - Remap conserving update, only winds updated
945 
946 !! Note that nestupdate > 3 will not update delp.
947 
948 !! "Remap update" remaps updated variables from the nested grid's
949 !! vertical coordinate to that of the coarse grid. When delp is not
950 !! updated (nestbctype >= 3) the vertical coordinates differ on
951 !! the two grids, because the surface pressure will be different
952 !! on the two grids.
953 !! Note: "conserving updates" do not guarantee global conservation
954 !! unless flux nested grid BCs are specified, or if a quantity is
955 !! not updated at all. This ability has not been implemented.
956 
957 subroutine twoway_nesting(Atm, ngrids, grids_on_this_pe, zvir)
959  type(fv_atmos_type), intent(INOUT) :: atm(ngrids)
960  integer, intent(IN) :: ngrids
961  logical, intent(IN) :: grids_on_this_pe(ngrids)
962  real, intent(IN) :: zvir
963 
964  integer :: n, p, sphum
965 
966 
967  if (ngrids > 1) then
968 
969  do n=ngrids,2,-1 !loop backwards to allow information to propagate from finest to coarsest grids
970 
971  !two-way updating
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
974  sphum = get_tracer_index(model_atmos, 'sphum')
975  call twoway_nest_update(atm(n)%npx, atm(n)%npy, atm(n)%npz, zvir, &
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.)
980  endif
981  endif
982 
983  end do
984 
985  !NOTE: these routines need to be used with any grid which has been updated to, not just the coarsest grid.
986  do n=1,ngrids
987  if (atm(n)%neststruct%parent_of_twoway .and. grids_on_this_pe(n)) then
988  call after_twoway_nest_update( atm(n)%npx, atm(n)%npy, atm(n)%npz, atm(n)%ng, atm(n)%ncnst, &
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)
995  endif
996  enddo
997 
998  endif ! ngrids > 1
999 
1000 
1001 
1002 
1003  end subroutine twoway_nesting
1004 
1005 !!!CLEANUP: this routine assumes that the PARENT GRID has pt = (regular) temperature,
1006 !!!not potential temperature; which may cause problems when updating if this is not the case.
1007  subroutine twoway_nest_update(npx, npy, npz, zvir, ncnst, sphum, &
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
1014 
1015  integer, intent(IN) :: npx, npy, npz
1016  integer, intent(IN) :: ncnst, sphum
1017  logical, intent(IN), OPTIONAL :: conv_theta_in
1018 
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 ! D grid zonal wind (m/s)
1021  real, intent(inout), dimension(bd%isd:bd%ied+1,bd%jsd:bd%jed ,npz) :: v ! D grid meridional wind (m/s)
1022  real, intent(inout) :: w( bd%isd: ,bd%jsd: ,1: ) ! W (m/s)
1023  real, intent(inout) :: omga(bd%isd:bd%ied,bd%jsd:bd%jed,npz) ! Vertical pressure velocity (pa/s)
1024  real, intent(inout) :: pt( bd%isd:bd%ied ,bd%jsd:bd%jed ,npz) ! temperature (K)
1025  real, intent(inout) :: delp(bd%isd:bd%ied ,bd%jsd:bd%jed ,npz) ! pressure thickness (pascal)
1026  real, intent(inout) :: q( bd%isd:bd%ied ,bd%jsd:bd%jed ,npz, ncnst) ! specific humidity and constituents
1027  real, intent(inout) :: uc(bd%isd:bd%ied+1,bd%jsd:bd%jed ,npz) ! (uc,vc) C grid winds
1028  real, intent(inout) :: vc(bd%isd:bd%ied ,bd%jsd:bd%jed+1,npz)
1029 
1030  real, intent(inout) :: pkz (bd%is:bd%ie,bd%js:bd%je,npz) ! finite-volume mean pk
1031  real, intent(inout) :: delz(bd%isd: ,bd%jsd: ,1: ) ! delta-height (m); non-hydrostatic only
1032  real, intent(inout) :: ps (bd%isd:bd%ied ,bd%jsd:bd%jed) ! Surface pressure (pascal)
1033 
1034  type(fv_grid_type), intent(INOUT) :: gridstruct
1035  type(fv_flags_type), intent(INOUT) :: flagstruct
1036  type(fv_nest_type), intent(INOUT) :: neststruct
1037 
1038  type(fv_atmos_type), intent(INOUT) :: parent_grid
1039 
1040  real, allocatable :: t_nest(:,:,:), ps0(:,:)
1041  integer :: i,j,k,n
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.
1047 
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)
1052 
1053  integer :: upoff
1054  integer :: is, ie, js, je
1055  integer :: isd, ied, jsd, jed
1056  integer :: isu, ieu, jsu, jeu
1057 
1058  is = bd%is
1059  ie = bd%ie
1060  js = bd%js
1061  je = bd%je
1062  isd = bd%isd
1063  ied = bd%ied
1064  jsd = bd%jsd
1065  jed = bd%jed
1066  isu = neststruct%isu
1067  ieu = neststruct%ieu
1068  jsu = neststruct%jsu
1069  jeu = neststruct%jeu
1070 
1071  upoff = neststruct%upoff
1072 
1073  !We update actual temperature, not theta.
1074  !If pt is actual temperature, set conv_theta to .false.
1075  if (present(conv_theta_in)) conv_theta = conv_theta_in
1076 
1077  if ((.not. neststruct%parent_proc) .and. (.not. neststruct%child_proc)) return
1078 
1079  call mpp_get_data_domain( parent_grid%domain, &
1080  isd_p, ied_p, jsd_p, jed_p )
1081  call mpp_get_compute_domain( parent_grid%domain, &
1082  isc_p, iec_p, jsc_p, jec_p )
1083 
1084 
1085  !delp/ps
1086 
1087  if (neststruct%nestupdate < 3) then
1088 
1089  call update_coarse_grid(parent_grid%delp, delp, neststruct%nest_domain,&
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)
1096 
1097  call mpp_sync!self
1098 
1099 #ifdef SW_DYNAMICS
1100  if (neststruct%parent_proc) then
1101  do j=jsd_p,jed_p
1102  do i=isd_p,ied_p
1103 
1104  parent_grid%ps(i,j) = &
1105  parent_grid%delp(i,j,1)/grav
1106 
1107  end do
1108  end do
1109  endif
1110 #endif
1111 
1112  end if
1113 
1114  !if (neststruct%nestupdate /= 3 .and. neststruct%nestbctype /= 3) then
1115  if (neststruct%nestupdate /= 3 .and. neststruct%nestupdate /= 7 .and. neststruct%nestupdate /= 8) then
1116 
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))
1120  q_diff = 0.
1121  endif
1122 
1123  do n=1,parent_grid%flagstruct%nwat
1124 
1125  qdp_coarse = 0.
1126  if (neststruct%child_proc) then
1127  do k=1,npz
1128  do j=jsd,jed
1129  do i=isd,ied
1130  qdp(i,j,k) = q(i,j,k,n)*delp(i,j,k)
1131  enddo
1132  enddo
1133  enddo
1134  else
1135  qdp = 0.
1136  endif
1137 
1138  if (neststruct%parent_proc) then
1139  !Add up ONLY region being replaced by nested grid
1140  do k=1,npz
1141  do j=jsu,jeu
1142  do i=isu,ieu
1143  qdp_coarse(i,j,k) = parent_grid%q(i,j,k,n)*parent_grid%delp(i,j,k)
1144  enddo
1145  enddo
1146  enddo
1147  call level_sum(qdp_coarse, parent_grid%gridstruct%area, parent_grid%domain, &
1148  parent_grid%bd, npz, l_sum_b)
1149  else
1150  qdp_coarse = 0.
1151  endif
1152  if (neststruct%parent_proc) then
1153  if (n <= parent_grid%flagstruct%nwat) then
1154  do k=1,npz
1155  do j=jsu,jeu
1156  do i=isu,ieu
1157  q_diff(i,j,k) = q_diff(i,j,k) - qdp_coarse(i,j,k)
1158  enddo
1159  enddo
1160  enddo
1161  endif
1162  endif
1163 
1164  call update_coarse_grid(qdp_coarse, qdp, neststruct%nest_domain, &
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)
1170 
1171  call mpp_sync!self
1172 
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)
1176  do k=1,npz
1177  if (l_sum_a(k) > 0.) then
1178  fix = l_sum_b(k)/l_sum_a(k)
1179  do j=jsu,jeu
1180  do i=isu,ieu
1181  !Normalization mass fixer
1182  parent_grid%q(i,j,k,n) = qdp_coarse(i,j,k)*fix
1183  enddo
1184  enddo
1185  endif
1186  enddo
1187  if (n == 1) sphum_ll_fix = 1. - fix
1188  endif
1189  if (neststruct%parent_proc) then
1190  if (n <= parent_grid%flagstruct%nwat) then
1191  do k=1,npz
1192  do j=jsu,jeu
1193  do i=isu,ieu
1194  q_diff(i,j,k) = q_diff(i,j,k) + parent_grid%q(i,j,k,n)
1195  enddo
1196  enddo
1197  enddo
1198  endif
1199  endif
1200 
1201  end do
1202 
1203  if (neststruct%parent_proc) then
1204  if (parent_grid%flagstruct%nwat > 0) then
1205  do k=1,npz
1206  do j=jsu,jeu
1207  do i=isu,ieu
1208  parent_grid%delp(i,j,k) = parent_grid%delp(i,j,k) + q_diff(i,j,k)
1209  enddo
1210  enddo
1211  enddo
1212  endif
1213 
1214  do n=1,parent_grid%flagstruct%nwat
1215  do k=1,npz
1216  do j=jsu,jeu
1217  do i=isu,ieu
1218  parent_grid%q(i,j,k,n) = parent_grid%q(i,j,k,n)/parent_grid%delp(i,j,k)
1219  enddo
1220  enddo
1221  enddo
1222  enddo
1223  endif
1224 
1225  deallocate(qdp_coarse)
1226  if (allocated(q_diff)) deallocate(q_diff)
1227 
1228  endif
1229 
1230 #ifndef SW_DYNAMICS
1231  if (neststruct%nestupdate /= 3 .and. neststruct%nestupdate /= 8) then
1232 
1233  if (conv_theta) then
1234 
1235  if (neststruct%child_proc) then
1236  !pt is potential temperature on the nested grid, but actual
1237  !temperature on the coarse grid. Compute actual temperature
1238  !on the nested grid, then gather.
1239  allocate(t_nest(isd:ied,jsd:jed,1:npz))
1240 !$OMP parallel do default(none) shared(npz,js,je,is,ie,t_nest,pt,pkz,zvir,q,sphum)
1241  do k=1,npz
1242  do j=js,je
1243  do i=is,ie
1244  t_nest(i,j,k) = pt(i,j,k)*pkz(i,j,k)/(1.+zvir*q(i,j,k,sphum))
1245  enddo
1246  enddo
1247  enddo
1248  deallocate(t_nest)
1249  endif
1250 
1251  call update_coarse_grid(parent_grid%pt, &
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)
1258  else
1259 
1260  call update_coarse_grid(parent_grid%pt, &
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)
1267 
1268  endif !conv_theta
1269 
1270  call mpp_sync!self
1271 
1272  if (.not. flagstruct%hydrostatic) then
1273 
1274  call update_coarse_grid(parent_grid%w, w, neststruct%nest_domain, &
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)
1280  !Updating for delz not yet implemented; may be problematic
1281 !!$ call update_coarse_grid(parent_grid%delz, delz, neststruct%nest_domain, &
1282 !!$ neststruct%ind_update_h, &
1283 !!$ isd_p, ied_p, jsd_p, jed_p, isd, ied, jsd, jed, npz, 0, 0, &
1284 !!$ neststruct%refinement, neststruct%nestupdate, upoff, 0, neststruct%parent_proc, neststruct%child_proc)
1285 
1286  call mpp_sync!self
1287 
1288  end if
1289 
1290  end if !Neststruct%nestupdate /= 3
1291 
1292 #endif
1293 
1294  call update_coarse_grid(parent_grid%u, u, neststruct%nest_domain, &
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)
1300 
1301  call update_coarse_grid(parent_grid%v, v, neststruct%nest_domain, &
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)
1307 
1308  call mpp_sync!self
1309 
1310 
1311 #ifndef SW_DYNAMICS
1312  if (neststruct%nestupdate >= 5 .and. npz > 4) then
1313 
1314  !Use PS0 from nested grid, NOT the full delp. Also we assume the same number of levels on both grids.
1315  !PS0 should be initially set to be ps so that this routine does NOTHING outside of the update region
1316 
1317  !Re-compute nested (AND COARSE) grid ps
1318 
1319  allocate(ps0(isd_p:ied_p,jsd_p:jed_p))
1320  if (neststruct%parent_proc) then
1321 
1322  parent_grid%ps = parent_grid%ptop
1323 !This loop appears to cause problems with OMP
1324 !$OMP parallel do default(none) shared(npz,jsd_p,jed_p,isd_p,ied_p,parent_grid)
1325  do j=jsd_p,jed_p
1326  do k=1,npz
1327  do i=isd_p,ied_p
1328  parent_grid%ps(i,j) = parent_grid%ps(i,j) + &
1329  parent_grid%delp(i,j,k)
1330  end do
1331  end do
1332  end do
1333 
1334  ps0 = parent_grid%ps
1335  endif
1336 
1337  if (neststruct%child_proc) then
1338 
1339  ps = ptop
1340 !$OMP parallel do default(none) shared(npz,jsd,jed,isd,ied,ps,delp)
1341  do j=jsd,jed
1342  do k=1,npz
1343  do i=isd,ied
1344  ps(i,j) = ps(i,j) + delp(i,j,k)
1345  end do
1346  end do
1347  end do
1348  endif
1349 
1350  call update_coarse_grid(ps0, ps, neststruct%nest_domain, &
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, &
1354  npx, npy, 0, 0, &
1355  neststruct%refinement, neststruct%nestupdate, upoff, 0, neststruct%parent_proc, neststruct%child_proc, parent_grid)
1356 
1357  !!! The mpp version of update_coarse_grid does not return a consistent value of ps
1358  !!! across PEs, as it does not go into the haloes of a given coarse-grid PE. This
1359  !!! update_domains call takes care of the problem.
1360 
1361  if (neststruct%parent_proc) then
1362  call mpp_update_domains(parent_grid%ps, parent_grid%domain, complete=.false.)
1363  call mpp_update_domains(ps0, parent_grid%domain, complete=.true.)
1364  endif
1365 
1366 
1367  call mpp_sync!self
1368 
1369  if (parent_grid%tile == neststruct%parent_tile) then
1370 
1371  if (neststruct%parent_proc) then
1372 
1373  !comment out if statement to always remap theta instead of t in the remap-update.
1374  !(In LtE typically we use remap_t = .true.: remapping t is better (except in
1375  !idealized simulations with a background uniform theta) since near the top
1376  !boundary theta is exponential, which is hard to accurately interpolate with a spline
1377  if (parent_grid%flagstruct%remap_option /= 0) then
1378 !$OMP parallel do default(none) shared(npz,jsc_p,jec_p,isc_p,iec_p,parent_grid,zvir,sphum)
1379  do k=1,npz
1380  do j=jsc_p,jec_p
1381  do i=isc_p,iec_p
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))
1385  end do
1386  end do
1387  end do
1388  end if
1389  call update_remap_tqw(npz, parent_grid%ak, parent_grid%bk, &
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. ) !neststruct%nestupdate < 7)
1397  if (parent_grid%flagstruct%remap_option /= 0) then
1398 !$OMP parallel do default(none) shared(npz,jsc_p,jec_p,isc_p,iec_p,parent_grid,zvir,sphum)
1399  do k=1,npz
1400  do j=jsc_p,jec_p
1401  do i=isc_p,iec_p
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))
1405  end do
1406  end do
1407  end do
1408  end if
1409 
1410  call update_remap_uv(npz, parent_grid%ak, parent_grid%bk, &
1411  parent_grid%ps, &
1412  parent_grid%u, &
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)
1415 
1416  endif !neststruct%parent_proc
1417 
1418  end if
1419 
1420  if (allocated(ps0)) deallocate(ps0)
1421 
1422  end if
1423 
1424 #endif
1425 
1426  end subroutine twoway_nest_update
1427 
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
1436 
1437  integer :: i, j, k, n
1438  real :: qA!(bd%is:bd%ie, bd%js:bd%je)
1439 
1440  do k=1,npz
1441  qa = 0.
1442  do j=bd%js,bd%je
1443  do i=bd%is,bd%ie
1444  !qA(i,j) = q(i,j,k)*area(i,j)
1445  qa = qa + q(i,j,k)*area(i,j)
1446  enddo
1447  enddo
1448  call mp_reduce_sum(qa)
1449  l_sum(k) = qa
1450 ! L_sum(k) = mpp_global_sum(domain, qA, flags=BITWISE_EXACT_SUM)
1451 ! L_sum(k) = mpp_global_sum(domain, qA, flags=BITWISE_EFP_SUM) ! doesn't work??
1452  enddo
1453 
1454  end subroutine level_sum
1455 
1456 
1457  subroutine after_twoway_nest_update(npx, npy, npz, ng, ncnst, &
1458  u, v, w, delz, pt, delp, q, &
1459  ps, pe, pk, peln, pkz, phis, ua, va, &
1460  ptop, gridstruct, flagstruct, &
1461  domain, bd)
1463  type(fv_grid_bounds_type), intent(IN) :: bd
1464  real, intent(IN) :: ptop
1465 
1466  integer, intent(IN) :: ng, npx, npy, npz
1467  integer, intent(IN) :: ncnst
1468 
1469  real, intent(inout), dimension(bd%isd:bd%ied ,bd%jsd:bd%jed+1,npz) :: u ! D grid zonal wind (m/s)
1470  real, intent(inout), dimension(bd%isd:bd%ied+1,bd%jsd:bd%jed ,npz) :: v ! D grid meridional wind (m/s)
1471  real, intent(inout) :: w( bd%isd: ,bd%jsd: ,1: ) ! W (m/s)
1472  real, intent(inout) :: pt( bd%isd:bd%ied ,bd%jsd:bd%jed ,npz) ! temperature (K)
1473  real, intent(inout) :: delp(bd%isd:bd%ied ,bd%jsd:bd%jed ,npz) ! pressure thickness (pascal)
1474  real, intent(inout) :: q( bd%isd:bd%ied ,bd%jsd:bd%jed ,npz, ncnst) ! specific humidity and constituents
1475  real, intent(inout) :: delz(bd%isd: ,bd%jsd: ,1: ) ! delta-height (m); non-hydrostatic only
1476 
1477 !-----------------------------------------------------------------------
1478 ! Auxilliary pressure arrays:
1479 ! The 5 vars below can be re-computed from delp and ptop.
1480 !-----------------------------------------------------------------------
1481 ! dyn_aux:
1482  real, intent(inout) :: ps (bd%isd:bd%ied ,bd%jsd:bd%jed) ! Surface pressure (pascal)
1483  real, intent(inout) :: pe (bd%is-1:bd%ie+1, npz+1,bd%js-1:bd%je+1) ! edge pressure (pascal)
1484  real, intent(inout) :: pk (bd%is:bd%ie,bd%js:bd%je, npz+1) ! pe**cappa
1485  real, intent(inout) :: peln(bd%is:bd%ie,npz+1,bd%js:bd%je) ! ln(pe)
1486  real, intent(inout) :: pkz (bd%is:bd%ie,bd%js:bd%je,npz) ! finite-volume mean pk
1487 
1488 !-----------------------------------------------------------------------
1489 ! Others:
1490 !-----------------------------------------------------------------------
1491  real, intent(inout) :: phis(bd%isd:bd%ied,bd%jsd:bd%jed) ! Surface geopotential (g*Z_surf)
1492 
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
1497 
1498  logical :: bad_range
1499 
1500  integer :: is, ie, js, je
1501  integer :: isd, ied, jsd, jed
1502 
1503  is = bd%is
1504  ie = bd%ie
1505  js = bd%js
1506  je = bd%je
1507  isd = bd%isd
1508  ied = bd%ied
1509  jsd = bd%jsd
1510  jed = bd%jed
1511 
1512  call cubed_to_latlon(u, v, ua, va, &
1513  gridstruct, npx, npy, npz, &
1514  1, gridstruct%grid_type, domain, &
1515  gridstruct%nested, flagstruct%c2l_ord, bd)
1516 
1517 #ifndef SW_DYNAMICS
1518 
1519  !To get coarse grid pkz, etc right after a two-way update so
1520  !that it is consistent across a restart:
1521  !(should only be called after doing such an update)
1522 
1523  !! CLEANUP: move to twoway_nest_update??
1524  call p_var(npz, is, ie, js, je, ptop, ptop_min, &
1525  delp, delz, &
1526  pt, ps, &
1527  pe, peln, &
1528  pk, pkz, kappa, &
1529  q, ng, flagstruct%ncnst, gridstruct%area_64, 0., &
1530  .false., .false., & !mountain argument not used
1531  flagstruct%moist_phys, flagstruct%hydrostatic, &
1532  flagstruct%nwat, domain, .false.)
1533 
1534 #endif
1535 
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)
1542  endif
1543  endif
1544 
1545 
1546 
1547  end subroutine after_twoway_nest_update
1548 
1549  !Routines for remapping (interpolated) nested-grid data to the coarse-grid's vertical coordinate.
1550 
1551  !This does not yet do anything for the tracers
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
1565 ! local:
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
1570  integer i,j,k,iq
1571 
1572 !$OMP parallel do default(none) shared(js,je,kmd,is,ie,ak,bk,ps0,q,npz,ptop,do_q,&
1573 !$OMP t,w,ps,nq,hydrostatic,kord_tm,kord_tr,kord_wz) &
1574 !$OMP private(pe0,pn0,pe1,pn1,qp,tp,qn1)
1575  do 5000 j=js,je
1576 
1577  do k=1,kmd+1
1578  do i=is,ie
1579  pe0(i,k) = ak(k) + bk(k)*ps0(i,j)
1580  pn0(i,k) = log(pe0(i,k))
1581  enddo
1582  enddo
1583  do k=1,kmd+1
1584  do i=is,ie
1585  pe1(i,k) = ak(k) + bk(k)*ps(i,j)
1586  pn1(i,k) = log(pe1(i,k))
1587  enddo
1588  enddo
1589  if (do_q) then
1590  do iq=1,nq
1591  do k=1,kmd
1592  do i=is,ie
1593  qp(i,k) = q(i,j,k,iq)
1594  enddo
1595  enddo
1596  call mappm(kmd, pe0, qp, npz, pe1, qn1, is,ie, 0, kord_tr, ptop)
1597  do k=1,npz
1598  do i=is,ie
1599  q(i,j,k,iq) = qn1(i,k)
1600  enddo
1601  enddo
1602  enddo
1603  endif
1604 
1605  do k=1,kmd
1606  do i=is,ie
1607  tp(i,k) = t(i,j,k)
1608  enddo
1609  enddo
1610  !Remap T using logp
1611  call mappm(kmd, pn0, tp, npz, pn1, qn1, is,ie, 1, abs(kord_tm), ptop)
1612 
1613  do k=1,npz
1614  do i=is,ie
1615  t(i,j,k) = qn1(i,k)
1616  enddo
1617  enddo
1618 
1619  if (.not. hydrostatic) then
1620  do k=1,kmd
1621  do i=is,ie
1622  tp(i,k) = w(i,j,k)
1623  enddo
1624  enddo
1625  !Remap w using p
1626  !Using iv == -1 instead of -2
1627  call mappm(kmd, pe0, tp, npz, pe1, qn1, is,ie, -1, kord_wz, ptop)
1628 
1629  do k=1,npz
1630  do i=is,ie
1631  w(i,j,k) = qn1(i,k)
1632  enddo
1633  enddo
1634  endif
1635 
1636 5000 continue
1637 
1638  end subroutine update_remap_tqw
1639 
1640  !remap_uv as-is remaps only a-grid velocities. A new routine has been written to handle staggered grids.
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
1648 !
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
1653 !
1654 ! local:
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
1659  integer i,j,k
1660 
1661 !------
1662 ! map u
1663 !------
1664 !$OMP parallel do default(none) shared(js,je,kmd,is,ie,ak,bk,ps,ps0,npz,u,ptop,kord_mt) &
1665 !$OMP private(pe0,pe1,qt,qn1)
1666  do j=js,je+1
1667 !------
1668 ! Data
1669 !------
1670  do k=1,kmd+1
1671  do i=is,ie
1672  pe0(i,k) = ak(k) + bk(k)*0.5*(ps0(i,j)+ps0(i,j-1))
1673  enddo
1674  enddo
1675 !------
1676 ! Model
1677 !------
1678  do k=1,kmd+1
1679  do i=is,ie
1680  pe1(i,k) = ak(k) + bk(k)*0.5*(ps(i,j)+ps(i,j-1))
1681  enddo
1682  enddo
1683 !------
1684 !Do map
1685 !------
1686  qt = 0.
1687  do k=1,kmd
1688  do i=is,ie
1689  qt(i,k) = u(i,j,k)
1690  enddo
1691  enddo
1692  qn1 = 0.
1693  call mappm(kmd, pe0(is:ie,:), qt(is:ie,:), npz, pe1(is:ie,:), qn1(is:ie,:), is,ie, -1, kord_mt, ptop)
1694  do k=1,npz
1695  do i=is,ie
1696  u(i,j,k) = qn1(i,k)
1697  enddo
1698  enddo
1699 
1700  end do
1701 
1702 !------
1703 ! map v
1704 !------
1705 !$OMP parallel do default(none) shared(js,je,kmd,is,ie,ak,bk,ps,ps0,npz,v,ptop) &
1706 !$OMP private(pe0,pe1,qt,qn1)
1707  do j=js,je
1708 !------
1709 ! Data
1710 !------
1711  do k=1,kmd+1
1712  do i=is,ie+1
1713  pe0(i,k) = ak(k) + bk(k)*0.5*(ps0(i,j)+ps0(i-1,j))
1714  enddo
1715  enddo
1716 !------
1717 ! Model
1718 !------
1719  do k=1,kmd+1
1720  do i=is,ie+1
1721  pe1(i,k) = ak(k) + bk(k)*0.5*(ps(i,j)+ps(i-1,j))
1722  enddo
1723  enddo
1724 !------
1725 !Do map
1726 !------
1727  qt = 0.
1728  do k=1,kmd
1729  do i=is,ie+1
1730  qt(i,k) = v(i,j,k)
1731  enddo
1732  enddo
1733  qn1 = 0.
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)
1735  do k=1,npz
1736  do i=is,ie+1
1737  v(i,j,k) = qn1(i,k)
1738  enddo
1739  enddo
1740  end do
1741 
1742  end subroutine update_remap_uv
1743 
1744 
1745 end module fv_nesting_nlm_mod
real, parameter, public radius
Radius of the Earth [m].
Definition: constants.F90:72
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].
Definition: constants.F90:73
real, dimension(:,:,:), allocatable, target dum_south
real, parameter, public hlv
Latent heat of evaporation [J/kg].
Definition: constants.F90:80
real, parameter, public rdgas
Gas constant for dry air [J/kg/deg].
Definition: constants.F90:77
real, parameter, public cp_vapor
Specific heat capacity of water vapor at constant pressure [J/kg/deg].
Definition: constants.F90:89
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)
Definition: mpp.F90:39
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].
Definition: constants.F90:78
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].
Definition: constants.F90:83
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].
Definition: constants.F90:76
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)
Definition: fv_sg_nlm.F90:1132
subroutine level_sum(q, area, domain, bd, npz, L_sum)
subroutine, public divergence_corner_nest(u, v, ua, va, divg_d, gridstruct, flagstruct, bd)
#define max(a, b)
Definition: mosaic_util.h:33
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
#define min(a, b)
Definition: mosaic_util.h:32
real, dimension(:), allocatable rw
real, parameter, public kappa
RDGAS / CP_AIR [dimensionless].
Definition: constants.F90:82
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)