FV3DYCORE  Version1.0.0
boundary.F90
Go to the documentation of this file.
1 !***********************************************************************
2 !* GNU Lesser General Public License
3 !*
4 !* This file is part of the FV3 dynamical core.
5 !*
6 !* The FV3 dynamical core is free software: you can redistribute it
7 !* and/or modify it under the terms of the
8 !* GNU Lesser General Public License as published by the
9 !* Free Software Foundation, either version 3 of the License, or
10 !* (at your option) any later version.
11 !*
12 !* The FV3 dynamical core is distributed in the hope that it will be
13 !* useful, but WITHOUT ANYWARRANTY; without even the implied warranty
14 !* of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
15 !* See the GNU General Public License for more details.
16 !*
17 !* You should have received a copy of the GNU Lesser General Public
18 !* License along with the FV3 dynamical core.
19 !* If not, see <http://www.gnu.org/licenses/>.
20 !***********************************************************************
21 
24 
26 
27 ! Modules Included:
28 ! <table>
29 ! <tr>
30 ! <th>Module Name</th>
31 ! <th>Functions Included</th>
32 ! </tr>
33 ! <tr>
34 ! <td>constants_mod</td>
35 ! <td>grav</td>
36 ! <tr>
37 ! <td>fv_arrays_mod</td>
38 ! <td>fv_atmos_type, fv_nest_BC_type_3D, fv_grid_bounds_type</td>
39 ! </tr>
40 ! <tr>
41 ! <td>fv_mp_mod</td>
42 ! <td>ng, isc,jsc,iec,jec, isd,jsd,ied,jed, is,js,ie,je, is_master, mp_bcst</td>
43 ! </tr>
44 ! <tr>
45 ! <td>fv_timing_mod</td>
46 ! <td>timing_on, timing_off</td>
47 ! </tr>
48 ! <tr>
49 ! <td>mpp_mod/td>
50 ! <td>mpp_error, FATAL, mpp_sum, mpp_sync, mpp_npes, mpp_broadcast, WARNING, mpp_pe,
51 ! mpp_send, mpp_recv</td>
52 ! </tr>
53 ! <tr>
54 ! <td>mpp_domains_mod/td>
55 ! <td>mpp_get_compute_domain, mpp_get_data_domain, mpp_get_global_domain,
56 ! ENTER, CORNER, NORTH, EAST,nest_domain_type, WEST, SOUTH,
57 ! mpp_get_C2F_index, mpp_update_nest_fine,mpp_global_field, mpp_get_pelist
58 ! mpp_get_F2C_index, mpp_update_nest_coarse</td>
59 ! </tr>
60 ! </table>
61 
62  use fv_mp_mod, only: ng, isc,jsc,iec,jec, isd,jsd,ied,jed, is,js,ie,je, is_master
63  use constants_mod, only: grav
64 
65  use mpp_domains_mod, only: mpp_get_compute_domain, mpp_get_data_domain, mpp_get_global_domain
66  use mpp_domains_mod, only: center, corner, north, east
67  use mpp_domains_mod, only: mpp_global_field, mpp_get_pelist
68  use mpp_mod, only: mpp_error, fatal, mpp_sum, mpp_sync, mpp_npes, mpp_broadcast, warning, mpp_pe
69 
70  use fv_mp_mod, only: mp_bcst
72  use mpp_mod, only: mpp_send, mpp_recv
74  use mpp_domains_mod, only : nest_domain_type, west, south
75  use mpp_domains_mod, only : mpp_get_c2f_index, mpp_update_nest_fine
76  use mpp_domains_mod, only : mpp_get_f2c_index, mpp_update_nest_coarse
77  !use mpp_domains_mod, only : mpp_get_domain_shift
78 
79  implicit none
80  public extrapolation_bc
84 
88  interface nested_grid_bc
89  module procedure nested_grid_bc_2d
90  module procedure nested_grid_bc_mpp
91  module procedure nested_grid_bc_mpp_send
92  module procedure nested_grid_bc_2d_mpp
93  module procedure nested_grid_bc_3d
94  end interface
95 
99  interface fill_nested_grid
100  module procedure fill_nested_grid_2d
101  module procedure fill_nested_grid_3d
102  end interface
103 
109  module procedure update_coarse_grid_mpp
110  module procedure update_coarse_grid_mpp_2d
111  end interface
112 
113 contains
114 
116 !Not to be confused with extrapolated-in-time nested BCs
117  subroutine extrapolation_bc(q, istag, jstag, npx, npy, bd, pd_in, debug_in)
119  type(fv_grid_bounds_type), intent(IN) :: bd
120  integer, intent(in) :: istag, jstag, npx, npy
121  real, intent(inout), dimension(bd%isd:bd%ied+istag, bd%jsd:bd%jed+jstag) :: q
122  logical, intent(in), OPTIONAL :: pd_in, debug_in
123 
124  integer :: i,j, istart, iend, jstart, jend
125  logical :: pd, debug
126 
127  integer :: is, ie, js, je
128  integer :: isd, ied, jsd, jed
129 
130  is = bd%is
131  ie = bd%ie
132  js = bd%js
133  je = bd%je
134  isd = bd%isd
135  ied = bd%ied
136  jsd = bd%jsd
137  jed = bd%jed
138 
139  istart = max(isd, 1)
140  iend = min(ied,npx-1)
141  jstart = max(jsd, 1)
142  jend = min(jed,npy-1)
143 
144  !Positive-definite extrapolation: shift from linear extrapolation to zero-gradient when the extrapolated value turns negative.
145  if (present(pd_in)) then
146  pd = pd_in
147  else
148  pd = .false.
149  end if
150 
151  if (present(debug_in)) then
152  debug = debug_in
153  else
154  debug = .false.
155  end if
156 
157  if (is == 1) then
158 
159  if (pd) then
160 
161  do j = jstart,jend+jstag
162  do i = 0,isd,-1
163 
164  if (real(i) <= 1. - q(1,j)/(q(2,j) - q(1,j) + 1.e-12) .and. q(1,j) < q(2,j)) then
165  q(i,j) = q(i+1,j)
166  else
167  q(i,j) = real(2-i)*q(1,j) - real(1-i)*q(2,j)
168  end if
169 
170  end do
171  end do
172 
173  else
174 
175  do j = jstart,jend+jstag
176  do i = 0,isd,-1
177 
178  q(i,j) = real(2-i)*q(1,j) - real(1-i)*q(2,j)
179 
180  end do
181  end do
182 
183  end if
184 
185  end if
186 
187  if (js == 1) then
188 
189  if (pd) then
190 
191  do j = 0,jsd,-1
192  do i = istart,iend+istag
193 
194  if (real(j) <= 1. - q(i,1)/(q(i,2) - q(i,1) + 1.e-12) .and. q(i,1) < q(i,2)) then
195  q(i,j) = q(i,j+1)
196  else
197  q(i,j) = real(2-j)*q(i,1) - real(1-j)*q(i,2)
198  end if
199 
200  end do
201  end do
202 
203  else
204 
205  do j = 0,jsd,-1
206  do i = istart,iend+istag
207 
208  q(i,j) = real(2-j)*q(i,1) - real(1-j)*q(i,2)
209 
210  end do
211  end do
212 
213  end if
214 
215  end if
216 
217  if (ie == npx - 1) then
218 
219  if (pd) then
220 
221  do j=jstart,jend+jstag
222  do i=ie+1+istag,ied+istag
223 
224  if (real(i) >= ie+istag + q(ie+istag,j)/(q(ie+istag-1,j)-q(ie+istag,j)+1.e-12) .and. &
225  q(ie+istag,j) < q(ie+istag-1,j)) then
226  q(i,j) = q(i-1,j)
227  else
228  q(i,j) = real(i - (ie+istag-1))*q(ie+istag,j) + real((ie+istag) - i)*q(ie+istag-1,j)
229  end if
230 
231  end do
232  end do
233 
234  else
235 
236  do j=jstart,jend+jstag
237  do i=ie+1+istag,ied+istag
238 
239  q(i,j) = real(i - (ie+istag-1))*q(ie+istag,j) + real((ie+istag) - i)*q(ie+istag-1,j)
240 
241  end do
242  end do
243 
244  end if
245 
246  end if
247 
248  if (je == npy - 1) then
249 
250  if (pd) then
251 
252  do j=je+1+jstag,jed+jstag
253  do i=istart,iend+istag
254 
255  if (real(j) >= je+jstag + q(i,je+jstag)/(q(i,je+jstag-1)-q(i,je+jstag)+1.e-12) .and. &
256  q(i,je+jstag-1) > q(i,je+jstag)) then
257  q(i,j) = q(i,j-1)
258  else
259  q(i,j) = real(j - (je+jstag-1))*q(i,je+jstag) + real((je+jstag) - j)*q(i,je+jstag-1)
260  end if
261 
262  end do
263  end do
264 
265  else
266 
267  do j=je+1+jstag,jed+jstag
268  do i=istart,iend+istag
269 
270  q(i,j) = real(j - (je+jstag-1))*q(i,je+jstag) + real((je+jstag) - j)*q(i,je+jstag-1)
271 
272  end do
273  end do
274 
275  end if
276 
277  end if
278 
279 
280  !CORNERS: Average of extrapolations
281 
282  if (is == 1 .and. js == 1) then
283 
284  if (pd) then
285 
286  do j=0,jsd,-1
287  do i=0,isd,-1
288 
289  if (real(i) <= 1. - q(1,j)/(q(2,j) - q(1,j) + 1.e-12) .and. q(2,j) > q(1,j)) then
290  q(i,j) = 0.5*q(i+1,j)
291  else
292  q(i,j) = 0.5*( real(2-i)*q(1,j) - real(1-i)*q(2,j) )
293  end if
294 
295  if (real(j) <= 1. - q(i,1)/(q(i,2) - q(i,1) + 1.e-12) .and. q(i,2) > q(i,1)) then
296  q(i,j) = q(i,j) + 0.5*q(i,j+1)
297 
298  else
299  q(i,j) = q(i,j) + 0.5*(real(2-j)*q(i,1) - real(1-j)*q(i,2))
300  end if
301 
302  end do
303  end do
304 
305  else
306 
307  do j=jsd,0
308  do i=isd,0
309 
310  q(i,j) = 0.5*( real(2-i)*q(1,j) - real(1-i)*q(2,j) ) + &
311  0.5*( real(2-j)*q(i,1) - real(1-j)*q(i,2) )
312 
313  end do
314  end do
315 
316  end if
317 
318  end if
319 
320  if (is == 1 .and. je == npy-1) then
321 
322  if (pd) then
323 
324  do j=je+1+jstag,jed+jstag
325  do i=0,isd,-1
326 
327  if (real(i) <= 1. - q(1,j)/(q(2,j) - q(1,j) + 1.e-12) .and. q(2,j) > q(1,j)) then
328  q(i,j) = 0.5*q(i+1,j)
329  else
330  q(i,j) = 0.5*( real(2-i)*q(1,j) - real(1-i)*q(2,j) )
331  end if
332 
333  !'Unary plus' removed to appease IBM compiler
334  !if (real(j) >= je+jstag - q(i,je+jstag)/(q(i,je+jstag-1)-q(i,je+jstag)+1.e-12) .and. &
335  if (real(j) >= je+jstag - q(i,je+jstag)/(q(i,je+jstag-1)-q(i,je+jstag)+1.e-12) .and. &
336  q(i,je+jstag-1) > q(i,je+jstag) ) then
337  q(i,j) = q(i,j) + 0.5*q(i,j-1)
338  else
339  q(i,j) = q(i,j) + 0.5*( real(j - (je+jstag-1))*q(i,je+jstag) + real((je+jstag) - j)*q(i,je+jstag-1) )
340  end if
341 
342  end do
343  end do
344 
345  else
346 
347  do j=je+1+jstag,jed+jstag
348  do i=isd,0
349 
350  q(i,j) = 0.5*( real(2-i)*q(1,j) - real(1-i)*q(2,j) ) + &
351  0.5*( real(j - (je+jstag-1))*q(i,je+jstag) + real((je+jstag) - j)*q(i,je+jstag-1) )
352 
353  end do
354  end do
355 
356  end if
357 
358  end if
359 
360  if (ie == npx-1 .and. je == npy-1) then
361 
362  if (pd) then
363 
364  do j=je+1+jstag,jed+jstag
365  do i=ie+1+istag,ied+istag
366 
367 
368  if (real(i) >= ie+istag + q(ie+istag,j)/(q(ie+istag-1,j)-q(ie+istag,j)+1.e-12) .and. &
369  q(ie+istag-1,j) > q(ie+istag,j)) then
370  q(i,j) = 0.5*q(i-1,j)
371  else
372  q(i,j) = 0.5*(real(i - (ie+istag-1))*q(ie+istag,j) + real((ie+istag) - i)*q(ie+istag-1,j))
373  end if
374 
375  if (real(j) >= je+jstag + q(i,je+jstag)/(q(i,je+jstag-1)-q(i,je+jstag)+1.e-12) .and. &
376  q(i,je+jstag-1) > q(i,je+jstag)) then
377  q(i,j) = q(i,j) + 0.5*q(i,j-1)
378  else
379  q(i,j) = q(i,j) + 0.5*( real(j - (je+jstag-1))*q(i,je+jstag) + real((je+jstag) - j)*q(i,je+jstag-1) )
380  end if
381 
382  end do
383  end do
384 
385  else
386 
387  do j=je+1+jstag,jed+jstag
388  do i=ie+1+istag,ied+istag
389 
390  q(i,j) = 0.5*( real(i - (ie+istag-1))*q(ie+istag,j) + real((ie+istag) - i)*q(ie+istag-1,j) ) + &
391  0.5*( real(j - (je+jstag-1))*q(i,je+jstag) + real((je+jstag) - j)*q(i,je+jstag-1) )
392 
393  end do
394  end do
395 
396  end if
397 
398  end if
399 
400  if (ie == npx-1 .and. js == 1) then
401 
402  if (pd) then
403 
404  do j=0,jsd,-1
405  do i=ie+1+istag,ied+istag
406 
407 
408  if (real(i) >= ie+istag + q(ie+istag,j)/(q(ie+istag-1,j)-q(ie+istag,j)+1.e-12) .and. &
409  q(ie+istag-1,j) > q(ie+istag,j)) then
410  q(i,j) = 0.5*q(i-1,j)
411  else
412  q(i,j) = 0.5*(real(i - (ie+istag-1))*q(ie+istag,j) + real((ie+istag) - i)*q(ie+istag-1,j))
413  end if
414 
415  if (real(j) <= 1. - q(i,1)/(q(i,2) - q(i,1) + 1.e-12) .and. &
416  q(i,2) > q(i,1)) then
417  q(i,j) = q(i,j) + 0.5*q(i,j+1)
418  else
419  q(i,j) = q(i,j) + 0.5*(real(2-j)*q(i,1) - real(1-j)*q(i,2))
420  end if
421 
422  end do
423  end do
424 
425 
426  else
427 
428  do j=jsd,0
429  do i=ie+1+istag,ied+istag
430 
431  q(i,j) = 0.5*( real(i - (ie+istag-1))*q(ie+istag,j) + real((ie+istag) - i)*q(ie+istag-1,j) ) + &
432  0.5*( real(2-j)*q(i,1) - real(1-j)*q(i,2) )
433 
434  end do
435  end do
436 
437  end if
438 
439  end if
440 
441 
442  end subroutine extrapolation_bc
443 
444  subroutine fill_nested_grid_2d(var_nest, var_coarse, ind, wt, istag, jstag, &
445  isg, ieg, jsg, jeg, bd, istart_in, iend_in, jstart_in, jend_in)
447  type(fv_grid_bounds_type), intent(IN) :: bd
448  real, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag), intent(INOUT) :: var_nest
449  real, dimension(isg:ieg+istag,jsg:jeg+jstag), intent(IN) :: var_coarse
450  integer, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,2), intent(IN) :: ind
451  real, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,4), intent(IN) :: wt
452  integer, intent(IN) :: istag, jstag, isg, ieg, jsg, jeg
453  integer, intent(IN), OPTIONAL :: istart_in, iend_in, jstart_in, jend_in
454 
455  integer :: i,j, ic, jc
456  integer :: istart, iend, jstart, jend
457 
458  integer :: is, ie, js, je
459  integer :: isd, ied, jsd, jed
460 
461  is = bd%is
462  ie = bd%ie
463  js = bd%js
464  je = bd%je
465  isd = bd%isd
466  ied = bd%ied
467  jsd = bd%jsd
468  jed = bd%jed
469 
470  if (present(istart_in)) then
471  istart = istart_in
472  else
473  istart = isd
474  end if
475  if (present(iend_in)) then
476  iend = iend_in+istag
477  else
478  iend = ied+istag
479  end if
480 
481  if (present(jstart_in)) then
482  jstart = jstart_in
483  else
484  jstart = jsd
485  end if
486  if (present(jend_in)) then
487  jend = jend_in+jstag
488  else
489  jend = jed+jstag
490  end if
491 
492  do j=jstart,jend
493  do i=istart,iend
494 
495  ic = ind(i,j,1)
496  jc = ind(i,j,2)
497 
498  var_nest(i,j) = &
499  wt(i,j,1)*var_coarse(ic, jc) + &
500  wt(i,j,2)*var_coarse(ic, jc+1) + &
501  wt(i,j,3)*var_coarse(ic+1,jc+1) + &
502  wt(i,j,4)*var_coarse(ic+1,jc)
503 
504  end do
505  end do
506 
507  end subroutine fill_nested_grid_2d
508 
509  subroutine fill_nested_grid_3d(var_nest, var_coarse, ind, wt, istag, jstag, &
510  isg, ieg, jsg, jeg, npz, bd, istart_in, iend_in, jstart_in, jend_in)
512  type(fv_grid_bounds_type), intent(IN) :: bd
513  real, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,npz), intent(INOUT) :: var_nest
514  real, dimension(isg:ieg+istag,jsg:jeg+jstag,npz), intent(IN) :: var_coarse
515  integer, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,2), intent(IN) :: ind
516  real, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,4), intent(IN) :: wt
517  integer, intent(IN) :: istag, jstag, isg, ieg, jsg, jeg, npz
518  integer, intent(IN), OPTIONAL :: istart_in, iend_in, jstart_in, jend_in
519 
520  integer :: i,j, ic, jc, k
521  integer :: istart, iend, jstart, jend
522 
523  integer :: is, ie, js, je
524  integer :: isd, ied, jsd, jed
525 
526  is = bd%is
527  ie = bd%ie
528  js = bd%js
529  je = bd%je
530  isd = bd%isd
531  ied = bd%ied
532  jsd = bd%jsd
533  jed = bd%jed
534 
535  if (present(istart_in)) then
536  istart = istart_in
537  else
538  istart = isd
539  end if
540  if (present(iend_in)) then
541  iend = iend_in+istag
542  else
543  iend = ied+istag
544  end if
545 
546  if (present(jstart_in)) then
547  jstart = jstart_in
548  else
549  jstart = jsd
550  end if
551  if (present(jend_in)) then
552  jend = jend_in+jstag
553  else
554  jend = jed+jstag
555  end if
556 
557  do k=1,npz
558 
559  do j=jstart,jend
560  do i=istart,iend
561 
562  ic = ind(i,j,1)
563  jc = ind(i,j,2)
564 
565  var_nest(i,j,k) = &
566  wt(i,j,1)*var_coarse(ic, jc, k) + &
567  wt(i,j,2)*var_coarse(ic, jc+1,k) + &
568  wt(i,j,3)*var_coarse(ic+1,jc+1,k) + &
569  wt(i,j,4)*var_coarse(ic+1,jc, k)
570 
571  end do
572  end do
573 
574  end do
575 
576  end subroutine fill_nested_grid_3d
577 
578  subroutine nested_grid_bc_mpp(var_nest, var_coarse, nest_domain, ind, wt, istag, jstag, &
579  npx, npy, npz, bd, isg, ieg, jsg, jeg, nstep_in, nsplit_in, proc_in)
581  type(fv_grid_bounds_type), intent(IN) :: bd
582  real, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,npz), intent(INOUT) :: var_nest
583  real, dimension(isg:ieg+istag,jsg:jeg+jstag,npz), intent(IN) :: var_coarse
584  type(nest_domain_type), intent(INOUT) :: nest_domain
585  integer, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,2), intent(IN) :: ind
586  real, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,4), intent(IN) :: wt
587  integer, intent(IN) :: istag, jstag, npx, npy, npz, isg, ieg, jsg, jeg
588  integer, intent(IN), OPTIONAL :: nstep_in, nsplit_in
589  logical, intent(IN), OPTIONAL :: proc_in
590 
591  integer :: isw_f, iew_f, jsw_f, jew_f, isw_c, iew_c, jsw_c, jew_c
592  integer :: ise_f, iee_f, jse_f, jee_f, ise_c, iee_c, jse_c, jee_c
593  integer :: iss_f, ies_f, jss_f, jes_f, iss_c, ies_c, jss_c, jes_c
594  integer :: isn_f, ien_f, jsn_f, jen_f, isn_c, ien_c, jsn_c, jen_c
595  real, allocatable :: wbuffer(:,:,:)
596  real, allocatable :: ebuffer(:,:,:)
597  real, allocatable :: sbuffer(:,:,:)
598  real, allocatable :: nbuffer(:,:,:)
599 
600  integer :: i,j, ic, jc, istart, iend, k
601 
602  integer :: position
603  logical :: process
604 
605  integer :: is, ie, js, je
606  integer :: isd, ied, jsd, jed
607 
608  is = bd%is
609  ie = bd%ie
610  js = bd%js
611  je = bd%je
612  isd = bd%isd
613  ied = bd%ied
614  jsd = bd%jsd
615  jed = bd%jed
616 
617  if (PRESENT(proc_in)) then
618  process = proc_in
619  else
620  process = .true.
621  endif
622 
623  if (istag == 1 .and. jstag == 1) then
624  position = corner
625  else if (istag == 0 .and. jstag == 1) then
626  position = north
627  else if (istag == 1 .and. jstag == 0) then
628  position = east
629  else
630  position = center
631  end if
632 
633  call mpp_get_c2f_index(nest_domain, isw_f, iew_f, jsw_f, jew_f, isw_c, iew_c, jsw_c, jew_c, &
634  west, position=position)
635  call mpp_get_c2f_index(nest_domain, ise_f, iee_f, jse_f, jee_f, ise_c, iee_c, jse_c, jee_c, &
636  east, position=position)
637  call mpp_get_c2f_index(nest_domain, iss_f, ies_f, jss_f, jes_f, iss_c, ies_c, jss_c, jes_c, &
638  south, position=position)
639  call mpp_get_c2f_index(nest_domain, isn_f, ien_f, jsn_f, jen_f, isn_c, ien_c, jsn_c, jen_c, &
640  north, position=position)
641 
642  if( iew_c .GE. isw_c .AND. jew_c .GE. jsw_c ) then
643  allocate(wbuffer(isw_c:iew_c, jsw_c:jew_c,npz))
644  else
645  allocate(wbuffer(1,1,1))
646  endif
647  wbuffer = 0
648 
649  if( iee_c .GE. ise_c .AND. jee_c .GE. jse_c ) then
650  allocate(ebuffer(ise_c:iee_c, jse_c:jee_c,npz))
651  else
652  allocate(ebuffer(1,1,1))
653  endif
654  ebuffer = 0
655 
656  if( ies_c .GE. iss_c .AND. jes_c .GE. jss_c ) then
657  allocate(sbuffer(iss_c:ies_c, jss_c:jes_c,npz))
658  else
659  allocate(sbuffer(1,1,1))
660  endif
661  sbuffer = 0
662 
663  if( ien_c .GE. isn_c .AND. jen_c .GE. jsn_c ) then
664  allocate(nbuffer(isn_c:ien_c, jsn_c:jen_c,npz))
665  else
666  allocate(nbuffer(1,1,1))
667  endif
668  nbuffer = 0
669 
670 
671  call timing_on ('COMM_TOTAL')
672  call mpp_update_nest_fine(var_coarse, nest_domain, wbuffer, sbuffer, ebuffer, nbuffer, position=position)
673  call timing_off('COMM_TOTAL')
674 
675  if (process) then
676 
677  if (is == 1) then
678  do k=1,npz
679  do j=jsd,jed+jstag
680  do i=isd,0
681 
682  ic = ind(i,j,1)
683  jc = ind(i,j,2)
684 
685  var_nest(i,j,k) = &
686  wt(i,j,1)*wbuffer(ic, jc, k) + &
687  wt(i,j,2)*wbuffer(ic, jc+1,k) + &
688  wt(i,j,3)*wbuffer(ic+1,jc+1,k) + &
689  wt(i,j,4)*wbuffer(ic+1,jc, k)
690 
691  end do
692  end do
693  end do
694  end if
695 
696  if (js == 1) then
697 
698  if (is == 1) then
699  istart = is
700  else
701  istart = isd
702  end if
703 
704  if (ie == npx-1) then
705  iend = ie
706  else
707  iend = ied
708  end if
709 
710  do k=1,npz
711  do j=jsd,0
712  do i=istart,iend+istag
713 
714  ic = ind(i,j,1)
715  jc = ind(i,j,2)
716 
717  var_nest(i,j,k) = &
718  wt(i,j,1)*sbuffer(ic, jc, k) + &
719  wt(i,j,2)*sbuffer(ic, jc+1,k) + &
720  wt(i,j,3)*sbuffer(ic+1,jc+1,k) + &
721  wt(i,j,4)*sbuffer(ic+1,jc, k)
722 
723  end do
724  end do
725  end do
726  end if
727 
728 
729  if (ie == npx-1) then
730  do k=1,npz
731  do j=jsd,jed+jstag
732  do i=npx+istag,ied+istag
733 
734  ic = ind(i,j,1)
735  jc = ind(i,j,2)
736 
737  var_nest(i,j,k) = &
738  wt(i,j,1)*ebuffer(ic, jc, k) + &
739  wt(i,j,2)*ebuffer(ic, jc+1,k) + &
740  wt(i,j,3)*ebuffer(ic+1,jc+1,k) + &
741  wt(i,j,4)*ebuffer(ic+1,jc, k)
742 
743  end do
744  end do
745  end do
746  end if
747 
748  if (je == npy-1) then
749 
750  if (is == 1) then
751  istart = is
752  else
753  istart = isd
754  end if
755 
756  if (ie == npx-1) then
757  iend = ie
758  else
759  iend = ied
760  end if
761 
762  do k=1,npz
763  do j=npy+jstag,jed+jstag
764  do i=istart,iend+istag
765 
766  ic = ind(i,j,1)
767  jc = ind(i,j,2)
768 
769  var_nest(i,j,k) = &
770  wt(i,j,1)*nbuffer(ic, jc, k) + &
771  wt(i,j,2)*nbuffer(ic, jc+1,k) + &
772  wt(i,j,3)*nbuffer(ic+1,jc+1,k) + &
773  wt(i,j,4)*nbuffer(ic+1,jc, k)
774 
775  end do
776  end do
777  end do
778  end if
779 
780  endif !process
781 
782  deallocate(wbuffer, ebuffer, sbuffer, nbuffer)
783 
784  end subroutine nested_grid_bc_mpp
785 
786  subroutine nested_grid_bc_mpp_send(var_coarse, nest_domain, istag, jstag)
788  real, dimension(:,:,:), intent(IN) :: var_coarse
789  type(nest_domain_type), intent(INOUT) :: nest_domain
790  integer, intent(IN) :: istag, jstag
791 
792  real, allocatable :: wbuffer(:,:,:)
793  real, allocatable :: ebuffer(:,:,:)
794  real, allocatable :: sbuffer(:,:,:)
795  real, allocatable :: nbuffer(:,:,:)
796 
797  integer :: i,j, ic, jc, istart, iend, k
798 
799  integer :: position
800 
801 
802  if (istag == 1 .and. jstag == 1) then
803  position = corner
804  else if (istag == 0 .and. jstag == 1) then
805  position = north
806  else if (istag == 1 .and. jstag == 0) then
807  position = east
808  else
809  position = center
810  end if
811 
812 
813  allocate(wbuffer(1,1,1))
814 
815  allocate(ebuffer(1,1,1))
816 
817  allocate(sbuffer(1,1,1))
818 
819  allocate(nbuffer(1,1,1))
820 
821 
822  call timing_on ('COMM_TOTAL')
823  call mpp_update_nest_fine(var_coarse, nest_domain, wbuffer, sbuffer, ebuffer, nbuffer, position=position)
824  call timing_off('COMM_TOTAL')
825 
826 
827  deallocate(wbuffer, ebuffer, sbuffer, nbuffer)
828 
829  end subroutine nested_grid_bc_mpp_send
830 
831  subroutine nested_grid_bc_2d_mpp(var_nest, var_coarse, nest_domain, ind, wt, istag, jstag, &
832  npx, npy, bd, isg, ieg, jsg, jeg, nstep_in, nsplit_in, proc_in)
834  type(fv_grid_bounds_type), intent(IN) :: bd
835  real, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag), intent(INOUT) :: var_nest
836  real, dimension(isg:ieg+istag,jsg:jeg+jstag), intent(IN) :: var_coarse
837  type(nest_domain_type), intent(INOUT) :: nest_domain
838  integer, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,2), intent(IN) :: ind
839  real, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,4), intent(IN) :: wt
840  integer, intent(IN) :: istag, jstag, npx, npy, isg, ieg, jsg, jeg
841  integer, intent(IN), OPTIONAL :: nstep_in, nsplit_in
842  logical, intent(IN), OPTIONAL :: proc_in
843 
844  integer :: isw_f, iew_f, jsw_f, jew_f, isw_c, iew_c, jsw_c, jew_c
845  integer :: ise_f, iee_f, jse_f, jee_f, ise_c, iee_c, jse_c, jee_c
846  integer :: iss_f, ies_f, jss_f, jes_f, iss_c, ies_c, jss_c, jes_c
847  integer :: isn_f, ien_f, jsn_f, jen_f, isn_c, ien_c, jsn_c, jen_c
848  real, allocatable :: wbuffer(:,:)
849  real, allocatable :: ebuffer(:,:)
850  real, allocatable :: sbuffer(:,:)
851  real, allocatable :: nbuffer(:,:)
852 
853  integer :: i,j, ic, jc, istart, iend, k
854 
855  integer :: position
856  logical :: process
857 
858  integer :: is, ie, js, je
859  integer :: isd, ied, jsd, jed
860 
861  is = bd%is
862  ie = bd%ie
863  js = bd%js
864  je = bd%je
865  isd = bd%isd
866  ied = bd%ied
867  jsd = bd%jsd
868  jed = bd%jed
869 
870  if (PRESENT(proc_in)) then
871  process = proc_in
872  else
873  process = .true.
874  endif
875 
876  if (istag == 1 .and. jstag == 1) then
877  position = corner
878  else if (istag == 0 .and. jstag == 1) then
879  position = north
880  else if (istag == 1 .and. jstag == 0) then
881  position = east
882  else
883  position = center
884  end if
885 
886  call mpp_get_c2f_index(nest_domain, isw_f, iew_f, jsw_f, jew_f, isw_c, iew_c, jsw_c, jew_c, &
887  west, position=position)
888  call mpp_get_c2f_index(nest_domain, ise_f, iee_f, jse_f, jee_f, ise_c, iee_c, jse_c, jee_c, &
889  east, position=position)
890  call mpp_get_c2f_index(nest_domain, iss_f, ies_f, jss_f, jes_f, iss_c, ies_c, jss_c, jes_c, &
891  south, position=position)
892  call mpp_get_c2f_index(nest_domain, isn_f, ien_f, jsn_f, jen_f, isn_c, ien_c, jsn_c, jen_c, &
893  north, position=position)
894 
895  if( iew_c .GE. isw_c .AND. jew_c .GE. jsw_c ) then
896  allocate(wbuffer(isw_c:iew_c, jsw_c:jew_c))
897  else
898  allocate(wbuffer(1,1))
899  endif
900  wbuffer = 0
901 
902  if( iee_c .GE. ise_c .AND. jee_c .GE. jse_c ) then
903  allocate(ebuffer(ise_c:iee_c, jse_c:jee_c))
904  else
905  allocate(ebuffer(1,1))
906  endif
907  ebuffer = 0
908 
909  if( ies_c .GE. iss_c .AND. jes_c .GE. jss_c ) then
910  allocate(sbuffer(iss_c:ies_c, jss_c:jes_c))
911  else
912  allocate(sbuffer(1,1))
913  endif
914  sbuffer = 0
915 
916  if( ien_c .GE. isn_c .AND. jen_c .GE. jsn_c ) then
917  allocate(nbuffer(isn_c:ien_c, jsn_c:jen_c))
918  else
919  allocate(nbuffer(1,1))
920  endif
921  nbuffer = 0
922 
923  call timing_on ('COMM_TOTAL')
924  call mpp_update_nest_fine(var_coarse, nest_domain, wbuffer, sbuffer, ebuffer, nbuffer, position=position)
925  call timing_off('COMM_TOTAL')
926 
927  if (process) then
928 
929  if (is == 1) then
930  do j=jsd,jed+jstag
931  do i=isd,0
932 
933  ic = ind(i,j,1)
934  jc = ind(i,j,2)
935 
936  var_nest(i,j) = &
937  wt(i,j,1)*wbuffer(ic, jc) + &
938  wt(i,j,2)*wbuffer(ic, jc+1) + &
939  wt(i,j,3)*wbuffer(ic+1,jc+1) + &
940  wt(i,j,4)*wbuffer(ic+1,jc)
941 
942  end do
943  end do
944  end if
945 
946  if (js == 1) then
947 
948  if (is == 1) then
949  istart = is
950  else
951  istart = isd
952  end if
953 
954  if (ie == npx-1) then
955  iend = ie
956  else
957  iend = ied
958  end if
959 
960  do j=jsd,0
961  do i=istart,iend+istag
962 
963  ic = ind(i,j,1)
964  jc = ind(i,j,2)
965 
966  var_nest(i,j) = &
967  wt(i,j,1)*sbuffer(ic, jc) + &
968  wt(i,j,2)*sbuffer(ic, jc+1) + &
969  wt(i,j,3)*sbuffer(ic+1,jc+1) + &
970  wt(i,j,4)*sbuffer(ic+1,jc)
971 
972  end do
973  end do
974  end if
975 
976 
977  if (ie == npx-1) then
978  do j=jsd,jed+jstag
979  do i=npx+istag,ied+istag
980 
981  ic = ind(i,j,1)
982  jc = ind(i,j,2)
983 
984  var_nest(i,j) = &
985  wt(i,j,1)*ebuffer(ic, jc) + &
986  wt(i,j,2)*ebuffer(ic, jc+1) + &
987  wt(i,j,3)*ebuffer(ic+1,jc+1) + &
988  wt(i,j,4)*ebuffer(ic+1,jc)
989 
990  end do
991  end do
992  end if
993 
994  if (je == npy-1) then
995 
996  if (is == 1) then
997  istart = is
998  else
999  istart = isd
1000  end if
1001 
1002  if (ie == npx-1) then
1003  iend = ie
1004  else
1005  iend = ied
1006  end if
1007 
1008  do j=npy+jstag,jed+jstag
1009  do i=istart,iend+istag
1010 
1011  ic = ind(i,j,1)
1012  jc = ind(i,j,2)
1013 
1014  var_nest(i,j) = &
1015  wt(i,j,1)*nbuffer(ic, jc) + &
1016  wt(i,j,2)*nbuffer(ic, jc+1) + &
1017  wt(i,j,3)*nbuffer(ic+1,jc+1) + &
1018  wt(i,j,4)*nbuffer(ic+1,jc)
1019 
1020  end do
1021  end do
1022  end if
1023 
1024  endif !process
1025 
1026  deallocate(wbuffer, ebuffer, sbuffer, nbuffer)
1027 
1028  end subroutine nested_grid_bc_2d_mpp
1029 
1030  subroutine nested_grid_bc_2d(var_nest, var_coarse, ind, wt, istag, jstag, &
1031  npx, npy, bd, isg, ieg, jsg, jeg, nstep_in, nsplit_in)
1033  type(fv_grid_bounds_type), intent(IN) :: bd
1034  real, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag), intent(INOUT) :: var_nest
1035  real, dimension(isg:ieg+istag,jsg:jeg+jstag), intent(IN) :: var_coarse
1036  integer, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,2), intent(IN) :: ind
1037  real, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,4), intent(IN) :: wt
1038  integer, intent(IN) :: istag, jstag, npx, npy, isg, ieg, jsg, jeg
1039  integer, intent(IN), OPTIONAL :: nstep_in, nsplit_in
1040 
1041  integer :: nstep, nsplit
1042 
1043  integer :: i,j, ic, jc, istart, iend
1044 
1045  integer :: is, ie, js, je
1046  integer :: isd, ied, jsd, jed
1047 
1048  is = bd%is
1049  ie = bd%ie
1050  js = bd%js
1051  je = bd%je
1052  isd = bd%isd
1053  ied = bd%ied
1054  jsd = bd%jsd
1055  jed = bd%jed
1056 
1057  if ( .not. present(nstep_in) .or. .not. present(nsplit_in) ) then
1058  nstep = 1
1059  nsplit = 2
1060  else
1061  nstep = nstep_in
1062  nsplit = nsplit_in
1063  end if
1064 
1065  if (is == 1) then
1066  do j=jsd,jed+jstag
1067  do i=isd,0
1068 
1069  ic = ind(i,j,1)
1070  jc = ind(i,j,2)
1071 
1072  var_nest(i,j) = &
1073  wt(i,j,1)*var_coarse(ic, jc) + &
1074  wt(i,j,2)*var_coarse(ic, jc+1) + &
1075  wt(i,j,3)*var_coarse(ic+1,jc+1) + &
1076  wt(i,j,4)*var_coarse(ic+1,jc)
1077 
1078  end do
1079  end do
1080  end if
1081 
1082  if (js == 1) then
1083 
1084  if (is == 1) then
1085  istart = is
1086  else
1087  istart = isd
1088  end if
1089 
1090  if (ie == npx-1) then
1091  iend = ie
1092  else
1093  iend = ied
1094  end if
1095 
1096  do j=jsd,0
1097  do i=istart,iend+istag
1098 
1099  ic = ind(i,j,1)
1100  jc = ind(i,j,2)
1101 
1102  var_nest(i,j) = &
1103  wt(i,j,1)*var_coarse(ic, jc) + &
1104  wt(i,j,2)*var_coarse(ic, jc+1) + &
1105  wt(i,j,3)*var_coarse(ic+1,jc+1) + &
1106  wt(i,j,4)*var_coarse(ic+1,jc)
1107 
1108  end do
1109  end do
1110  end if
1111 
1112 
1113  if (ie == npx-1) then
1114  do j=jsd,jed+jstag
1115  do i=npx+istag,ied+istag
1116 
1117  ic = ind(i,j,1)
1118  jc = ind(i,j,2)
1119 
1120  var_nest(i,j) = &
1121  wt(i,j,1)*var_coarse(ic, jc) + &
1122  wt(i,j,2)*var_coarse(ic, jc+1) + &
1123  wt(i,j,3)*var_coarse(ic+1,jc+1) + &
1124  wt(i,j,4)*var_coarse(ic+1,jc)
1125 
1126  end do
1127  end do
1128  end if
1129 
1130  if (je == npy-1) then
1131 
1132  if (is == 1) then
1133  istart = is
1134  else
1135  istart = isd
1136  end if
1137 
1138  if (ie == npx-1) then
1139  iend = ie
1140  else
1141  iend = ied
1142  end if
1143 
1144 
1145  do j=npy+jstag,jed+jstag
1146  do i=istart,iend+istag
1147 
1148  ic = ind(i,j,1)
1149  jc = ind(i,j,2)
1150 
1151  var_nest(i,j) = &
1152  wt(i,j,1)*var_coarse(ic, jc) + &
1153  wt(i,j,2)*var_coarse(ic, jc+1) + &
1154  wt(i,j,3)*var_coarse(ic+1,jc+1) + &
1155  wt(i,j,4)*var_coarse(ic+1,jc)
1156 
1157  end do
1158  end do
1159  end if
1160 
1161 
1162 
1163  end subroutine nested_grid_bc_2d
1164 
1165  subroutine nested_grid_bc_3d(var_nest, var_coarse, ind, wt, istag, jstag, &
1166  npx, npy, npz, bd, isg, ieg, jsg, jeg, nstep_in, nsplit_in)
1168  type(fv_grid_bounds_type), intent(IN) :: bd
1169  real, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,npz), intent(INOUT) :: var_nest
1170  real, dimension(isg:ieg+istag,jsg:jeg+jstag,npz), intent(IN) :: var_coarse
1171  integer, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,2), intent(IN) :: ind
1172  real, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,4), intent(IN) :: wt
1173  integer, intent(IN) :: istag, jstag, npx, npy, isg, ieg, jsg, jeg, npz
1174  integer, intent(IN), OPTIONAL :: nstep_in, nsplit_in
1175 
1176  integer :: nstep, nsplit
1177 
1178  integer :: i,j, ic, jc, istart, iend, k
1179 
1180  integer :: is, ie, js, je
1181  integer :: isd, ied, jsd, jed
1182 
1183  is = bd%is
1184  ie = bd%ie
1185  js = bd%js
1186  je = bd%je
1187  isd = bd%isd
1188  ied = bd%ied
1189  jsd = bd%jsd
1190  jed = bd%jed
1191 
1192  if ( .not. present(nstep_in) .or. .not. present(nsplit_in) ) then
1193  nstep = 1
1194  nsplit = 2
1195  else
1196  nstep = nstep_in
1197  nsplit = nsplit_in
1198  end if
1199 
1200  if (is == 1) then
1201  do k=1,npz
1202  do j=jsd,jed+jstag
1203  do i=isd,0
1204 
1205  ic = ind(i,j,1)
1206  jc = ind(i,j,2)
1207 
1208  var_nest(i,j,k) = &
1209  wt(i,j,1)*var_coarse(ic, jc, k) + &
1210  wt(i,j,2)*var_coarse(ic, jc+1,k) + &
1211  wt(i,j,3)*var_coarse(ic+1,jc+1,k) + &
1212  wt(i,j,4)*var_coarse(ic+1,jc, k)
1213 
1214  end do
1215  end do
1216  end do
1217  end if
1218 
1219  if (js == 1) then
1220 
1221  if (is == 1) then
1222  istart = is
1223  else
1224  istart = isd
1225  end if
1226 
1227  if (ie == npx-1) then
1228  iend = ie
1229  else
1230  iend = ied
1231  end if
1232 
1233  do k=1,npz
1234  do j=jsd,0
1235  do i=istart,iend+istag
1236 
1237  ic = ind(i,j,1)
1238  jc = ind(i,j,2)
1239 
1240  var_nest(i,j,k) = &
1241  wt(i,j,1)*var_coarse(ic, jc, k) + &
1242  wt(i,j,2)*var_coarse(ic, jc+1,k) + &
1243  wt(i,j,3)*var_coarse(ic+1,jc+1,k) + &
1244  wt(i,j,4)*var_coarse(ic+1,jc, k)
1245 
1246  end do
1247  end do
1248  end do
1249  end if
1250 
1251 
1252  if (ie == npx-1) then
1253  do k=1,npz
1254  do j=jsd,jed+jstag
1255  do i=npx+istag,ied+istag
1256 
1257  ic = ind(i,j,1)
1258  jc = ind(i,j,2)
1259 
1260  var_nest(i,j,k) = &
1261  wt(i,j,1)*var_coarse(ic, jc, k) + &
1262  wt(i,j,2)*var_coarse(ic, jc+1,k) + &
1263  wt(i,j,3)*var_coarse(ic+1,jc+1,k) + &
1264  wt(i,j,4)*var_coarse(ic+1,jc, k)
1265 
1266  end do
1267  end do
1268  end do
1269  end if
1270 
1271  if (je == npy-1) then
1272 
1273  if (is == 1) then
1274  istart = is
1275  else
1276  istart = isd
1277  end if
1278 
1279  if (ie == npx-1) then
1280  iend = ie
1281  else
1282  iend = ied
1283  end if
1284 
1285  do k=1,npz
1286  do j=npy+jstag,jed+jstag
1287  do i=istart,iend+istag
1288 
1289  ic = ind(i,j,1)
1290  jc = ind(i,j,2)
1291 
1292  var_nest(i,j,k) = &
1293  wt(i,j,1)*var_coarse(ic, jc, k) + &
1294  wt(i,j,2)*var_coarse(ic, jc+1,k) + &
1295  wt(i,j,3)*var_coarse(ic+1,jc+1,k) + &
1296  wt(i,j,4)*var_coarse(ic+1,jc, k)
1297 
1298  end do
1299  end do
1300  end do
1301  end if
1302 
1303 
1304 
1305  end subroutine nested_grid_bc_3d
1306 
1308  subroutine nested_grid_bc_send(var_coarse, nest_domain, istag, jstag)
1310  real, dimension(:,:,:), intent(IN) :: var_coarse
1311  type(nest_domain_type), intent(INOUT) :: nest_domain
1312  integer, intent(IN) :: istag, jstag
1313 
1314  integer :: position
1315 
1316  real :: wbuffer(1,1,1)
1317  real :: ebuffer(1,1,1)
1318  real :: sbuffer(1,1,1)
1319  real :: nbuffer(1,1,1)
1320 
1321 
1322  if (istag == 1 .and. jstag == 1) then
1323  position = corner
1324  else if (istag == 0 .and. jstag == 1) then
1325  position = north
1326  else if (istag == 1 .and. jstag == 0) then
1327  position = east
1328  else
1329  position = center
1330  end if
1331 
1332  call timing_on ('COMM_TOTAL')
1333  call mpp_update_nest_fine(var_coarse, nest_domain, wbuffer, sbuffer, ebuffer, nbuffer, position=position)
1334  call timing_off('COMM_TOTAL')
1335 
1336  end subroutine nested_grid_bc_send
1337 
1339  subroutine nested_grid_bc_recv(nest_domain, istag, jstag, npz, &
1340  bd, nest_BC_buffers)
1342  type(fv_grid_bounds_type), intent(IN) :: bd
1343  type(nest_domain_type), intent(INOUT) :: nest_domain
1344  integer, intent(IN) :: istag, jstag, npz
1345 
1346  type(fv_nest_bc_type_3d), intent(INOUT), target :: nest_bc_buffers
1347 
1348  real, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,npz) :: var_coarse_dummy
1349 
1350  integer :: position
1351 
1352  integer :: isw_f, iew_f, jsw_f, jew_f, isw_c, iew_c, jsw_c, jew_c
1353  integer :: ise_f, iee_f, jse_f, jee_f, ise_c, iee_c, jse_c, jee_c
1354  integer :: iss_f, ies_f, jss_f, jes_f, iss_c, ies_c, jss_c, jes_c
1355  integer :: isn_f, ien_f, jsn_f, jen_f, isn_c, ien_c, jsn_c, jen_c
1356 
1357  integer :: i,j, k
1358 
1359  if (istag == 1 .and. jstag == 1) then
1360  position = corner
1361  else if (istag == 0 .and. jstag == 1) then
1362  position = north
1363  else if (istag == 1 .and. jstag == 0) then
1364  position = east
1365  else
1366  position = center
1367  end if
1368 
1369  if (.not. allocated(nest_bc_buffers%west_t1) ) then
1370 
1371  call mpp_get_c2f_index(nest_domain, isw_f, iew_f, jsw_f, jew_f, isw_c, iew_c, jsw_c, jew_c, &
1372  west, position=position)
1373  call mpp_get_c2f_index(nest_domain, ise_f, iee_f, jse_f, jee_f, ise_c, iee_c, jse_c, jee_c, &
1374  east, position=position)
1375  call mpp_get_c2f_index(nest_domain, iss_f, ies_f, jss_f, jes_f, iss_c, ies_c, jss_c, jes_c, &
1376  south, position=position)
1377  call mpp_get_c2f_index(nest_domain, isn_f, ien_f, jsn_f, jen_f, isn_c, ien_c, jsn_c, jen_c, &
1378  north, position=position)
1379 
1380  if( iew_c .GE. isw_c .AND. jew_c .GE. jsw_c ) then
1381  If (.not. allocated(nest_bc_buffers%west_t1)) allocate(nest_bc_buffers%west_t1(isw_c:iew_c, jsw_c:jew_c,npz))
1382  !compatible with first touch principle
1383  do k=1,npz
1384  do j=jsw_c,jew_c
1385  do i=isw_c,iew_c
1386  nest_bc_buffers%west_t1(i,j,k) = 0.
1387  enddo
1388  enddo
1389  enddo
1390  else
1391  allocate(nest_bc_buffers%west_t1(1,1,1))
1392  nest_bc_buffers%west_t1(1,1,1) = 0.
1393  endif
1394 
1395  if( iee_c .GE. ise_c .AND. jee_c .GE. jse_c ) then
1396  If (.not. allocated(nest_bc_buffers%east_t1)) allocate(nest_bc_buffers%east_t1(ise_c:iee_c, jse_c:jee_c,npz))
1397  do k=1,npz
1398  do j=jse_c,jee_c
1399  do i=ise_c,iee_c
1400  nest_bc_buffers%east_t1(i,j,k) = 0.
1401  enddo
1402  enddo
1403  enddo
1404  else
1405  allocate(nest_bc_buffers%east_t1(1,1,1))
1406  nest_bc_buffers%east_t1(1,1,1) = 0.
1407  endif
1408 
1409  if( ies_c .GE. iss_c .AND. jes_c .GE. jss_c ) then
1410  If (.not. allocated(nest_bc_buffers%south_t1)) allocate(nest_bc_buffers%south_t1(iss_c:ies_c, jss_c:jes_c,npz))
1411  do k=1,npz
1412  do j=jss_c,jes_c
1413  do i=iss_c,ies_c
1414  nest_bc_buffers%south_t1(i,j,k) = 0.
1415  enddo
1416  enddo
1417  enddo
1418  else
1419  allocate(nest_bc_buffers%south_t1(1,1,1))
1420  nest_bc_buffers%south_t1(1,1,1) = 0.
1421  endif
1422 
1423  if( ien_c .GE. isn_c .AND. jen_c .GE. jsn_c ) then
1424  If (.not. allocated(nest_bc_buffers%north_t1)) allocate(nest_bc_buffers%north_t1(isn_c:ien_c, jsn_c:jen_c,npz))
1425  do k=1,npz
1426  do j=jsn_c,jen_c
1427  do i=isn_c,ien_c
1428  nest_bc_buffers%north_t1(i,j,k) = 0.
1429  enddo
1430  enddo
1431  enddo
1432  else
1433  allocate(nest_bc_buffers%north_t1(1,1,1))
1434  nest_bc_buffers%north_t1(1,1,1) = 0
1435  endif
1436 
1437  endif
1438 
1439  call timing_on ('COMM_TOTAL')
1440  call mpp_update_nest_fine(var_coarse_dummy, nest_domain, nest_bc_buffers%west_t1, nest_bc_buffers%south_t1, nest_bc_buffers%east_t1, nest_bc_buffers%north_t1, position=position)
1441  call timing_off('COMM_TOTAL')
1442 
1443  end subroutine nested_grid_bc_recv
1444 
1447  subroutine nested_grid_bc_save_proc(nest_domain, ind, wt, istag, jstag, &
1448  npx, npy, npz, bd, nest_BC, nest_BC_buffers, pd_in)
1450  type(fv_grid_bounds_type), intent(IN) :: bd
1451  type(nest_domain_type), intent(INOUT) :: nest_domain
1452  integer, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,2), intent(IN) :: ind
1453  real, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,4), intent(IN) :: wt
1454  integer, intent(IN) :: istag, jstag, npx, npy, npz
1455  logical, intent(IN), OPTIONAL :: pd_in
1456 
1457  !!NOTE: if declaring an ALLOCATABLE array with intent(OUT), the resulting dummy array
1458  !! will NOT be allocated! This goes for allocatable members of derived types as well.
1459  type(fv_nest_bc_type_3d), intent(INOUT), target :: nest_bc, nest_bc_buffers
1460 
1461  real, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,npz) :: var_coarse_dummy
1462 
1463  real, dimension(:,:,:), pointer :: var_east, var_west, var_south, var_north
1464  real, dimension(:,:,:), pointer :: buf_east, buf_west, buf_south, buf_north
1465 
1466  integer :: position
1467 
1468 
1469  integer :: i,j, k, ic, jc, istart, iend
1470  logical :: process, pd = .false.
1471 
1472  integer :: is, ie, js, je
1473  integer :: isd, ied, jsd, jed
1474 
1475  is = bd%is
1476  ie = bd%ie
1477  js = bd%js
1478  je = bd%je
1479  isd = bd%isd
1480  ied = bd%ied
1481  jsd = bd%jsd
1482  jed = bd%jed
1483 
1484 
1485  if (present(pd_in)) then
1486  pd = pd_in
1487  else
1488  pd = .false.
1489  endif
1490 
1491 
1492  var_east => nest_bc%east_t1
1493  var_west => nest_bc%west_t1
1494  var_north => nest_bc%north_t1
1495  var_south => nest_bc%south_t1
1496 
1497  buf_east => nest_bc_buffers%east_t1
1498  buf_west => nest_bc_buffers%west_t1
1499  buf_north => nest_bc_buffers%north_t1
1500  buf_south => nest_bc_buffers%south_t1
1501  ! ?buffer has uninterpolated coarse-grid data; need to perform interpolation ourselves
1502  !To do this more securely, instead of using is/etc we could use the fine-grid indices defined above
1503  if (is == 1 ) then
1504 
1505 !$NO-MP parallel do default(none) shared(npz,isd,ied,jsd,jed,jstag,ind,var_west,wt,buf_west) private(ic,jc)
1506  do k=1,npz
1507  do j=jsd,jed+jstag
1508  do i=isd,0
1509 
1510  ic = ind(i,j,1)
1511  jc = ind(i,j,2)
1512 
1513 
1514  var_west(i,j,k) = &
1515  wt(i,j,1)*buf_west(ic, jc,k) + &
1516  wt(i,j,2)*buf_west(ic, jc+1,k) + &
1517  wt(i,j,3)*buf_west(ic+1,jc+1,k) + &
1518  wt(i,j,4)*buf_west(ic+1,jc,k)
1519 
1520  end do
1521  end do
1522  end do
1523 
1524  if (pd) then
1525 !$NO-MP parallel do default(none) shared(npz,jsd,jed,jstag,isd,var_west,nest_BC)
1526  do k=1,npz
1527  do j=jsd,jed+jstag
1528  do i=isd,0
1529 
1530  var_west(i,j,k) = max(var_west(i,j,k), 0.5*nest_bc%west_t0(i,j,k))
1531  end do
1532  end do
1533  end do
1534  endif
1535 
1536  end if
1537 
1538  if (js == 1 ) then
1539 
1540  if (is == 1) then
1541  istart = is
1542  else
1543  istart = isd
1544  end if
1545 
1546  if (ie == npx-1) then
1547  iend = ie
1548  else
1549  iend = ied
1550  end if
1551 
1552 !$NO-MP parallel do default(none) shared(npz,istart,iend,jsd,jed,istag,ind,var_south,wt,buf_south) private(ic,jc)
1553  do k=1,npz
1554  do j=jsd,0
1555  do i=istart,iend+istag
1556 
1557  ic = ind(i,j,1)
1558  jc = ind(i,j,2)
1559 
1560 
1561  var_south(i,j,k) = &
1562  wt(i,j,1)*buf_south(ic, jc,k) + &
1563  wt(i,j,2)*buf_south(ic, jc+1,k) + &
1564  wt(i,j,3)*buf_south(ic+1,jc+1,k) + &
1565  wt(i,j,4)*buf_south(ic+1,jc,k)
1566 
1567  end do
1568  end do
1569  end do
1570 
1571  if (pd) then
1572 !$NO-MP parallel do default(none) shared(npz,jsd,jed,istart,iend,istag,var_south,nest_BC)
1573  do k=1,npz
1574  do j=jsd,0
1575  do i=istart,iend+istag
1576 
1577  var_south(i,j,k) = max(var_south(i,j,k), 0.5*nest_bc%south_t0(i,j,k))
1578 
1579  end do
1580  end do
1581  end do
1582  endif
1583 
1584  end if
1585 
1586 
1587  if (ie == npx-1 ) then
1588 
1589 !$NO-MP parallel do default(none) shared(npx,npz,isd,ied,jsd,jed,istag,jstag,ind,var_east,wt,buf_east) private(ic,jc)
1590  do k=1,npz
1591  do j=jsd,jed+jstag
1592  do i=npx+istag,ied+istag
1593 
1594  ic = ind(i,j,1)
1595  jc = ind(i,j,2)
1596 
1597 
1598  var_east(i,j,k) = &
1599  wt(i,j,1)*buf_east(ic, jc,k) + &
1600  wt(i,j,2)*buf_east(ic, jc+1,k) + &
1601  wt(i,j,3)*buf_east(ic+1,jc+1,k) + &
1602  wt(i,j,4)*buf_east(ic+1,jc,k)
1603 
1604  end do
1605  end do
1606  end do
1607 
1608  if (pd) then
1609 !$NO-MP parallel do default(none) shared(npx,npz,jsd,jed,istag,jstag,ied,var_east,nest_BC)
1610  do k=1,npz
1611  do j=jsd,jed+jstag
1612  do i=npx+istag,ied+istag
1613 
1614  var_east(i,j,k) = max(var_east(i,j,k), 0.5*nest_bc%east_t0(i,j,k))
1615 
1616  end do
1617  end do
1618  end do
1619  endif
1620 
1621  end if
1622 
1623  if (je == npy-1 ) then
1624 
1625  if (is == 1) then
1626  istart = is
1627  else
1628  istart = isd
1629  end if
1630 
1631  if (ie == npx-1) then
1632  iend = ie
1633  else
1634  iend = ied
1635  end if
1636 
1637 !$NO-MP parallel do default(none) shared(npy,npz,istart,iend,jsd,jed,istag,jstag,ind,var_north,wt,buf_north) private(ic,jc)
1638  do k=1,npz
1639  do j=npy+jstag,jed+jstag
1640  do i=istart,iend+istag
1641 
1642  ic = ind(i,j,1)
1643  jc = ind(i,j,2)
1644 
1645 
1646  var_north(i,j,k) = &
1647  wt(i,j,1)*buf_north(ic, jc,k) + &
1648  wt(i,j,2)*buf_north(ic, jc+1,k) + &
1649  wt(i,j,3)*buf_north(ic+1,jc+1,k) + &
1650  wt(i,j,4)*buf_north(ic+1,jc,k)
1651 
1652  end do
1653  end do
1654  end do
1655 
1656  if (pd) then
1657 !$NO-MP parallel do default(none) shared(npy,npz,jsd,jed,istart,iend,istag,jstag,ied,var_north,nest_BC)
1658  do k=1,npz
1659  do j=npy+jstag,jed+jstag
1660  do i=istart,iend+istag
1661 
1662  var_north(i,j,k) = max(var_north(i,j,k), 0.5*nest_bc%north_t0(i,j,k))
1663 
1664  end do
1665  end do
1666  end do
1667  endif
1668 
1669  end if
1670 
1671  end subroutine nested_grid_bc_save_proc
1672 
1673 
1674  ! A NOTE ON BCTYPE: currently only an interpolation BC is implemented,
1675  ! bctype >= 2 currently correspond
1676  ! to a flux BC on the tracers ONLY, which is implemented in fv_tracer.
1677 
1681  subroutine nested_grid_bc_apply_intt(var_nest, istag, jstag, &
1682  npx, npy, npz, bd, step, split, &
1683  BC, bctype)
1685  type(fv_grid_bounds_type), intent(IN) :: bd
1686  real, dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag, npz), intent(INOUT) :: var_nest
1687  integer, intent(IN) :: istag, jstag, npx, npy, npz
1688  real, intent(IN) :: split, step
1689  integer, intent(IN) :: bctype
1690 
1691  type(fv_nest_bc_type_3d), intent(IN), target :: bc
1692  real, pointer, dimension(:,:,:) :: var_t0, var_t1
1693 
1694  integer :: i,j, istart, iend, k
1695  real :: denom
1696 
1697  logical, save :: printdiag = .true.
1698 
1699  integer :: is, ie, js, je
1700  integer :: isd, ied, jsd, jed
1701 
1702  is = bd%is
1703  ie = bd%ie
1704  js = bd%js
1705  je = bd%je
1706  isd = bd%isd
1707  ied = bd%ied
1708  jsd = bd%jsd
1709  jed = bd%jed
1710 
1711  denom = 1./split
1712  if (is == 1 ) then
1713  var_t0 => bc%west_t0
1714  var_t1 => bc%west_t1
1715  do k=1,npz
1716  do j=jsd,jed+jstag
1717  do i=isd,0
1718  var_nest(i,j,k) = (var_t0(i,j,k)*(split-step) + step*var_t1(i,j,k))*denom
1719  end do
1720 
1721  end do
1722  end do
1723  end if
1724 
1725  if (js == 1 ) then
1726 
1727  if (is == 1) then
1728  istart = is
1729  else
1730  istart = isd
1731  end if
1732 
1733  if (ie == npx-1) then
1734  iend = ie
1735  else
1736  iend = ied
1737  end if
1738 
1739  var_t0 => bc%south_t0
1740  var_t1 => bc%south_t1
1741  do k=1,npz
1742  do j=jsd,0
1743  do i=istart,iend+istag
1744 
1745  var_nest(i,j,k) = (var_t0(i,j,k)*(split-step) + step*var_t1(i,j,k))*denom
1746  end do
1747  end do
1748  end do
1749  end if
1750 
1751 
1752  if (ie == npx-1 ) then
1753  var_t0 => bc%east_t0
1754  var_t1 => bc%east_t1
1755  do k=1,npz
1756  do j=jsd,jed+jstag
1757  do i=npx+istag,ied+istag
1758  var_nest(i,j,k) = (var_t0(i,j,k)*(split-step) + step*var_t1(i,j,k))*denom
1759 
1760  end do
1761  end do
1762  end do
1763 
1764  end if
1765 
1766  if (je == npy-1 ) then
1767 
1768  if (is == 1) then
1769  istart = is
1770  else
1771  istart = isd
1772  end if
1773 
1774  if (ie == npx-1) then
1775  iend = ie
1776  else
1777  iend = ied
1778  end if
1779 
1780  var_t0 => bc%north_t0
1781  var_t1 => bc%north_t1
1782  do k=1,npz
1783  do j=npy+jstag,jed+jstag
1784  do i=istart,iend+istag
1785 
1786  var_nest(i,j,k) = (var_t0(i,j,k)*(split-step) + step*var_t1(i,j,k))*denom
1787 
1788  end do
1789  end do
1790  end do
1791 
1792  end if
1793 
1794 
1795  end subroutine nested_grid_bc_apply_intt
1796 
1797  subroutine update_coarse_grid_mpp_2d(var_coarse, var_nest, nest_domain, ind_update, dx, dy, area, &
1798  isd_p, ied_p, jsd_p, jed_p, is_n, ie_n, js_n, je_n, isu, ieu, jsu, jeu, npx, npy, &
1799  istag, jstag, r, nestupdate, upoff, nsponge, parent_proc, child_proc, parent_grid)
1801  integer, intent(IN) :: isd_p, ied_p, jsd_p, jed_p, is_n, ie_n, js_n, je_n
1802  integer, intent(IN) :: isu, ieu, jsu, jeu
1803  integer, intent(IN) :: istag, jstag, r, nestupdate, upoff, nsponge
1804  integer, intent(IN) :: ind_update(isd_p:ied_p+1,jsd_p:jed_p+1,2)
1805  integer, intent(IN) :: npx, npy
1806  real, intent(IN) :: var_nest(is_n:ie_n+istag,js_n:je_n+jstag)
1807  real, intent(INOUT) :: var_coarse(isd_p:ied_p+istag,jsd_p:jed_p+jstag)
1808  real, intent(IN) :: dx(isd:ied,jsd:jed+1)
1809  real, intent(IN) :: dy(isd:ied+1,jsd:jed)
1810  real, intent(IN) :: area(isd:ied,jsd:jed)
1811  logical, intent(IN) :: parent_proc, child_proc
1812  type(fv_atmos_type), intent(INOUT) :: parent_grid
1813  type(nest_domain_type), intent(INOUT) :: nest_domain
1814 
1815  real :: var_nest_3d(is_n:ie_n+istag,js_n:je_n+jstag,1)
1816  real :: var_coarse_3d(isd_p:ied_p+istag,jsd_p:jed_p+jstag,1)
1817 
1818  if (child_proc .and. size(var_nest) > 1) var_nest_3d(is_n:ie_n+istag,js_n:je_n+jstag,1) = var_nest(is_n:ie_n+istag,js_n:je_n+jstag)
1819  if (parent_proc .and. size(var_coarse) > 1) var_coarse_3d(isd_p:ied_p+istag,jsd_p:jed_p,1) = var_coarse(isd_p:ied_p+istag,jsd_p:jed_p+jstag)
1820 
1821  call update_coarse_grid_mpp(var_coarse_3d, var_nest_3d, &
1822  nest_domain, ind_update, dx, dy, area, &
1823  isd_p, ied_p, jsd_p, jed_p, is_n, ie_n, js_n, je_n, &
1824  isu, ieu, jsu, jeu, npx, npy, 1, &
1825  istag, jstag, r, nestupdate, upoff, nsponge, &
1826  parent_proc, child_proc, parent_grid)
1827 
1828  if (size(var_coarse) > 1 .and. parent_proc) var_coarse(isd_p:ied_p+istag,jsd_p:jed_p+jstag) = var_coarse_3d(isd_p:ied_p+istag,jsd_p:jed_p,1)
1829 
1830  end subroutine update_coarse_grid_mpp_2d
1831 
1832 
1833  subroutine update_coarse_grid_mpp(var_coarse, var_nest, nest_domain, ind_update, dx, dy, area, &
1834  isd_p, ied_p, jsd_p, jed_p, is_n, ie_n, js_n, je_n, &
1835  isu, ieu, jsu, jeu, npx, npy, npz, &
1836  istag, jstag, r, nestupdate, upoff, nsponge, &
1837  parent_proc, child_proc, parent_grid)
1839  !This routine assumes the coarse and nested grids are properly
1840  ! aligned, and that in particular for odd refinement ratios all
1841  ! coarse-grid cells (faces) coincide with nested-grid cells (faces)
1842 
1843  integer, intent(IN) :: isd_p, ied_p, jsd_p, jed_p, is_n, ie_n, js_n, je_n
1844  integer, intent(IN) :: isu, ieu, jsu, jeu
1845  integer, intent(IN) :: istag, jstag, npx, npy, npz, r, nestupdate, upoff, nsponge
1846  integer, intent(IN) :: ind_update(isd_p:ied_p+1,jsd_p:jed_p+1,2)
1847  real, intent(IN) :: var_nest(is_n:ie_n+istag,js_n:je_n+jstag,npz)
1848  real, intent(INOUT) :: var_coarse(isd_p:ied_p+istag,jsd_p:jed_p+jstag,npz)
1849  real, intent(IN) :: area(isd:ied,jsd:jed)
1850  real, intent(IN) :: dx(isd:ied,jsd:jed+1)
1851  real, intent(IN) :: dy(isd:ied+1,jsd:jed)
1852  logical, intent(IN) :: parent_proc, child_proc
1853  type(fv_atmos_type), intent(INOUT) :: parent_grid
1854  type(nest_domain_type), intent(INOUT) :: nest_domain
1855 
1856  integer :: in, jn, ini, jnj, s, qr
1857  integer :: is_c, ie_c, js_c, je_c, is_f, ie_f, js_f, je_f
1858  integer :: istart, istop, jstart, jstop, ishift, jshift, j, i, k
1859  real :: val
1860  real, allocatable, dimension(:,:,:) :: nest_dat
1861  real :: var_nest_send(is_n:ie_n+istag,js_n:je_n+jstag,npz)
1862  integer :: position
1863 
1864  if (istag == 1 .and. jstag == 1) then
1865  position = corner
1866  else if (istag == 0 .and. jstag == 1) then
1867  position = north
1868  else if (istag == 1 .and. jstag == 0) then
1869  position = east
1870  else
1871  position = center
1872  end if
1873 
1874  call mpp_get_f2c_index(nest_domain, is_c, ie_c, js_c, je_c, is_f, ie_f, js_f, je_f, position=position)
1875  if (ie_f > is_f .and. je_f > js_f) then
1876  allocate(nest_dat(is_f:ie_f, js_f:je_f,npz))
1877  else
1878  allocate(nest_dat(1,1,1))
1879  endif
1880  nest_dat = -600
1881 
1882  if (child_proc) then
1883 !! IF an area average (for istag == jstag == 0) or a linear average then multiply in the areas before sending data
1884  if (istag == 0 .and. jstag == 0) then
1885  select case (nestupdate)
1886  case (1,2,6,7,8)
1887 
1888 !$NO-MP parallel do default(none) shared(npz,js_n,je_n,is_n,ie_n,var_nest_send,var_nest,area)
1889  do k=1,npz
1890  do j=js_n,je_n
1891  do i=is_n,ie_n
1892 
1893  var_nest_send(i,j,k) = var_nest(i,j,k)*area(i,j)
1894 
1895  end do
1896  end do
1897  end do
1898 
1899  end select
1900  else if (istag == 0 .and. jstag > 0) then
1901 
1902  select case (nestupdate)
1903  case (1,6,7,8)
1904 
1905 !$NO-MP parallel do default(none) shared(npz,js_n,je_n,is_n,ie_n,var_nest_send,var_nest,dx)
1906  do k=1,npz
1907  do j=js_n,je_n+1
1908  do i=is_n,ie_n
1909 
1910 
1911  var_nest_send(i,j,k) = var_nest(i,j,k)*dx(i,j)
1912 
1913  end do
1914  end do
1915  end do
1916 
1917  case default
1918 
1919  call mpp_error(fatal, 'nestupdate type not implemented')
1920 
1921  end select
1922 
1923  else if (istag > 0 .and. jstag == 0) then
1924  select case (nestupdate)
1925 
1926  case (1,6,7,8) !averaging update; in-line average for face-averaged values instead of areal average
1927 
1928 !$NO-MP parallel do default(none) shared(npz,js_n,je_n,is_n,ie_n,var_nest_send,var_nest,dy)
1929  do k=1,npz
1930  do j=js_n,je_n
1931  do i=is_n,ie_n+1
1932 
1933  var_nest_send(i,j,k) = var_nest(i,j,k)*dy(i,j)
1934 
1935  end do
1936  end do
1937  end do
1938 
1939  case default
1940 
1941  call mpp_error(fatal, 'nestupdate type not implemented')
1942 
1943  end select
1944 
1945  else
1946 
1947  call mpp_error(fatal, "Cannot have both nonzero istag and jstag.")
1948 
1949  endif
1950  endif
1951 
1952  call timing_on('COMM_TOTAL')
1953  call mpp_update_nest_coarse(var_nest_send, nest_domain, nest_dat, position=position)
1954  call timing_off('COMM_TOTAL')
1955 
1956  s = r/2 !rounds down (since r > 0)
1957  qr = r*upoff + nsponge - s
1958 
1959  if (parent_proc .and. .not. (ieu < isu .or. jeu < jsu)) then
1960  if (istag == 0 .and. jstag == 0) then
1961 
1962  select case (nestupdate)
1963  case (1,2,6,7,8) ! 1 = Conserving update on all variables; 2 = conserving update for cell-centered values; 6 = conserving remap-update
1964 
1965 !$NO-MP parallel do default(none) shared(npz,jsu,jeu,isu,ieu,ind_update,nest_dat,parent_grid,var_coarse,r) &
1966 !$NO-MP private(in,jn,val)
1967  do k=1,npz
1968  do j=jsu,jeu
1969  do i=isu,ieu
1970 
1971  in = ind_update(i,j,1)
1972  jn = ind_update(i,j,2)
1973 
1974 !!$ if (in < max(1+qr,is_f) .or. in > min(npx-1-qr-r+1,ie_f) .or. &
1975 !!$ jn < max(1+qr,js_f) .or. jn > min(npy-1-qr-r+1,je_f)) then
1976 !!$ write(mpp_pe()+3000,'(A, 14I6)') 'SKIP: ', i, j, in, jn, 1+qr, is_f, ie_f, js_f, je_f, npy-1-qr-r+1, isu, ieu, jsu, jeu
1977 !!$ cycle
1978 !!$ endif
1979 
1980  val = 0.
1981  do jnj=jn,jn+r-1
1982  do ini=in,in+r-1
1983  val = val + nest_dat(ini,jnj,k)
1984  end do
1985  end do
1986 
1987  !var_coarse(i,j,k) = val/r**2.
1988 
1989  !!! CLEANUP: Couldn't rarea and rdx and rdy be built into the weight arrays?
1990  !!! Two-way updates do not yet have weights, tho
1991  var_coarse(i,j,k) = val*parent_grid%gridstruct%rarea(i,j)
1992 
1993  end do
1994  end do
1995  end do
1996 
1997 
1998  case default
1999 
2000  call mpp_error(fatal, 'nestupdate type not implemented')
2001 
2002 
2003  end select
2004 
2005  else if (istag == 0 .and. jstag > 0) then
2006 
2007 
2008  select case (nestupdate)
2009  case (1,6,7,8)
2010 
2011 !$NO-MP parallel do default(none) shared(npz,jsu,jeu,isu,ieu,ind_update,nest_dat,parent_grid,var_coarse,r) &
2012 !$NO-MP private(in,jn,val)
2013  do k=1,npz
2014  do j=jsu,jeu+1
2015  do i=isu,ieu
2016 
2017  in = ind_update(i,j,1)
2018  jn = ind_update(i,j,2)
2019 
2020 !!$ if (in < max(1+qr,is_f) .or. in > min(npx-1-qr-r+1,ie_f) .or. &
2021 !!$ jn < max(1+qr+s,js_f) .or. jn > min(npy-1-qr-s+1,je_f)) then
2022 !!$ write(mpp_pe()+3000,'(A, 14I)') 'SKIP u: ', i, j, in, jn, 1+qr, is_f, ie_f, js_f, je_f, npy-1-qr-s+1, isu, ieu, jsu, jeu
2023 !!$ cycle
2024 !!$ endif
2025 
2026  val = 0.
2027  do ini=in,in+r-1
2028  val = val + nest_dat(ini,jn,k)
2029  end do
2030 
2031 ! var_coarse(i,j,k) = val/r
2032  var_coarse(i,j,k) = val*parent_grid%gridstruct%rdx(i,j)
2033 
2034  end do
2035  end do
2036  end do
2037 
2038  case default
2039 
2040  call mpp_error(fatal, 'nestupdate type not implemented')
2041 
2042  end select
2043 
2044  else if (istag > 0 .and. jstag == 0) then
2045 
2046  select case (nestupdate)
2047  case (1,6,7,8) !averaging update; in-line average for face-averaged values instead of areal average
2048 
2049 !$NO-MP parallel do default(none) shared(npz,jsu,jeu,isu,ieu,ind_update,nest_dat,parent_grid,var_coarse,r) &
2050 !$NO-MP private(in,jn,val)
2051  do k=1,npz
2052  do j=jsu,jeu
2053  do i=isu,ieu+1
2054 
2055  in = ind_update(i,j,1)
2056  jn = ind_update(i,j,2)
2057 
2058 !!$ if (in < max(1+qr+s,is_f) .or. in > min(npx-1-qr-s+1,ie_f) .or. &
2059 !!$ jn < max(1+qr,js_f) .or. jn > min(npy-1-qr-r+1,je_f)) then
2060 !!$ write(mpp_pe()+3000,'(A, 14I6)') 'SKIP v: ', i, j, in, jn, 1+qr, is_f, ie_f, js_f, je_f, npx-1-qr-s+1, isu, ieu, jsu, jeu
2061 !!$ cycle
2062 !!$ endif
2063 
2064  val = 0.
2065  do jnj=jn,jn+r-1
2066  val = val + nest_dat(in,jnj,k)
2067  end do
2068 
2069 ! var_coarse(i,j,k) = val/r
2070  var_coarse(i,j,k) = val*parent_grid%gridstruct%rdy(i,j)
2071 
2072  end do
2073  end do
2074  end do
2075 
2076  case default
2077 
2078  call mpp_error(fatal, 'nestupdate type not implemented')
2079 
2080  end select
2081 
2082  end if
2083 
2084 
2085  endif
2086  deallocate(nest_dat)
2087 
2088  end subroutine update_coarse_grid_mpp
2089 
2090 
2091 
2092 end module boundary_mod
The module &#39;fv_mp_mod&#39; is a single program multiple data (SPMD) parallel decompostion/communication m...
Definition: fv_mp_mod.F90:24
subroutine timing_off(blk_name)
The subroutine &#39;timing_off&#39; stops a timer.
Definition: fv_timing.F90:180
subroutine fill_nested_grid_3d(var_nest, var_coarse, ind, wt, istag, jstag, isg, ieg, jsg, jeg, npz, bd, istart_in, iend_in, jstart_in, jend_in)
Definition: boundary.F90:511
subroutine, public nested_grid_bc_send(var_coarse, nest_domain, istag, jstag)
The subroutine &#39;nested_grid_BC_send&#39; sends coarse-grid data to create boundary conditions.
Definition: boundary.F90:1309
The interface&#39;update_coarse_grid_mpp&#39;contains subroutines that fetch data from the nested grid and in...
Definition: boundary.F90:108
subroutine update_coarse_grid_mpp(var_coarse, var_nest, nest_domain, ind_update, dx, dy, area, isd_p, ied_p, jsd_p, jed_p, is_n, ie_n, js_n, je_n, isu, ieu, jsu, jeu, npx, npy, npz, istag, jstag, r, nestupdate, upoff, nsponge, parent_proc, child_proc, parent_grid)
Definition: boundary.F90:1838
subroutine nested_grid_bc_mpp(var_nest, var_coarse, nest_domain, ind, wt, istag, jstag, npx, npy, npz, bd, isg, ieg, jsg, jeg, nstep_in, nsplit_in, proc_in)
Definition: boundary.F90:580
subroutine update_coarse_grid_mpp_2d(var_coarse, var_nest, nest_domain, ind_update, dx, dy, area, isd_p, ied_p, jsd_p, jed_p, is_n, ie_n, js_n, je_n, isu, ieu, jsu, jeu, npx, npy, istag, jstag, r, nestupdate, upoff, nsponge, parent_proc, child_proc, parent_grid)
Definition: boundary.F90:1800
The module &#39;fv_timing&#39; contains FV3 timers.
Definition: fv_timing.F90:24
The module &#39;boundary&#39; contains utility routines for grid nesting and boundary conditions.
Definition: boundary.F90:25
subroutine, public nested_grid_bc_recv(nest_domain, istag, jstag, npz, bd, nest_BC_buffers)
subroutine &#39;nested_grid_BC_recv&#39; receives coarse-grid data to create boundary conditions.
Definition: boundary.F90:1341
subroutine nested_grid_bc_2d_mpp(var_nest, var_coarse, nest_domain, ind, wt, istag, jstag, npx, npy, bd, isg, ieg, jsg, jeg, nstep_in, nsplit_in, proc_in)
Definition: boundary.F90:833
The module &#39;fv_arrays&#39; contains the &#39;fv_atmos_type&#39; and associated datatypes.
Definition: fv_arrays.F90:24
subroutine nested_grid_bc_2d(var_nest, var_coarse, ind, wt, istag, jstag, npx, npy, bd, isg, ieg, jsg, jeg, nstep_in, nsplit_in)
Definition: boundary.F90:1032
interface &#39;nested_grid_BC&#39; includes subroutines &#39;nested_grid_BC_2d&#39; and &#39;nested_grid_BC_3d&#39; that fetc...
Definition: boundary.F90:88
The interface &#39;fill_nested_grid&#39; includes subroutines &#39;fill_nested_grid_2d&#39; and &#39;fill_nested_grid_3d&#39;...
Definition: boundary.F90:99
subroutine nested_grid_bc_3d(var_nest, var_coarse, ind, wt, istag, jstag, npx, npy, npz, bd, isg, ieg, jsg, jeg, nstep_in, nsplit_in)
Definition: boundary.F90:1167
subroutine timing_on(blk_name)
The subroutine &#39;timing_on&#39; starts a timer.
Definition: fv_timing.F90:116
integer, parameter, public ng
Definition: fv_mp_mod.F90:2716
subroutine, public nested_grid_bc_apply_intt(var_nest, istag, jstag, npx, npy, npz, bd, step, split, BC, bctype)
The subroutine &#39;nested_grid_BC_apply_intT&#39; performs linear interpolation or extrapolation in time for...
Definition: boundary.F90:1684
subroutine, public nested_grid_bc_save_proc(nest_domain, ind, wt, istag, jstag, npx, npy, npz, bd, nest_BC, nest_BC_buffers, pd_in)
The subroutine &#39;nested_grid_BC_save_proc&#39; saves data received by &#39;nested_grid_BC_recv&#39; into the datat...
Definition: boundary.F90:1449
subroutine, public extrapolation_bc(q, istag, jstag, npx, npy, bd, pd_in, debug_in)
The subroutine &#39;extrapolation_BC&#39; performs linear extrapolation into the halo region.
Definition: boundary.F90:118
subroutine nested_grid_bc_mpp_send(var_coarse, nest_domain, istag, jstag)
Definition: boundary.F90:787
subroutine fill_nested_grid_2d(var_nest, var_coarse, ind, wt, istag, jstag, isg, ieg, jsg, jeg, bd, istart_in, iend_in, jstart_in, jend_in)
Definition: boundary.F90:446