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
105 integer,
parameter::
ng = 3
106 integer,
parameter :: max_nnest=20, max_ntile=50
109 integer,
parameter :: xdir=1
110 integer,
parameter :: ydir=2
111 integer :: commglobal, ierror, npes
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
124 integer :: this_pe_grid = 0
125 integer,
EXTERNAL :: omp_get_thread_num, omp_get_num_threads
127 integer :: npes_this_grid
132 integer :: is, ie, js, je
133 integer :: isd, ied, jsd, jed
134 integer :: isc, iec, jsc, jec
136 integer,
allocatable :: grids_master_procs(:)
137 integer,
dimension(MAX_NNEST) :: tile_fine = 0
138 type(nest_domain_type) :: global_nest_domain
142 public mp_start, mp_assign_gid, mp_barrier, mp_stop
143 public domain_decomp, mp_bcst, mp_reduce_max, mp_reduce_sum, mp_gather
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 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
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
169 INTERFACE fill_corners_agrid
170 MODULE PROCEDURE fill_corners_agrid_r4
171 MODULE PROCEDURE fill_corners_agrid_r8
174 INTERFACE fill_corners_cgrid
175 MODULE PROCEDURE fill_corners_cgrid_r4
176 MODULE PROCEDURE fill_corners_cgrid_r8
179 INTERFACE fill_corners_dgrid
180 MODULE PROCEDURE fill_corners_dgrid_r4
181 MODULE PROCEDURE fill_corners_dgrid_r8
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
207 INTERFACE mp_reduce_min
208 MODULE PROCEDURE mp_reduce_min_r4
209 MODULE PROCEDURE mp_reduce_min_r8
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
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
242 MODULE PROCEDURE mp_gather_4d_r4
243 MODULE PROCEDURE mp_gather_3d_r4
244 MODULE PROCEDURE mp_gather_3d_r8
247 integer :: halo_update_type = 1
251 subroutine mp_assign_gid
256 end subroutine mp_assign_gid
261 subroutine mp_start(commID, halo_update_type_in)
262 integer,
intent(in),
optional :: commid
263 integer,
intent(in),
optional :: halo_update_type_in
269 commglobal = mpi_comm_world
270 if(
PRESENT(commid) )
then 273 halo_update_type = halo_update_type_in
282 if ( mpp_pe()==mpp_root_pe() )
then 285 write(unit,*)
'Starting PEs : ', mpp_npes()
286 write(unit,*)
'Starting Threads : ', numthreads
291 if (mpp_npes() > 1)
call mpi_barrier(commglobal, ierror)
293 end subroutine mp_start
298 logical function is_master()
302 end function is_master
304 subroutine setup_master(pelist_local)
306 integer,
intent(IN) :: pelist_local(:)
308 if (any(
gid == pelist_local))
then 315 end subroutine setup_master
320 subroutine mp_barrier()
322 call mpi_barrier(commglobal, ierror)
324 end subroutine mp_barrier
334 call mpi_barrier(commglobal, ierror)
339 end subroutine mp_stop
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)
354 integer,
allocatable :: pe_start(:), pe_end(:)
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(:)
363 integer :: npes_x, npes_y
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
378 call mpp_domains_init(mpp_domain_time)
380 select case(nregions)
383 select case (grid_type)
386 type =
"Cubed-sphere nested grid" 388 type =
"Cubed-sphere, single face" 392 npes_per_tile = npes_x*npes_y
394 call mpp_define_layout( (/1,npx-1,1,npy-1/), npes_per_tile, layout )
396 if ( npes_x == 0 )
then 399 if ( npes_y == 0 )
then 403 if ( npes_x==npes_y .and. (npx-1)==((npx-1)/npes_x)*npes_x ) square_domain = .true.
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
411 layout = (/npes_x,npes_y/)
413 type=
"Lat-Lon: cyclic" 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. ' )
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/)
425 type=
"Cartesian: double periodic" 428 npes_per_tile = npes/nregions
429 if(npes_x*npes_y == npes_per_tile)
then 430 layout = (/npes_x,npes_y/)
432 call mpp_define_layout( (/1,npx-1,1,npy-1/), npes_per_tile, layout )
435 type=
"Lat-Lon: patch" 438 npes_per_tile = npes/nregions
439 call mpp_define_layout( (/1,npx-1,1,npy-1/), npes_per_tile, layout )
441 type=
"Lat-Lon: strip" 444 npes_per_tile = npes/nregions
445 call mpp_define_layout( (/1,npx-1,1,npy-1/), npes_per_tile, layout )
447 type=
"Cartesian: channel" 450 npes_per_tile = npes/nregions
451 call mpp_define_layout( (/1,npx-1,1,npy-1/), npes_per_tile, layout )
455 type=
"Cubic: cubed-sphere" 457 call mpp_error(fatal,
'For a nested grid with grid_type < 3 nregions_domain must equal 1.')
462 npes_per_tile = npes_x*npes_y
463 call mpp_define_layout( (/1,npx-1,1,npy-1/), npes_per_tile, layout )
465 if ( npes_x == 0 )
then 468 if ( npes_y == 0 )
then 472 if ( npes_x==npes_y .and. (npx-1)==((npx-1)/npes_x)*npes_x ) square_domain = .true.
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)
481 layout = (/npes_x,npes_y/)
483 call mpp_error(fatal,
'domain_decomp: no such test: '//type)
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
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
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) )
501 select case(nregions)
504 select case (grid_type)
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
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
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
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
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
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
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
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.
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
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
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
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
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
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
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
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
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
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
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
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
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
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
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
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
615 if ( any(pelist ==
gid) )
then 616 allocate(tile_id(nregions))
618 if( nregions .NE. 1 )
then 619 call mpp_error(fatal,
'domain_decomp: nregions should be 1 for nested region, contact developer')
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)
636 call mpp_define_io_domain(domain, io_layout)
637 call mpp_define_io_domain(domain_for_coupler, io_layout)
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)
648 tile = (
gid-pelist(1))/npes_per_tile+1
649 if (any(pelist ==
gid))
then 650 npes_this_grid = npes_per_tile*nregions
652 call mpp_get_compute_domain( domain, is, ie, js, je )
653 call mpp_get_data_domain ( domain, isd, ied, jsd, jed )
670 if (debug .and. nregions==1)
then 672 write(*,200) tile, is, ie, js, je
676 200
format(i4.4,
' ', i4.4,
' ', i4.4,
' ', i4.4,
' ', i4.4,
' ')
696 end subroutine domain_decomp
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
711 logical :: is_complete
726 if (mpp_group_update_initialized(group))
then 727 call mpp_reset_group_update_field(group,array)
729 call mpp_create_group_update(group, array, domain, flags=flags, position=position, &
730 whalo=whalo, ehalo=ehalo, shalo=shalo, nhalo=nhalo)
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)
739 end subroutine start_var_group_update_2d
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
752 logical :: is_complete
768 if (mpp_group_update_initialized(group))
then 769 call mpp_reset_group_update_field(group,array)
771 call mpp_create_group_update(group, array, domain, flags=flags, position=position, &
772 whalo=whalo, ehalo=ehalo, shalo=shalo, nhalo=nhalo)
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)
781 end subroutine start_var_group_update_3d
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
794 logical :: is_complete
812 if (mpp_group_update_initialized(group))
then 813 call mpp_reset_group_update_field(group,array)
815 call mpp_create_group_update(group, array, domain, flags=flags, position=position, &
816 whalo=whalo, ehalo=ehalo, shalo=shalo, nhalo=nhalo)
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)
825 end subroutine start_var_group_update_4d
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
843 logical :: is_complete
863 if (mpp_group_update_initialized(group))
then 864 call mpp_reset_group_update_field(group,u_cmpt, v_cmpt)
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)
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)
877 end subroutine start_vector_group_update_2d
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
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
893 logical :: is_complete
913 if (mpp_group_update_initialized(group))
then 914 call mpp_reset_group_update_field(group,u_cmpt, v_cmpt)
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)
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)
927 end subroutine start_vector_group_update_3d
930 subroutine complete_group_halo_update(group, domain)
931 type(group_halo_update_type),
intent(inout) :: group
932 type(domain2d),
intent(inout) :: domain
939 if( halo_update_type == 1 )
then 940 call mpp_complete_group_update(group, domain, d_type)
942 call mpp_do_group_update(group, domain, d_type)
945 end subroutine complete_group_halo_update
950 subroutine broadcast_domains(Atm,current_pelist,current_npes)
953 integer,
intent(IN) :: current_npes
954 integer,
intent(IN) :: current_pelist(current_npes)
957 integer :: ens_root_pe, ensemble_id
964 ensemble_id = get_ensemble_id()
965 ens_root_pe = (ensemble_id-1)*npes
968 call mpp_set_current_pelist((/ (i,i=ens_root_pe,npes-1+ens_root_pe) /))
970 call mpp_broadcast_domain(atm(n)%domain)
971 call mpp_broadcast_domain(atm(n)%domain_for_coupler)
973 call mpp_set_current_pelist(current_pelist)
975 end subroutine broadcast_domains
978 subroutine switch_current_domain(new_domain,new_domain_for_coupler)
980 type(domain2d),
intent(in),
target :: new_domain, new_domain_for_coupler
981 logical,
parameter :: debug = .false.
986 call mpp_get_compute_domain( new_domain, is, ie, js, je )
989 call mpp_get_data_domain ( new_domain, isd, ied, jsd, jed )
995 call set_domain(new_domain)
998 end subroutine switch_current_domain
1001 subroutine switch_current_atm(new_Atm, switch_domain)
1004 logical,
intent(IN),
optional :: switch_domain
1005 logical,
parameter :: debug = .false.
1009 call mpp_error(fatal,
"switch_current_Atm depreciated. call set_domain instead.")
1022 end subroutine switch_current_atm
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
1034 if (
present(bgrid))
then 1040 if ((is== 1) .and. (js== 1)) q(1-i ,1-j ) = q(1-j ,i+1 )
1041 if ((is== 1) .and. (je==npy-1)) q(1-i ,npy+j) = q(1-j ,npy-i )
1042 if ((ie==npx-1) .and. (js== 1)) q(npx+i,1-j ) = q(npx+j,i+1 )
1043 if ((ie==npx-1) .and. (je==npy-1)) q(npx+i,npy+j) = q(npx+j,npy-i )
1049 if ((is== 1) .and. (js== 1)) q(1-j ,1-i ) = q(i+1 ,1-j )
1050 if ((is== 1) .and. (je==npy-1)) q(1-j ,npy+i) = q(i+1 ,npy+j )
1051 if ((ie==npx-1) .and. (js== 1)) q(npx+j,1-i ) = q(npx-i,1-j )
1052 if ((ie==npx-1) .and. (je==npy-1)) q(npx+j,npy+i) = q(npx-i,npy+j )
1058 if ((is== 1) .and. (js== 1)) q(1-i ,1-j ) = q(1-j ,i+1 )
1059 if ((is== 1) .and. (je==npy-1)) q(1-i ,npy+j) = q(1-j ,npy-i )
1060 if ((ie==npx-1) .and. (js== 1)) q(npx+i,1-j ) = q(npx+j,i+1 )
1061 if ((ie==npx-1) .and. (je==npy-1)) q(npx+i,npy+j) = q(npx+j,npy-i )
1066 elseif (
present(agrid))
then 1072 if ((is== 1) .and. (js== 1)) q(1-i ,1-j ) = q(1-j ,i )
1073 if ((is== 1) .and. (je==npy-1)) q(1-i ,npy-1+j) = q(1-j ,npy-1-i+1)
1074 if ((ie==npx-1) .and. (js== 1)) q(npx-1+i,1-j ) = q(npx-1+j,i )
1075 if ((ie==npx-1) .and. (je==npy-1)) q(npx-1+i,npy-1+j) = q(npx-1+j,npy-1-i+1)
1081 if ((is== 1) .and. (js== 1)) q(1-j ,1-i ) = q(i ,1-j )
1082 if ((is== 1) .and. (je==npy-1)) q(1-j ,npy-1+i) = q(i ,npy-1+j)
1083 if ((ie==npx-1) .and. (js== 1)) q(npx-1+j,1-i ) = q(npx-1-i+1,1-j )
1084 if ((ie==npx-1) .and. (je==npy-1)) q(npx-1+j,npy-1+i) = q(npx-1-i+1,npy-1+j)
1090 if ((is== 1) .and. (js== 1)) q(1-j ,1-i ) = q(i ,1-j )
1091 if ((is== 1) .and. (je==npy-1)) q(1-j ,npy-1+i) = q(i ,npy-1+j)
1092 if ((ie==npx-1) .and. (js== 1)) q(npx-1+j,1-i ) = q(npx-1-i+1,1-j )
1093 if ((ie==npx-1) .and. (je==npy-1)) q(npx-1+j,npy-1+i) = q(npx-1-i+1,npy-1+j)
1100 end subroutine fill_corners_2d_r4
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
1111 logical,
OPTIONAL,
intent(IN) :: agrid, bgrid
1114 if (
present(bgrid))
then 1120 if ((is== 1) .and. (js== 1)) q(1-i ,1-j ) = q(1-j ,i+1 )
1121 if ((is== 1) .and. (je==npy-1)) q(1-i ,npy+j) = q(1-j ,npy-i )
1122 if ((ie==npx-1) .and. (js== 1)) q(npx+i,1-j ) = q(npx+j,i+1 )
1123 if ((ie==npx-1) .and. (je==npy-1)) q(npx+i,npy+j) = q(npx+j,npy-i )
1129 if ((is== 1) .and. (js== 1)) q(1-j ,1-i ) = q(i+1 ,1-j )
1130 if ((is== 1) .and. (je==npy-1)) q(1-j ,npy+i) = q(i+1 ,npy+j )
1131 if ((ie==npx-1) .and. (js== 1)) q(npx+j,1-i ) = q(npx-i,1-j )
1132 if ((ie==npx-1) .and. (je==npy-1)) q(npx+j,npy+i) = q(npx-i,npy+j )
1138 if ((is== 1) .and. (js== 1)) q(1-i ,1-j ) = q(1-j ,i+1 )
1139 if ((is== 1) .and. (je==npy-1)) q(1-i ,npy+j) = q(1-j ,npy-i )
1140 if ((ie==npx-1) .and. (js== 1)) q(npx+i,1-j ) = q(npx+j,i+1 )
1141 if ((ie==npx-1) .and. (je==npy-1)) q(npx+i,npy+j) = q(npx+j,npy-i )
1146 elseif (
present(agrid))
then 1152 if ((is== 1) .and. (js== 1)) q(1-i ,1-j ) = q(1-j ,i )
1153 if ((is== 1) .and. (je==npy-1)) q(1-i ,npy-1+j) = q(1-j ,npy-1-i+1)
1154 if ((ie==npx-1) .and. (js== 1)) q(npx-1+i,1-j ) = q(npx-1+j,i )
1155 if ((ie==npx-1) .and. (je==npy-1)) q(npx-1+i,npy-1+j) = q(npx-1+j,npy-1-i+1)
1161 if ((is== 1) .and. (js== 1)) q(1-j ,1-i ) = q(i ,1-j )
1162 if ((is== 1) .and. (je==npy-1)) q(1-j ,npy-1+i) = q(i ,npy-1+j)
1163 if ((ie==npx-1) .and. (js== 1)) q(npx-1+j,1-i ) = q(npx-1-i+1,1-j )
1164 if ((ie==npx-1) .and. (je==npy-1)) q(npx-1+j,npy-1+i) = q(npx-1-i+1,npy-1+j)
1170 if ((is== 1) .and. (js== 1)) q(1-j ,1-i ) = q(i ,1-j )
1171 if ((is== 1) .and. (je==npy-1)) q(1-j ,npy-1+i) = q(i ,npy-1+j)
1172 if ((ie==npx-1) .and. (js== 1)) q(npx-1+j,1-i ) = q(npx-1-i+1,1-j )
1173 if ((ie==npx-1) .and. (je==npy-1)) q(npx-1+j,npy-1+i) = q(npx-1-i+1,npy-1+j)
1180 end subroutine fill_corners_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
1195 real(kind=8) :: mysign
1198 if (
present(vector))
then 1199 if (vector) mysign = -1.0
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)
1209 call fill_corners_agrid(x, y, npx, npy, mysign)
1212 end subroutine fill_corners_xy_2d_r8
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
1227 real(kind=4) :: mysign
1230 if (
present(vector))
then 1231 if (vector) mysign = -1.0
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)
1241 call fill_corners_agrid(x, y, npx, npy, mysign)
1244 end subroutine fill_corners_xy_2d_r4
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
1259 real(kind=8) :: mysign
1262 if (
present(vector))
then 1263 if (vector) mysign = -1.0
1266 if (
present(dgrid))
then 1268 call fill_corners_dgrid(x(:,:,k), y(:,:,k), npx, npy, mysign)
1270 elseif (
present(cgrid))
then 1272 call fill_corners_cgrid(x(:,:,k), y(:,:,k), npx, npy, mysign)
1274 elseif (
present(agrid))
then 1276 call fill_corners_agrid(x(:,:,k), y(:,:,k), npx, npy, mysign)
1280 call fill_corners_agrid(x(:,:,k), y(:,:,k), npx, npy, mysign)
1284 end subroutine fill_corners_xy_3d_r8
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
1299 real(kind=4) :: mysign
1302 if (
present(vector))
then 1303 if (vector) mysign = -1.0
1306 if (
present(dgrid))
then 1308 call fill_corners_dgrid(x(:,:,k), y(:,:,k), npx, npy, mysign)
1310 elseif (
present(cgrid))
then 1312 call fill_corners_cgrid(x(:,:,k), y(:,:,k), npx, npy, mysign)
1314 elseif (
present(agrid))
then 1316 call fill_corners_agrid(x(:,:,k), y(:,:,k), npx, npy, mysign)
1320 call fill_corners_agrid(x(:,:,k), y(:,:,k), npx, npy, mysign)
1324 end subroutine fill_corners_xy_3d_r4
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
1345 if ((is == 1) .and. (js == 1)) x(1-i ,1-j ) = mysign*y(1-j ,i )
1346 if ((is == 1) .and. (je+1==npy)) x(1-i ,npy+j) = y(1-j ,npy-i)
1347 if ((ie+1==npx) .and. (js == 1)) x(npx-1+i,1-j ) = y(npx+j,i )
1348 if ((ie+1==npx) .and. (je+1==npy)) x(npx-1+i,npy+j) = mysign*y(npx+j,npy-i)
1357 if ((is == 1) .and. (js == 1)) y(1-i ,1-j ) = mysign*x(j ,1-i )
1358 if ((is == 1) .and. (je+1==npy)) y(1-i ,npy-1+j) = x(j ,npy+i)
1359 if ((ie+1==npx) .and. (js == 1)) y(npx+i ,1-j ) = x(npx-j ,1-i )
1360 if ((ie+1==npx) .and. (je+1==npy)) y(npx+i ,npy-1+j) = mysign*x(npx-j ,npy+i)
1364 end subroutine fill_corners_dgrid_r8
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
1385 if ((is == 1) .and. (js == 1)) x(1-i ,1-j ) = mysign*y(1-j ,i )
1386 if ((is == 1) .and. (je+1==npy)) x(1-i ,npy+j) = y(1-j ,npy-i)
1387 if ((ie+1==npx) .and. (js == 1)) x(npx-1+i,1-j ) = y(npx+j,i )
1388 if ((ie+1==npx) .and. (je+1==npy)) x(npx-1+i,npy+j) = mysign*y(npx+j,npy-i)
1397 if ((is == 1) .and. (js == 1)) y(1-i ,1-j ) = mysign*x(j ,1-i )
1398 if ((is == 1) .and. (je+1==npy)) y(1-i ,npy-1+j) = x(j ,npy+i)
1399 if ((ie+1==npx) .and. (js == 1)) y(npx+i ,1-j ) = x(npx-j ,1-i )
1400 if ((ie+1==npx) .and. (je+1==npy)) y(npx+i ,npy-1+j) = mysign*x(npx-j ,npy+i)
1404 end subroutine fill_corners_dgrid_r4
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
1421 if ((is == 1) .and. (js == 1)) x(1-i ,1-j ) = y(j ,1-i )
1422 if ((is == 1) .and. (je+1==npy)) x(1-i ,npy-1+j) = mysign*y(j ,npy+i)
1423 if ((ie+1==npx) .and. (js == 1)) x(npx+i ,1-j ) = mysign*y(npx-j ,1-i )
1424 if ((ie+1==npx) .and. (je+1==npy)) x(npx+i ,npy-1+j) = y(npx-j ,npy+i)
1429 if ((is == 1) .and. (js == 1)) y(1-i ,1-j ) = x(1-j ,i )
1430 if ((is == 1) .and. (je+1==npy)) y(1-i ,npy+j) = mysign*x(1-j ,npy-i)
1431 if ((ie+1==npx) .and. (js == 1)) y(npx-1+i,1-j ) = mysign*x(npx+j,i )
1432 if ((ie+1==npx) .and. (je+1==npy)) y(npx-1+i,npy+j) = x(npx+j,npy-i)
1436 end subroutine fill_corners_cgrid_r4
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
1453 if ((is == 1) .and. (js == 1)) x(1-i ,1-j ) = y(j ,1-i )
1454 if ((is == 1) .and. (je+1==npy)) x(1-i ,npy-1+j) = mysign*y(j ,npy+i)
1455 if ((ie+1==npx) .and. (js == 1)) x(npx+i ,1-j ) = mysign*y(npx-j ,1-i )
1456 if ((ie+1==npx) .and. (je+1==npy)) x(npx+i ,npy-1+j) = y(npx-j ,npy+i)
1461 if ((is == 1) .and. (js == 1)) y(1-i ,1-j ) = x(1-j ,i )
1462 if ((is == 1) .and. (je+1==npy)) y(1-i ,npy+j) = mysign*x(1-j ,npy-i)
1463 if ((ie+1==npx) .and. (js == 1)) y(npx-1+i,1-j ) = mysign*x(npx+j,i )
1464 if ((ie+1==npx) .and. (je+1==npy)) y(npx-1+i,npy+j) = x(npx+j,npy-i)
1468 end subroutine fill_corners_cgrid_r8
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
1485 if ((is== 1) .and. (js== 1)) x(1-i ,1-j ) = mysign*y(1-j ,i )
1486 if ((is== 1) .and. (je==npy-1)) x(1-i ,npy-1+j) = y(1-j ,npy-1-i+1)
1487 if ((ie==npx-1) .and. (js== 1)) x(npx-1+i,1-j ) = y(npx-1+j,i )
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)
1493 if ((is== 1) .and. (js== 1)) y(1-j ,1-i ) = mysign*x(i ,1-j )
1494 if ((is== 1) .and. (je==npy-1)) y(1-j ,npy-1+i) = x(i ,npy-1+j)
1495 if ((ie==npx-1) .and. (js== 1)) y(npx-1+j,1-i ) = x(npx-1-i+1,1-j )
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)
1500 end subroutine fill_corners_agrid_r4
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
1517 if ((is== 1) .and. (js== 1)) x(1-i ,1-j ) = mysign*y(1-j ,i )
1518 if ((is== 1) .and. (je==npy-1)) x(1-i ,npy-1+j) = y(1-j ,npy-1-i+1)
1519 if ((ie==npx-1) .and. (js== 1)) x(npx-1+i,1-j ) = y(npx-1+j,i )
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)
1525 if ((is== 1) .and. (js== 1)) y(1-j ,1-i ) = mysign*x(i ,1-j )
1526 if ((is== 1) .and. (je==npy-1)) y(1-j ,npy-1+i) = x(i ,npy-1+j)
1527 if ((ie==npx-1) .and. (js== 1)) y(npx-1+j,1-i ) = x(npx-1-i+1,1-j )
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)
1532 end subroutine fill_corners_agrid_r8
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)
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
1557 do l=1,npes_this_grid
1561 call mpp_gather(ldims, gdims)
1564 lsize = ( (i2 - i1 + 1) * (j2 - j1 + 1) ) * kdim
1565 do l=1,npes_this_grid
1570 lsize_buf(1) = lsize
1571 call mpp_gather(lsize_buf, lsizes)
1574 allocate ( larr(lsize) )
1579 larr(icnt) = q(i,j,k,tile)
1586 call mpp_broadcast(lsizes, npes_this_grid,
masterproc)
1588 do l=2,npes_this_grid
1590 ldispl(l) = ldispl(l-1) + lsizes(l-1)
1591 gsize = gsize + lsizes(l)
1593 allocate ( garr(gsize) )
1595 call mpp_gather(larr, lsize, garr, lsizes)
1599 do n=2,npes_this_grid
1601 do l=gdims( (n-1)*5 + 5 ), gdims( (n-1)*5 + 5 )
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)
1616 end subroutine mp_gather_4d_r4
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)
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
1643 do l=1,npes_this_grid
1648 call mpp_gather(ldims, gdims)
1650 lsize = ( (i2 - i1 + 1) * (j2 - j1 + 1) )
1651 do l=1,npes_this_grid
1656 lsize_buf(1) = lsize
1657 call mpp_gather(lsize_buf, lsizes)
1660 allocate ( larr(lsize) )
1664 larr(icnt) = q(i,j,tile)
1670 call mpp_broadcast(lsizes, npes_this_grid,
masterproc)
1672 do l=2,npes_this_grid
1674 ldispl(l) = ldispl(l-1) + lsizes(l-1)
1675 gsize = gsize + lsizes(l)
1677 allocate ( garr(gsize) )
1678 call mpp_gather(larr, lsize, garr, lsizes)
1681 do n=2,npes_this_grid
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)
1696 end subroutine mp_gather_3d_r4
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)
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
1722 do l=1,npes_this_grid
1727 call mpp_gather(ldims, gdims)
1728 lsize = ( (i2 - i1 + 1) * (j2 - j1 + 1) )
1729 do l=1,npes_this_grid
1736 lsize_buf(1) = lsize
1737 call mpp_gather(lsize_buf, lsizes)
1739 allocate ( larr(lsize) )
1743 larr(icnt) = q(i,j,tile)
1748 call mpp_broadcast(lsizes, npes_this_grid,
masterproc)
1751 do l=2,npes_this_grid
1753 ldispl(l) = ldispl(l-1) + lsizes(l-1)
1754 gsize = gsize + lsizes(l)
1757 allocate ( garr(gsize) )
1758 call mpp_gather(larr, lsize, garr, lsizes)
1761 do n=2,npes_this_grid
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)
1776 end subroutine mp_gather_3d_r8
1786 subroutine mp_bcst_i(q)
1787 integer,
intent(INOUT) :: q
1789 call mpi_bcast(q, 1, mpi_integer,
masterproc, commglobal, ierror)
1791 end subroutine mp_bcst_i
1801 subroutine mp_bcst_r4(q)
1802 real(kind=4),
intent(INOUT) :: q
1804 call mpi_bcast(q, 1, mpi_real,
masterproc, commglobal, ierror)
1806 end subroutine mp_bcst_r4
1816 subroutine mp_bcst_r8(q)
1817 real(kind=8),
intent(INOUT) :: q
1819 call mpi_bcast(q, 1, mpi_double_precision,
masterproc, commglobal, ierror)
1821 end subroutine mp_bcst_r8
1831 subroutine mp_bcst_1d_r4(q, idim)
1832 integer,
intent(IN) :: idim
1833 real(kind=4),
intent(INOUT) :: q(idim)
1835 call mpi_bcast(q, idim, mpi_real,
masterproc, commglobal, ierror)
1837 end subroutine mp_bcst_1d_r4
1847 subroutine mp_bcst_1d_r8(q, idim)
1848 integer,
intent(IN) :: idim
1849 real(kind=8),
intent(INOUT) :: q(idim)
1851 call mpi_bcast(q, idim, mpi_double_precision,
masterproc, commglobal, ierror)
1853 end subroutine mp_bcst_1d_r8
1863 subroutine mp_bcst_2d_r4(q, idim, jdim)
1864 integer,
intent(IN) :: idim, jdim
1865 real(kind=4),
intent(INOUT) :: q(idim,jdim)
1867 call mpi_bcast(q, idim*jdim, mpi_real,
masterproc, commglobal, ierror)
1869 end subroutine mp_bcst_2d_r4
1879 subroutine mp_bcst_2d_r8(q, idim, jdim)
1880 integer,
intent(IN) :: idim, jdim
1881 real(kind=8),
intent(INOUT) :: q(idim,jdim)
1883 call mpi_bcast(q, idim*jdim, mpi_double_precision,
masterproc, commglobal, ierror)
1885 end subroutine mp_bcst_2d_r8
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)
1899 call mpi_bcast(q, idim*jdim*kdim, mpi_real,
masterproc, commglobal, ierror)
1901 end subroutine mp_bcst_3d_r4
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)
1915 call mpi_bcast(q, idim*jdim*kdim, mpi_double_precision,
masterproc, commglobal, ierror)
1917 end subroutine mp_bcst_3d_r8
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)
1931 call mpi_bcast(q, idim*jdim*kdim*ldim, mpi_real,
masterproc, commglobal, ierror)
1933 end subroutine mp_bcst_4d_r4
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)
1947 call mpi_bcast(q, idim*jdim*kdim*ldim, mpi_double_precision,
masterproc, commglobal, ierror)
1949 end subroutine mp_bcst_4d_r8
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)
1963 call mpi_bcast(q, idim*jdim*kdim, mpi_integer,
masterproc, commglobal, ierror)
1965 end subroutine mp_bcst_3d_i
1975 subroutine mp_bcst_1d_i(q, idim)
1976 integer,
intent(IN) :: idim
1977 integer,
intent(INOUT) :: q(idim)
1979 call mpi_bcast(q, idim, mpi_integer,
masterproc, commglobal, ierror)
1981 end subroutine mp_bcst_1d_i
1991 subroutine mp_bcst_2d_i(q, idim, jdim)
1992 integer,
intent(IN) :: idim, jdim
1993 integer,
intent(INOUT) :: q(idim,jdim)
1995 call mpi_bcast(q, idim*jdim, mpi_integer,
masterproc, commglobal, ierror)
1997 end subroutine mp_bcst_2d_i
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)
2010 call mpi_bcast(q, idim*jdim*kdim*ldim, mpi_integer,
masterproc, commglobal, ierror)
2012 end subroutine mp_bcst_4d_i
2023 subroutine mp_reduce_max_r4_1d(mymax,npts)
2024 integer,
intent(IN) :: npts
2025 real(kind=4),
intent(INOUT) :: mymax(npts)
2027 real(kind=4) :: gmax(npts)
2029 call mpi_allreduce( mymax, gmax, npts, mpi_real, mpi_max, &
2030 commglobal, ierror )
2034 end subroutine mp_reduce_max_r4_1d
2045 subroutine mp_reduce_max_r8_1d(mymax,npts)
2046 integer,
intent(IN) :: npts
2047 real(kind=8),
intent(INOUT) :: mymax(npts)
2049 real(kind=8) :: gmax(npts)
2051 call mpi_allreduce( mymax, gmax, npts, mpi_double_precision, mpi_max, &
2052 commglobal, ierror )
2056 end subroutine mp_reduce_max_r8_1d
2067 subroutine mp_reduce_max_r4(mymax)
2068 real(kind=4),
intent(INOUT) :: mymax
2070 real(kind=4) :: gmax
2072 call mpi_allreduce( mymax, gmax, 1, mpi_real, mpi_max, &
2073 commglobal, ierror )
2077 end subroutine mp_reduce_max_r4
2084 subroutine mp_reduce_max_r8(mymax)
2085 real(kind=8),
intent(INOUT) :: mymax
2087 real(kind=8) :: gmax
2089 call mpi_allreduce( mymax, gmax, 1, mpi_double_precision, mpi_max, &
2090 commglobal, ierror )
2094 end subroutine mp_reduce_max_r8
2096 subroutine mp_reduce_min_r4(mymin)
2097 real(kind=4),
intent(INOUT) :: mymin
2099 real(kind=4) :: gmin
2101 call mpi_allreduce( mymin, gmin, 1, mpi_real, mpi_min, &
2102 commglobal, ierror )
2106 end subroutine mp_reduce_min_r4
2108 subroutine mp_reduce_min_r8(mymin)
2109 real(kind=8),
intent(INOUT) :: mymin
2111 real(kind=8) :: gmin
2113 call mpi_allreduce( mymin, gmin, 1, mpi_double_precision, mpi_min, &
2114 commglobal, ierror )
2118 end subroutine mp_reduce_min_r8
2128 subroutine mp_reduce_max_i(mymax)
2129 integer,
intent(INOUT) :: mymax
2133 call mpi_allreduce( mymax, gmax, 1, mpi_integer, mpi_max, &
2134 commglobal, ierror )
2138 end subroutine mp_reduce_max_i
2148 subroutine mp_reduce_sum_r4(mysum)
2149 real(kind=4),
intent(INOUT) :: mysum
2151 real(kind=4) :: gsum
2153 call mpi_allreduce( mysum, gsum, 1, mpi_real, mpi_sum, &
2154 commglobal, ierror )
2158 end subroutine mp_reduce_sum_r4
2168 subroutine mp_reduce_sum_r8(mysum)
2169 real(kind=8),
intent(INOUT) :: mysum
2171 real(kind=8) :: gsum
2173 call mpi_allreduce( mysum, gsum, 1, mpi_double_precision, mpi_sum, &
2174 commglobal, ierror )
2178 end subroutine mp_reduce_sum_r8
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)
2196 call mpi_allreduce( mysum, gsum, npts, mpi_real, mpi_sum, &
2197 commglobal, ierror )
2201 end subroutine mp_reduce_sum_r4_1darr
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)
2219 call mpi_allreduce( mysum, gsum, npts1*npts2, mpi_real, mpi_sum, &
2220 commglobal, ierror )
2224 end subroutine mp_reduce_sum_r4_2darr
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
2240 real(kind=4) :: gsum
2245 mysum = mysum + sum1d(i)
2248 call mpi_allreduce( mysum, gsum, 1, mpi_double_precision, mpi_sum, &
2249 commglobal, ierror )
2253 end subroutine mp_reduce_sum_r4_1d
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
2268 real(kind=8) :: gsum
2273 mysum = mysum + sum1d(i)
2276 call mpi_allreduce( mysum, gsum, 1, mpi_double_precision, mpi_sum, &
2277 commglobal, ierror )
2281 end subroutine mp_reduce_sum_r8_1d
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)
2297 call mpi_allreduce( mysum, gsum, npts, mpi_double_precision, &
2299 commglobal, ierror )
2303 end subroutine mp_reduce_sum_r8_1darr
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)
2321 call mpi_allreduce( mysum, gsum, npts1*npts2, &
2322 mpi_double_precision, mpi_sum, &
2323 commglobal, ierror )
2327 end subroutine mp_reduce_sum_r8_2darr
2337 integer,
parameter::
ng = 3
The module 'fv_mp_mod' is a single program multiple data (SPMD) parallel decompostion/communication m...
The module 'fv_arrays' contains the 'fv_atmos_type' and associated datatypes.
integer, parameter, public ng
integer, public masterproc