FV3DYCORE  Version 2.0.0
fv_mp_mod.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  module fv_mp_mod
25 
26 ! <table>
27 ! <tr>
28 ! <th>Module Name</th>
29 ! <th>Functions Included</th>
30 ! </tr>
31 ! <tr>
32 ! <td>ensemble_manager_mod</td>
33 ! <td>get_ensemble_id</td>
34 ! </tr>
35 ! <tr>
36 ! <td>fms_mod</td>
37 ! <td>fms_init, fms_end</td>
38 ! </tr>
39 ! <tr>
40 ! <td>fms_io_mod</td>
41 ! <td>set_domain</td>
42 ! </tr>
43 ! <tr>
44 ! <td>fv_arrays_mod</td>
45 ! <td>fv_atmos_type</td>
46 ! </tr>
47 ! <td>mpp_mod</td>
48 ! <td>FATAL, MPP_DEBUG, NOTE, MPP_CLOCK_SYNC,MPP_CLOCK_DETAILED, WARNING,
49 ! mpp_pe, mpp_npes, mpp_node, mpp_root_pe, mpp_error, mpp_set_warn_level,
50 ! mpp_declare_pelist, mpp_set_current_pelist, mpp_sync, mpp_clock_begin,
51 ! mpp_clock_end, mpp_clock_id,mpp_chksum, stdout, stderr, mpp_broadcast,
52 ! mpp_send, mpp_recv, mpp_sync_self, EVENT_RECV, mpp_gather,mpp_get_current_pelist,</td>
53 ! </tr>
54 ! <tr>
55 ! <td>mpp_domains_mod</td>
56 ! <td>GLOBAL_DATA_DOMAIN, BITWISE_EXACT_SUM, BGRID_NE, FOLD_NORTH_EDGE, CGRID_NE,
57 ! MPP_DOMAIN_TIME, CYCLIC_GLOBAL_DOMAIN, NUPDATE,EUPDATE, XUPDATE, YUPDATE, SCALAR_PAIR,
58 ! domain1D, domain2D, DomainCommunicator2D, mpp_get_ntile_count,mpp_get_compute_domain,
59 ! mpp_get_data_domain,mpp_global_field, mpp_global_sum, mpp_global_max, mpp_global_min,
60 ! mpp_domains_init, mpp_domains_exit, mpp_broadcast_domain,mpp_check_field,
61 ! mpp_define_layout,mpp_get_neighbor_pe, mpp_define_mosaic, mpp_define_io_domain,
62 ! NORTH, NORTH_EAST, EAST, SOUTH_EAST, SOUTH, SOUTH_WEST, WEST, NORTH_WEST,
63 ! mpp_start_group_update, mpp_complete_group_update,mpp_create_group_update,
64 ! mpp_reset_group_update_field,group_halo_update_type => mpp_group_update_type,
65 ! mpp_define_domains, mpp_define_nest_domains, nest_domain_type,
66 ! pp_get_C2F_index, mpp_update_nest_fine, mpp_get_F2C_index, mpp_update_nest_coarse,
67 ! mpp_get_domain_shift</td>
68 ! </tr>
69 ! </table>
70 
71 #if defined(SPMD)
72 ! !USES:
73  use fms_mod, only : fms_init, fms_end
74  use mpp_mod, only : fatal, mpp_debug, note, mpp_clock_sync,mpp_clock_detailed, warning
75  use mpp_mod, only : mpp_pe, mpp_npes, mpp_node, mpp_root_pe, mpp_error, mpp_set_warn_level
76  use mpp_mod, only : mpp_declare_pelist, mpp_set_current_pelist, mpp_sync
77  use mpp_mod, only : mpp_clock_begin, mpp_clock_end, mpp_clock_id
78  use mpp_mod, only : mpp_chksum, stdout, stderr, mpp_broadcast
79  use mpp_mod, only : mpp_send, mpp_recv, mpp_sync_self, event_recv, mpp_gather
80  use mpp_domains_mod, only : global_data_domain, bitwise_exact_sum, bgrid_ne, fold_north_edge, cgrid_ne
81  use mpp_domains_mod, only : mpp_domain_time, cyclic_global_domain, nupdate,eupdate, xupdate, yupdate, scalar_pair
82  use mpp_domains_mod, only : domain1d, domain2d, domaincommunicator2d, mpp_get_ntile_count
83  use mpp_domains_mod, only : mpp_get_compute_domain, mpp_get_data_domain
84  use mpp_domains_mod, only : mpp_global_field, mpp_global_sum, mpp_global_max, mpp_global_min
85  use mpp_domains_mod, only : mpp_domains_init, mpp_domains_exit, mpp_broadcast_domain
86  use mpp_domains_mod, only : mpp_check_field, mpp_define_layout
87  use mpp_domains_mod, only : mpp_get_neighbor_pe, mpp_define_mosaic, mpp_define_io_domain
88  use mpp_domains_mod, only : north, north_east, east, south_east
89  use mpp_domains_mod, only : south, south_west, west, north_west
90  use mpp_domains_mod, only : mpp_start_group_update, mpp_complete_group_update
91  use mpp_domains_mod, only : mpp_group_update_initialized, mpp_do_group_update
92  use mpp_domains_mod, only : mpp_create_group_update,mpp_reset_group_update_field
93  use mpp_domains_mod, only : group_halo_update_type => mpp_group_update_type
94  use mpp_domains_mod, only: nest_domain_type
95  use mpp_parameter_mod, only : wupdate, eupdate, supdate, nupdate, xupdate, yupdate
97  use fms_io_mod, only: set_domain
98  use mpp_mod, only : mpp_get_current_pelist, mpp_set_current_pelist
99  use mpp_domains_mod, only : mpp_get_domain_shift
100  use ensemble_manager_mod, only : get_ensemble_id
101 
102  implicit none
103  private
104 
105  integer, parameter:: ng = 3 ! Number of ghost zones required
106  integer, parameter :: max_nnest=20, max_ntile=50
107 
108 #include "mpif.h"
109  integer, parameter :: xdir=1
110  integer, parameter :: ydir=2
111  integer :: commglobal, ierror, npes
112 
113  !need tile as a module variable so that some of the mp_ routines below will work
114  integer::tile
115 
116  integer, allocatable, dimension(:) :: npes_tile, tile1, tile2
117  integer, allocatable, dimension(:) :: istart1, iend1, jstart1, jend1
118  integer, allocatable, dimension(:) :: istart2, iend2, jstart2, jend2
119  integer, allocatable, dimension(:,:) :: layout2d, global_indices
120  integer :: numthreads, gid, masterproc
121 
122  logical :: master
123 
124  integer :: this_pe_grid = 0
125  integer, EXTERNAL :: omp_get_thread_num, omp_get_num_threads
126 
127  integer :: npes_this_grid
128 
129  !! CLEANUP: these are currently here for convenience
130  !! Right now calling switch_current_atm sets these to the value on the "current" grid
131  !! (as well as changing the "current" domain)
132  integer :: is, ie, js, je
133  integer :: isd, ied, jsd, jed
134  integer :: isc, iec, jsc, jec
135 
136  integer, allocatable :: grids_master_procs(:)
137  integer, dimension(MAX_NNEST) :: tile_fine = 0 !Global index of LAST tile in a mosaic
138  type(nest_domain_type) :: global_nest_domain !ONE structure for ALL levels of nesting
139 #ifdef CCPP
140  public commglobal
141 #endif
142  public mp_start, mp_assign_gid, mp_barrier, mp_stop!, npes
143  public domain_decomp, mp_bcst, mp_reduce_max, mp_reduce_sum, mp_gather
144  public mp_reduce_min
145  public fill_corners, xdir, ydir
146  public switch_current_domain, switch_current_atm, broadcast_domains
147  public is_master, setup_master
148  public start_group_halo_update, complete_group_halo_update
149  public group_halo_update_type, grids_master_procs, tile_fine
150  public global_nest_domain, max_nnest, max_ntile, ng
151 
152  interface start_group_halo_update
153  module procedure start_var_group_update_2d
154  module procedure start_var_group_update_3d
155  module procedure start_var_group_update_4d
156  module procedure start_vector_group_update_2d
157  module procedure start_vector_group_update_3d
158  end interface start_group_halo_update
159 
160  INTERFACE fill_corners
161  MODULE PROCEDURE fill_corners_2d_r4
162  MODULE PROCEDURE fill_corners_2d_r8
163  MODULE PROCEDURE fill_corners_xy_2d_r4
164  MODULE PROCEDURE fill_corners_xy_2d_r8
165  MODULE PROCEDURE fill_corners_xy_3d_r4
166  MODULE PROCEDURE fill_corners_xy_3d_r8
167  END INTERFACE
168 
169  INTERFACE fill_corners_agrid
170  MODULE PROCEDURE fill_corners_agrid_r4
171  MODULE PROCEDURE fill_corners_agrid_r8
172  END INTERFACE
173 
174  INTERFACE fill_corners_cgrid
175  MODULE PROCEDURE fill_corners_cgrid_r4
176  MODULE PROCEDURE fill_corners_cgrid_r8
177  END INTERFACE
178 
179  INTERFACE fill_corners_dgrid
180  MODULE PROCEDURE fill_corners_dgrid_r4
181  MODULE PROCEDURE fill_corners_dgrid_r8
182  END INTERFACE
183 
186  INTERFACE mp_bcst
187  MODULE PROCEDURE mp_bcst_i
188  MODULE PROCEDURE mp_bcst_r4
189  MODULE PROCEDURE mp_bcst_r8
190  MODULE PROCEDURE mp_bcst_1d_r4
191  MODULE PROCEDURE mp_bcst_1d_r8
192  MODULE PROCEDURE mp_bcst_2d_r4
193  MODULE PROCEDURE mp_bcst_2d_r8
194  MODULE PROCEDURE mp_bcst_3d_r4
195  MODULE PROCEDURE mp_bcst_3d_r8
196  MODULE PROCEDURE mp_bcst_4d_r4
197  MODULE PROCEDURE mp_bcst_4d_r8
198  MODULE PROCEDURE mp_bcst_1d_i
199  MODULE PROCEDURE mp_bcst_2d_i
200  MODULE PROCEDURE mp_bcst_3d_i
201  MODULE PROCEDURE mp_bcst_4d_i
202  END INTERFACE
203 
207  INTERFACE mp_reduce_min
208  MODULE PROCEDURE mp_reduce_min_r4
209  MODULE PROCEDURE mp_reduce_min_r8
210  END INTERFACE
211 
215  INTERFACE mp_reduce_max
216  MODULE PROCEDURE mp_reduce_max_r4_1d
217  MODULE PROCEDURE mp_reduce_max_r4
218  MODULE PROCEDURE mp_reduce_max_r8_1d
219  MODULE PROCEDURE mp_reduce_max_r8
220  MODULE PROCEDURE mp_reduce_max_i
221  END INTERFACE
222 
223 
227  INTERFACE mp_reduce_sum
228  MODULE PROCEDURE mp_reduce_sum_r4
229  MODULE PROCEDURE mp_reduce_sum_r4_1d
230  MODULE PROCEDURE mp_reduce_sum_r4_1darr
231  MODULE PROCEDURE mp_reduce_sum_r4_2darr
232  MODULE PROCEDURE mp_reduce_sum_r8
233  MODULE PROCEDURE mp_reduce_sum_r8_1d
234  MODULE PROCEDURE mp_reduce_sum_r8_1darr
235  MODULE PROCEDURE mp_reduce_sum_r8_2darr
236  END INTERFACE
237 
240  ! WARNING only works with one level (ldim == 1)
241  INTERFACE mp_gather
242  MODULE PROCEDURE mp_gather_4d_r4
243  MODULE PROCEDURE mp_gather_3d_r4
244  MODULE PROCEDURE mp_gather_3d_r8
245  END INTERFACE
246 
247  integer :: halo_update_type = 1
248 
249 contains
250 
251  subroutine mp_assign_gid
252 
253  gid = mpp_pe()
254  npes = mpp_npes()
255 
256  end subroutine mp_assign_gid
257 
258 !-------------------------------------------------------------------------------
259 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
261  subroutine mp_start(commID, halo_update_type_in)
262  integer, intent(in), optional :: commid
263  integer, intent(in), optional :: halo_update_type_in
264 
265  integer :: ios
266  integer :: unit
267 
268  masterproc = mpp_root_pe()
269  commglobal = mpi_comm_world
270  if( PRESENT(commid) )then
271  commglobal = commid
272  end if
273  halo_update_type = halo_update_type_in
274 
275  numthreads = 1
276 !$OMP PARALLEL
277 !$OMP MASTER
278 !$ numthreads = omp_get_num_threads()
279 !$OMP END MASTER
280 !$OMP END PARALLEL
281 
282  if ( mpp_pe()==mpp_root_pe() ) then
283  master = .true.
284  unit = stdout()
285  write(unit,*) 'Starting PEs : ', mpp_npes() !Should be for current pelist
286  write(unit,*) 'Starting Threads : ', numthreads
287  else
288  master = .false.
289  endif
290 
291  if (mpp_npes() > 1) call mpi_barrier(commglobal, ierror)
292 
293  end subroutine mp_start
294 !
295 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
296 !-------------------------------------------------------------------------------
297 
298  logical function is_master()
299 
300  is_master = master
301 
302  end function is_master
303 
304  subroutine setup_master(pelist_local)
305 
306  integer, intent(IN) :: pelist_local(:)
307 
308  if (any(gid == pelist_local)) then
309 
310  masterproc = pelist_local(1)
311  master = (gid == masterproc)
312 
313  endif
314 
315  end subroutine setup_master
316 
317 !-------------------------------------------------------------------------------
318 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
320  subroutine mp_barrier()
321 
322  call mpi_barrier(commglobal, ierror)
323 
324  end subroutine mp_barrier
325 !
326 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
327 !-------------------------------------------------------------------------------
328 
329 !-------------------------------------------------------------------------------
330 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
332  subroutine mp_stop()
333 
334  call mpi_barrier(commglobal, ierror)
335  if (gid==masterproc) print*, 'Stopping PEs : ', npes
336  call fms_end()
337  ! call MPI_FINALIZE (ierror)
338 
339  end subroutine mp_stop
340 !
341 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
342 !-------------------------------------------------------------------------------
343 
344 !-------------------------------------------------------------------------------
345 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
347  subroutine domain_decomp(npx,npy,nregions,grid_type,nested,layout,io_layout,bd,tile,square_domain,&
348  npes_per_tile,domain,domain_for_coupler,num_contact,pelist)
349  integer, intent(IN) :: npx,npy,grid_type
350  integer, intent(INOUT) :: nregions, tile
351  logical, intent(IN):: nested
352  integer, intent(INOUT) :: layout(2), io_layout(2)
353 
354  integer, allocatable :: pe_start(:), pe_end(:)
355 
356  integer :: nx,ny,n,num_alloc
357  character(len=32) :: type = "unknown"
358  logical :: is_symmetry
359  logical :: debug=.false.
360  integer, allocatable :: tile_id(:)
361 
362  integer i
363  integer :: npes_x, npes_y
364 
365  integer, intent(INOUT) :: pelist(:)
366  integer, intent(OUT) :: num_contact, npes_per_tile
367  logical, intent(OUT) :: square_domain
368  type(domain2d), intent(OUT) :: domain, domain_for_coupler
369  type(fv_grid_bounds_type), intent(INOUT) :: bd
370 
371  nx = npx-1
372  ny = npy-1
373 
374  npes_x = layout(1)
375  npes_y = layout(2)
376 
377 
378  call mpp_domains_init(mpp_domain_time)
379 
380  select case(nregions)
381  case ( 1 ) ! Lat-Lon "cyclic"
382 
383  select case (grid_type)
384  case (0,1,2) !Gnomonic nested grid
385  if (nested) then
386  type = "Cubed-sphere nested grid"
387  else
388  type = "Cubed-sphere, single face"
389  end if
390  nregions = 1
391  num_contact = 0
392  npes_per_tile = npes_x*npes_y !/nregions !Set up for concurrency
393  is_symmetry = .true.
394  call mpp_define_layout( (/1,npx-1,1,npy-1/), npes_per_tile, layout )
395 
396  if ( npes_x == 0 ) then
397  npes_x = layout(1)
398  endif
399  if ( npes_y == 0 ) then
400  npes_y = layout(2)
401  endif
402 
403  if ( npes_x==npes_y .and. (npx-1)==((npx-1)/npes_x)*npes_x ) square_domain = .true.
404 
405  if ( (npx/npes_x < ng) .or. (npy/npes_y < ng) ) then
406  write(*,310) npes_x, npes_y, npx/npes_x, npy/npes_y
407  call mp_stop
408  call exit(1)
409  endif
410 
411  layout = (/npes_x,npes_y/)
412  case (3) ! Lat-Lon "cyclic"
413  type="Lat-Lon: cyclic"
414  nregions = 4
415  num_contact = 8
416  if( mod(npes,nregions) .NE. 0 ) then
417  call mpp_error(note,'TEST_MPP_DOMAINS: for Cyclic mosaic, npes should be multiple of nregions. ' // &
418  'No test is done for Cyclic mosaic. ' )
419  return
420  end if
421  npes_per_tile = npes/nregions
422  call mpp_define_layout( (/1,npx-1,1,npy-1/), npes_per_tile, layout )
423  layout = (/1,npes_per_tile/) ! force decomp only in Lat-Direction
424  case (4) ! Cartesian, double periodic
425  type="Cartesian: double periodic"
426  nregions = 1
427  num_contact = 2
428  npes_per_tile = npes/nregions
429  if(npes_x*npes_y == npes_per_tile) then
430  layout = (/npes_x,npes_y/)
431  else
432  call mpp_define_layout( (/1,npx-1,1,npy-1/), npes_per_tile, layout )
433  endif
434  case (5) ! latlon patch
435  type="Lat-Lon: patch"
436  nregions = 1
437  num_contact = 0
438  npes_per_tile = npes/nregions
439  call mpp_define_layout( (/1,npx-1,1,npy-1/), npes_per_tile, layout )
440  case (6) ! latlon strip
441  type="Lat-Lon: strip"
442  nregions = 1
443  num_contact = 1
444  npes_per_tile = npes/nregions
445  call mpp_define_layout( (/1,npx-1,1,npy-1/), npes_per_tile, layout )
446  case (7) ! Cartesian, channel
447  type="Cartesian: channel"
448  nregions = 1
449  num_contact = 1
450  npes_per_tile = npes/nregions
451  call mpp_define_layout( (/1,npx-1,1,npy-1/), npes_per_tile, layout )
452  end select
453 
454  case ( 6 ) ! Cubed-Sphere
455  type="Cubic: cubed-sphere"
456  if (nested) then
457  call mpp_error(fatal, 'For a nested grid with grid_type < 3 nregions_domain must equal 1.')
458  endif
459  nregions = 6
460  num_contact = 12
461  !--- cubic grid always have six tiles, so npes should be multiple of 6
462  npes_per_tile = npes_x*npes_y
463  call mpp_define_layout( (/1,npx-1,1,npy-1/), npes_per_tile, layout )
464 
465  if ( npes_x == 0 ) then
466  npes_x = layout(1)
467  endif
468  if ( npes_y == 0 ) then
469  npes_y = layout(2)
470  endif
471 
472  if ( npes_x==npes_y .and. (npx-1)==((npx-1)/npes_x)*npes_x ) square_domain = .true.
473 
474  if ( (npx/npes_x < ng) .or. (npy/npes_y < ng) ) then
475  write(*,310) npes_x, npes_y, npx/npes_x, npy/npes_y
476  310 format('Invalid layout, NPES_X:',i4.4,'NPES_Y:',i4.4,'ncells_X:',i4.4,'ncells_Y:',i4.4)
477  call mp_stop
478  call exit(1)
479  endif
480 
481  layout = (/npes_x,npes_y/)
482  case default
483  call mpp_error(fatal, 'domain_decomp: no such test: '//type)
484  end select
485 
486  allocate(layout2d(2,nregions), global_indices(4,nregions), npes_tile(nregions) )
487  allocate(pe_start(nregions),pe_end(nregions))
488  npes_tile = npes_per_tile
489  do n = 1, nregions
490  global_indices(:,n) = (/1,npx-1,1,npy-1/)
491  layout2d(:,n) = layout
492  pe_start(n) = pelist(1) + (n-1)*layout(1)*layout(2)
493  pe_end(n) = pe_start(n) + layout(1)*layout(2) -1
494  end do
495  num_alloc=max(1,num_contact)
496  allocate(tile1(num_alloc), tile2(num_alloc) )
497  allocate(istart1(num_alloc), iend1(num_alloc), jstart1(num_alloc), jend1(num_alloc) )
498  allocate(istart2(num_alloc), iend2(num_alloc), jstart2(num_alloc), jend2(num_alloc) )
499 
500  is_symmetry = .true.
501  select case(nregions)
502  case ( 1 )
503 
504  select case (grid_type)
505  case (0,1,2) !Gnomonic nested grid
506  !No contacts, don't need to do anything
507  case (3) ! Lat-Lon "cyclic"
508  !--- Contact line 1, between tile 1 (EAST) and tile 2 (WEST)
509  tile1(1) = 1; tile2(1) = 2
510  istart1(1) = nx; iend1(1) = nx; jstart1(1) = 1; jend1(1) = ny
511  istart2(1) = 1; iend2(1) = 1; jstart2(1) = 1; jend2(1) = ny
512  !--- Contact line 2, between tile 1 (SOUTH) and tile 3 (NORTH) --- cyclic
513  tile1(2) = 1; tile2(2) = 3
514  istart1(2) = 1; iend1(2) = nx; jstart1(2) = 1; jend1(2) = 1
515  istart2(2) = 1; iend2(2) = nx; jstart2(2) = ny; jend2(2) = ny
516  !--- Contact line 3, between tile 1 (WEST) and tile 2 (EAST) --- cyclic
517  tile1(3) = 1; tile2(3) = 2
518  istart1(3) = 1; iend1(3) = 1; jstart1(3) = 1; jend1(3) = ny
519  istart2(3) = nx; iend2(3) = nx; jstart2(3) = 1; jend2(3) = ny
520  !--- Contact line 4, between tile 1 (NORTH) and tile 3 (SOUTH)
521  tile1(4) = 1; tile2(4) = 3
522  istart1(4) = 1; iend1(4) = nx; jstart1(4) = ny; jend1(4) = ny
523  istart2(4) = 1; iend2(4) = nx; jstart2(4) = 1; jend2(4) = 1
524  !--- Contact line 5, between tile 2 (SOUTH) and tile 4 (NORTH) --- cyclic
525  tile1(5) = 2; tile2(5) = 4
526  istart1(5) = 1; iend1(5) = nx; jstart1(5) = 1; jend1(5) = 1
527  istart2(5) = 1; iend2(5) = nx; jstart2(5) = ny; jend2(5) = ny
528  !--- Contact line 6, between tile 2 (NORTH) and tile 4 (SOUTH)
529  tile1(6) = 2; tile2(6) = 4
530  istart1(6) = 1; iend1(6) = nx; jstart1(6) = ny; jend1(6) = ny
531  istart2(6) = 1; iend2(6) = nx; jstart2(6) = 1; jend2(6) = 1
532  !--- Contact line 7, between tile 3 (EAST) and tile 4 (WEST)
533  tile1(7) = 3; tile2(7) = 4
534  istart1(7) = nx; iend1(7) = nx; jstart1(7) = 1; jend1(7) = ny
535  istart2(7) = 1; iend2(7) = 1; jstart2(7) = 1; jend2(7) = ny
536  !--- Contact line 8, between tile 3 (WEST) and tile 4 (EAST) --- cyclic
537  tile1(8) = 3; tile2(8) = 4
538  istart1(8) = 1; iend1(8) = 1; jstart1(8) = 1; jend1(8) = ny
539  istart2(8) = nx; iend2(8) = nx; jstart2(8) = 1; jend2(8) = ny
540  is_symmetry = .false.
541  case (4) ! Cartesian, double periodic
542  !--- Contact line 1, between tile 1 (EAST) and tile 1 (WEST)
543  tile1(1) = 1; tile2(1) = 1
544  istart1(1) = nx; iend1(1) = nx; jstart1(1) = 1; jend1(1) = ny
545  istart2(1) = 1; iend2(1) = 1; jstart2(1) = 1; jend2(1) = ny
546  !--- Contact line 2, between tile 1 (SOUTH) and tile 1 (NORTH) --- cyclic
547  tile1(2) = 1; tile2(2) = 1
548  istart1(2) = 1; iend1(2) = nx; jstart1(2) = 1; jend1(2) = 1
549  istart2(2) = 1; iend2(2) = nx; jstart2(2) = ny; jend2(2) = ny
550  case (5) ! latlon patch
551 
552  case (6) !latlon strip
553  !--- Contact line 1, between tile 1 (EAST) and tile 1 (WEST)
554  tile1(1) = 1; tile2(1) = 1
555  istart1(1) = nx; iend1(1) = nx; jstart1(1) = 1; jend1(1) = ny
556  istart2(1) = 1; iend2(1) = 1; jstart2(1) = 1; jend2(1) = ny
557  case (7) ! Cartesian, channel
558  !--- Contact line 1, between tile 1 (EAST) and tile 1 (WEST)
559  tile1(1) = 1; tile2(1) = 1
560  istart1(1) = nx; iend1(1) = nx; jstart1(1) = 1; jend1(1) = ny
561  istart2(1) = 1; iend2(1) = 1; jstart2(1) = 1; jend2(1) = ny
562  end select
563 
564  case ( 6 ) ! Cubed-Sphere
565  !--- Contact line 1, between tile 1 (EAST) and tile 2 (WEST)
566  tile1(1) = 1; tile2(1) = 2
567  istart1(1) = nx; iend1(1) = nx; jstart1(1) = 1; jend1(1) = ny
568  istart2(1) = 1; iend2(1) = 1; jstart2(1) = 1; jend2(1) = ny
569  !--- Contact line 2, between tile 1 (NORTH) and tile 3 (WEST)
570  tile1(2) = 1; tile2(2) = 3
571  istart1(2) = 1; iend1(2) = nx; jstart1(2) = ny; jend1(2) = ny
572  istart2(2) = 1; iend2(2) = 1; jstart2(2) = ny; jend2(2) = 1
573  !--- Contact line 3, between tile 1 (WEST) and tile 5 (NORTH)
574  tile1(3) = 1; tile2(3) = 5
575  istart1(3) = 1; iend1(3) = 1; jstart1(3) = 1; jend1(3) = ny
576  istart2(3) = nx; iend2(3) = 1; jstart2(3) = ny; jend2(3) = ny
577  !--- Contact line 4, between tile 1 (SOUTH) and tile 6 (NORTH)
578  tile1(4) = 1; tile2(4) = 6
579  istart1(4) = 1; iend1(4) = nx; jstart1(4) = 1; jend1(4) = 1
580  istart2(4) = 1; iend2(4) = nx; jstart2(4) = ny; jend2(4) = ny
581  !--- Contact line 5, between tile 2 (NORTH) and tile 3 (SOUTH)
582  tile1(5) = 2; tile2(5) = 3
583  istart1(5) = 1; iend1(5) = nx; jstart1(5) = ny; jend1(5) = ny
584  istart2(5) = 1; iend2(5) = nx; jstart2(5) = 1; jend2(5) = 1
585  !--- Contact line 6, between tile 2 (EAST) and tile 4 (SOUTH)
586  tile1(6) = 2; tile2(6) = 4
587  istart1(6) = nx; iend1(6) = nx; jstart1(6) = 1; jend1(6) = ny
588  istart2(6) = nx; iend2(6) = 1; jstart2(6) = 1; jend2(6) = 1
589  !--- Contact line 7, between tile 2 (SOUTH) and tile 6 (EAST)
590  tile1(7) = 2; tile2(7) = 6
591  istart1(7) = 1; iend1(7) = nx; jstart1(7) = 1; jend1(7) = 1
592  istart2(7) = nx; iend2(7) = nx; jstart2(7) = ny; jend2(7) = 1
593  !--- Contact line 8, between tile 3 (EAST) and tile 4 (WEST)
594  tile1(8) = 3; tile2(8) = 4
595  istart1(8) = nx; iend1(8) = nx; jstart1(8) = 1; jend1(8) = ny
596  istart2(8) = 1; iend2(8) = 1; jstart2(8) = 1; jend2(8) = ny
597  !--- Contact line 9, between tile 3 (NORTH) and tile 5 (WEST)
598  tile1(9) = 3; tile2(9) = 5
599  istart1(9) = 1; iend1(9) = nx; jstart1(9) = ny; jend1(9) = ny
600  istart2(9) = 1; iend2(9) = 1; jstart2(9) = ny; jend2(9) = 1
601  !--- Contact line 10, between tile 4 (NORTH) and tile 5 (SOUTH)
602  tile1(10) = 4; tile2(10) = 5
603  istart1(10) = 1; iend1(10) = nx; jstart1(10) = ny; jend1(10) = ny
604  istart2(10) = 1; iend2(10) = nx; jstart2(10) = 1; jend2(10) = 1
605  !--- Contact line 11, between tile 4 (EAST) and tile 6 (SOUTH)
606  tile1(11) = 4; tile2(11) = 6
607  istart1(11) = nx; iend1(11) = nx; jstart1(11) = 1; jend1(11) = ny
608  istart2(11) = nx; iend2(11) = 1; jstart2(11) = 1; jend2(11) = 1
609  !--- Contact line 12, between tile 5 (EAST) and tile 6 (WEST)
610  tile1(12) = 5; tile2(12) = 6
611  istart1(12) = nx; iend1(12) = nx; jstart1(12) = 1; jend1(12) = ny
612  istart2(12) = 1; iend2(12) = 1; jstart2(12) = 1; jend2(12) = ny
613  end select
614 
615  if ( any(pelist == gid) ) then
616  allocate(tile_id(nregions))
617  if( nested ) then
618  if( nregions .NE. 1 ) then
619  call mpp_error(fatal, 'domain_decomp: nregions should be 1 for nested region, contact developer')
620  endif
621  tile_id(1) = 7 ! TODO need update for multiple nests
622  else
623  do n = 1, nregions
624  tile_id(n) = n
625  enddo
626  endif
627  call mpp_define_mosaic(global_indices, layout2d, domain, nregions, num_contact, tile1, tile2, &
628  istart1, iend1, jstart1, jend1, istart2, iend2, jstart2, jend2, &
629  pe_start=pe_start, pe_end=pe_end, symmetry=is_symmetry, &
630  shalo = ng, nhalo = ng, whalo = ng, ehalo = ng, tile_id=tile_id, name = type)
631  call mpp_define_mosaic(global_indices, layout2d, domain_for_coupler, nregions, num_contact, tile1, tile2, &
632  istart1, iend1, jstart1, jend1, istart2, iend2, jstart2, jend2, &
633  pe_start=pe_start, pe_end=pe_end, symmetry=is_symmetry, &
634  shalo = 1, nhalo = 1, whalo = 1, ehalo = 1, tile_id=tile_id, name = type)
635  deallocate(tile_id)
636  call mpp_define_io_domain(domain, io_layout)
637  call mpp_define_io_domain(domain_for_coupler, io_layout)
638 
639  endif
640 
641  deallocate(pe_start,pe_end)
642  deallocate(layout2d, global_indices, npes_tile)
643  deallocate(tile1, tile2)
644  deallocate(istart1, iend1, jstart1, jend1)
645  deallocate(istart2, iend2, jstart2, jend2)
646 
647  !--- find the tile number
648  tile = (gid-pelist(1))/npes_per_tile+1
649  if (any(pelist == gid)) then
650  npes_this_grid = npes_per_tile*nregions
651  tile = tile
652  call mpp_get_compute_domain( domain, is, ie, js, je )
653  call mpp_get_data_domain ( domain, isd, ied, jsd, jed )
654 
655  bd%is = is
656  bd%js = js
657  bd%ie = ie
658  bd%je = je
659 
660  bd%isd = isd
661  bd%jsd = jsd
662  bd%ied = ied
663  bd%jed = jed
664 
665  bd%isc = is
666  bd%jsc = js
667  bd%iec = ie
668  bd%jec = je
669 
670  if (debug .and. nregions==1) then
671  tile=1
672  write(*,200) tile, is, ie, js, je
673  ! call mp_stop
674  ! stop
675  endif
676 200 format(i4.4, ' ', i4.4, ' ', i4.4, ' ', i4.4, ' ', i4.4, ' ')
677  else
678 
679  bd%is = 0
680  bd%js = 0
681  bd%ie = -1
682  bd%je = -1
683 
684  bd%isd = 0
685  bd%jsd = 0
686  bd%ied = -1
687  bd%jed = -1
688 
689  bd%isc = 0
690  bd%jsc = 0
691  bd%iec = -1
692  bd%jec = -1
693 
694  endif
695 
696  end subroutine domain_decomp
697 !
698 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
699 !-------------------------------------------------------------------------------
700 
701 subroutine start_var_group_update_2d(group, array, domain, flags, position, whalo, ehalo, shalo, nhalo, complete)
702  type(group_halo_update_type), intent(inout) :: group
703  real, dimension(:,:), intent(inout) :: array
704  type(domain2d), intent(inout) :: domain
705  integer, optional, intent(in) :: flags
706  integer, optional, intent(in) :: position
707  integer, optional, intent(in) :: whalo, ehalo, shalo, nhalo
708  logical, optional, intent(in) :: complete
710  real :: d_type
711  logical :: is_complete
712 ! Arguments:
713 ! (inout) group - The data type that store information for group update.
714 ! This data will be used in do_group_pass.
715 ! (inout) array - The array which is having its halos points exchanged.
716 ! (in) domain - contains domain information.
717 ! (in) flags - An optional integer indicating which directions the
718 ! data should be sent.
719 ! (in) position - An optional argument indicating the position. This is
720 ! may be CORNER, but is CENTER by default.
721 ! (in) complete - An optional argument indicating whether the halo updates
722 ! should be initiated immediately or wait for second
723 ! pass_..._start call. Omitting complete is the same as
724 ! setting complete to .true.
725 
726  if (mpp_group_update_initialized(group)) then
727  call mpp_reset_group_update_field(group,array)
728  else
729  call mpp_create_group_update(group, array, domain, flags=flags, position=position, &
730  whalo=whalo, ehalo=ehalo, shalo=shalo, nhalo=nhalo)
731  endif
732 
733  is_complete = .true.
734  if(present(complete)) is_complete = complete
735  if(is_complete .and. halo_update_type == 1) then
736  call mpp_start_group_update(group, domain, d_type)
737  endif
738 
739 end subroutine start_var_group_update_2d
740 
741 
742 subroutine start_var_group_update_3d(group, array, domain, flags, position, whalo, ehalo, shalo, nhalo, complete)
743  type(group_halo_update_type), intent(inout) :: group
744  real, dimension(:,:,:), intent(inout) :: array
745  type(domain2d), intent(inout) :: domain
746  integer, optional, intent(in) :: flags
747  integer, optional, intent(in) :: position
748  integer, optional, intent(in) :: whalo, ehalo, shalo, nhalo
749  logical, optional, intent(in) :: complete
751  real :: d_type
752  logical :: is_complete
753 
754 ! Arguments:
755 ! (inout) group - The data type that store information for group update.
756 ! This data will be used in do_group_pass.
757 ! (inout) array - The array which is having its halos points exchanged.
758 ! (in) domain - contains domain information.
759 ! (in) flags - An optional integer indicating which directions the
760 ! data should be sent.
761 ! (in) position - An optional argument indicating the position. This is
762 ! may be CORNER, but is CENTER by default.
763 ! (in) complete - An optional argument indicating whether the halo updates
764 ! should be initiated immediately or wait for second
765 ! pass_..._start call. Omitting complete is the same as
766 ! setting complete to .true.
767 
768  if (mpp_group_update_initialized(group)) then
769  call mpp_reset_group_update_field(group,array)
770  else
771  call mpp_create_group_update(group, array, domain, flags=flags, position=position, &
772  whalo=whalo, ehalo=ehalo, shalo=shalo, nhalo=nhalo)
773  endif
774 
775  is_complete = .true.
776  if(present(complete)) is_complete = complete
777  if(is_complete .and. halo_update_type == 1 ) then
778  call mpp_start_group_update(group, domain, d_type)
779  endif
780 
781 end subroutine start_var_group_update_3d
782 
783 subroutine start_var_group_update_4d(group, array, domain, flags, position, whalo, ehalo, shalo, nhalo, complete)
784  type(group_halo_update_type), intent(inout) :: group
785  real, dimension(:,:,:,:), intent(inout) :: array
786  type(domain2d), intent(inout) :: domain
787  integer, optional, intent(in) :: flags
788  integer, optional, intent(in) :: position
790  integer, optional, intent(in) :: whalo, ehalo, shalo, nhalo
791  logical, optional, intent(in) :: complete
793  real :: d_type
794  logical :: is_complete
795 
796 ! Arguments:
797 ! (inout) group - The data type that store information for group update.
798 ! This data will be used in do_group_pass.
799 ! (inout) array - The array which is having its halos points exchanged.
800 ! (in) domain - contains domain information.
801 ! (in) flags - An optional integer indicating which directions the
802 ! data should be sent.
803 ! (in) position - An optional argument indicating the position. This is
804 ! may be CORNER, but is CENTER by default.
805 ! (in) complete - An optional argument indicating whether the halo updates
806 ! should be initiated immediately or wait for second
807 ! pass_..._start call. Omitting complete is the same as
808 ! setting complete to .true.
809 
810  integer :: dirflag
811 
812  if (mpp_group_update_initialized(group)) then
813  call mpp_reset_group_update_field(group,array)
814  else
815  call mpp_create_group_update(group, array, domain, flags=flags, position=position, &
816  whalo=whalo, ehalo=ehalo, shalo=shalo, nhalo=nhalo)
817  endif
818 
819  is_complete = .true.
820  if(present(complete)) is_complete = complete
821  if(is_complete .and. halo_update_type == 1 ) then
822  call mpp_start_group_update(group, domain, d_type)
823  endif
824 
825 end subroutine start_var_group_update_4d
826 
827 
828 
829 subroutine start_vector_group_update_2d(group, u_cmpt, v_cmpt, domain, flags, gridtype, whalo, ehalo, shalo, nhalo, complete)
830  type(group_halo_update_type), intent(inout) :: group
831  real, dimension(:,:), intent(inout) :: u_cmpt, v_cmpt
834  type(domain2d), intent(inout) :: domain
835  integer, optional, intent(in) :: flags
836  integer, optional, intent(in) :: gridtype
839  integer, optional, intent(in) :: whalo, ehalo, shalo, nhalo
840  logical, optional, intent(in) :: complete
842  real :: d_type
843  logical :: is_complete
844 
845 ! Arguments:
846 ! (inout) group - The data type that store information for group update.
847 ! This data will be used in do_group_pass.
848 ! (inout) u_cmpt - The nominal zonal (u) component of the vector pair which
849 ! is having its halos points exchanged.
850 ! (inout) v_cmpt - The nominal meridional (v) component of the vector pair
851 ! which is having its halos points exchanged.
852 ! (in) domain - Contains domain decomposition information.
853 ! (in) flags - An optional integer indicating which directions the
854 ! data should be sent.
855 ! (in) gridtype - An optional flag, which may be one of A_GRID, BGRID_NE,
856 ! CGRID_NE or DGRID_NE, indicating where the two components of the
857 ! vector are discretized.
858 ! (in) complete - An optional argument indicating whether the halo updates
859 ! should be initiated immediately or wait for second
860 ! pass_..._start call. Omitting complete is the same as
861 ! setting complete to .true.
862 
863  if (mpp_group_update_initialized(group)) then
864  call mpp_reset_group_update_field(group,u_cmpt, v_cmpt)
865  else
866  call mpp_create_group_update(group, u_cmpt, v_cmpt, domain, &
867  flags=flags, gridtype=gridtype, &
868  whalo=whalo, ehalo=ehalo, shalo=shalo, nhalo=nhalo)
869  endif
870 
871  is_complete = .true.
872  if(present(complete)) is_complete = complete
873  if(is_complete .and. halo_update_type == 1 ) then
874  call mpp_start_group_update(group, domain, d_type)
875  endif
876 
877 end subroutine start_vector_group_update_2d
878 
879 subroutine start_vector_group_update_3d(group, u_cmpt, v_cmpt, domain, flags, gridtype, whalo, ehalo, shalo, nhalo, complete)
880  type(group_halo_update_type), intent(inout) :: group
881  real, dimension(:,:,:), intent(inout) :: u_cmpt, v_cmpt !! The nominal zonal (u) and meridional (v)
882  !! components of the vector pair that
883  !! is having its halos points exchanged.
884  type(domain2d), intent(inout) :: domain
885  integer, optional, intent(in) :: flags
886  integer, optional, intent(in) :: gridtype
889  integer, optional, intent(in) :: whalo, ehalo, shalo, nhalo
890  logical, optional, intent(in) :: complete
892  real :: d_type
893  logical :: is_complete
894 
895 ! Arguments:
896 ! (inout) group - The data type that store information for group update.
897 ! This data will be used in do_group_pass.
898 ! (inout) u_cmpt - The nominal zonal (u) component of the vector pair which
899 ! is having its halos points exchanged.
900 ! (inout) v_cmpt - The nominal meridional (v) component of the vector pair
901 ! which is having its halos points exchanged.
902 ! (in) domain - Contains domain decomposition information.
903 ! (in) flags - An optional integer indicating which directions the
904 ! data should be sent.
905 ! (in) gridtype - An optional flag, which may be one of A_GRID, BGRID_NE,
906 ! CGRID_NE or DGRID_NE, indicating where the two components of the
907 ! vector are discretized.
908 ! (in) complete - An optional argument indicating whether the halo updates
909 ! should be initiated immediately or wait for second
910 ! pass_..._start call. Omitting complete is the same as
911 ! setting complete to .true.
912 
913  if (mpp_group_update_initialized(group)) then
914  call mpp_reset_group_update_field(group,u_cmpt, v_cmpt)
915  else
916  call mpp_create_group_update(group, u_cmpt, v_cmpt, domain, &
917  flags=flags, gridtype=gridtype, &
918  whalo=whalo, ehalo=ehalo, shalo=shalo, nhalo=nhalo)
919  endif
920 
921  is_complete = .true.
922  if(present(complete)) is_complete = complete
923  if(is_complete .and. halo_update_type == 1) then
924  call mpp_start_group_update(group, domain, d_type)
925  endif
926 
927 end subroutine start_vector_group_update_3d
928 
929 
930 subroutine complete_group_halo_update(group, domain)
931  type(group_halo_update_type), intent(inout) :: group
932  type(domain2d), intent(inout) :: domain
933  real :: d_type
934 
935 ! Arguments:
936 ! (inout) group - The data type that store information for group update.
937 ! (in) domain - Contains domain decomposition information.
938 
939  if( halo_update_type == 1 ) then
940  call mpp_complete_group_update(group, domain, d_type)
941  else
942  call mpp_do_group_update(group, domain, d_type)
943  endif
944 
945 end subroutine complete_group_halo_update
946 
947 
948 
949 !Depreciated
950 subroutine broadcast_domains(Atm,current_pelist,current_npes)
951 
952  type(fv_atmos_type), intent(INOUT) :: atm(:)
953  integer, intent(IN) :: current_npes
954  integer, intent(IN) :: current_pelist(current_npes)
955 
956  integer :: n, i
957  integer :: ens_root_pe, ensemble_id
958 
959  !I think the idea is that each process needs to properly be part of a pelist,
960  !the pelist on which the domain is currently defined is ONLY for the pes which have the domain.
961 
962  ! This is needed to set the proper pelist for the ensemble. The pelist
963  ! needs to include the non-nested+nested tile for the ensemble.
964  ensemble_id = get_ensemble_id()
965  ens_root_pe = (ensemble_id-1)*npes
966 
967  !Pelist needs to be set to ALL ensemble PEs for broadcast_domain to work
968  call mpp_set_current_pelist((/ (i,i=ens_root_pe,npes-1+ens_root_pe) /))
969  do n=1,size(atm)
970  call mpp_broadcast_domain(atm(n)%domain)
971  call mpp_broadcast_domain(atm(n)%domain_for_coupler)
972  end do
973  call mpp_set_current_pelist(current_pelist)
974 
975 end subroutine broadcast_domains
976 
977 !depreciated
978 subroutine switch_current_domain(new_domain,new_domain_for_coupler)
979 
980  type(domain2d), intent(in), target :: new_domain, new_domain_for_coupler
981  logical, parameter :: debug = .false.
982 
983  !--- find the tile number
984  !tile = mpp_pe()/npes_per_tile+1
985  !ntiles = mpp_get_ntile_count(new_domain)
986  call mpp_get_compute_domain( new_domain, is, ie, js, je )
987  isc = is ; jsc = js
988  iec = ie ; jec = je
989  call mpp_get_data_domain ( new_domain, isd, ied, jsd, jed )
990 ! if ( npes_x==npes_y .and. (npx-1)==((npx-1)/npes_x)*npes_x ) square_domain = .true.
991 
992 ! if (debug .AND. (gid==masterproc)) write(*,200) tile, is, ie, js, je
993 !200 format('New domain: ', i4.4, ' ', i4.4, ' ', i4.4, ' ', i4.4, ' ', i4.4, ' ')
994 
995  call set_domain(new_domain)
996 
997 
998 end subroutine switch_current_domain
999 
1000 !depreciated
1001 subroutine switch_current_atm(new_Atm, switch_domain)
1002 
1003  type(fv_atmos_type), intent(IN), target :: new_atm
1004  logical, intent(IN), optional :: switch_domain
1005  logical, parameter :: debug = .false.
1006  logical :: swd
1007 
1008 
1009  call mpp_error(fatal, "switch_current_Atm depreciated. call set_domain instead.")
1010 
1011 !!$ if (debug .AND. (gid==masterproc)) print*, 'SWITCHING ATM STRUCTURES', new_Atm%grid_number
1012 !!$ if (present(switch_domain)) then
1013 !!$ swD = switch_domain
1014 !!$ else
1015 !!$ swD = .true.
1016 !!$ end if
1017 !!$ if (swD) call switch_current_domain(new_Atm%domain, new_Atm%domain_for_coupler)
1018 
1019 !!$ if (debug .AND. (gid==masterproc)) WRITE(*,'(A, 6I5)') 'NEW GRID DIMENSIONS: ', &
1020 !!$ isd, ied, jsd, jed, new_Atm%npx, new_Atm%npy
1021 
1022 end subroutine switch_current_atm
1023 
1024 !-------------------------------------------------------------------------------
1025 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !!
1026 !
1027  subroutine fill_corners_2d_r4(q, npx, npy, FILL, AGRID, BGRID)
1028  real(kind=4), DIMENSION(isd:,jsd:), intent(INOUT):: q
1029  integer, intent(IN):: npx,npy
1030  integer, intent(IN):: fill
1031  logical, OPTIONAL, intent(IN) :: agrid, bgrid
1032  integer :: i,j
1033 
1034  if (present(bgrid)) then
1035  if (bgrid) then
1036  select case (fill)
1037  case (xdir)
1038  do j=1,ng
1039  do i=1,ng
1040  if ((is== 1) .and. (js== 1)) q(1-i ,1-j ) = q(1-j ,i+1 ) !SW Corner
1041  if ((is== 1) .and. (je==npy-1)) q(1-i ,npy+j) = q(1-j ,npy-i ) !NW Corner
1042  if ((ie==npx-1) .and. (js== 1)) q(npx+i,1-j ) = q(npx+j,i+1 ) !SE Corner
1043  if ((ie==npx-1) .and. (je==npy-1)) q(npx+i,npy+j) = q(npx+j,npy-i ) !NE Corner
1044  enddo
1045  enddo
1046  case (ydir)
1047  do j=1,ng
1048  do i=1,ng
1049  if ((is== 1) .and. (js== 1)) q(1-j ,1-i ) = q(i+1 ,1-j ) !SW Corner
1050  if ((is== 1) .and. (je==npy-1)) q(1-j ,npy+i) = q(i+1 ,npy+j ) !NW Corner
1051  if ((ie==npx-1) .and. (js== 1)) q(npx+j,1-i ) = q(npx-i,1-j ) !SE Corner
1052  if ((ie==npx-1) .and. (je==npy-1)) q(npx+j,npy+i) = q(npx-i,npy+j ) !NE Corner
1053  enddo
1054  enddo
1055  case default
1056  do j=1,ng
1057  do i=1,ng
1058  if ((is== 1) .and. (js== 1)) q(1-i ,1-j ) = q(1-j ,i+1 ) !SW Corner
1059  if ((is== 1) .and. (je==npy-1)) q(1-i ,npy+j) = q(1-j ,npy-i ) !NW Corner
1060  if ((ie==npx-1) .and. (js== 1)) q(npx+i,1-j ) = q(npx+j,i+1 ) !SE Corner
1061  if ((ie==npx-1) .and. (je==npy-1)) q(npx+i,npy+j) = q(npx+j,npy-i ) !NE Corner
1062  enddo
1063  enddo
1064  end select
1065  endif
1066  elseif (present(agrid)) then
1067  if (agrid) then
1068  select case (fill)
1069  case (xdir)
1070  do j=1,ng
1071  do i=1,ng
1072  if ((is== 1) .and. (js== 1)) q(1-i ,1-j ) = q(1-j ,i ) !SW Corner
1073  if ((is== 1) .and. (je==npy-1)) q(1-i ,npy-1+j) = q(1-j ,npy-1-i+1) !NW Corner
1074  if ((ie==npx-1) .and. (js== 1)) q(npx-1+i,1-j ) = q(npx-1+j,i ) !SE Corner
1075  if ((ie==npx-1) .and. (je==npy-1)) q(npx-1+i,npy-1+j) = q(npx-1+j,npy-1-i+1) !NE Corner
1076  enddo
1077  enddo
1078  case (ydir)
1079  do j=1,ng
1080  do i=1,ng
1081  if ((is== 1) .and. (js== 1)) q(1-j ,1-i ) = q(i ,1-j ) !SW Corner
1082  if ((is== 1) .and. (je==npy-1)) q(1-j ,npy-1+i) = q(i ,npy-1+j) !NW Corner
1083  if ((ie==npx-1) .and. (js== 1)) q(npx-1+j,1-i ) = q(npx-1-i+1,1-j ) !SE Corner
1084  if ((ie==npx-1) .and. (je==npy-1)) q(npx-1+j,npy-1+i) = q(npx-1-i+1,npy-1+j) !NE Corner
1085  enddo
1086  enddo
1087  case default
1088  do j=1,ng
1089  do i=1,ng
1090  if ((is== 1) .and. (js== 1)) q(1-j ,1-i ) = q(i ,1-j ) !SW Corner
1091  if ((is== 1) .and. (je==npy-1)) q(1-j ,npy-1+i) = q(i ,npy-1+j) !NW Corner
1092  if ((ie==npx-1) .and. (js== 1)) q(npx-1+j,1-i ) = q(npx-1-i+1,1-j ) !SE Corner
1093  if ((ie==npx-1) .and. (je==npy-1)) q(npx-1+j,npy-1+i) = q(npx-1-i+1,npy-1+j) !NE Corner
1094  enddo
1095  enddo
1096  end select
1097  endif
1098  endif
1099 
1100  end subroutine fill_corners_2d_r4
1101 !
1102 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1103 !-------------------------------------------------------------------------------
1104 !-------------------------------------------------------------------------------
1105 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !!
1106 !
1107  subroutine fill_corners_2d_r8(q, npx, npy, FILL, AGRID, BGRID)
1108  real(kind=8), DIMENSION(isd:,jsd:), intent(INOUT):: q
1109  integer, intent(IN):: npx,npy
1110  integer, intent(IN):: fill ! <X-Dir or Y-Dir
1111  logical, OPTIONAL, intent(IN) :: agrid, bgrid
1112  integer :: i,j
1113 
1114  if (present(bgrid)) then
1115  if (bgrid) then
1116  select case (fill)
1117  case (xdir)
1118  do j=1,ng
1119  do i=1,ng
1120  if ((is== 1) .and. (js== 1)) q(1-i ,1-j ) = q(1-j ,i+1 ) !SW Corner
1121  if ((is== 1) .and. (je==npy-1)) q(1-i ,npy+j) = q(1-j ,npy-i ) !NW Corner
1122  if ((ie==npx-1) .and. (js== 1)) q(npx+i,1-j ) = q(npx+j,i+1 ) !SE Corner
1123  if ((ie==npx-1) .and. (je==npy-1)) q(npx+i,npy+j) = q(npx+j,npy-i ) !NE Corner
1124  enddo
1125  enddo
1126  case (ydir)
1127  do j=1,ng
1128  do i=1,ng
1129  if ((is== 1) .and. (js== 1)) q(1-j ,1-i ) = q(i+1 ,1-j ) !SW Corner
1130  if ((is== 1) .and. (je==npy-1)) q(1-j ,npy+i) = q(i+1 ,npy+j ) !NW Corner
1131  if ((ie==npx-1) .and. (js== 1)) q(npx+j,1-i ) = q(npx-i,1-j ) !SE Corner
1132  if ((ie==npx-1) .and. (je==npy-1)) q(npx+j,npy+i) = q(npx-i,npy+j ) !NE Corner
1133  enddo
1134  enddo
1135  case default
1136  do j=1,ng
1137  do i=1,ng
1138  if ((is== 1) .and. (js== 1)) q(1-i ,1-j ) = q(1-j ,i+1 ) !SW Corner
1139  if ((is== 1) .and. (je==npy-1)) q(1-i ,npy+j) = q(1-j ,npy-i ) !NW Corner
1140  if ((ie==npx-1) .and. (js== 1)) q(npx+i,1-j ) = q(npx+j,i+1 ) !SE Corner
1141  if ((ie==npx-1) .and. (je==npy-1)) q(npx+i,npy+j) = q(npx+j,npy-i ) !NE Corner
1142  enddo
1143  enddo
1144  end select
1145  endif
1146  elseif (present(agrid)) then
1147  if (agrid) then
1148  select case (fill)
1149  case (xdir)
1150  do j=1,ng
1151  do i=1,ng
1152  if ((is== 1) .and. (js== 1)) q(1-i ,1-j ) = q(1-j ,i ) !SW Corner
1153  if ((is== 1) .and. (je==npy-1)) q(1-i ,npy-1+j) = q(1-j ,npy-1-i+1) !NW Corner
1154  if ((ie==npx-1) .and. (js== 1)) q(npx-1+i,1-j ) = q(npx-1+j,i ) !SE Corner
1155  if ((ie==npx-1) .and. (je==npy-1)) q(npx-1+i,npy-1+j) = q(npx-1+j,npy-1-i+1) !NE Corner
1156  enddo
1157  enddo
1158  case (ydir)
1159  do j=1,ng
1160  do i=1,ng
1161  if ((is== 1) .and. (js== 1)) q(1-j ,1-i ) = q(i ,1-j ) !SW Corner
1162  if ((is== 1) .and. (je==npy-1)) q(1-j ,npy-1+i) = q(i ,npy-1+j) !NW Corner
1163  if ((ie==npx-1) .and. (js== 1)) q(npx-1+j,1-i ) = q(npx-1-i+1,1-j ) !SE Corner
1164  if ((ie==npx-1) .and. (je==npy-1)) q(npx-1+j,npy-1+i) = q(npx-1-i+1,npy-1+j) !NE Corner
1165  enddo
1166  enddo
1167  case default
1168  do j=1,ng
1169  do i=1,ng
1170  if ((is== 1) .and. (js== 1)) q(1-j ,1-i ) = q(i ,1-j ) !SW Corner
1171  if ((is== 1) .and. (je==npy-1)) q(1-j ,npy-1+i) = q(i ,npy-1+j) !NW Corner
1172  if ((ie==npx-1) .and. (js== 1)) q(npx-1+j,1-i ) = q(npx-1-i+1,1-j ) !SE Corner
1173  if ((ie==npx-1) .and. (je==npy-1)) q(npx-1+j,npy-1+i) = q(npx-1-i+1,npy-1+j) !NE Corner
1174  enddo
1175  enddo
1176  end select
1177  endif
1178  endif
1179 
1180  end subroutine fill_corners_2d_r8
1181 !
1182 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1183 !-------------------------------------------------------------------------------
1184 
1185 !-------------------------------------------------------------------------------
1186 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !!
1187 ! fill_corners_xy_2d_r8
1188  subroutine fill_corners_xy_2d_r8(x, y, npx, npy, DGRID, AGRID, CGRID, VECTOR)
1189  real(kind=8), DIMENSION(isd:,jsd:), intent(INOUT):: x
1190  real(kind=8), DIMENSION(isd:,jsd:), intent(INOUT):: y
1191  integer, intent(IN):: npx,npy
1192  logical, OPTIONAL, intent(IN) :: dgrid, agrid, cgrid, vector
1193  integer :: i,j
1194 
1195  real(kind=8) :: mysign
1196 
1197  mysign = 1.0
1198  if (present(vector)) then
1199  if (vector) mysign = -1.0
1200  endif
1201 
1202  if (present(dgrid)) then
1203  call fill_corners_dgrid(x, y, npx, npy, mysign)
1204  elseif (present(cgrid)) then
1205  call fill_corners_cgrid(x, y, npx, npy, mysign)
1206  elseif (present(agrid)) then
1207  call fill_corners_agrid(x, y, npx, npy, mysign)
1208  else
1209  call fill_corners_agrid(x, y, npx, npy, mysign)
1210  endif
1211 
1212  end subroutine fill_corners_xy_2d_r8
1213 !
1214 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1215 !-------------------------------------------------------------------------------
1216 
1217 !-------------------------------------------------------------------------------
1218 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !!
1219 ! fill_corners_xy_2d_r4
1220  subroutine fill_corners_xy_2d_r4(x, y, npx, npy, DGRID, AGRID, CGRID, VECTOR)
1221  real(kind=4), DIMENSION(isd:,jsd:), intent(INOUT):: x
1222  real(kind=4), DIMENSION(isd:,jsd:), intent(INOUT):: y
1223  integer, intent(IN):: npx,npy
1224  logical, OPTIONAL, intent(IN) :: dgrid, agrid, cgrid, vector
1225  integer :: i,j
1226 
1227  real(kind=4) :: mysign
1228 
1229  mysign = 1.0
1230  if (present(vector)) then
1231  if (vector) mysign = -1.0
1232  endif
1233 
1234  if (present(dgrid)) then
1235  call fill_corners_dgrid(x, y, npx, npy, mysign)
1236  elseif (present(cgrid)) then
1237  call fill_corners_cgrid(x, y, npx, npy, mysign)
1238  elseif (present(agrid)) then
1239  call fill_corners_agrid(x, y, npx, npy, mysign)
1240  else
1241  call fill_corners_agrid(x, y, npx, npy, mysign)
1242  endif
1243 
1244  end subroutine fill_corners_xy_2d_r4
1245 !
1246 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1247 !-------------------------------------------------------------------------------
1248 
1249 !-------------------------------------------------------------------------------
1250 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !!
1251 ! fill_corners_xy_3d_r8
1252  subroutine fill_corners_xy_3d_r8(x, y, npx, npy, npz, DGRID, AGRID, CGRID, VECTOR)
1253  real(kind=8), DIMENSION(isd:,jsd:,:), intent(INOUT):: x
1254  real(kind=8), DIMENSION(isd:,jsd:,:), intent(INOUT):: y
1255  integer, intent(IN):: npx,npy,npz
1256  logical, OPTIONAL, intent(IN) :: dgrid, agrid, cgrid, vector
1257  integer :: i,j,k
1258 
1259  real(kind=8) :: mysign
1260 
1261  mysign = 1.0
1262  if (present(vector)) then
1263  if (vector) mysign = -1.0
1264  endif
1265 
1266  if (present(dgrid)) then
1267  do k=1,npz
1268  call fill_corners_dgrid(x(:,:,k), y(:,:,k), npx, npy, mysign)
1269  enddo
1270  elseif (present(cgrid)) then
1271  do k=1,npz
1272  call fill_corners_cgrid(x(:,:,k), y(:,:,k), npx, npy, mysign)
1273  enddo
1274  elseif (present(agrid)) then
1275  do k=1,npz
1276  call fill_corners_agrid(x(:,:,k), y(:,:,k), npx, npy, mysign)
1277  enddo
1278  else
1279  do k=1,npz
1280  call fill_corners_agrid(x(:,:,k), y(:,:,k), npx, npy, mysign)
1281  enddo
1282  endif
1283 
1284  end subroutine fill_corners_xy_3d_r8
1285 !
1286 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1287 !-------------------------------------------------------------------------------
1288 
1289 !-------------------------------------------------------------------------------
1290 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !!
1291 ! fill_corners_xy_3d_r4
1292  subroutine fill_corners_xy_3d_r4(x, y, npx, npy, npz, DGRID, AGRID, CGRID, VECTOR)
1293  real(kind=4), DIMENSION(isd:,jsd:,:), intent(INOUT):: x
1294  real(kind=4), DIMENSION(isd:,jsd:,:), intent(INOUT):: y
1295  integer, intent(IN):: npx,npy,npz
1296  logical, OPTIONAL, intent(IN) :: dgrid, agrid, cgrid, vector
1297  integer :: i,j,k
1298 
1299  real(kind=4) :: mysign
1300 
1301  mysign = 1.0
1302  if (present(vector)) then
1303  if (vector) mysign = -1.0
1304  endif
1305 
1306  if (present(dgrid)) then
1307  do k=1,npz
1308  call fill_corners_dgrid(x(:,:,k), y(:,:,k), npx, npy, mysign)
1309  enddo
1310  elseif (present(cgrid)) then
1311  do k=1,npz
1312  call fill_corners_cgrid(x(:,:,k), y(:,:,k), npx, npy, mysign)
1313  enddo
1314  elseif (present(agrid)) then
1315  do k=1,npz
1316  call fill_corners_agrid(x(:,:,k), y(:,:,k), npx, npy, mysign)
1317  enddo
1318  else
1319  do k=1,npz
1320  call fill_corners_agrid(x(:,:,k), y(:,:,k), npx, npy, mysign)
1321  enddo
1322  endif
1323 
1324  end subroutine fill_corners_xy_3d_r4
1325 !
1326 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1327 !-------------------------------------------------------------------------------
1328 
1329 !-------------------------------------------------------------------------------
1330 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1331 !
1332  subroutine fill_corners_dgrid_r8(x, y, npx, npy, mySign)
1333  real(kind=8), DIMENSION(isd:,jsd:), intent(INOUT):: x
1334  real(kind=8), DIMENSION(isd:,jsd:), intent(INOUT):: y
1335  integer, intent(IN):: npx,npy
1336  real(kind=8), intent(IN) :: mysign
1337  integer :: i,j
1338 
1339  do j=1,ng
1340  do i=1,ng
1341  ! if ((is == 1) .and. (js == 1)) x(1-i ,1-j ) = y(j+1 ,1-i ) !SW Corner
1342  ! if ((is == 1) .and. (je+1==npy)) x(1-i ,npy+j) = mySign*y(j+1 ,npy-1+i) !NW Corner
1343  ! if ((ie+1==npx) .and. (js == 1)) x(npx-1+i,1-j ) = mySign*y(npx-j,1-i ) !SE Corner
1344  ! if ((ie+1==npx) .and. (je+1==npy)) x(npx-1+i,npy+j) = y(npx-j,npy-1+i) !NE Corner
1345  if ((is == 1) .and. (js == 1)) x(1-i ,1-j ) = mysign*y(1-j ,i ) !SW Corner
1346  if ((is == 1) .and. (je+1==npy)) x(1-i ,npy+j) = y(1-j ,npy-i) !NW Corner
1347  if ((ie+1==npx) .and. (js == 1)) x(npx-1+i,1-j ) = y(npx+j,i ) !SE Corner
1348  if ((ie+1==npx) .and. (je+1==npy)) x(npx-1+i,npy+j) = mysign*y(npx+j,npy-i) !NE Corner
1349  enddo
1350  enddo
1351  do j=1,ng
1352  do i=1,ng
1353  ! if ((is == 1) .and. (js == 1)) y(1-i ,1-j ) = x(1-j ,i+1 ) !SW Corner
1354  ! if ((is == 1) .and. (je+1==npy)) y(1-i ,npy-1+j) = mySign*x(1-j ,npy-i) !NW Corner
1355  ! if ((ie+1==npx) .and. (js == 1)) y(npx+i ,1-j ) = mySign*x(npx-1+j,i+1 ) !SE Corner
1356  ! if ((ie+1==npx) .and. (je+1==npy)) y(npx+i ,npy-1+j) = x(npx-1+j,npy-i) !NE Corner
1357  if ((is == 1) .and. (js == 1)) y(1-i ,1-j ) = mysign*x(j ,1-i ) !SW Corner
1358  if ((is == 1) .and. (je+1==npy)) y(1-i ,npy-1+j) = x(j ,npy+i) !NW Corner
1359  if ((ie+1==npx) .and. (js == 1)) y(npx+i ,1-j ) = x(npx-j ,1-i ) !SE Corner
1360  if ((ie+1==npx) .and. (je+1==npy)) y(npx+i ,npy-1+j) = mysign*x(npx-j ,npy+i) !NE Corner
1361  enddo
1362  enddo
1363 
1364  end subroutine fill_corners_dgrid_r8
1365 !
1366 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1367 !-------------------------------------------------------------------------------
1368 
1369 !-------------------------------------------------------------------------------
1370 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1371 !
1372  subroutine fill_corners_dgrid_r4(x, y, npx, npy, mySign)
1373  real(kind=4), DIMENSION(isd:,jsd:), intent(INOUT):: x
1374  real(kind=4), DIMENSION(isd:,jsd:), intent(INOUT):: y
1375  integer, intent(IN):: npx,npy
1376  real(kind=4), intent(IN) :: mysign
1377  integer :: i,j
1378 
1379  do j=1,ng
1380  do i=1,ng
1381  ! if ((is == 1) .and. (js == 1)) x(1-i ,1-j ) = y(j+1 ,1-i ) !SW Corner
1382  ! if ((is == 1) .and. (je+1==npy)) x(1-i ,npy+j) = mySign*y(j+1 ,npy-1+i) !NW Corner
1383  ! if ((ie+1==npx) .and. (js == 1)) x(npx-1+i,1-j ) = mySign*y(npx-j,1-i ) !SE Corner
1384  ! if ((ie+1==npx) .and. (je+1==npy)) x(npx-1+i,npy+j) = y(npx-j,npy-1+i) !NE Corner
1385  if ((is == 1) .and. (js == 1)) x(1-i ,1-j ) = mysign*y(1-j ,i ) !SW Corner
1386  if ((is == 1) .and. (je+1==npy)) x(1-i ,npy+j) = y(1-j ,npy-i) !NW Corner
1387  if ((ie+1==npx) .and. (js == 1)) x(npx-1+i,1-j ) = y(npx+j,i ) !SE Corner
1388  if ((ie+1==npx) .and. (je+1==npy)) x(npx-1+i,npy+j) = mysign*y(npx+j,npy-i) !NE Corner
1389  enddo
1390  enddo
1391  do j=1,ng
1392  do i=1,ng
1393  ! if ((is == 1) .and. (js == 1)) y(1-i ,1-j ) = x(1-j ,i+1 ) !SW Corner
1394  ! if ((is == 1) .and. (je+1==npy)) y(1-i ,npy-1+j) = mySign*x(1-j ,npy-i) !NW Corner
1395  ! if ((ie+1==npx) .and. (js == 1)) y(npx+i ,1-j ) = mySign*x(npx-1+j,i+1 ) !SE Corner
1396  ! if ((ie+1==npx) .and. (je+1==npy)) y(npx+i ,npy-1+j) = x(npx-1+j,npy-i) !NE Corner
1397  if ((is == 1) .and. (js == 1)) y(1-i ,1-j ) = mysign*x(j ,1-i ) !SW Corner
1398  if ((is == 1) .and. (je+1==npy)) y(1-i ,npy-1+j) = x(j ,npy+i) !NW Corner
1399  if ((ie+1==npx) .and. (js == 1)) y(npx+i ,1-j ) = x(npx-j ,1-i ) !SE Corner
1400  if ((ie+1==npx) .and. (je+1==npy)) y(npx+i ,npy-1+j) = mysign*x(npx-j ,npy+i) !NE Corner
1401  enddo
1402  enddo
1403 
1404  end subroutine fill_corners_dgrid_r4
1405 !
1406 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1407 !-------------------------------------------------------------------------------
1408 
1409 !-------------------------------------------------------------------------------
1410 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1411 !
1412  subroutine fill_corners_cgrid_r4(x, y, npx, npy, mySign)
1413  real(kind=4), DIMENSION(isd:,jsd:), intent(INOUT):: x
1414  real(kind=4), DIMENSION(isd:,jsd:), intent(INOUT):: y
1415  integer, intent(IN):: npx,npy
1416  real(kind=4), intent(IN) :: mysign
1417  integer :: i,j
1418 
1419  do j=1,ng
1420  do i=1,ng
1421  if ((is == 1) .and. (js == 1)) x(1-i ,1-j ) = y(j ,1-i ) !SW Corner
1422  if ((is == 1) .and. (je+1==npy)) x(1-i ,npy-1+j) = mysign*y(j ,npy+i) !NW Corner
1423  if ((ie+1==npx) .and. (js == 1)) x(npx+i ,1-j ) = mysign*y(npx-j ,1-i ) !SE Corner
1424  if ((ie+1==npx) .and. (je+1==npy)) x(npx+i ,npy-1+j) = y(npx-j ,npy+i) !NE Corner
1425  enddo
1426  enddo
1427  do j=1,ng
1428  do i=1,ng
1429  if ((is == 1) .and. (js == 1)) y(1-i ,1-j ) = x(1-j ,i ) !SW Corner
1430  if ((is == 1) .and. (je+1==npy)) y(1-i ,npy+j) = mysign*x(1-j ,npy-i) !NW Corner
1431  if ((ie+1==npx) .and. (js == 1)) y(npx-1+i,1-j ) = mysign*x(npx+j,i ) !SE Corner
1432  if ((ie+1==npx) .and. (je+1==npy)) y(npx-1+i,npy+j) = x(npx+j,npy-i) !NE Corner
1433  enddo
1434  enddo
1435 
1436  end subroutine fill_corners_cgrid_r4
1437 !
1438 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1439 !-------------------------------------------------------------------------------
1440 
1441 !-------------------------------------------------------------------------------
1442 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1443 !
1444  subroutine fill_corners_cgrid_r8(x, y, npx, npy, mySign)
1445  real(kind=8), DIMENSION(isd:,jsd:), intent(INOUT):: x
1446  real(kind=8), DIMENSION(isd:,jsd:), intent(INOUT):: y
1447  integer, intent(IN):: npx,npy
1448  real(kind=8), intent(IN) :: mysign
1449  integer :: i,j
1450 
1451  do j=1,ng
1452  do i=1,ng
1453  if ((is == 1) .and. (js == 1)) x(1-i ,1-j ) = y(j ,1-i ) !SW Corner
1454  if ((is == 1) .and. (je+1==npy)) x(1-i ,npy-1+j) = mysign*y(j ,npy+i) !NW Corner
1455  if ((ie+1==npx) .and. (js == 1)) x(npx+i ,1-j ) = mysign*y(npx-j ,1-i ) !SE Corner
1456  if ((ie+1==npx) .and. (je+1==npy)) x(npx+i ,npy-1+j) = y(npx-j ,npy+i) !NE Corner
1457  enddo
1458  enddo
1459  do j=1,ng
1460  do i=1,ng
1461  if ((is == 1) .and. (js == 1)) y(1-i ,1-j ) = x(1-j ,i ) !SW Corner
1462  if ((is == 1) .and. (je+1==npy)) y(1-i ,npy+j) = mysign*x(1-j ,npy-i) !NW Corner
1463  if ((ie+1==npx) .and. (js == 1)) y(npx-1+i,1-j ) = mysign*x(npx+j,i ) !SE Corner
1464  if ((ie+1==npx) .and. (je+1==npy)) y(npx-1+i,npy+j) = x(npx+j,npy-i) !NE Corner
1465  enddo
1466  enddo
1467 
1468  end subroutine fill_corners_cgrid_r8
1469 !
1470 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1471 !-------------------------------------------------------------------------------
1472 
1473 !-------------------------------------------------------------------------------
1474 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1475 !
1476  subroutine fill_corners_agrid_r4(x, y, npx, npy, mySign)
1477  real(kind=4), DIMENSION(isd:,jsd:), intent(INOUT):: x
1478  real(kind=4), DIMENSION(isd:,jsd:), intent(INOUT):: y
1479  integer, intent(IN):: npx,npy
1480  real(kind=4), intent(IN) :: mysign
1481  integer :: i,j
1482 
1483  do j=1,ng
1484  do i=1,ng
1485  if ((is== 1) .and. (js== 1)) x(1-i ,1-j ) = mysign*y(1-j ,i ) !SW Corner
1486  if ((is== 1) .and. (je==npy-1)) x(1-i ,npy-1+j) = y(1-j ,npy-1-i+1) !NW Corner
1487  if ((ie==npx-1) .and. (js== 1)) x(npx-1+i,1-j ) = y(npx-1+j,i ) !SE Corner
1488  if ((ie==npx-1) .and. (je==npy-1)) x(npx-1+i,npy-1+j) = mysign*y(npx-1+j,npy-1-i+1) !NE Corner
1489  enddo
1490  enddo
1491  do j=1,ng
1492  do i=1,ng
1493  if ((is== 1) .and. (js== 1)) y(1-j ,1-i ) = mysign*x(i ,1-j ) !SW Corner
1494  if ((is== 1) .and. (je==npy-1)) y(1-j ,npy-1+i) = x(i ,npy-1+j) !NW Corner
1495  if ((ie==npx-1) .and. (js== 1)) y(npx-1+j,1-i ) = x(npx-1-i+1,1-j ) !SE Corner
1496  if ((ie==npx-1) .and. (je==npy-1)) y(npx-1+j,npy-1+i) = mysign*x(npx-1-i+1,npy-1+j) !NE Corner
1497  enddo
1498  enddo
1499 
1500  end subroutine fill_corners_agrid_r4
1501 !
1502 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1503 !-------------------------------------------------------------------------------
1504 
1505 !-------------------------------------------------------------------------------
1506 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1507 !
1508  subroutine fill_corners_agrid_r8(x, y, npx, npy, mySign)
1509  real(kind=8), DIMENSION(isd:,jsd:), intent(INOUT):: x
1510  real(kind=8), DIMENSION(isd:,jsd:), intent(INOUT):: y
1511  integer, intent(IN):: npx,npy
1512  real(kind=8), intent(IN) :: mysign
1513  integer :: i,j
1514 
1515  do j=1,ng
1516  do i=1,ng
1517  if ((is== 1) .and. (js== 1)) x(1-i ,1-j ) = mysign*y(1-j ,i ) !SW Corner
1518  if ((is== 1) .and. (je==npy-1)) x(1-i ,npy-1+j) = y(1-j ,npy-1-i+1) !NW Corner
1519  if ((ie==npx-1) .and. (js== 1)) x(npx-1+i,1-j ) = y(npx-1+j,i ) !SE Corner
1520  if ((ie==npx-1) .and. (je==npy-1)) x(npx-1+i,npy-1+j) = mysign*y(npx-1+j,npy-1-i+1) !NE Corner
1521  enddo
1522  enddo
1523  do j=1,ng
1524  do i=1,ng
1525  if ((is== 1) .and. (js== 1)) y(1-j ,1-i ) = mysign*x(i ,1-j ) !SW Corner
1526  if ((is== 1) .and. (je==npy-1)) y(1-j ,npy-1+i) = x(i ,npy-1+j) !NW Corner
1527  if ((ie==npx-1) .and. (js== 1)) y(npx-1+j,1-i ) = x(npx-1-i+1,1-j ) !SE Corner
1528  if ((ie==npx-1) .and. (je==npy-1)) y(npx-1+j,npy-1+i) = mysign*x(npx-1-i+1,npy-1+j) !NE Corner
1529  enddo
1530  enddo
1531 
1532  end subroutine fill_corners_agrid_r8
1533 !
1534 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1535 !-------------------------------------------------------------------------------
1536 !-------------------------------------------------------------------------------
1537 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1538 !
1539 ! mp_gather_4d_r4 :: Call SPMD Gather
1540 !
1541  subroutine mp_gather_4d_r4(q, i1,i2, j1,j2, idim, jdim, kdim, ldim)
1542  integer, intent(IN) :: i1,i2, j1,j2
1543  integer, intent(IN) :: idim, jdim, kdim, ldim
1544  real(kind=4), intent(INOUT):: q(idim,jdim,kdim,ldim)
1545  integer :: i,j,k,l,n,icnt
1546  integer :: lsize, lsize_buf(1)
1547  integer :: gsize
1548  integer :: lsizes(npes_this_grid), ldispl(npes_this_grid), cnts(npes_this_grid)
1549  integer :: ldims(5), gdims(5*npes_this_grid)
1550  real(kind=4), allocatable, dimension(:) :: larr, garr
1551 
1552  ldims(1) = i1
1553  ldims(2) = i2
1554  ldims(3) = j1
1555  ldims(4) = j2
1556  ldims(5) = tile
1557  do l=1,npes_this_grid
1558  cnts(l) = 5
1559  ldispl(l) = 5*(l-1)
1560  enddo
1561  call mpp_gather(ldims, gdims)
1562 ! call MPI_GATHERV(Ldims, 5, MPI_INTEGER, Gdims, cnts, Ldispl, MPI_INTEGER, masterproc, commglobal, ierror)
1563 
1564  lsize = ( (i2 - i1 + 1) * (j2 - j1 + 1) ) * kdim
1565  do l=1,npes_this_grid
1566  cnts(l) = 1
1567  ldispl(l) = l-1
1568  enddo
1569  lsizes(:)=1
1570  lsize_buf(1) = lsize
1571  call mpp_gather(lsize_buf, lsizes)
1572 ! call MPI_GATHERV(Lsize, 1, MPI_INTEGER, LsizeS, cnts, Ldispl, MPI_INTEGER, masterproc, commglobal, ierror)
1573 
1574  allocate ( larr(lsize) )
1575  icnt = 1
1576  do k=1,kdim
1577  do j=j1,j2
1578  do i=i1,i2
1579  larr(icnt) = q(i,j,k,tile)
1580  icnt=icnt+1
1581  enddo
1582  enddo
1583  enddo
1584  ldispl(1) = 0.0
1585 ! call mp_bcst(LsizeS(1))
1586  call mpp_broadcast(lsizes, npes_this_grid, masterproc)
1587  gsize = lsizes(1)
1588  do l=2,npes_this_grid
1589 ! call mp_bcst(LsizeS(l))
1590  ldispl(l) = ldispl(l-1) + lsizes(l-1)
1591  gsize = gsize + lsizes(l)
1592  enddo
1593  allocate ( garr(gsize) )
1594 
1595  call mpp_gather(larr, lsize, garr, lsizes)
1596 ! call MPI_GATHERV(larr, Lsize, MPI_REAL, garr, LsizeS, Ldispl, MPI_REAL, masterproc, commglobal, ierror)
1597 
1598  if (gid==masterproc) then
1599  do n=2,npes_this_grid
1600  icnt=1
1601  do l=gdims( (n-1)*5 + 5 ), gdims( (n-1)*5 + 5 )
1602  do k=1,kdim
1603  do j=gdims( (n-1)*5 + 3 ), gdims( (n-1)*5 + 4 )
1604  do i=gdims( (n-1)*5 + 1 ), gdims( (n-1)*5 + 2 )
1605  q(i,j,k,l) = garr(ldispl(n)+icnt)
1606  icnt=icnt+1
1607  enddo
1608  enddo
1609  enddo
1610  enddo
1611  enddo
1612  endif
1613  deallocate( larr )
1614  deallocate( garr )
1615 
1616  end subroutine mp_gather_4d_r4
1617 !
1618 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1619 !-------------------------------------------------------------------------------
1620 
1621 
1622 !-------------------------------------------------------------------------------
1623 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1624 !
1625 ! mp_gather_3d_r4 :: Call SPMD Gather
1626 !
1627  subroutine mp_gather_3d_r4(q, i1,i2, j1,j2, idim, jdim, ldim)
1628  integer, intent(IN) :: i1,i2, j1,j2
1629  integer, intent(IN) :: idim, jdim, ldim
1630  real(kind=4), intent(INOUT):: q(idim,jdim,ldim)
1631  integer :: i,j,l,n,icnt
1632  integer :: lsize, lsize_buf(1)
1633  integer :: gsize
1634  integer :: lsizes(npes_this_grid), ldispl(npes_this_grid), cnts(npes_this_grid)
1635  integer :: ldims(5), gdims(5*npes_this_grid)
1636  real(kind=4), allocatable, dimension(:) :: larr, garr
1637 
1638  ldims(1) = i1
1639  ldims(2) = i2
1640  ldims(3) = j1
1641  ldims(4) = j2
1642  ldims(5) = tile
1643  do l=1,npes_this_grid
1644  cnts(l) = 5
1645  ldispl(l) = 5*(l-1)
1646  enddo
1647 ! call MPI_GATHERV(Ldims, 5, MPI_INTEGER, Gdims, cnts, Ldispl, MPI_INTEGER, masterproc, commglobal, ierror)
1648  call mpp_gather(ldims, gdims)
1649 
1650  lsize = ( (i2 - i1 + 1) * (j2 - j1 + 1) )
1651  do l=1,npes_this_grid
1652  cnts(l) = 1
1653  ldispl(l) = l-1
1654  enddo
1655  lsizes(:)=1
1656  lsize_buf(1) = lsize
1657  call mpp_gather(lsize_buf, lsizes)
1658 ! call MPI_GATHERV(Lsize, 1, MPI_INTEGER, LsizeS, cnts, Ldispl, MPI_INTEGER, masterproc, commglobal, ierror)
1659 
1660  allocate ( larr(lsize) )
1661  icnt = 1
1662  do j=j1,j2
1663  do i=i1,i2
1664  larr(icnt) = q(i,j,tile)
1665  icnt=icnt+1
1666  enddo
1667  enddo
1668  ldispl(1) = 0.0
1669 ! call mp_bcst(LsizeS(1))
1670  call mpp_broadcast(lsizes, npes_this_grid, masterproc)
1671  gsize = lsizes(1)
1672  do l=2,npes_this_grid
1673 ! call mp_bcst(LsizeS(l))
1674  ldispl(l) = ldispl(l-1) + lsizes(l-1)
1675  gsize = gsize + lsizes(l)
1676  enddo
1677  allocate ( garr(gsize) )
1678  call mpp_gather(larr, lsize, garr, lsizes)
1679 ! call MPI_GATHERV(larr, Lsize, MPI_REAL, garr, LsizeS, Ldispl, MPI_REAL, masterproc, commglobal, ierror)
1680  if (gid==masterproc) then
1681  do n=2,npes_this_grid
1682  icnt=1
1683  do l=gdims( (n-1)*5 + 5 ), gdims( (n-1)*5 + 5 )
1684  do j=gdims( (n-1)*5 + 3 ), gdims( (n-1)*5 + 4 )
1685  do i=gdims( (n-1)*5 + 1 ), gdims( (n-1)*5 + 2 )
1686  q(i,j,l) = garr(ldispl(n)+icnt)
1687  icnt=icnt+1
1688  enddo
1689  enddo
1690  enddo
1691  enddo
1692  endif
1693  deallocate( larr )
1694  deallocate( garr )
1695 
1696  end subroutine mp_gather_3d_r4
1697 !
1698 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1699 !-------------------------------------------------------------------------------
1700 
1701 !-------------------------------------------------------------------------------
1702 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1703 !
1704 ! mp_gather_3d_r8 :: Call SPMD Gather
1705 !
1706  subroutine mp_gather_3d_r8(q, i1,i2, j1,j2, idim, jdim, ldim)
1707  integer, intent(IN) :: i1,i2, j1,j2
1708  integer, intent(IN) :: idim, jdim, ldim
1709  real(kind=8), intent(INOUT):: q(idim,jdim,ldim)
1710  integer :: i,j,l,n,icnt
1711  integer :: lsize, lsize_buf(1)
1712  integer :: gsize
1713  integer :: lsizes(npes_this_grid), ldispl(npes_this_grid), cnts(npes_this_grid)
1714  integer :: ldims(5), gdims(5*npes_this_grid)
1715  real(kind=8), allocatable, dimension(:) :: larr, garr
1716 
1717  ldims(1) = i1
1718  ldims(2) = i2
1719  ldims(3) = j1
1720  ldims(4) = j2
1721  ldims(5) = tile
1722  do l=1,npes_this_grid
1723  cnts(l) = 5
1724  ldispl(l) = 5*(l-1)
1725  enddo
1726 ! call MPI_GATHER(Ldims, 5, MPI_INTEGER, Gdims, cnts, MPI_INTEGER, masterproc, commglobal, ierror)
1727  call mpp_gather(ldims, gdims)
1728  lsize = ( (i2 - i1 + 1) * (j2 - j1 + 1) )
1729  do l=1,npes_this_grid
1730  cnts(l) = 1
1731  ldispl(l) = l-1
1732  enddo
1733  lsizes(:)=0.
1734 
1735 ! call MPI_GATHERV(Lsize, 1, MPI_INTEGER, LsizeS, cnts, Ldispl, MPI_INTEGER, masterproc, commglobal, ierror)
1736  lsize_buf(1) = lsize
1737  call mpp_gather(lsize_buf, lsizes)
1738 
1739  allocate ( larr(lsize) )
1740  icnt = 1
1741  do j=j1,j2
1742  do i=i1,i2
1743  larr(icnt) = q(i,j,tile)
1744  icnt=icnt+1
1745  enddo
1746  enddo
1747  ldispl(1) = 0.0
1748  call mpp_broadcast(lsizes, npes_this_grid, masterproc)
1749 ! call mp_bcst(LsizeS(1))
1750  gsize = lsizes(1)
1751  do l=2,npes_this_grid
1752 ! call mp_bcst(LsizeS(l))
1753  ldispl(l) = ldispl(l-1) + lsizes(l-1)
1754  gsize = gsize + lsizes(l)
1755  enddo
1756 
1757  allocate ( garr(gsize) )
1758  call mpp_gather(larr, lsize, garr, lsizes)
1759 ! call MPI_GATHERV(larr, Lsize, MPI_DOUBLE_PRECISION, garr, LsizeS, Ldispl, MPI_DOUBLE_PRECISION, masterproc, commglobal, ierror)
1760  if (gid==masterproc) then
1761  do n=2,npes_this_grid
1762  icnt=1
1763  do l=gdims( (n-1)*5 + 5 ), gdims( (n-1)*5 + 5 )
1764  do j=gdims( (n-1)*5 + 3 ), gdims( (n-1)*5 + 4 )
1765  do i=gdims( (n-1)*5 + 1 ), gdims( (n-1)*5 + 2 )
1766  q(i,j,l) = garr(ldispl(n)+icnt)
1767  icnt=icnt+1
1768  enddo
1769  enddo
1770  enddo
1771  enddo
1772  endif
1773  deallocate( larr )
1774  deallocate( garr )
1775 
1776  end subroutine mp_gather_3d_r8
1777 !
1778 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1779 !-------------------------------------------------------------------------------
1780 
1781 !-------------------------------------------------------------------------------
1782 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1783 !
1784 ! mp_bcst_i :: Call SPMD broadcast
1785 !
1786  subroutine mp_bcst_i(q)
1787  integer, intent(INOUT) :: q
1788 
1789  call mpi_bcast(q, 1, mpi_integer, masterproc, commglobal, ierror)
1790 
1791  end subroutine mp_bcst_i
1792 !
1793 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1794 !-------------------------------------------------------------------------------
1795 
1796 !-------------------------------------------------------------------------------
1797 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1798 !
1799 ! mp_bcst_r4 :: Call SPMD broadcast
1800 !
1801  subroutine mp_bcst_r4(q)
1802  real(kind=4), intent(INOUT) :: q
1803 
1804  call mpi_bcast(q, 1, mpi_real, masterproc, commglobal, ierror)
1805 
1806  end subroutine mp_bcst_r4
1807 !
1808 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1809 !-------------------------------------------------------------------------------
1810 
1811 !-------------------------------------------------------------------------------
1812 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1813 !
1814 ! mp_bcst_r8 :: Call SPMD broadcast
1815 !
1816  subroutine mp_bcst_r8(q)
1817  real(kind=8), intent(INOUT) :: q
1818 
1819  call mpi_bcast(q, 1, mpi_double_precision, masterproc, commglobal, ierror)
1820 
1821  end subroutine mp_bcst_r8
1822 !
1823 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1824 !-------------------------------------------------------------------------------
1825 
1826 !-------------------------------------------------------------------------------
1827 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1828 !
1829 ! mp_bcst_1d_r4 :: Call SPMD broadcast
1830 !
1831  subroutine mp_bcst_1d_r4(q, idim)
1832  integer, intent(IN) :: idim
1833  real(kind=4), intent(INOUT) :: q(idim)
1834 
1835  call mpi_bcast(q, idim, mpi_real, masterproc, commglobal, ierror)
1836 
1837  end subroutine mp_bcst_1d_r4
1838 !
1839 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1840 !-------------------------------------------------------------------------------
1841 
1842 !-------------------------------------------------------------------------------
1843 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1844 !
1845 ! mp_bcst_1d_r8 :: Call SPMD broadcast
1846 !
1847  subroutine mp_bcst_1d_r8(q, idim)
1848  integer, intent(IN) :: idim
1849  real(kind=8), intent(INOUT) :: q(idim)
1850 
1851  call mpi_bcast(q, idim, mpi_double_precision, masterproc, commglobal, ierror)
1852 
1853  end subroutine mp_bcst_1d_r8
1854 !
1855 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1856 !-------------------------------------------------------------------------------
1857 
1858 !-------------------------------------------------------------------------------
1859 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1860 !
1861 ! mp_bcst_2d_r4 :: Call SPMD broadcast
1862 !
1863  subroutine mp_bcst_2d_r4(q, idim, jdim)
1864  integer, intent(IN) :: idim, jdim
1865  real(kind=4), intent(INOUT) :: q(idim,jdim)
1866 
1867  call mpi_bcast(q, idim*jdim, mpi_real, masterproc, commglobal, ierror)
1868 
1869  end subroutine mp_bcst_2d_r4
1870 !
1871 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1872 !-------------------------------------------------------------------------------
1873 
1874 !-------------------------------------------------------------------------------
1875 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1876 !
1877 ! mp_bcst_2d_r8 :: Call SPMD broadcast
1878 !
1879  subroutine mp_bcst_2d_r8(q, idim, jdim)
1880  integer, intent(IN) :: idim, jdim
1881  real(kind=8), intent(INOUT) :: q(idim,jdim)
1882 
1883  call mpi_bcast(q, idim*jdim, mpi_double_precision, masterproc, commglobal, ierror)
1884 
1885  end subroutine mp_bcst_2d_r8
1886 !
1887 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1888 !-------------------------------------------------------------------------------
1889 
1890 !-------------------------------------------------------------------------------
1891 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1892 !
1893 ! mp_bcst_3d_r4 :: Call SPMD broadcast
1894 !
1895  subroutine mp_bcst_3d_r4(q, idim, jdim, kdim)
1896  integer, intent(IN) :: idim, jdim, kdim
1897  real(kind=4), intent(INOUT) :: q(idim,jdim,kdim)
1898 
1899  call mpi_bcast(q, idim*jdim*kdim, mpi_real, masterproc, commglobal, ierror)
1900 
1901  end subroutine mp_bcst_3d_r4
1902 !
1903 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1904 !-------------------------------------------------------------------------------
1905 
1906 !-------------------------------------------------------------------------------
1907 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1908 !
1909 ! mp_bcst_3d_r8 :: Call SPMD broadcast
1910 !
1911  subroutine mp_bcst_3d_r8(q, idim, jdim, kdim)
1912  integer, intent(IN) :: idim, jdim, kdim
1913  real(kind=8), intent(INOUT) :: q(idim,jdim,kdim)
1914 
1915  call mpi_bcast(q, idim*jdim*kdim, mpi_double_precision, masterproc, commglobal, ierror)
1916 
1917  end subroutine mp_bcst_3d_r8
1918 !
1919 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1920 !-------------------------------------------------------------------------------
1921 
1922 !-------------------------------------------------------------------------------
1923 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1924 !
1925 ! mp_bcst_4d_r4 :: Call SPMD broadcast
1926 !
1927  subroutine mp_bcst_4d_r4(q, idim, jdim, kdim, ldim)
1928  integer, intent(IN) :: idim, jdim, kdim, ldim
1929  real(kind=4), intent(INOUT) :: q(idim,jdim,kdim,ldim)
1930 
1931  call mpi_bcast(q, idim*jdim*kdim*ldim, mpi_real, masterproc, commglobal, ierror)
1932 
1933  end subroutine mp_bcst_4d_r4
1934 !
1935 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1936 !-------------------------------------------------------------------------------
1937 
1938 !-------------------------------------------------------------------------------
1939 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1940 !
1941 ! mp_bcst_4d_r8 :: Call SPMD broadcast
1942 !
1943  subroutine mp_bcst_4d_r8(q, idim, jdim, kdim, ldim)
1944  integer, intent(IN) :: idim, jdim, kdim, ldim
1945  real(kind=8), intent(INOUT) :: q(idim,jdim,kdim,ldim)
1946 
1947  call mpi_bcast(q, idim*jdim*kdim*ldim, mpi_double_precision, masterproc, commglobal, ierror)
1948 
1949  end subroutine mp_bcst_4d_r8
1950 !
1951 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1952 !-------------------------------------------------------------------------------
1953 
1954 !-------------------------------------------------------------------------------
1955 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1956 !
1957 ! mp_bcst_3d_i :: Call SPMD broadcast
1958 !
1959  subroutine mp_bcst_3d_i(q, idim, jdim, kdim)
1960  integer, intent(IN) :: idim, jdim, kdim
1961  integer, intent(INOUT) :: q(idim,jdim,kdim)
1962 
1963  call mpi_bcast(q, idim*jdim*kdim, mpi_integer, masterproc, commglobal, ierror)
1964 
1965  end subroutine mp_bcst_3d_i
1966 !
1967 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1968 !-------------------------------------------------------------------------------
1969 
1970 !-------------------------------------------------------------------------------
1971 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1972 !
1973 ! mp_bcst_1d_i :: Call SPMD broadcast
1974 !
1975  subroutine mp_bcst_1d_i(q, idim)
1976  integer, intent(IN) :: idim
1977  integer, intent(INOUT) :: q(idim)
1978 
1979  call mpi_bcast(q, idim, mpi_integer, masterproc, commglobal, ierror)
1980 
1981  end subroutine mp_bcst_1d_i
1982 !
1983 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
1984 !-------------------------------------------------------------------------------
1985 
1986 !-------------------------------------------------------------------------------
1987 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
1988 !
1989 ! mp_bcst_2d_i :: Call SPMD broadcast
1990 !
1991  subroutine mp_bcst_2d_i(q, idim, jdim)
1992  integer, intent(IN) :: idim, jdim
1993  integer, intent(INOUT) :: q(idim,jdim)
1994 
1995  call mpi_bcast(q, idim*jdim, mpi_integer, masterproc, commglobal, ierror)
1996 
1997  end subroutine mp_bcst_2d_i
1998 !
1999 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
2000 !-------------------------------------------------------------------------------
2001 !-------------------------------------------------------------------------------
2002 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
2003 !
2004 ! mp_bcst_4d_i :: Call SPMD broadcast
2005 !
2006  subroutine mp_bcst_4d_i(q, idim, jdim, kdim, ldim)
2007  integer, intent(IN) :: idim, jdim, kdim, ldim
2008  integer, intent(INOUT) :: q(idim,jdim,kdim,ldim)
2009 
2010  call mpi_bcast(q, idim*jdim*kdim*ldim, mpi_integer, masterproc, commglobal, ierror)
2011 
2012  end subroutine mp_bcst_4d_i
2013 !
2014 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
2015 !-------------------------------------------------------------------------------
2016 
2017 
2018 !-------------------------------------------------------------------------------
2019 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
2020 !
2021 ! mp_reduce_max_r4_1d :: Call SPMD REDUCE_MAX
2022 !
2023  subroutine mp_reduce_max_r4_1d(mymax,npts)
2024  integer, intent(IN) :: npts
2025  real(kind=4), intent(INOUT) :: mymax(npts)
2026 
2027  real(kind=4) :: gmax(npts)
2028 
2029  call mpi_allreduce( mymax, gmax, npts, mpi_real, mpi_max, &
2030  commglobal, ierror )
2031 
2032  mymax = gmax
2033 
2034  end subroutine mp_reduce_max_r4_1d
2035 !
2036 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
2037 !-------------------------------------------------------------------------------
2038 
2039 
2040 !-------------------------------------------------------------------------------
2041 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
2042 !
2043 ! mp_reduce_max_r8_1d :: Call SPMD REDUCE_MAX
2044 !
2045  subroutine mp_reduce_max_r8_1d(mymax,npts)
2046  integer, intent(IN) :: npts
2047  real(kind=8), intent(INOUT) :: mymax(npts)
2048 
2049  real(kind=8) :: gmax(npts)
2050 
2051  call mpi_allreduce( mymax, gmax, npts, mpi_double_precision, mpi_max, &
2052  commglobal, ierror )
2053 
2054  mymax = gmax
2055 
2056  end subroutine mp_reduce_max_r8_1d
2057 !
2058 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
2059 !-------------------------------------------------------------------------------
2060 
2061 
2062 !-------------------------------------------------------------------------------
2063 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
2064 !
2065 ! mp_reduce_max_r4 :: Call SPMD REDUCE_MAX
2066 !
2067  subroutine mp_reduce_max_r4(mymax)
2068  real(kind=4), intent(INOUT) :: mymax
2069 
2070  real(kind=4) :: gmax
2071 
2072  call mpi_allreduce( mymax, gmax, 1, mpi_real, mpi_max, &
2073  commglobal, ierror )
2074 
2075  mymax = gmax
2076 
2077  end subroutine mp_reduce_max_r4
2078 
2079 !-------------------------------------------------------------------------------
2080 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
2081 !
2082 ! mp_reduce_max_r8 :: Call SPMD REDUCE_MAX
2083 !
2084  subroutine mp_reduce_max_r8(mymax)
2085  real(kind=8), intent(INOUT) :: mymax
2086 
2087  real(kind=8) :: gmax
2088 
2089  call mpi_allreduce( mymax, gmax, 1, mpi_double_precision, mpi_max, &
2090  commglobal, ierror )
2091 
2092  mymax = gmax
2093 
2094  end subroutine mp_reduce_max_r8
2095 
2096  subroutine mp_reduce_min_r4(mymin)
2097  real(kind=4), intent(INOUT) :: mymin
2098 
2099  real(kind=4) :: gmin
2100 
2101  call mpi_allreduce( mymin, gmin, 1, mpi_real, mpi_min, &
2102  commglobal, ierror )
2103 
2104  mymin = gmin
2105 
2106  end subroutine mp_reduce_min_r4
2107 
2108  subroutine mp_reduce_min_r8(mymin)
2109  real(kind=8), intent(INOUT) :: mymin
2110 
2111  real(kind=8) :: gmin
2112 
2113  call mpi_allreduce( mymin, gmin, 1, mpi_double_precision, mpi_min, &
2114  commglobal, ierror )
2115 
2116  mymin = gmin
2117 
2118  end subroutine mp_reduce_min_r8
2119 !
2120 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
2121 !-------------------------------------------------------------------------------
2122 
2123 !-------------------------------------------------------------------------------
2124 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
2125 !
2126 ! mp_bcst_4d_i :: Call SPMD REDUCE_MAX
2127 !
2128  subroutine mp_reduce_max_i(mymax)
2129  integer, intent(INOUT) :: mymax
2130 
2131  integer :: gmax
2132 
2133  call mpi_allreduce( mymax, gmax, 1, mpi_integer, mpi_max, &
2134  commglobal, ierror )
2135 
2136  mymax = gmax
2137 
2138  end subroutine mp_reduce_max_i
2139 !
2140 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
2141 !-------------------------------------------------------------------------------
2142 
2143 !-------------------------------------------------------------------------------
2144 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
2145 !
2146 ! mp_reduce_sum_r4 :: Call SPMD REDUCE_SUM
2147 !
2148  subroutine mp_reduce_sum_r4(mysum)
2149  real(kind=4), intent(INOUT) :: mysum
2150 
2151  real(kind=4) :: gsum
2152 
2153  call mpi_allreduce( mysum, gsum, 1, mpi_real, mpi_sum, &
2154  commglobal, ierror )
2155 
2156  mysum = gsum
2157 
2158  end subroutine mp_reduce_sum_r4
2159 !
2160 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
2161 !-------------------------------------------------------------------------------
2162 
2163 !-------------------------------------------------------------------------------
2164 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
2165 !
2166 ! mp_reduce_sum_r8 :: Call SPMD REDUCE_SUM
2167 !
2168  subroutine mp_reduce_sum_r8(mysum)
2169  real(kind=8), intent(INOUT) :: mysum
2170 
2171  real(kind=8) :: gsum
2172 
2173  call mpi_allreduce( mysum, gsum, 1, mpi_double_precision, mpi_sum, &
2174  commglobal, ierror )
2175 
2176  mysum = gsum
2177 
2178  end subroutine mp_reduce_sum_r8
2179 !
2180 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
2181 !-------------------------------------------------------------------------------
2182 
2183 
2184 !-------------------------------------------------------------------------------
2185 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv
2186 ! !
2187 !
2188 ! mp_reduce_sum_r4_1darr :: Call SPMD REDUCE_SUM
2189 !
2190  subroutine mp_reduce_sum_r4_1darr(mysum, npts)
2191  integer, intent(in) :: npts
2192  real(kind=4), intent(inout) :: mysum(npts)
2193  real(kind=4) :: gsum(npts)
2194 
2195  gsum = 0.0
2196  call mpi_allreduce( mysum, gsum, npts, mpi_real, mpi_sum, &
2197  commglobal, ierror )
2198 
2199  mysum = gsum
2200 
2201  end subroutine mp_reduce_sum_r4_1darr
2202 !
2203 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
2204 ! !
2205 !-------------------------------------------------------------------------------
2206 
2207 !-------------------------------------------------------------------------------
2208 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv
2209 ! !
2210 !
2211 ! mp_reduce_sum_r4_2darr :: Call SPMD REDUCE_SUM
2212 !
2213  subroutine mp_reduce_sum_r4_2darr(mysum, npts1,npts2)
2214  integer, intent(in) :: npts1,npts2
2215  real(kind=4), intent(inout) :: mysum(npts1,npts2)
2216  real(kind=4) :: gsum(npts1,npts2)
2217 
2218  gsum = 0.0
2219  call mpi_allreduce( mysum, gsum, npts1*npts2, mpi_real, mpi_sum, &
2220  commglobal, ierror )
2221 
2222  mysum = gsum
2223 
2224  end subroutine mp_reduce_sum_r4_2darr
2225 !
2226 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
2227 ! !
2228 !-------------------------------------------------------------------------------
2229 
2230 !-------------------------------------------------------------------------------
2231 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
2232 !
2233 ! mp_reduce_sum_r4_1d :: Call SPMD REDUCE_SUM
2234 !
2235  subroutine mp_reduce_sum_r4_1d(mysum, sum1d, npts)
2236  integer, intent(in) :: npts
2237  real(kind=4), intent(in) :: sum1d(npts)
2238  real(kind=4), intent(INOUT) :: mysum
2239 
2240  real(kind=4) :: gsum
2241  integer :: i
2242 
2243  mysum = 0.0
2244  do i=1,npts
2245  mysum = mysum + sum1d(i)
2246  enddo
2247 
2248  call mpi_allreduce( mysum, gsum, 1, mpi_double_precision, mpi_sum, &
2249  commglobal, ierror )
2250 
2251  mysum = gsum
2252 
2253  end subroutine mp_reduce_sum_r4_1d
2254 !
2255 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
2256 !-------------------------------------------------------------------------------
2257 
2258 !-------------------------------------------------------------------------------
2259 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv !
2260 !
2261 ! mp_reduce_sum_r8_1d :: Call SPMD REDUCE_SUM
2262 !
2263  subroutine mp_reduce_sum_r8_1d(mysum, sum1d, npts)
2264  integer, intent(in) :: npts
2265  real(kind=8), intent(in) :: sum1d(npts)
2266  real(kind=8), intent(INOUT) :: mysum
2267 
2268  real(kind=8) :: gsum
2269  integer :: i
2270 
2271  mysum = 0.0
2272  do i=1,npts
2273  mysum = mysum + sum1d(i)
2274  enddo
2275 
2276  call mpi_allreduce( mysum, gsum, 1, mpi_double_precision, mpi_sum, &
2277  commglobal, ierror )
2278 
2279  mysum = gsum
2280 
2281  end subroutine mp_reduce_sum_r8_1d
2282 !
2283 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !
2284 !-------------------------------------------------------------------------------
2285 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv
2286 ! !
2287 !
2288 ! mp_reduce_sum_r8_1darr :: Call SPMD REDUCE_SUM
2289 !
2290  subroutine mp_reduce_sum_r8_1darr(mysum, npts)
2291  integer, intent(in) :: npts
2292  real(kind=8), intent(inout) :: mysum(npts)
2293  real(kind=8) :: gsum(npts)
2294 
2295  gsum = 0.0
2296 
2297  call mpi_allreduce( mysum, gsum, npts, mpi_double_precision, &
2298  mpi_sum, &
2299  commglobal, ierror )
2300 
2301  mysum = gsum
2302 
2303  end subroutine mp_reduce_sum_r8_1darr
2304 !
2305 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
2306 ! !
2307 
2308 !-------------------------------------------------------------------------------
2309 ! vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv
2310 ! !
2311 !
2312 ! mp_reduce_sum_r8_2darr :: Call SPMD REDUCE_SUM
2313 !
2314  subroutine mp_reduce_sum_r8_2darr(mysum, npts1,npts2)
2315  integer, intent(in) :: npts1,npts2
2316  real(kind=8), intent(inout) :: mysum(npts1,npts2)
2317  real(kind=8) :: gsum(npts1,npts2)
2318 
2319  gsum = 0.0
2320 
2321  call mpi_allreduce( mysum, gsum, npts1*npts2, &
2322  mpi_double_precision, mpi_sum, &
2323  commglobal, ierror )
2324 
2325  mysum = gsum
2326 
2327  end subroutine mp_reduce_sum_r8_2darr
2328 !
2329 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
2330 ! !
2331 
2332 #else
2333  implicit none
2334  private
2335  integer :: masterproc = 0
2336  integer :: gid = 0
2337  integer, parameter:: ng = 3 ! Number of ghost zones required
2338  public gid, masterproc, ng
2339 #endif
2340 
2341  end module fv_mp_mod
2342 !-------------------------------------------------------------------------------
2343 
2344 
The module &#39;fv_mp_mod&#39; is a single program multiple data (SPMD) parallel decompostion/communication m...
Definition: fv_mp_mod.F90:24
The module &#39;fv_arrays&#39; contains the &#39;fv_atmos_type&#39; and associated datatypes.
Definition: fv_arrays.F90:24
integer, parameter, public ng
Definition: fv_mp_mod.F90:2337
integer, public gid
Definition: fv_mp_mod.F90:2336
integer, public masterproc
Definition: fv_mp_mod.F90:2335