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