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
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
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
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
124 integer :: i,j, istart, iend, jstart, jend
127 integer :: is, ie, js, je
128 integer :: isd, ied, jsd, jed
140 iend = min(ied,npx-1)
142 jend = min(jed,npy-1)
145 if (
present(pd_in))
then 151 if (
present(debug_in))
then 161 do j = jstart,jend+jstag
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 167 q(i,j) =
real(2-i)*q(1,j) -
real(1-i)*q(2,j)
175 do j = jstart,jend+jstag
178 q(i,j) =
real(2-i)*q(1,j) -
real(1-i)*q(2,j)
192 do i = istart,iend+istag
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 197 q(i,j) =
real(2-j)*q(i,1) -
real(1-j)*q(i,2)
206 do i = istart,iend+istag
208 q(i,j) =
real(2-j)*q(i,1) -
real(1-j)*q(i,2)
217 if (ie == npx - 1)
then 221 do j=jstart,jend+jstag
222 do i=ie+1+istag,ied+istag
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 228 q(i,j) =
real(i - (ie+istag-1))*q(ie+istag,j) +
real((ie+istag) - i)*q(ie+istag-1,j)
236 do j=jstart,jend+jstag
237 do i=ie+1+istag,ied+istag
239 q(i,j) =
real(i - (ie+istag-1))*q(ie+istag,j) +
real((ie+istag) - i)*q(ie+istag-1,j)
248 if (je == npy - 1)
then 252 do j=je+1+jstag,jed+jstag
253 do i=istart,iend+istag
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 259 q(i,j) =
real(j - (je+jstag-1))*q(i,je+jstag) +
real((je+jstag) - j)*q(i,je+jstag-1)
267 do j=je+1+jstag,jed+jstag
268 do i=istart,iend+istag
270 q(i,j) =
real(j - (je+jstag-1))*q(i,je+jstag) +
real((je+jstag) - j)*q(i,je+jstag-1)
282 if (is == 1 .and. js == 1)
then 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)
292 q(i,j) = 0.5*(
real(2-i)*q(1,j) -
real(1-i)*q(2,j) )
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)
299 q(i,j) = q(i,j) + 0.5*(
real(2-j)*q(i,1) -
real(1-j)*q(i,2))
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) )
320 if (is == 1 .and. je == npy-1)
then 324 do j=je+1+jstag,jed+jstag
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)
330 q(i,j) = 0.5*(
real(2-i)*q(1,j) -
real(1-i)*q(2,j) )
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)
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) )
347 do j=je+1+jstag,jed+jstag
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) )
360 if (ie == npx-1 .and. je == npy-1)
then 364 do j=je+1+jstag,jed+jstag
365 do i=ie+1+istag,ied+istag
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)
372 q(i,j) = 0.5*(
real(i - (ie+istag-1))*q(ie+istag,j) +
real((ie+istag) - i)*q(ie+istag-1,j))
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)
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) )
387 do j=je+1+jstag,jed+jstag
388 do i=ie+1+istag,ied+istag
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) )
400 if (ie == npx-1 .and. js == 1)
then 405 do i=ie+1+istag,ied+istag
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)
412 q(i,j) = 0.5*(
real(i - (ie+istag-1))*q(ie+istag,j) +
real((ie+istag) - i)*q(ie+istag-1,j))
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)
419 q(i,j) = q(i,j) + 0.5*(
real(2-j)*q(i,1) -
real(1-j)*q(i,2))
429 do i=ie+1+istag,ied+istag
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) )
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
455 integer :: i,j, ic, jc
456 integer :: istart, iend, jstart, jend
458 integer :: is, ie, js, je
459 integer :: isd, ied, jsd, jed
470 if (
present(istart_in))
then 475 if (
present(iend_in))
then 481 if (
present(jstart_in))
then 486 if (
present(jend_in))
then 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)
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
520 integer :: i,j, ic, jc, k
521 integer :: istart, iend, jstart, jend
523 integer :: is, ie, js, je
524 integer :: isd, ied, jsd, jed
535 if (
present(istart_in))
then 540 if (
present(iend_in))
then 546 if (
present(jstart_in))
then 551 if (
present(jend_in))
then 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)
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
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(:,:,:)
600 integer :: i,j, ic, jc, istart, iend, k
605 integer :: is, ie, js, je
606 integer :: isd, ied, jsd, jed
617 if (
PRESENT(proc_in))
then 623 if (istag == 1 .and. jstag == 1)
then 625 else if (istag == 0 .and. jstag == 1)
then 627 else if (istag == 1 .and. jstag == 0)
then 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)
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))
645 allocate(wbuffer(1,1,1))
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))
652 allocate(ebuffer(1,1,1))
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))
659 allocate(sbuffer(1,1,1))
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))
666 allocate(nbuffer(1,1,1))
672 call mpp_update_nest_fine(var_coarse, nest_domain, wbuffer, sbuffer, ebuffer, nbuffer, position=position)
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)
704 if (ie == npx-1)
then 712 do i=istart,iend+istag
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)
729 if (ie == npx-1)
then 732 do i=npx+istag,ied+istag
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)
748 if (je == npy-1)
then 756 if (ie == npx-1)
then 763 do j=npy+jstag,jed+jstag
764 do i=istart,iend+istag
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)
782 deallocate(wbuffer, ebuffer, sbuffer, nbuffer)
788 real,
dimension(:,:,:),
intent(IN) :: var_coarse
789 type(nest_domain_type),
intent(INOUT) :: nest_domain
790 integer,
intent(IN) :: istag, jstag
792 real,
allocatable :: wbuffer(:,:,:)
793 real,
allocatable :: ebuffer(:,:,:)
794 real,
allocatable :: sbuffer(:,:,:)
795 real,
allocatable :: nbuffer(:,:,:)
797 integer :: i,j, ic, jc, istart, iend, k
802 if (istag == 1 .and. jstag == 1)
then 804 else if (istag == 0 .and. jstag == 1)
then 806 else if (istag == 1 .and. jstag == 0)
then 813 allocate(wbuffer(1,1,1))
815 allocate(ebuffer(1,1,1))
817 allocate(sbuffer(1,1,1))
819 allocate(nbuffer(1,1,1))
823 call mpp_update_nest_fine(var_coarse, nest_domain, wbuffer, sbuffer, ebuffer, nbuffer, position=position)
827 deallocate(wbuffer, ebuffer, sbuffer, nbuffer)
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
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(:,:)
853 integer :: i,j, ic, jc, istart, iend, k
858 integer :: is, ie, js, je
859 integer :: isd, ied, jsd, jed
870 if (
PRESENT(proc_in))
then 876 if (istag == 1 .and. jstag == 1)
then 878 else if (istag == 0 .and. jstag == 1)
then 880 else if (istag == 1 .and. jstag == 0)
then 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)
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))
898 allocate(wbuffer(1,1))
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))
905 allocate(ebuffer(1,1))
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))
912 allocate(sbuffer(1,1))
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))
919 allocate(nbuffer(1,1))
924 call mpp_update_nest_fine(var_coarse, nest_domain, wbuffer, sbuffer, ebuffer, nbuffer, position=position)
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)
954 if (ie == npx-1)
then 961 do i=istart,iend+istag
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)
977 if (ie == npx-1)
then 979 do i=npx+istag,ied+istag
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)
994 if (je == npy-1)
then 1002 if (ie == npx-1)
then 1008 do j=npy+jstag,jed+jstag
1009 do i=istart,iend+istag
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)
1026 deallocate(wbuffer, ebuffer, sbuffer, nbuffer)
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
1041 integer :: nstep, nsplit
1043 integer :: i,j, ic, jc, istart, iend
1045 integer :: is, ie, js, je
1046 integer :: isd, ied, jsd, jed
1057 if ( .not.
present(nstep_in) .or. .not.
present(nsplit_in) )
then 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)
1090 if (ie == npx-1)
then 1097 do i=istart,iend+istag
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)
1113 if (ie == npx-1)
then 1115 do i=npx+istag,ied+istag
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)
1130 if (je == npy-1)
then 1138 if (ie == npx-1)
then 1145 do j=npy+jstag,jed+jstag
1146 do i=istart,iend+istag
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)
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
1176 integer :: nstep, nsplit
1178 integer :: i,j, ic, jc, istart, iend, k
1180 integer :: is, ie, js, je
1181 integer :: isd, ied, jsd, jed
1192 if ( .not.
present(nstep_in) .or. .not.
present(nsplit_in) )
then 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)
1227 if (ie == npx-1)
then 1235 do i=istart,iend+istag
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)
1252 if (ie == npx-1)
then 1255 do i=npx+istag,ied+istag
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)
1271 if (je == npy-1)
then 1279 if (ie == npx-1)
then 1286 do j=npy+jstag,jed+jstag
1287 do i=istart,iend+istag
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)
1310 real,
dimension(:,:,:),
intent(IN) :: var_coarse
1311 type(nest_domain_type),
intent(INOUT) :: nest_domain
1312 integer,
intent(IN) :: istag, jstag
1316 real :: wbuffer(1,1,1)
1317 real :: ebuffer(1,1,1)
1318 real :: sbuffer(1,1,1)
1319 real :: nbuffer(1,1,1)
1322 if (istag == 1 .and. jstag == 1)
then 1324 else if (istag == 0 .and. jstag == 1)
then 1326 else if (istag == 1 .and. jstag == 0)
then 1333 call mpp_update_nest_fine(var_coarse, nest_domain, wbuffer, sbuffer, ebuffer, nbuffer, position=position)
1340 bd, nest_BC_buffers)
1343 type(nest_domain_type),
intent(INOUT) :: nest_domain
1344 integer,
intent(IN) :: istag, jstag, npz
1348 real,
dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,npz) :: var_coarse_dummy
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
1359 if (istag == 1 .and. jstag == 1)
then 1361 else if (istag == 0 .and. jstag == 1)
then 1363 else if (istag == 1 .and. jstag == 0)
then 1369 if (.not.
allocated(nest_bc_buffers%west_t1) )
then 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)
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))
1386 nest_bc_buffers%west_t1(i,j,k) = 0.
1391 allocate(nest_bc_buffers%west_t1(1,1,1))
1392 nest_bc_buffers%west_t1(1,1,1) = 0.
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))
1400 nest_bc_buffers%east_t1(i,j,k) = 0.
1405 allocate(nest_bc_buffers%east_t1(1,1,1))
1406 nest_bc_buffers%east_t1(1,1,1) = 0.
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))
1414 nest_bc_buffers%south_t1(i,j,k) = 0.
1419 allocate(nest_bc_buffers%south_t1(1,1,1))
1420 nest_bc_buffers%south_t1(1,1,1) = 0.
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))
1428 nest_bc_buffers%north_t1(i,j,k) = 0.
1433 allocate(nest_bc_buffers%north_t1(1,1,1))
1434 nest_bc_buffers%north_t1(1,1,1) = 0
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)
1448 npx, npy, npz, bd, nest_BC, nest_BC_buffers, pd_in)
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
1461 real,
dimension(bd%isd:bd%ied+istag,bd%jsd:bd%jed+jstag,npz) :: var_coarse_dummy
1463 real,
dimension(:,:,:),
pointer :: var_east, var_west, var_south, var_north
1464 real,
dimension(:,:,:),
pointer :: buf_east, buf_west, buf_south, buf_north
1469 integer :: i,j, k, ic, jc, istart, iend
1470 logical :: process, pd = .false.
1472 integer :: is, ie, js, je
1473 integer :: isd, ied, jsd, jed
1485 if (
present(pd_in))
then 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
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
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)
1530 var_west(i,j,k) = max(var_west(i,j,k), 0.5*nest_bc%west_t0(i,j,k))
1546 if (ie == npx-1)
then 1555 do i=istart,iend+istag
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)
1575 do i=istart,iend+istag
1577 var_south(i,j,k) = max(var_south(i,j,k), 0.5*nest_bc%south_t0(i,j,k))
1587 if (ie == npx-1 )
then 1592 do i=npx+istag,ied+istag
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)
1612 do i=npx+istag,ied+istag
1614 var_east(i,j,k) = max(var_east(i,j,k), 0.5*nest_bc%east_t0(i,j,k))
1623 if (je == npy-1 )
then 1631 if (ie == npx-1)
then 1639 do j=npy+jstag,jed+jstag
1640 do i=istart,iend+istag
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)
1659 do j=npy+jstag,jed+jstag
1660 do i=istart,iend+istag
1662 var_north(i,j,k) = max(var_north(i,j,k), 0.5*nest_bc%north_t0(i,j,k))
1682 npx, npy, npz, bd, step, split, &
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
1692 real,
pointer,
dimension(:,:,:) :: var_t0, var_t1
1694 integer :: i,j, istart, iend, k
1697 logical,
save :: printdiag = .true.
1699 integer :: is, ie, js, je
1700 integer :: isd, ied, jsd, jed
1713 var_t0 => bc%west_t0
1714 var_t1 => bc%west_t1
1718 var_nest(i,j,k) = (var_t0(i,j,k)*(split-step) + step*var_t1(i,j,k))*denom
1733 if (ie == npx-1)
then 1739 var_t0 => bc%south_t0
1740 var_t1 => bc%south_t1
1743 do i=istart,iend+istag
1745 var_nest(i,j,k) = (var_t0(i,j,k)*(split-step) + step*var_t1(i,j,k))*denom
1752 if (ie == npx-1 )
then 1753 var_t0 => bc%east_t0
1754 var_t1 => bc%east_t1
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
1766 if (je == npy-1 )
then 1774 if (ie == npx-1)
then 1780 var_t0 => bc%north_t0
1781 var_t1 => bc%north_t1
1783 do j=npy+jstag,jed+jstag
1784 do i=istart,iend+istag
1786 var_nest(i,j,k) = (var_t0(i,j,k)*(split-step) + step*var_t1(i,j,k))*denom
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
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)
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)
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)
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)
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)
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
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
1860 real,
allocatable,
dimension(:,:,:) :: nest_dat
1861 real :: var_nest_send(is_n:ie_n+istag,js_n:je_n+jstag,npz)
1864 if (istag == 1 .and. jstag == 1)
then 1866 else if (istag == 0 .and. jstag == 1)
then 1868 else if (istag == 1 .and. jstag == 0)
then 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))
1878 allocate(nest_dat(1,1,1))
1882 if (child_proc)
then 1884 if (istag == 0 .and. jstag == 0)
then 1885 select case (nestupdate)
1893 var_nest_send(i,j,k) = var_nest(i,j,k)*area(i,j)
1900 else if (istag == 0 .and. jstag > 0)
then 1902 select case (nestupdate)
1911 var_nest_send(i,j,k) = var_nest(i,j,k)*dx(i,j)
1919 call mpp_error(fatal,
'nestupdate type not implemented')
1923 else if (istag > 0 .and. jstag == 0)
then 1924 select case (nestupdate)
1933 var_nest_send(i,j,k) = var_nest(i,j,k)*dy(i,j)
1941 call mpp_error(fatal,
'nestupdate type not implemented')
1947 call mpp_error(fatal,
"Cannot have both nonzero istag and jstag.")
1953 call mpp_update_nest_coarse(var_nest_send, nest_domain, nest_dat, position=position)
1957 qr = r*upoff + nsponge - s
1959 if (parent_proc .and. .not. (ieu < isu .or. jeu < jsu))
then 1960 if (istag == 0 .and. jstag == 0)
then 1962 select case (nestupdate)
1971 in = ind_update(i,j,1)
1972 jn = ind_update(i,j,2)
1983 val = val + nest_dat(ini,jnj,k)
1991 var_coarse(i,j,k) = val*parent_grid%gridstruct%rarea(i,j)
2000 call mpp_error(fatal,
'nestupdate type not implemented')
2005 else if (istag == 0 .and. jstag > 0)
then 2008 select case (nestupdate)
2017 in = ind_update(i,j,1)
2018 jn = ind_update(i,j,2)
2028 val = val + nest_dat(ini,jn,k)
2032 var_coarse(i,j,k) = val*parent_grid%gridstruct%rdx(i,j)
2040 call mpp_error(fatal,
'nestupdate type not implemented')
2044 else if (istag > 0 .and. jstag == 0)
then 2046 select case (nestupdate)
2055 in = ind_update(i,j,1)
2056 jn = ind_update(i,j,2)
2066 val = val + nest_dat(in,jnj,k)
2070 var_coarse(i,j,k) = val*parent_grid%gridstruct%rdy(i,j)
2078 call mpp_error(fatal,
'nestupdate type not implemented')
2086 deallocate(nest_dat)
The module 'fv_mp_mod' is a single program multiple data (SPMD) parallel decompostion/communication m...
subroutine timing_off(blk_name)
The subroutine 'timing_off' stops a timer.
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)
subroutine, public nested_grid_bc_send(var_coarse, nest_domain, istag, jstag)
The subroutine 'nested_grid_BC_send' sends coarse-grid data to create boundary conditions.
The interface'update_coarse_grid_mpp'contains subroutines that fetch data from the nested grid and in...
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)
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)
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)
The module 'fv_timing' contains FV3 timers.
The module 'boundary' contains utility routines for grid nesting and boundary conditions.
subroutine, public nested_grid_bc_recv(nest_domain, istag, jstag, npz, bd, nest_BC_buffers)
subroutine 'nested_grid_BC_recv' receives coarse-grid data to create boundary conditions.
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)
The module 'fv_arrays' contains the 'fv_atmos_type' and associated datatypes.
subroutine nested_grid_bc_2d(var_nest, var_coarse, ind, wt, istag, jstag, npx, npy, bd, isg, ieg, jsg, jeg, nstep_in, nsplit_in)
interface 'nested_grid_BC' includes subroutines 'nested_grid_BC_2d' and 'nested_grid_BC_3d' that fetc...
The interface 'fill_nested_grid' includes subroutines 'fill_nested_grid_2d' and 'fill_nested_grid_3d'...
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)
subroutine timing_on(blk_name)
The subroutine 'timing_on' starts a timer.
integer, parameter, public ng
subroutine, public nested_grid_bc_apply_intt(var_nest, istag, jstag, npx, npy, npz, bd, step, split, BC, bctype)
The subroutine 'nested_grid_BC_apply_intT' performs linear interpolation or extrapolation in time for...
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 'nested_grid_BC_save_proc' saves data received by 'nested_grid_BC_recv' into the datat...
subroutine, public extrapolation_bc(q, istag, jstag, npx, npy, bd, pd_in, debug_in)
The subroutine 'extrapolation_BC' performs linear extrapolation into the halo region.
subroutine nested_grid_bc_mpp_send(var_coarse, nest_domain, istag, jstag)
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)