FMS  2025.04
Flexible Modeling System
mpp_comm_nocomm.inc
1 ! -*-f90-*-
2 
3 !***********************************************************************
4 !* Apache License 2.0
5 !*
6 !* This file is part of the GFDL Flexible Modeling System (FMS).
7 !*
8 !* Licensed under the Apache License, Version 2.0 (the "License");
9 !* you may not use this file except in compliance with the License.
10 !* You may obtain a copy of the License at
11 !*
12 !* http://www.apache.org/licenses/LICENSE-2.0
13 !*
14 !* FMS is distributed in the hope that it will be useful, but WITHOUT
15 !* WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied;
16 !* without even the implied warranty of MERCHANTABILITY or FITNESS FOR A
17 !* PARTICULAR PURPOSE. See the License for the specific language
18 !* governing permissions and limitations under the License.
19 !***********************************************************************
20 !> @file
21 !> @brief Routines to initialize and finalize @ref mpp_mod without MPI.
22 
23 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
24 ! !
25 ! ROUTINES TO INITIALIZE/FINALIZE MPP MODULE: mpp_init, mpp_exit !
26 ! !
27 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
28 !> @brief Initialize the @ref mpp_mod module
29 subroutine mpp_init( flags, localcomm, test_level, alt_input_nml_path )
30  integer, optional, intent(in) :: flags !< Flags for debug output, can be MPP_VERBOSE or MPP_DEBUG
31  integer, optional, intent(in) :: localcomm !< Id of MPI communicator used to initialize
32  integer, optional, intent(in) :: test_level !< Used to exit initialization at certain stages
33  !! before completion for testing purposes
34  character(len=*), optional, intent(in) :: alt_input_nml_path !< Input path for namelist
35  integer :: my_pe, num_pes, len, i, logunit
36  logical :: opened, existed
37  integer :: io_status
38  integer :: t_level
39 
40  if( module_is_initialized )return
41 
42  module_is_initialized = .true.
43  if(present(test_level)) then
44  t_level = test_level
45  else
46  t_level = -1
47  endif
48  if(t_level == 0) return
49 
50  allocate(peset(0:0))
51  !PEsets: make defaults illegal
52  peset(:)%count = -1
53  peset(:)%id = -1
54  peset(:)%group = -1
55  !0=single-PE, initialized so that count returns 1
56  peset(0)%count = 1
57  allocate( peset(0)%list(1) )
58  peset(0)%list = pe
59  current_peset_num = 0
60  peset(0)%id = 0
61  world_peset_num = 0
62  current_peset_num = world_peset_num !initialize current PEset to world
63  if(t_level == 1) return
64 
65  !initialize clocks
66  call system_clock( count=tick0, count_rate=ticks_per_sec, count_max=max_ticks )
67  tick_rate = 1./ticks_per_sec
68  clock0 = mpp_clock_id( 'Total runtime', flags=mpp_clock_sync )
69  if(t_level == 2) return
70 
71  ! Initialize mpp_datatypes
72  ! NOTE: mpp_datatypes is unused in serial mode; this is an empty list
73  datatypes%head => null()
74  datatypes%tail => null()
75  datatypes%length = 0
76 
77  ! Create the bytestream (default) mpp_datatype
78  ! NOTE: mpp_byte is unused in serial mode
79  mpp_byte%counter = -1
80  mpp_byte%ndims = -1
81  allocate(mpp_byte%sizes(0))
82  allocate(mpp_byte%subsizes(0))
83  allocate(mpp_byte%starts(0))
84  mpp_byte%etype = -1
85  mpp_byte%id = -1
86 
87  mpp_byte%prev => null()
88  mpp_byte%next => null()
89 
90  if( PRESENT(flags) )then
91  debug = flags.EQ.mpp_debug
92  verbose = flags.EQ.mpp_verbose .OR. debug
93  end if
94  if(t_level == 3) return
95 
96  call mpp_init_logfile()
97  if (present(alt_input_nml_path)) then
98  call read_input_nml(alt_input_nml_path=alt_input_nml_path)
99  else
100  call read_input_nml
101  end if
102  if(t_level == 4) return
103 
104  !--- read namelist
105  read (input_nml_file, mpp_nml, iostat=io_status)
106  if (io_status > 0) then
107  call mpp_error(fatal,'=>mpp_init: Error reading mpp_nml')
108  endif
109  if(t_level == 5) return
110 
111 ! non-root pe messages written to other location than stdout()
112  if (trim(etcfile) /= '/dev/null') then
113  write( etcfile,'(a,i6.6)' )trim(etcfile)//'.', pe
114  endif
115  inquire(file=etcfile, exist=existed)
116  if(existed) then
117  open( newunit=etc_unit, file=trim(etcfile), status='REPLACE' )
118  else
119  open( newunit=etc_unit, file=trim(etcfile) )
120  endif
121 
122  !messages
123  if( verbose )call mpp_error( note, 'MPP_INIT: initializing MPP module...' )
124  if( pe.EQ.root_pe )then
125  logunit = stdlog()
126  write( logunit,'(/a)' )'MPP module '//trim(version)
127  write( logunit,'(a,i6)' )'MPP started with NPES=', npes
128  write( logunit,'(a)' )'Using no library for message passing...'
129  write( logunit, '(a26,es12.4,a6,i10,a11)' ) &
130  'Realtime clock resolution=', tick_rate, ' sec (', ticks_per_sec, ' ticks/sec)'
131  write( logunit, '(a23,es12.4,a6,i20,a7)' ) &
132  'Clock rolls over after ', max_ticks*tick_rate, ' sec (', max_ticks, ' ticks)'
133  end if
134 
135  call mpp_clock_begin(clock0)
136 
137  return
138 end subroutine mpp_init
139 
140 !#######################################################################
141 !> @brief To be called at the end of a run
142 subroutine mpp_exit()
143  integer :: i, j, k, n, nmax, istat, out_unit
144  real :: t, tmin, tmax, tavg, tstd
145  real :: m, mmin, mmax, mavg, mstd, t_total
146  logical :: opened
147 
148  if( .NOT.module_is_initialized )return
150  call mpp_clock_end(clock0)
151  t_total = clocks(clock0)%total_ticks*tick_rate
152  out_unit = stdout()
153  if( clock_num.GT.0 )then
154  if( any(clocks(1:clock_num)%detailed) )then
155  call sum_clock_data; call dump_clock_summary
156  end if
157  if( pe.EQ.root_pe )then
158  write( out_unit,'(/a,i6,a)' ) 'Tabulating mpp_clock statistics across ', npes, ' PEs...'
159  if( any(clocks(1:clock_num)%detailed) ) &
160  write( out_unit,'(a)' )' ... see mpp_clock.out.#### for details on individual PEs.'
161  write( out_unit,'(/32x,a)' ) &
162  & ' hits tmin tmax tavg tstd tfrac grain pemin pemax'
163  else
164  write( out_unit,'(/37x,a)' ) 'time'
165  end if
166  call flush( out_unit )
167  call mpp_sync()
168  do i = 1,clock_num
169  if( .NOT.any(peset(clocks(i)%peset_num)%list(:).EQ.pe) )cycle
170  call mpp_set_current_pelist( peset(clocks(i)%peset_num)%list )
171  !times between mpp_clock ticks
172  t = clocks(i)%total_ticks*tick_rate
173  tmin = t; call mpp_min(tmin)
174  tmax = t; call mpp_max(tmax)
175  tavg = t; call mpp_sum(tavg); tavg = tavg/mpp_npes()
176  tstd = (t-tavg)**2; call mpp_sum(tstd); tstd = sqrt( tstd/mpp_npes() )
177  if( pe.EQ.root_pe )write( out_unit,'(a32,i10,4f14.6,f7.3,3i6)' ) &
178  clocks(i)%name, clocks(i)%hits, tmin, tmax, tavg, tstd, tavg/t_total, &
179  clocks(i)%grain, minval(peset(clocks(i)%peset_num)%list), &
180  maxval(peset(clocks(i)%peset_num)%list)
181  if (pe.NE.root_pe) write(out_unit,'(a32,f14.6)') clocks(i)%name, clocks(i)%total_ticks*tick_rate
182  end do
183  if( any(clocks(1:clock_num)%detailed) .AND. pe.EQ.root_pe )write( out_unit,'(/32x,a)' ) &
184  ' tmin tmax tavg tstd mmin mmax mavg mstd mavg/tavg'
185 
186  do i = 1,clock_num
187  !messages: bytelengths and times
188  if( .NOT.clocks(i)%detailed )cycle
189  do j = 1,max_event_types
190  n = clocks(i)%events(j)%calls; nmax = n
191  call mpp_max(nmax)
192  if( nmax.NE.0 )then
193  !don't divide by n because n might be 0
194  m = 0
195  if( n.GT.0 )m = sum(clocks(i)%events(j)%bytes(1:n))
196  mmin = m; call mpp_min(mmin)
197  mmax = m; call mpp_max(mmax)
198  mavg = m; call mpp_sum(mavg); mavg = mavg/mpp_npes()
199  mstd = (m-mavg)**2; call mpp_sum(mstd); mstd = sqrt( mstd/mpp_npes() )
200  t = 0
201  if( n.GT.0 )t = sum(clocks(i)%events(j)%ticks(1:n))*tick_rate
202  tmin = t; call mpp_min(tmin)
203  tmax = t; call mpp_max(tmax)
204  tavg = t; call mpp_sum(tavg); tavg = tavg/mpp_npes()
205  tstd = (t-tavg)**2; call mpp_sum(tstd); tstd = sqrt( tstd/mpp_npes() )
206  if( pe.EQ.root_pe )write( out_unit,'(a32,4f11.3,5es11.3)' ) &
207  trim(clocks(i)%name)//' '//trim(clocks(i)%events(j)%name), &
208  tmin, tmax, tavg, tstd, mmin, mmax, mavg, mstd, mavg/tavg
209  end if
210  end do
211  end do
212  end if
213 
214  inquire(unit=etc_unit, opened=opened)
215  if (opened) then
216  call flush (etc_unit)
217  close(etc_unit)
218  endif
219 
221  call mpp_sync()
222  call mpp_max(mpp_stack_hwm)
223  if( pe.EQ.root_pe )write( out_unit,* )'MPP_STACK high water mark=', mpp_stack_hwm
224 
225  return
226 end subroutine mpp_exit
227 
228 !#######################################################################
229  !> Set the mpp_stack variable to be at least n LONG words long
230  subroutine mpp_set_stack_size(n)
231  integer, intent(in) :: n
232  character(len=8) :: text
233 
234  if( n.GT.mpp_stack_size .AND. allocated(mpp_stack) )deallocate(mpp_stack)
235  if( .NOT.allocated(mpp_stack) )then
236  allocate( mpp_stack(n) )
237  mpp_stack_size = n
238  end if
239 
240  write( text,'(i8)' )n
241  if( pe.EQ.root_pe )call mpp_error( note, 'MPP_SET_STACK_SIZE: stack size set to '//text//'.' )
242 
243  return
244  end subroutine mpp_set_stack_size
245 
246  subroutine mpp_broadcast_char(char_data, length, from_pe, pelist )
247  character(len=*), intent(inout) :: char_data(:)
248  integer, intent(in) :: length, from_pe
249  integer, intent(in), optional :: pelist(:)
250 
251  if( .NOT.module_is_initialized )call mpp_error( fatal, 'mpp_broadcast_text: You must first call mpp_init.' )
252  return
253  end subroutine mpp_broadcast_char
254 
255 
256 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
257 ! !
258 ! BASIC MESSAGE PASSING ROUTINE: mpp_transmit !
259 ! !
260 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
261 
262 ! set init value for mpp_type
263 #define MPP_TYPE_INIT_VALUE 0.
264 
265 #undef MPP_TRANSMIT_
266 #define MPP_TRANSMIT_ mpp_transmit_real8
267 #undef MPP_TRANSMIT_SCALAR_
268 #define MPP_TRANSMIT_SCALAR_ mpp_transmit_real8_scalar
269 #undef MPP_TRANSMIT_2D_
270 #define MPP_TRANSMIT_2D_ mpp_transmit_real8_2d
271 #undef MPP_TRANSMIT_3D_
272 #define MPP_TRANSMIT_3D_ mpp_transmit_real8_3d
273 #undef MPP_TRANSMIT_4D_
274 #define MPP_TRANSMIT_4D_ mpp_transmit_real8_4d
275 #undef MPP_TRANSMIT_5D_
276 #define MPP_TRANSMIT_5D_ mpp_transmit_real8_5d
277 #undef MPP_RECV_
278 #define MPP_RECV_ mpp_recv_real8
279 #undef MPP_RECV_SCALAR_
280 #define MPP_RECV_SCALAR_ mpp_recv_real8_scalar
281 #undef MPP_RECV_2D_
282 #define MPP_RECV_2D_ mpp_recv_real8_2d
283 #undef MPP_RECV_3D_
284 #define MPP_RECV_3D_ mpp_recv_real8_3d
285 #undef MPP_RECV_4D_
286 #define MPP_RECV_4D_ mpp_recv_real8_4d
287 #undef MPP_RECV_5D_
288 #define MPP_RECV_5D_ mpp_recv_real8_5d
289 #undef MPP_SEND_
290 #define MPP_SEND_ mpp_send_real8
291 #undef MPP_SEND_SCALAR_
292 #define MPP_SEND_SCALAR_ mpp_send_real8_scalar
293 #undef MPP_SEND_2D_
294 #define MPP_SEND_2D_ mpp_send_real8_2d
295 #undef MPP_SEND_3D_
296 #define MPP_SEND_3D_ mpp_send_real8_3d
297 #undef MPP_SEND_4D_
298 #define MPP_SEND_4D_ mpp_send_real8_4d
299 #undef MPP_SEND_5D_
300 #define MPP_SEND_5D_ mpp_send_real8_5d
301 #undef MPP_BROADCAST_
302 #define MPP_BROADCAST_ mpp_broadcast_real8
303 #undef MPP_BROADCAST_SCALAR_
304 #define MPP_BROADCAST_SCALAR_ mpp_broadcast_real8_scalar
305 #undef MPP_BROADCAST_2D_
306 #define MPP_BROADCAST_2D_ mpp_broadcast_real8_2d
307 #undef MPP_BROADCAST_3D_
308 #define MPP_BROADCAST_3D_ mpp_broadcast_real8_3d
309 #undef MPP_BROADCAST_4D_
310 #define MPP_BROADCAST_4D_ mpp_broadcast_real8_4d
311 #undef MPP_BROADCAST_5D_
312 #define MPP_BROADCAST_5D_ mpp_broadcast_real8_5d
313 #undef MPP_SCATTERV_
314 #define MPP_SCATTERV_ mpp_scatterv_real8
315 #undef MPP_GATHER_
316 #define MPP_GATHER_ mpp_gather_real8
317 #undef MPP_GATHERV_
318 #define MPP_GATHERV_ mpp_gatherv_real8
319 #undef MPP_TYPE_
320 #define MPP_TYPE_ real(r8_kind)
321 #undef MPP_TYPE_BYTELEN_
322 #define MPP_TYPE_BYTELEN_ 8
323 #undef MPI_TYPE_
324 #define MPI_TYPE_ MPI_REAL8
325 #include <mpp_transmit_nocomm.fh>
326 
327 #ifdef OVERLOAD_C8
328 #undef MPP_TRANSMIT_
329 #define MPP_TRANSMIT_ mpp_transmit_cmplx8
330 #undef MPP_TRANSMIT_SCALAR_
331 #define MPP_TRANSMIT_SCALAR_ mpp_transmit_cmplx8_scalar
332 #undef MPP_TRANSMIT_2D_
333 #define MPP_TRANSMIT_2D_ mpp_transmit_cmplx8_2d
334 #undef MPP_TRANSMIT_3D_
335 #define MPP_TRANSMIT_3D_ mpp_transmit_cmplx8_3d
336 #undef MPP_TRANSMIT_4D_
337 #define MPP_TRANSMIT_4D_ mpp_transmit_cmplx8_4d
338 #undef MPP_TRANSMIT_5D_
339 #define MPP_TRANSMIT_5D_ mpp_transmit_cmplx8_5d
340 #undef MPP_RECV_
341 #define MPP_RECV_ mpp_recv_cmplx8
342 #undef MPP_RECV_SCALAR_
343 #define MPP_RECV_SCALAR_ mpp_recv_cmplx8_scalar
344 #undef MPP_RECV_2D_
345 #define MPP_RECV_2D_ mpp_recv_cmplx8_2d
346 #undef MPP_RECV_3D_
347 #define MPP_RECV_3D_ mpp_recv_cmplx8_3d
348 #undef MPP_RECV_4D_
349 #define MPP_RECV_4D_ mpp_recv_cmplx8_4d
350 #undef MPP_RECV_5D_
351 #define MPP_RECV_5D_ mpp_recv_cmplx8_5d
352 #undef MPP_SEND_
353 #define MPP_SEND_ mpp_send_cmplx8
354 #undef MPP_SEND_SCALAR_
355 #define MPP_SEND_SCALAR_ mpp_send_cmplx8_scalar
356 #undef MPP_SEND_2D_
357 #define MPP_SEND_2D_ mpp_send_cmplx8_2d
358 #undef MPP_SEND_3D_
359 #define MPP_SEND_3D_ mpp_send_cmplx8_3d
360 #undef MPP_SEND_4D_
361 #define MPP_SEND_4D_ mpp_send_cmplx8_4d
362 #undef MPP_SEND_5D_
363 #define MPP_SEND_5D_ mpp_send_cmplx8_5d
364 #undef MPP_BROADCAST_
365 #define MPP_BROADCAST_ mpp_broadcast_cmplx8
366 #undef MPP_BROADCAST_SCALAR_
367 #define MPP_BROADCAST_SCALAR_ mpp_broadcast_cmplx8_scalar
368 #undef MPP_BROADCAST_2D_
369 #define MPP_BROADCAST_2D_ mpp_broadcast_cmplx8_2d
370 #undef MPP_BROADCAST_3D_
371 #define MPP_BROADCAST_3D_ mpp_broadcast_cmplx8_3d
372 #undef MPP_BROADCAST_4D_
373 #define MPP_BROADCAST_4D_ mpp_broadcast_cmplx8_4d
374 #undef MPP_BROADCAST_5D_
375 #define MPP_BROADCAST_5D_ mpp_broadcast_cmplx8_5d
376 #undef MPP_SCATTERV_
377 #define MPP_SCATTERV_ mpp_scatterv_cmplx8
378 #undef MPP_GATHER_
379 #define MPP_GATHER_ mpp_gather_cmplx8
380 #undef MPP_GATHERV_
381 #define MPP_GATHERV_ mpp_gatherv_cmplx8
382 #undef MPP_TYPE_
383 #define MPP_TYPE_ complex(c8_kind)
384 #undef MPP_TYPE_BYTELEN_
385 #define MPP_TYPE_BYTELEN_ 16
386 #undef MPI_TYPE_
387 #define MPI_TYPE_ MPI_DOUBLE_COMPLEX
388 #include <mpp_transmit_nocomm.fh>
389 #endif
390 
391 #undef MPP_TRANSMIT_
392 #define MPP_TRANSMIT_ mpp_transmit_real4
393 #undef MPP_TRANSMIT_SCALAR_
394 #define MPP_TRANSMIT_SCALAR_ mpp_transmit_real4_scalar
395 #undef MPP_TRANSMIT_2D_
396 #define MPP_TRANSMIT_2D_ mpp_transmit_real4_2d
397 #undef MPP_TRANSMIT_3D_
398 #define MPP_TRANSMIT_3D_ mpp_transmit_real4_3d
399 #undef MPP_TRANSMIT_4D_
400 #define MPP_TRANSMIT_4D_ mpp_transmit_real4_4d
401 #undef MPP_TRANSMIT_5D_
402 #define MPP_TRANSMIT_5D_ mpp_transmit_real4_5d
403 #undef MPP_RECV_
404 #define MPP_RECV_ mpp_recv_real4
405 #undef MPP_RECV_SCALAR_
406 #define MPP_RECV_SCALAR_ mpp_recv_real4_scalar
407 #undef MPP_RECV_2D_
408 #define MPP_RECV_2D_ mpp_recv_real4_2d
409 #undef MPP_RECV_3D_
410 #define MPP_RECV_3D_ mpp_recv_real4_3d
411 #undef MPP_RECV_4D_
412 #define MPP_RECV_4D_ mpp_recv_real4_4d
413 #undef MPP_RECV_5D_
414 #define MPP_RECV_5D_ mpp_recv_real4_5d
415 #undef MPP_SEND_
416 #define MPP_SEND_ mpp_send_real4
417 #undef MPP_SEND_SCALAR_
418 #define MPP_SEND_SCALAR_ mpp_send_real4_scalar
419 #undef MPP_SEND_2D_
420 #define MPP_SEND_2D_ mpp_send_real4_2d
421 #undef MPP_SEND_3D_
422 #define MPP_SEND_3D_ mpp_send_real4_3d
423 #undef MPP_SEND_4D_
424 #define MPP_SEND_4D_ mpp_send_real4_4d
425 #undef MPP_SEND_5D_
426 #define MPP_SEND_5D_ mpp_send_real4_5d
427 #undef MPP_BROADCAST_
428 #define MPP_BROADCAST_ mpp_broadcast_real4
429 #undef MPP_BROADCAST_SCALAR_
430 #define MPP_BROADCAST_SCALAR_ mpp_broadcast_real4_scalar
431 #undef MPP_BROADCAST_2D_
432 #define MPP_BROADCAST_2D_ mpp_broadcast_real4_2d
433 #undef MPP_BROADCAST_3D_
434 #define MPP_BROADCAST_3D_ mpp_broadcast_real4_3d
435 #undef MPP_BROADCAST_4D_
436 #define MPP_BROADCAST_4D_ mpp_broadcast_real4_4d
437 #undef MPP_BROADCAST_5D_
438 #define MPP_BROADCAST_5D_ mpp_broadcast_real4_5d
439 #undef MPP_SCATTERV_
440 #define MPP_SCATTERV_ mpp_scatterv_real4
441 #undef MPP_GATHER_
442 #define MPP_GATHER_ mpp_gather_real4
443 #undef MPP_GATHERV_
444 #define MPP_GATHERV_ mpp_gatherv_real4
445 #undef MPP_TYPE_
446 #define MPP_TYPE_ real(r4_kind)
447 #undef MPP_TYPE_BYTELEN_
448 #define MPP_TYPE_BYTELEN_ 4
449 #undef MPI_TYPE_
450 #define MPI_TYPE_ MPI_REAL4
451 #include <mpp_transmit_nocomm.fh>
452 
453 #ifdef OVERLOAD_C4
454 #undef MPP_TRANSMIT_
455 #define MPP_TRANSMIT_ mpp_transmit_cmplx4
456 #undef MPP_TRANSMIT_SCALAR_
457 #define MPP_TRANSMIT_SCALAR_ mpp_transmit_cmplx4_scalar
458 #undef MPP_TRANSMIT_2D_
459 #define MPP_TRANSMIT_2D_ mpp_transmit_cmplx4_2d
460 #undef MPP_TRANSMIT_3D_
461 #define MPP_TRANSMIT_3D_ mpp_transmit_cmplx4_3d
462 #undef MPP_TRANSMIT_4D_
463 #define MPP_TRANSMIT_4D_ mpp_transmit_cmplx4_4d
464 #undef MPP_TRANSMIT_5D_
465 #define MPP_TRANSMIT_5D_ mpp_transmit_cmplx4_5d
466 #undef MPP_RECV_
467 #define MPP_RECV_ mpp_recv_cmplx4
468 #undef MPP_RECV_SCALAR_
469 #define MPP_RECV_SCALAR_ mpp_recv_cmplx4_scalar
470 #undef MPP_RECV_2D_
471 #define MPP_RECV_2D_ mpp_recv_cmplx4_2d
472 #undef MPP_RECV_3D_
473 #define MPP_RECV_3D_ mpp_recv_cmplx4_3d
474 #undef MPP_RECV_4D_
475 #define MPP_RECV_4D_ mpp_recv_cmplx4_4d
476 #undef MPP_RECV_5D_
477 #define MPP_RECV_5D_ mpp_recv_cmplx4_5d
478 #undef MPP_SEND_
479 #define MPP_SEND_ mpp_send_cmplx4
480 #undef MPP_SEND_SCALAR_
481 #define MPP_SEND_SCALAR_ mpp_send_cmplx4_scalar
482 #undef MPP_SEND_2D_
483 #define MPP_SEND_2D_ mpp_send_cmplx4_2d
484 #undef MPP_SEND_3D_
485 #define MPP_SEND_3D_ mpp_send_cmplx4_3d
486 #undef MPP_SEND_4D_
487 #define MPP_SEND_4D_ mpp_send_cmplx4_4d
488 #undef MPP_SEND_5D_
489 #define MPP_SEND_5D_ mpp_send_cmplx4_5d
490 #undef MPP_BROADCAST_
491 #define MPP_BROADCAST_ mpp_broadcast_cmplx4
492 #undef MPP_BROADCAST_SCALAR_
493 #define MPP_BROADCAST_SCALAR_ mpp_broadcast_cmplx4_scalar
494 #undef MPP_BROADCAST_2D_
495 #define MPP_BROADCAST_2D_ mpp_broadcast_cmplx4_2d
496 #undef MPP_BROADCAST_3D_
497 #define MPP_BROADCAST_3D_ mpp_broadcast_cmplx4_3d
498 #undef MPP_BROADCAST_4D_
499 #define MPP_BROADCAST_4D_ mpp_broadcast_cmplx4_4d
500 #undef MPP_BROADCAST_5D_
501 #define MPP_BROADCAST_5D_ mpp_broadcast_cmplx4_5d
502 #undef MPP_SCATTERV_
503 #define MPP_SCATTERV_ mpp_scatterv_cmplx4
504 #undef MPP_GATHER_
505 #define MPP_GATHER_ mpp_gather_cmplx4
506 #undef MPP_GATHERV_
507 #define MPP_GATHERV_ mpp_gatherv_cmplx4
508 #undef MPP_TYPE_
509 #define MPP_TYPE_ complex(c4_kind)
510 #undef MPP_TYPE_BYTELEN_
511 #define MPP_TYPE_BYTELEN_ 8
512 #undef MPI_TYPE_
513 #define MPI_TYPE_ MPI_COMPLEX
514 #include <mpp_transmit_nocomm.fh>
515 #endif
516 
517 #undef MPP_TYPE_INIT_VALUE
518 #define MPP_TYPE_INIT_VALUE 0
519 #undef MPP_TRANSMIT_
520 #define MPP_TRANSMIT_ mpp_transmit_int8
521 #undef MPP_TRANSMIT_SCALAR_
522 #define MPP_TRANSMIT_SCALAR_ mpp_transmit_int8_scalar
523 #undef MPP_TRANSMIT_2D_
524 #define MPP_TRANSMIT_2D_ mpp_transmit_int8_2d
525 #undef MPP_TRANSMIT_3D_
526 #define MPP_TRANSMIT_3D_ mpp_transmit_int8_3d
527 #undef MPP_TRANSMIT_4D_
528 #define MPP_TRANSMIT_4D_ mpp_transmit_int8_4d
529 #undef MPP_TRANSMIT_5D_
530 #define MPP_TRANSMIT_5D_ mpp_transmit_int8_5d
531 #undef MPP_RECV_
532 #define MPP_RECV_ mpp_recv_int8
533 #undef MPP_RECV_SCALAR_
534 #define MPP_RECV_SCALAR_ mpp_recv_int8_scalar
535 #undef MPP_RECV_2D_
536 #define MPP_RECV_2D_ mpp_recv_int8_2d
537 #undef MPP_RECV_3D_
538 #define MPP_RECV_3D_ mpp_recv_int8_3d
539 #undef MPP_RECV_4D_
540 #define MPP_RECV_4D_ mpp_recv_int8_4d
541 #undef MPP_RECV_5D_
542 #define MPP_RECV_5D_ mpp_recv_int8_5d
543 #undef MPP_SEND_
544 #define MPP_SEND_ mpp_send_int8
545 #undef MPP_SEND_SCALAR_
546 #define MPP_SEND_SCALAR_ mpp_send_int8_scalar
547 #undef MPP_SEND_2D_
548 #define MPP_SEND_2D_ mpp_send_int8_2d
549 #undef MPP_SEND_3D_
550 #define MPP_SEND_3D_ mpp_send_int8_3d
551 #undef MPP_SEND_4D_
552 #define MPP_SEND_4D_ mpp_send_int8_4d
553 #undef MPP_SEND_5D_
554 #define MPP_SEND_5D_ mpp_send_int8_5d
555 #undef MPP_BROADCAST_
556 #define MPP_BROADCAST_ mpp_broadcast_int8
557 #undef MPP_BROADCAST_SCALAR_
558 #define MPP_BROADCAST_SCALAR_ mpp_broadcast_int8_scalar
559 #undef MPP_BROADCAST_2D_
560 #define MPP_BROADCAST_2D_ mpp_broadcast_int8_2d
561 #undef MPP_BROADCAST_3D_
562 #define MPP_BROADCAST_3D_ mpp_broadcast_int8_3d
563 #undef MPP_BROADCAST_4D_
564 #define MPP_BROADCAST_4D_ mpp_broadcast_int8_4d
565 #undef MPP_BROADCAST_5D_
566 #define MPP_BROADCAST_5D_ mpp_broadcast_int8_5d
567 #undef MPP_SCATTERV_
568 #define MPP_SCATTERV_ mpp_scatterv_int8
569 #undef MPP_GATHER_
570 #define MPP_GATHER_ mpp_gather_int8
571 #undef MPP_GATHERV_
572 #define MPP_GATHERV_ mpp_gatherv_int8
573 #undef MPP_TYPE_
574 #define MPP_TYPE_ integer(i8_kind)
575 #undef MPP_TYPE_BYTELEN_
576 #define MPP_TYPE_BYTELEN_ 8
577 #undef MPI_TYPE_
578 #define MPI_TYPE_ MPI_INTEGER8
579 #include <mpp_transmit_nocomm.fh>
580 
581 #undef MPP_TRANSMIT_
582 #define MPP_TRANSMIT_ mpp_transmit_int4
583 #undef MPP_TRANSMIT_SCALAR_
584 #define MPP_TRANSMIT_SCALAR_ mpp_transmit_int4_scalar
585 #undef MPP_TRANSMIT_2D_
586 #define MPP_TRANSMIT_2D_ mpp_transmit_int4_2d
587 #undef MPP_TRANSMIT_3D_
588 #define MPP_TRANSMIT_3D_ mpp_transmit_int4_3d
589 #undef MPP_TRANSMIT_4D_
590 #define MPP_TRANSMIT_4D_ mpp_transmit_int4_4d
591 #undef MPP_TRANSMIT_5D_
592 #define MPP_TRANSMIT_5D_ mpp_transmit_int4_5d
593 #undef MPP_RECV_
594 #define MPP_RECV_ mpp_recv_int4
595 #undef MPP_RECV_SCALAR_
596 #define MPP_RECV_SCALAR_ mpp_recv_int4_scalar
597 #undef MPP_RECV_2D_
598 #define MPP_RECV_2D_ mpp_recv_int4_2d
599 #undef MPP_RECV_3D_
600 #define MPP_RECV_3D_ mpp_recv_int4_3d
601 #undef MPP_RECV_4D_
602 #define MPP_RECV_4D_ mpp_recv_int4_4d
603 #undef MPP_RECV_5D_
604 #define MPP_RECV_5D_ mpp_recv_int4_5d
605 #undef MPP_SEND_
606 #define MPP_SEND_ mpp_send_int4
607 #undef MPP_SEND_SCALAR_
608 #define MPP_SEND_SCALAR_ mpp_send_int4_scalar
609 #undef MPP_SEND_2D_
610 #define MPP_SEND_2D_ mpp_send_int4_2d
611 #undef MPP_SEND_3D_
612 #define MPP_SEND_3D_ mpp_send_int4_3d
613 #undef MPP_SEND_4D_
614 #define MPP_SEND_4D_ mpp_send_int4_4d
615 #undef MPP_SEND_5D_
616 #define MPP_SEND_5D_ mpp_send_int4_5d
617 #undef MPP_BROADCAST_
618 #define MPP_BROADCAST_ mpp_broadcast_int4
619 #undef MPP_BROADCAST_SCALAR_
620 #define MPP_BROADCAST_SCALAR_ mpp_broadcast_int4_scalar
621 #undef MPP_BROADCAST_2D_
622 #define MPP_BROADCAST_2D_ mpp_broadcast_int4_2d
623 #undef MPP_BROADCAST_3D_
624 #define MPP_BROADCAST_3D_ mpp_broadcast_int4_3d
625 #undef MPP_BROADCAST_4D_
626 #define MPP_BROADCAST_4D_ mpp_broadcast_int4_4d
627 #undef MPP_BROADCAST_5D_
628 #define MPP_BROADCAST_5D_ mpp_broadcast_int4_5d
629 #undef MPP_SCATTERV_
630 #define MPP_SCATTERV_ mpp_scatterv_int4
631 #undef MPP_GATHER_
632 #define MPP_GATHER_ mpp_gather_int4
633 #undef MPP_GATHERV_
634 #define MPP_GATHERV_ mpp_gatherv_int4
635 #undef MPP_TYPE_
636 #define MPP_TYPE_ integer(i4_kind)
637 #undef MPP_TYPE_BYTELEN_
638 #define MPP_TYPE_BYTELEN_ 4
639 #undef MPI_TYPE_
640 #define MPI_TYPE_ MPI_INTEGER4
641 #include <mpp_transmit_nocomm.fh>
642 
643 #undef MPP_TYPE_INIT_VALUE
644 #define MPP_TYPE_INIT_VALUE .false.
645 #undef MPP_TRANSMIT_
646 #define MPP_TRANSMIT_ mpp_transmit_logical8
647 #undef MPP_TRANSMIT_SCALAR_
648 #define MPP_TRANSMIT_SCALAR_ mpp_transmit_logical8_scalar
649 #undef MPP_TRANSMIT_2D_
650 #define MPP_TRANSMIT_2D_ mpp_transmit_logical8_2d
651 #undef MPP_TRANSMIT_3D_
652 #define MPP_TRANSMIT_3D_ mpp_transmit_logical8_3d
653 #undef MPP_TRANSMIT_4D_
654 #define MPP_TRANSMIT_4D_ mpp_transmit_logical8_4d
655 #undef MPP_TRANSMIT_5D_
656 #define MPP_TRANSMIT_5D_ mpp_transmit_logical8_5d
657 #undef MPP_RECV_
658 #define MPP_RECV_ mpp_recv_logical8
659 #undef MPP_RECV_SCALAR_
660 #define MPP_RECV_SCALAR_ mpp_recv_logical8_scalar
661 #undef MPP_RECV_2D_
662 #define MPP_RECV_2D_ mpp_recv_logical8_2d
663 #undef MPP_RECV_3D_
664 #define MPP_RECV_3D_ mpp_recv_logical8_3d
665 #undef MPP_RECV_4D_
666 #define MPP_RECV_4D_ mpp_recv_logical8_4d
667 #undef MPP_RECV_5D_
668 #define MPP_RECV_5D_ mpp_recv_logical8_5d
669 #undef MPP_SEND_
670 #define MPP_SEND_ mpp_send_logical8
671 #undef MPP_SEND_SCALAR_
672 #define MPP_SEND_SCALAR_ mpp_send_logical8_scalar
673 #undef MPP_SEND_2D_
674 #define MPP_SEND_2D_ mpp_send_logical8_2d
675 #undef MPP_SEND_3D_
676 #define MPP_SEND_3D_ mpp_send_logical8_3d
677 #undef MPP_SEND_4D_
678 #define MPP_SEND_4D_ mpp_send_logical8_4d
679 #undef MPP_SEND_5D_
680 #define MPP_SEND_5D_ mpp_send_logical8_5d
681 #undef MPP_BROADCAST_
682 #define MPP_BROADCAST_ mpp_broadcast_logical8
683 #undef MPP_BROADCAST_SCALAR_
684 #define MPP_BROADCAST_SCALAR_ mpp_broadcast_logical8_scalar
685 #undef MPP_BROADCAST_2D_
686 #define MPP_BROADCAST_2D_ mpp_broadcast_logical8_2d
687 #undef MPP_BROADCAST_3D_
688 #define MPP_BROADCAST_3D_ mpp_broadcast_logical8_3d
689 #undef MPP_BROADCAST_4D_
690 #define MPP_BROADCAST_4D_ mpp_broadcast_logical8_4d
691 #undef MPP_BROADCAST_5D_
692 #define MPP_BROADCAST_5D_ mpp_broadcast_logical8_5d
693 #undef MPP_SCATTERV_
694 #define MPP_SCATTERV_ mpp_scatterv_logical8
695 #undef MPP_GATHER_
696 #define MPP_GATHER_ mpp_gather_logical8
697 #undef MPP_GATHERV_
698 #define MPP_GATHERV_ mpp_gatherv_logical8
699 #undef MPP_TYPE_
700 #define MPP_TYPE_ logical(l8_kind)
701 #undef MPP_TYPE_BYTELEN_
702 #define MPP_TYPE_BYTELEN_ 8
703 #undef MPI_TYPE_
704 #define MPI_TYPE_ MPI_INTEGER8
705 #include <mpp_transmit_nocomm.fh>
706 
707 #undef MPP_TRANSMIT_
708 #define MPP_TRANSMIT_ mpp_transmit_logical4
709 #undef MPP_TRANSMIT_SCALAR_
710 #define MPP_TRANSMIT_SCALAR_ mpp_transmit_logical4_scalar
711 #undef MPP_TRANSMIT_2D_
712 #define MPP_TRANSMIT_2D_ mpp_transmit_logical4_2d
713 #undef MPP_TRANSMIT_3D_
714 #define MPP_TRANSMIT_3D_ mpp_transmit_logical4_3d
715 #undef MPP_TRANSMIT_4D_
716 #define MPP_TRANSMIT_4D_ mpp_transmit_logical4_4d
717 #undef MPP_TRANSMIT_5D_
718 #define MPP_TRANSMIT_5D_ mpp_transmit_logical4_5d
719 #undef MPP_RECV_
720 #define MPP_RECV_ mpp_recv_logical4
721 #undef MPP_RECV_SCALAR_
722 #define MPP_RECV_SCALAR_ mpp_recv_logical4_scalar
723 #undef MPP_RECV_2D_
724 #define MPP_RECV_2D_ mpp_recv_logical4_2d
725 #undef MPP_RECV_3D_
726 #define MPP_RECV_3D_ mpp_recv_logical4_3d
727 #undef MPP_RECV_4D_
728 #define MPP_RECV_4D_ mpp_recv_logical4_4d
729 #undef MPP_RECV_5D_
730 #define MPP_RECV_5D_ mpp_recv_logical4_5d
731 #undef MPP_SEND_
732 #define MPP_SEND_ mpp_send_logical4
733 #undef MPP_SEND_SCALAR_
734 #define MPP_SEND_SCALAR_ mpp_send_logical4_scalar
735 #undef MPP_SEND_2D_
736 #define MPP_SEND_2D_ mpp_send_logical4_2d
737 #undef MPP_SEND_3D_
738 #define MPP_SEND_3D_ mpp_send_logical4_3d
739 #undef MPP_SEND_4D_
740 #define MPP_SEND_4D_ mpp_send_logical4_4d
741 #undef MPP_SEND_5D_
742 #define MPP_SEND_5D_ mpp_send_logical4_5d
743 #undef MPP_BROADCAST_
744 #define MPP_BROADCAST_ mpp_broadcast_logical4
745 #undef MPP_BROADCAST_SCALAR_
746 #define MPP_BROADCAST_SCALAR_ mpp_broadcast_logical4_scalar
747 #undef MPP_BROADCAST_2D_
748 #define MPP_BROADCAST_2D_ mpp_broadcast_logical4_2d
749 #undef MPP_BROADCAST_3D_
750 #define MPP_BROADCAST_3D_ mpp_broadcast_logical4_3d
751 #undef MPP_BROADCAST_4D_
752 #define MPP_BROADCAST_4D_ mpp_broadcast_logical4_4d
753 #undef MPP_BROADCAST_5D_
754 #define MPP_BROADCAST_5D_ mpp_broadcast_logical4_5d
755 #undef MPP_SCATTERV_
756 #define MPP_SCATTERV_ mpp_scatterv_logical4
757 #undef MPP_GATHER_
758 #define MPP_GATHER_ mpp_gather_logical4
759 #undef MPP_GATHERV_
760 #define MPP_GATHERV_ mpp_gatherv_logical4
761 #undef MPP_TYPE_
762 #define MPP_TYPE_ logical(l4_kind)
763 #undef MPP_TYPE_BYTELEN_
764 #define MPP_TYPE_BYTELEN_ 4
765 #undef MPI_TYPE_
766 #define MPI_TYPE_ MPI_INTEGER4
767 #include <mpp_transmit_nocomm.fh>
768 #undef MPP_TYPE_INIT_VALUE
769 
770 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
771 ! !
772 ! GLOBAL REDUCTION ROUTINES: mpp_max, mpp_sum, mpp_min !
773 ! !
774 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
775 #undef MPP_REDUCE_0D_
776 #define MPP_REDUCE_0D_ mpp_max_real8_0d
777 #undef MPP_REDUCE_1D_
778 #define MPP_REDUCE_1D_ mpp_max_real8_1d
779 #undef MPP_TYPE_
780 #define MPP_TYPE_ real(r8_kind)
781 #undef MPP_TYPE_BYTELEN_
782 #define MPP_TYPE_BYTELEN_ 8
783 #undef MPI_TYPE_
784 #define MPI_TYPE_ MPI_REAL8
785 #undef MPI_REDUCE_
786 #define MPI_REDUCE_ MPI_MAX
787 #include <mpp_reduce_nocomm.fh>
788 
789 #undef MPP_REDUCE_0D_
790 #define MPP_REDUCE_0D_ mpp_max_real4_0d
791 #undef MPP_REDUCE_1D_
792 #define MPP_REDUCE_1D_ mpp_max_real4_1d
793 #undef MPP_TYPE_
794 #define MPP_TYPE_ real(r4_kind)
795 #undef MPP_TYPE_BYTELEN_
796 #define MPP_TYPE_BYTELEN_ 4
797 #undef MPI_TYPE_
798 #define MPI_TYPE_ MPI_REAL4
799 #undef MPI_REDUCE_
800 #define MPI_REDUCE_ MPI_MAX
801 #include <mpp_reduce_nocomm.fh>
802 
803 #undef MPP_REDUCE_0D_
804 #define MPP_REDUCE_0D_ mpp_max_int8_0d
805 #undef MPP_REDUCE_1D_
806 #define MPP_REDUCE_1D_ mpp_max_int8_1d
807 #undef MPP_TYPE_
808 #define MPP_TYPE_ integer(i8_kind)
809 #undef MPP_TYPE_BYTELEN_
810 #define MPP_TYPE_BYTELEN_ 8
811 #undef MPI_TYPE_
812 #define MPI_TYPE_ MPI_INTEGER8
813 #undef MPI_REDUCE_
814 #define MPI_REDUCE_ MPI_MAX
815 #include <mpp_reduce_nocomm.fh>
816 
817 #undef MPP_REDUCE_0D_
818 #define MPP_REDUCE_0D_ mpp_max_int4_0d
819 #undef MPP_REDUCE_1D_
820 #define MPP_REDUCE_1D_ mpp_max_int4_1d
821 #undef MPP_TYPE_
822 #define MPP_TYPE_ integer(i4_kind)
823 #undef MPP_TYPE_BYTELEN_
824 #define MPP_TYPE_BYTELEN_ 4
825 #undef MPI_TYPE_
826 #define MPI_TYPE_ MPI_INTEGER4
827 #undef MPI_REDUCE_
828 #define MPI_REDUCE_ MPI_MAX
829 #include <mpp_reduce_nocomm.fh>
830 
831 #undef MPP_REDUCE_0D_
832 #define MPP_REDUCE_0D_ mpp_min_real8_0d
833 #undef MPP_REDUCE_1D_
834 #define MPP_REDUCE_1D_ mpp_min_real8_1d
835 #undef MPP_TYPE_
836 #define MPP_TYPE_ real(r8_kind)
837 #undef MPP_TYPE_BYTELEN_
838 #define MPP_TYPE_BYTELEN_ 8
839 #undef MPI_TYPE_
840 #define MPI_TYPE_ MPI_REAL8
841 #undef MPI_REDUCE_
842 #define MPI_REDUCE_ MPI_MIN
843 #include <mpp_reduce_nocomm.fh>
844 
845 #undef MPP_REDUCE_0D_
846 #define MPP_REDUCE_0D_ mpp_min_real4_0d
847 #undef MPP_REDUCE_1D_
848 #define MPP_REDUCE_1D_ mpp_min_real4_1d
849 #undef MPP_TYPE_
850 #define MPP_TYPE_ real(r4_kind)
851 #undef MPP_TYPE_BYTELEN_
852 #define MPP_TYPE_BYTELEN_ 4
853 #undef MPI_TYPE_
854 #define MPI_TYPE_ MPI_REAL4
855 #undef MPI_REDUCE_
856 #define MPI_REDUCE_ MPI_MIN
857 #include <mpp_reduce_nocomm.fh>
858 
859 #undef MPP_REDUCE_0D_
860 #define MPP_REDUCE_0D_ mpp_min_int8_0d
861 #undef MPP_REDUCE_1D_
862 #define MPP_REDUCE_1D_ mpp_min_int8_1d
863 #undef MPP_TYPE_
864 #define MPP_TYPE_ integer(i8_kind)
865 #undef MPP_TYPE_BYTELEN_
866 #define MPP_TYPE_BYTELEN_ 8
867 #undef MPI_TYPE_
868 #define MPI_TYPE_ MPI_INTEGER8
869 #undef MPI_REDUCE_
870 #define MPI_REDUCE_ MPI_MIN
871 #include <mpp_reduce_nocomm.fh>
872 
873 #undef MPP_REDUCE_0D_
874 #define MPP_REDUCE_0D_ mpp_min_int4_0d
875 #undef MPP_REDUCE_1D_
876 #define MPP_REDUCE_1D_ mpp_min_int4_1d
877 #undef MPP_TYPE_
878 #define MPP_TYPE_ integer(i4_kind)
879 #undef MPP_TYPE_BYTELEN_
880 #define MPP_TYPE_BYTELEN_ 4
881 #undef MPI_TYPE_
882 #define MPI_TYPE_ MPI_INTEGER4
883 #undef MPI_REDUCE_
884 #define MPI_REDUCE_ MPI_MIN
885 #include <mpp_reduce_nocomm.fh>
886 
887 #undef MPP_SUM_
888 #define MPP_SUM_ mpp_sum_real8
889 #undef MPP_SUM_SCALAR_
890 #define MPP_SUM_SCALAR_ mpp_sum_real8_scalar
891 #undef MPP_SUM_2D_
892 #define MPP_SUM_2D_ mpp_sum_real8_2d
893 #undef MPP_SUM_3D_
894 #define MPP_SUM_3D_ mpp_sum_real8_3d
895 #undef MPP_SUM_4D_
896 #define MPP_SUM_4D_ mpp_sum_real8_4d
897 #undef MPP_SUM_5D_
898 #define MPP_SUM_5D_ mpp_sum_real8_5d
899 #undef MPP_TYPE_
900 #define MPP_TYPE_ real(r8_kind)
901 #undef MPI_TYPE_
902 #define MPI_TYPE_ MPI_REAL8
903 #undef MPP_TYPE_BYTELEN_
904 #define MPP_TYPE_BYTELEN_ 8
905 #include <mpp_sum_nocomm.fh>
906 
907 #ifdef OVERLOAD_C8
908 #undef MPP_SUM_
909 #define MPP_SUM_ mpp_sum_cmplx8
910 #undef MPP_SUM_SCALAR_
911 #define MPP_SUM_SCALAR_ mpp_sum_cmplx8_scalar
912 #undef MPP_SUM_2D_
913 #define MPP_SUM_2D_ mpp_sum_cmplx8_2d
914 #undef MPP_SUM_3D_
915 #define MPP_SUM_3D_ mpp_sum_cmplx8_3d
916 #undef MPP_SUM_4D_
917 #define MPP_SUM_4D_ mpp_sum_cmplx8_4d
918 #undef MPP_SUM_5D_
919 #define MPP_SUM_5D_ mpp_sum_cmplx8_5d
920 #undef MPP_TYPE_
921 #define MPP_TYPE_ complex(c8_kind)
922 #undef MPI_TYPE_
923 #define MPI_TYPE_ MPI_DOUBLE_COMPLEX
924 #undef MPP_TYPE_BYTELEN_
925 #define MPP_TYPE_BYTELEN_ 16
926 #include <mpp_sum_nocomm.fh>
927 #endif
928 
929 #undef MPP_SUM_
930 #define MPP_SUM_ mpp_sum_real4
931 #undef MPP_SUM_SCALAR_
932 #define MPP_SUM_SCALAR_ mpp_sum_real4_scalar
933 #undef MPP_SUM_2D_
934 #define MPP_SUM_2D_ mpp_sum_real4_2d
935 #undef MPP_SUM_3D_
936 #define MPP_SUM_3D_ mpp_sum_real4_3d
937 #undef MPP_SUM_4D_
938 #define MPP_SUM_4D_ mpp_sum_real4_4d
939 #undef MPP_SUM_5D_
940 #define MPP_SUM_5D_ mpp_sum_real4_5d
941 #undef MPP_TYPE_
942 #define MPP_TYPE_ real(r4_kind)
943 #undef MPI_TYPE_
944 #define MPI_TYPE_ MPI_REAL4
945 #undef MPP_TYPE_BYTELEN_
946 #define MPP_TYPE_BYTELEN_ 4
947 #include <mpp_sum_nocomm.fh>
948 
949 #ifdef OVERLOAD_C4
950 #undef MPP_SUM_
951 #define MPP_SUM_ mpp_sum_cmplx4
952 #undef MPP_SUM_SCALAR_
953 #define MPP_SUM_SCALAR_ mpp_sum_cmplx4_scalar
954 #undef MPP_SUM_2D_
955 #define MPP_SUM_2D_ mpp_sum_cmplx4_2d
956 #undef MPP_SUM_3D_
957 #define MPP_SUM_3D_ mpp_sum_cmplx4_3d
958 #undef MPP_SUM_4D_
959 #define MPP_SUM_4D_ mpp_sum_cmplx4_4d
960 #undef MPP_SUM_5D_
961 #define MPP_SUM_5D_ mpp_sum_cmplx4_5d
962 #undef MPP_TYPE_
963 #define MPP_TYPE_ complex(c4_kind)
964 #undef MPI_TYPE_
965 #define MPI_TYPE_ MPI_COMPLEX
966 #undef MPP_TYPE_BYTELEN_
967 #define MPP_TYPE_BYTELEN_ 8
968 #include <mpp_sum_nocomm.fh>
969 #endif
970 
971 #undef MPP_SUM_
972 #define MPP_SUM_ mpp_sum_int8
973 #undef MPP_SUM_SCALAR_
974 #define MPP_SUM_SCALAR_ mpp_sum_int8_scalar
975 #undef MPP_SUM_2D_
976 #define MPP_SUM_2D_ mpp_sum_int8_2d
977 #undef MPP_SUM_3D_
978 #define MPP_SUM_3D_ mpp_sum_int8_3d
979 #undef MPP_SUM_4D_
980 #define MPP_SUM_4D_ mpp_sum_int8_4d
981 #undef MPP_SUM_5D_
982 #define MPP_SUM_5D_ mpp_sum_int8_5d
983 #undef MPP_TYPE_
984 #define MPP_TYPE_ integer(i8_kind)
985 #undef MPI_TYPE_
986 #define MPI_TYPE_ MPI_INTEGER8
987 #undef MPP_TYPE_BYTELEN_
988 #define MPP_TYPE_BYTELEN_ 8
989 #include <mpp_sum_nocomm.fh>
990 
991 #undef MPP_SUM_
992 #define MPP_SUM_ mpp_sum_int4
993 #undef MPP_SUM_SCALAR_
994 #define MPP_SUM_SCALAR_ mpp_sum_int4_scalar
995 #undef MPP_SUM_2D_
996 #define MPP_SUM_2D_ mpp_sum_int4_2d
997 #undef MPP_SUM_3D_
998 #define MPP_SUM_3D_ mpp_sum_int4_3d
999 #undef MPP_SUM_4D_
1000 #define MPP_SUM_4D_ mpp_sum_int4_4d
1001 #undef MPP_SUM_5D_
1002 #define MPP_SUM_5D_ mpp_sum_int4_5d
1003 #undef MPP_TYPE_
1004 #define MPP_TYPE_ integer(i4_kind)
1005 #undef MPI_TYPE_
1006 #define MPI_TYPE_ MPI_INTEGER4
1007 #undef MPP_TYPE_BYTELEN_
1008 #define MPP_TYPE_BYTELEN_ 4
1009 #include <mpp_sum_nocomm.fh>
1010 !--------------------------------
1011 #undef MPP_SUM_AD_
1012 #define MPP_SUM_AD_ mpp_sum_real8_ad
1013 #undef MPP_SUM_SCALAR_AD_
1014 #define MPP_SUM_SCALAR_AD_ mpp_sum_real8_scalar_ad
1015 #undef MPP_SUM_2D_AD_
1016 #define MPP_SUM_2D_AD_ mpp_sum_real8_2d_ad
1017 #undef MPP_SUM_3D_AD_
1018 #define MPP_SUM_3D_AD_ mpp_sum_real8_3d_ad
1019 #undef MPP_SUM_4D_AD_
1020 #define MPP_SUM_4D_AD_ mpp_sum_real8_4d_ad
1021 #undef MPP_SUM_5D_AD_
1022 #define MPP_SUM_5D_AD_ mpp_sum_real8_5d_ad
1023 #undef MPP_TYPE_
1024 #define MPP_TYPE_ real(r8_kind)
1025 #undef MPI_TYPE_
1026 #define MPI_TYPE_ MPI_REAL8
1027 #undef MPP_TYPE_BYTELEN_
1028 #define MPP_TYPE_BYTELEN_ 8
1029 #include <mpp_sum_nocomm_ad.fh>
1030 
1031 #ifdef OVERLOAD_C8
1032 #undef MPP_SUM_AD_
1033 #define MPP_SUM_AD_ mpp_sum_cmplx8_ad
1034 #undef MPP_SUM_SCALAR_AD_
1035 #define MPP_SUM_SCALAR_AD_ mpp_sum_cmplx8_scalar_ad
1036 #undef MPP_SUM_2D_AD_
1037 #define MPP_SUM_2D_AD_ mpp_sum_cmplx8_2d_ad
1038 #undef MPP_SUM_3D_AD_
1039 #define MPP_SUM_3D_AD_ mpp_sum_cmplx8_3d_ad
1040 #undef MPP_SUM_4D_AD_
1041 #define MPP_SUM_4D_AD_ mpp_sum_cmplx8_4d_ad
1042 #undef MPP_SUM_5D_AD_
1043 #define MPP_SUM_5D_AD_ mpp_sum_cmplx8_5d_ad
1044 #undef MPP_TYPE_
1045 #define MPP_TYPE_ complex(c8_kind)
1046 #undef MPI_TYPE_
1047 #define MPI_TYPE_ MPI_DOUBLE_COMPLEX
1048 #undef MPP_TYPE_BYTELEN_
1049 #define MPP_TYPE_BYTELEN_ 16
1050 #include <mpp_sum_nocomm_ad.fh>
1051 #endif
1052 
1053 #undef MPP_SUM_AD_
1054 #define MPP_SUM_AD_ mpp_sum_real4_ad
1055 #undef MPP_SUM_SCALAR_AD_
1056 #define MPP_SUM_SCALAR_AD_ mpp_sum_real4_scalar_ad
1057 #undef MPP_SUM_2D_AD_
1058 #define MPP_SUM_2D_AD_ mpp_sum_real4_2d_ad
1059 #undef MPP_SUM_3D_AD_
1060 #define MPP_SUM_3D_AD_ mpp_sum_real4_3d_ad
1061 #undef MPP_SUM_4D_AD_
1062 #define MPP_SUM_4D_AD_ mpp_sum_real4_4d_ad
1063 #undef MPP_SUM_5D_AD_
1064 #define MPP_SUM_5D_AD_ mpp_sum_real4_5d_ad
1065 #undef MPP_TYPE_
1066 #define MPP_TYPE_ real(r4_kind)
1067 #undef MPI_TYPE_
1068 #define MPI_TYPE_ MPI_REAL4
1069 #undef MPP_TYPE_BYTELEN_
1070 #define MPP_TYPE_BYTELEN_ 4
1071 #include <mpp_sum_nocomm_ad.fh>
1072 
1073 #ifdef OVERLOAD_C4
1074 #undef MPP_SUM_AD_
1075 #define MPP_SUM_AD_ mpp_sum_cmplx4_ad
1076 #undef MPP_SUM_SCALAR_AD_
1077 #define MPP_SUM_SCALAR_AD_ mpp_sum_cmplx4_scalar_ad
1078 #undef MPP_SUM_2D_AD_
1079 #define MPP_SUM_2D_AD_ mpp_sum_cmplx4_2d_ad
1080 #undef MPP_SUM_3D_AD_
1081 #define MPP_SUM_3D_AD_ mpp_sum_cmplx4_3d_ad
1082 #undef MPP_SUM_4D_AD_
1083 #define MPP_SUM_4D_AD_ mpp_sum_cmplx4_4d_ad
1084 #undef MPP_SUM_5D_AD_
1085 #define MPP_SUM_5D_AD_ mpp_sum_cmplx4_5d_ad
1086 #undef MPP_TYPE_
1087 #define MPP_TYPE_ complex(c4_kind)
1088 #undef MPI_TYPE_
1089 #define MPI_TYPE_ MPI_COMPLEX
1090 #undef MPP_TYPE_BYTELEN_
1091 #define MPP_TYPE_BYTELEN_ 8
1092 #include <mpp_sum_nocomm_ad.fh>
1093 #endif
1094 
1095 #undef MPP_SUM_AD_
1096 #define MPP_SUM_AD_ mpp_sum_int8_ad
1097 #undef MPP_SUM_SCALAR_AD_
1098 #define MPP_SUM_SCALAR_AD_ mpp_sum_int8_scalar_ad
1099 #undef MPP_SUM_2D_AD_
1100 #define MPP_SUM_2D_AD_ mpp_sum_int8_2d_ad
1101 #undef MPP_SUM_3D_AD_
1102 #define MPP_SUM_3D_AD_ mpp_sum_int8_3d_ad
1103 #undef MPP_SUM_4D_AD_
1104 #define MPP_SUM_4D_AD_ mpp_sum_int8_4d_ad
1105 #undef MPP_SUM_5D_AD_
1106 #define MPP_SUM_5D_AD_ mpp_sum_int8_5d_ad
1107 #undef MPP_TYPE_
1108 #define MPP_TYPE_ integer(i8_kind)
1109 #undef MPI_TYPE_
1110 #define MPI_TYPE_ MPI_INTEGER8
1111 #undef MPP_TYPE_BYTELEN_
1112 #define MPP_TYPE_BYTELEN_ 8
1113 #include <mpp_sum_nocomm_ad.fh>
1114 
1115 #undef MPP_SUM_AD_
1116 #define MPP_SUM_AD_ mpp_sum_int4_ad
1117 #undef MPP_SUM_SCALAR_AD_
1118 #define MPP_SUM_SCALAR_AD_ mpp_sum_int4_scalar_ad
1119 #undef MPP_SUM_2D_AD_
1120 #define MPP_SUM_2D_AD_ mpp_sum_int4_2d_ad
1121 #undef MPP_SUM_3D_AD_
1122 #define MPP_SUM_3D_AD_ mpp_sum_int4_3d_ad
1123 #undef MPP_SUM_4D_AD_
1124 #define MPP_SUM_4D_AD_ mpp_sum_int4_4d_ad
1125 #undef MPP_SUM_5D_AD_
1126 #define MPP_SUM_5D_AD_ mpp_sum_int4_5d_ad
1127 #undef MPP_TYPE_
1128 #define MPP_TYPE_ integer(i4_kind)
1129 #undef MPI_TYPE_
1130 #define MPI_TYPE_ MPI_INTEGER4
1131 #undef MPP_TYPE_BYTELEN_
1132 #define MPP_TYPE_BYTELEN_ 4
1133 #include <mpp_sum_nocomm_ad.fh>
1134 
1135 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1136 ! !
1137 ! SCATTER AND GATHER ROUTINES: mpp_alltoall !
1138 ! !
1139 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1140 
1141 #undef MPP_ALLTOALL_
1142 #undef MPP_ALLTOALLV_
1143 #undef MPP_ALLTOALLW_
1144 #undef MPP_TYPE_
1145 #undef MPP_TYPE_BYTELEN_
1146 #undef MPI_TYPE_
1147 #define MPP_ALLTOALL_ mpp_alltoall_int4
1148 #define MPP_ALLTOALLV_ mpp_alltoall_int4_v
1149 #define MPP_ALLTOALLW_ mpp_alltoall_int4_w
1150 #define MPP_TYPE_ integer(i4_kind)
1151 #define MPP_TYPE_BYTELEN_ 4
1152 #define MPI_TYPE_ MPI_INTEGER4
1153 #include <mpp_alltoall_nocomm.fh>
1154 
1155 #undef MPP_ALLTOALL_
1156 #undef MPP_ALLTOALLV_
1157 #undef MPP_ALLTOALLW_
1158 #undef MPP_TYPE_
1159 #undef MPP_TYPE_BYTELEN_
1160 #undef MPI_TYPE_
1161 #define MPP_ALLTOALL_ mpp_alltoall_int8
1162 #define MPP_ALLTOALLV_ mpp_alltoall_int8_v
1163 #define MPP_ALLTOALLW_ mpp_alltoall_int8_w
1164 #define MPP_TYPE_ integer(i8_kind)
1165 #define MPP_TYPE_BYTELEN_ 8
1166 #define MPI_TYPE_ MPI_INTEGER8
1167 #include <mpp_alltoall_nocomm.fh>
1168 
1169 #undef MPP_ALLTOALL_
1170 #undef MPP_ALLTOALLV_
1171 #undef MPP_ALLTOALLW_
1172 #undef MPP_TYPE_
1173 #undef MPP_TYPE_BYTELEN_
1174 #undef MPI_TYPE_
1175 #define MPP_ALLTOALL_ mpp_alltoall_real4
1176 #define MPP_ALLTOALLV_ mpp_alltoall_real4_v
1177 #define MPP_ALLTOALLW_ mpp_alltoall_real4_w
1178 #define MPP_TYPE_ real(r4_kind)
1179 #define MPP_TYPE_BYTELEN_ 4
1180 #define MPI_TYPE_ MPI_REAL4
1181 #include <mpp_alltoall_nocomm.fh>
1182 
1183 #undef MPP_ALLTOALL_
1184 #undef MPP_ALLTOALLV_
1185 #undef MPP_ALLTOALLW_
1186 #undef MPP_TYPE_
1187 #undef MPP_TYPE_BYTELEN_
1188 #undef MPI_TYPE_
1189 #define MPP_ALLTOALL_ mpp_alltoall_real8
1190 #define MPP_ALLTOALLV_ mpp_alltoall_real8_v
1191 #define MPP_ALLTOALLW_ mpp_alltoall_real8_w
1192 #define MPP_TYPE_ real(r8_kind)
1193 #define MPP_TYPE_BYTELEN_ 8
1194 #define MPI_TYPE_ MPI_REAL8
1195 #include <mpp_alltoall_nocomm.fh>
1196 
1197 #undef MPP_ALLTOALL_
1198 #undef MPP_ALLTOALLV_
1199 #undef MPP_ALLTOALLW_
1200 #undef MPP_TYPE_
1201 #undef MPP_TYPE_BYTELEN_
1202 #undef MPI_TYPE_
1203 #define MPP_ALLTOALL_ mpp_alltoall_logical4
1204 #define MPP_ALLTOALLV_ mpp_alltoall_logical4_v
1205 #define MPP_ALLTOALLW_ mpp_alltoall_logical4_w
1206 #define MPP_TYPE_ logical(l4_kind)
1207 #define MPP_TYPE_BYTELEN_ 4
1208 #define MPI_TYPE_ MPI_INTEGER4
1209 #include <mpp_alltoall_nocomm.fh>
1210 
1211 #undef MPP_ALLTOALL_
1212 #undef MPP_ALLTOALLV_
1213 #undef MPP_ALLTOALLW_
1214 #undef MPP_TYPE_
1215 #undef MPP_TYPE_BYTELEN_
1216 #undef MPI_TYPE_
1217 #define MPP_ALLTOALL_ mpp_alltoall_logical8
1218 #define MPP_ALLTOALLV_ mpp_alltoall_logical8_v
1219 #define MPP_ALLTOALLW_ mpp_alltoall_logical8_w
1220 #define MPP_TYPE_ logical(l8_kind)
1221 #define MPP_TYPE_BYTELEN_ 8
1222 #define MPI_TYPE_ MPI_INTEGER8
1223 #include <mpp_alltoall_nocomm.fh>
1224 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1225 ! !
1226 ! DATA TRANSFER TYPES: mpp_type_create, mpp_type_free !
1227 ! !
1228 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1229 
1230 #define MPP_TYPE_CREATE_ mpp_type_create_int4
1231 #define MPP_TYPE_ integer(i4_kind)
1232 #define MPI_TYPE_ MPI_INTEGER4
1233 #include <mpp_type_nocomm.fh>
1234 
1235 #define MPP_TYPE_CREATE_ mpp_type_create_int8
1236 #define MPP_TYPE_ integer(i8_kind)
1237 #define MPI_TYPE_ MPI_INTEGER8
1238 #include <mpp_type_nocomm.fh>
1239 
1240 #define MPP_TYPE_CREATE_ mpp_type_create_real4
1241 #define MPP_TYPE_ real(r4_kind)
1242 #define MPI_TYPE_ MPI_REAL4
1243 #include <mpp_type_nocomm.fh>
1244 
1245 #define MPP_TYPE_CREATE_ mpp_type_create_real8
1246 #define MPP_TYPE_ real(r8_kind)
1247 #define MPI_TYPE_ MPI_REAL8
1248 #include <mpp_type_nocomm.fh>
1249 
1250 #define MPP_TYPE_CREATE_ mpp_type_create_cmplx4
1251 #define MPP_TYPE_ complex(c4_kind)
1252 #define MPI_TYPE_ MPI_COMPLEX8
1253 #include <mpp_type_nocomm.fh>
1254 
1255 #define MPP_TYPE_CREATE_ mpp_type_create_cmplx8
1256 #define MPP_TYPE_ complex(c8_kind)
1257 #define MPI_TYPE_ MPI_COMPLEX16
1258 #include <mpp_type_nocomm.fh>
1259 
1260 #define MPP_TYPE_CREATE_ mpp_type_create_logical4
1261 #define MPP_TYPE_ logical(l4_kind)
1262 #define MPI_TYPE_ MPI_INTEGER4
1263 #include <mpp_type_nocomm.fh>
1264 
1265 #define MPP_TYPE_CREATE_ mpp_type_create_logical8
1266 #define MPP_TYPE_ logical(l8_kind)
1267 #define MPI_TYPE_ MPI_INTEGER8
1268 #include <mpp_type_nocomm.fh>
1269 
1270 ! Clear preprocessor flags
1271 #undef MPI_TYPE_
1272 #undef MPP_TYPE_
1273 #undef MPP_TYPE_CREATE_
1274 
1275 subroutine mpp_type_free(dtype)
1276  type(mpp_type), pointer, intent(inout) :: dtype
1277 
1278  call mpp_error(note, 'MPP_TYPE_FREE: ' &
1279  //'This function should not be used in serial mode.')
1280 
1281  ! For consistency with MPI, we deallocate the pointer
1282  deallocate(dtype)
1283 
1284 end subroutine mpp_type_free
integer function stdout()
This function returns the current standard fortran unit numbers for output.
Definition: mpp_util.inc:42
subroutine mpp_set_current_pelist(pelist, no_sync)
Set context pelist.
Definition: mpp_util.inc:498
subroutine mpp_init(flags, localcomm, test_level, alt_input_nml_path)
Initialize the mpp_mod module. Must be called before any usage.
subroutine read_input_nml(pelist_name_in, alt_input_nml_path)
Reads an existing input nml file into a character array and broadcasts it to the non-root mpi-tasks....
Definition: mpp_util.inc:1227
subroutine mpp_type_free(dtype)
Deallocates memory for mpp_type objects @TODO This should probably not take a pointer,...
subroutine mpp_exit()
Finalizes process termination. To be called at the end of a run. Certain mpi implementations(openmpi)...
integer function stdlog()
This function returns the current standard fortran unit numbers for log messages. Log messages,...
Definition: mpp_util.inc:58
integer function mpp_npes()
Returns processor count for current pelist.
Definition: mpp_util.inc:420
subroutine mpp_set_stack_size(n)
Set the mpp_stack variable to be at least n LONG words long.
subroutine mpp_sync(pelist, do_self)
Synchronize PEs in list.
integer function mpp_clock_id(name, flags, grain)
Return an ID for a new or existing clock.
Definition: mpp_util.inc:713
subroutine mpp_broadcast_char(char_data, length, from_pe, pelist)
Broadcasts a character string from the given pe to it's pelist.