FMS  2024.03
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_TYPE_
415 #define MPP_TYPE_ real(r8_kind)
416 #undef MPP_TYPE_BYTELEN_
417 #define MPP_TYPE_BYTELEN_ 8
418 #undef MPI_TYPE_
419 #define MPI_TYPE_ MPI_REAL8
420 #include <mpp_transmit_mpi.fh>
421 
422 #ifdef OVERLOAD_C8
423 #undef MPP_TRANSMIT_
424 #define MPP_TRANSMIT_ mpp_transmit_cmplx8
425 #undef MPP_TRANSMIT_SCALAR_
426 #define MPP_TRANSMIT_SCALAR_ mpp_transmit_cmplx8_scalar
427 #undef MPP_TRANSMIT_2D_
428 #define MPP_TRANSMIT_2D_ mpp_transmit_cmplx8_2d
429 #undef MPP_TRANSMIT_3D_
430 #define MPP_TRANSMIT_3D_ mpp_transmit_cmplx8_3d
431 #undef MPP_TRANSMIT_4D_
432 #define MPP_TRANSMIT_4D_ mpp_transmit_cmplx8_4d
433 #undef MPP_TRANSMIT_5D_
434 #define MPP_TRANSMIT_5D_ mpp_transmit_cmplx8_5d
435 #undef MPP_RECV_
436 #define MPP_RECV_ mpp_recv_cmplx8
437 #undef MPP_RECV_SCALAR_
438 #define MPP_RECV_SCALAR_ mpp_recv_cmplx8_scalar
439 #undef MPP_RECV_2D_
440 #define MPP_RECV_2D_ mpp_recv_cmplx8_2d
441 #undef MPP_RECV_3D_
442 #define MPP_RECV_3D_ mpp_recv_cmplx8_3d
443 #undef MPP_RECV_4D_
444 #define MPP_RECV_4D_ mpp_recv_cmplx8_4d
445 #undef MPP_RECV_5D_
446 #define MPP_RECV_5D_ mpp_recv_cmplx8_5d
447 #undef MPP_SEND_
448 #define MPP_SEND_ mpp_send_cmplx8
449 #undef MPP_SEND_SCALAR_
450 #define MPP_SEND_SCALAR_ mpp_send_cmplx8_scalar
451 #undef MPP_SEND_2D_
452 #define MPP_SEND_2D_ mpp_send_cmplx8_2d
453 #undef MPP_SEND_3D_
454 #define MPP_SEND_3D_ mpp_send_cmplx8_3d
455 #undef MPP_SEND_4D_
456 #define MPP_SEND_4D_ mpp_send_cmplx8_4d
457 #undef MPP_SEND_5D_
458 #define MPP_SEND_5D_ mpp_send_cmplx8_5d
459 #undef MPP_BROADCAST_
460 #define MPP_BROADCAST_ mpp_broadcast_cmplx8
461 #undef MPP_BROADCAST_SCALAR_
462 #define MPP_BROADCAST_SCALAR_ mpp_broadcast_cmplx8_scalar
463 #undef MPP_BROADCAST_2D_
464 #define MPP_BROADCAST_2D_ mpp_broadcast_cmplx8_2d
465 #undef MPP_BROADCAST_3D_
466 #define MPP_BROADCAST_3D_ mpp_broadcast_cmplx8_3d
467 #undef MPP_BROADCAST_4D_
468 #define MPP_BROADCAST_4D_ mpp_broadcast_cmplx8_4d
469 #undef MPP_BROADCAST_5D_
470 #define MPP_BROADCAST_5D_ mpp_broadcast_cmplx8_5d
471 #undef MPP_TYPE_
472 #define MPP_TYPE_ complex(c8_kind)
473 #undef MPP_TYPE_BYTELEN_
474 #define MPP_TYPE_BYTELEN_ 16
475 #undef MPI_TYPE_
476 #define MPI_TYPE_ MPI_DOUBLE_COMPLEX
477 #include <mpp_transmit_mpi.fh>
478 #endif
479 
480 #undef MPP_TRANSMIT_
481 #define MPP_TRANSMIT_ mpp_transmit_real4
482 #undef MPP_TRANSMIT_SCALAR_
483 #define MPP_TRANSMIT_SCALAR_ mpp_transmit_real4_scalar
484 #undef MPP_TRANSMIT_2D_
485 #define MPP_TRANSMIT_2D_ mpp_transmit_real4_2d
486 #undef MPP_TRANSMIT_3D_
487 #define MPP_TRANSMIT_3D_ mpp_transmit_real4_3d
488 #undef MPP_TRANSMIT_4D_
489 #define MPP_TRANSMIT_4D_ mpp_transmit_real4_4d
490 #undef MPP_TRANSMIT_5D_
491 #define MPP_TRANSMIT_5D_ mpp_transmit_real4_5d
492 #undef MPP_RECV_
493 #define MPP_RECV_ mpp_recv_real4
494 #undef MPP_RECV_SCALAR_
495 #define MPP_RECV_SCALAR_ mpp_recv_real4_scalar
496 #undef MPP_RECV_2D_
497 #define MPP_RECV_2D_ mpp_recv_real4_2d
498 #undef MPP_RECV_3D_
499 #define MPP_RECV_3D_ mpp_recv_real4_3d
500 #undef MPP_RECV_4D_
501 #define MPP_RECV_4D_ mpp_recv_real4_4d
502 #undef MPP_RECV_5D_
503 #define MPP_RECV_5D_ mpp_recv_real4_5d
504 #undef MPP_SEND_
505 #define MPP_SEND_ mpp_send_real4
506 #undef MPP_SEND_SCALAR_
507 #define MPP_SEND_SCALAR_ mpp_send_real4_scalar
508 #undef MPP_SEND_2D_
509 #define MPP_SEND_2D_ mpp_send_real4_2d
510 #undef MPP_SEND_3D_
511 #define MPP_SEND_3D_ mpp_send_real4_3d
512 #undef MPP_SEND_4D_
513 #define MPP_SEND_4D_ mpp_send_real4_4d
514 #undef MPP_SEND_5D_
515 #define MPP_SEND_5D_ mpp_send_real4_5d
516 #undef MPP_BROADCAST_
517 #define MPP_BROADCAST_ mpp_broadcast_real4
518 #undef MPP_BROADCAST_SCALAR_
519 #define MPP_BROADCAST_SCALAR_ mpp_broadcast_real4_scalar
520 #undef MPP_BROADCAST_2D_
521 #define MPP_BROADCAST_2D_ mpp_broadcast_real4_2d
522 #undef MPP_BROADCAST_3D_
523 #define MPP_BROADCAST_3D_ mpp_broadcast_real4_3d
524 #undef MPP_BROADCAST_4D_
525 #define MPP_BROADCAST_4D_ mpp_broadcast_real4_4d
526 #undef MPP_BROADCAST_5D_
527 #define MPP_BROADCAST_5D_ mpp_broadcast_real4_5d
528 #undef MPP_TYPE_
529 #define MPP_TYPE_ real(r4_kind)
530 #undef MPP_TYPE_BYTELEN_
531 #define MPP_TYPE_BYTELEN_ 4
532 #undef MPI_TYPE_
533 #define MPI_TYPE_ MPI_REAL4
534 #include <mpp_transmit_mpi.fh>
535 
536 #ifdef OVERLOAD_C4
537 #undef MPP_TRANSMIT_
538 #define MPP_TRANSMIT_ mpp_transmit_cmplx4
539 #undef MPP_TRANSMIT_SCALAR_
540 #define MPP_TRANSMIT_SCALAR_ mpp_transmit_cmplx4_scalar
541 #undef MPP_TRANSMIT_2D_
542 #define MPP_TRANSMIT_2D_ mpp_transmit_cmplx4_2d
543 #undef MPP_TRANSMIT_3D_
544 #define MPP_TRANSMIT_3D_ mpp_transmit_cmplx4_3d
545 #undef MPP_TRANSMIT_4D_
546 #define MPP_TRANSMIT_4D_ mpp_transmit_cmplx4_4d
547 #undef MPP_TRANSMIT_5D_
548 #define MPP_TRANSMIT_5D_ mpp_transmit_cmplx4_5d
549 #undef MPP_RECV_
550 #define MPP_RECV_ mpp_recv_cmplx4
551 #undef MPP_RECV_SCALAR_
552 #define MPP_RECV_SCALAR_ mpp_recv_cmplx4_scalar
553 #undef MPP_RECV_2D_
554 #define MPP_RECV_2D_ mpp_recv_cmplx4_2d
555 #undef MPP_RECV_3D_
556 #define MPP_RECV_3D_ mpp_recv_cmplx4_3d
557 #undef MPP_RECV_4D_
558 #define MPP_RECV_4D_ mpp_recv_cmplx4_4d
559 #undef MPP_RECV_5D_
560 #define MPP_RECV_5D_ mpp_recv_cmplx4_5d
561 #undef MPP_SEND_
562 #define MPP_SEND_ mpp_send_cmplx4
563 #undef MPP_SEND_SCALAR_
564 #define MPP_SEND_SCALAR_ mpp_send_cmplx4_scalar
565 #undef MPP_SEND_2D_
566 #define MPP_SEND_2D_ mpp_send_cmplx4_2d
567 #undef MPP_SEND_3D_
568 #define MPP_SEND_3D_ mpp_send_cmplx4_3d
569 #undef MPP_SEND_4D_
570 #define MPP_SEND_4D_ mpp_send_cmplx4_4d
571 #undef MPP_SEND_5D_
572 #define MPP_SEND_5D_ mpp_send_cmplx4_5d
573 #undef MPP_BROADCAST_
574 #define MPP_BROADCAST_ mpp_broadcast_cmplx4
575 #undef MPP_BROADCAST_SCALAR_
576 #define MPP_BROADCAST_SCALAR_ mpp_broadcast_cmplx4_scalar
577 #undef MPP_BROADCAST_2D_
578 #define MPP_BROADCAST_2D_ mpp_broadcast_cmplx4_2d
579 #undef MPP_BROADCAST_3D_
580 #define MPP_BROADCAST_3D_ mpp_broadcast_cmplx4_3d
581 #undef MPP_BROADCAST_4D_
582 #define MPP_BROADCAST_4D_ mpp_broadcast_cmplx4_4d
583 #undef MPP_BROADCAST_5D_
584 #define MPP_BROADCAST_5D_ mpp_broadcast_cmplx4_5d
585 #undef MPP_TYPE_
586 #define MPP_TYPE_ complex(c4_kind)
587 #undef MPP_TYPE_BYTELEN_
588 #define MPP_TYPE_BYTELEN_ 8
589 #undef MPI_TYPE_
590 #define MPI_TYPE_ MPI_COMPLEX
591 #include <mpp_transmit_mpi.fh>
592 #endif
593 
594 #undef MPP_TYPE_INIT_VALUE
595 #define MPP_TYPE_INIT_VALUE 0
596 #undef MPP_TRANSMIT_
597 #define MPP_TRANSMIT_ mpp_transmit_int8
598 #undef MPP_TRANSMIT_SCALAR_
599 #define MPP_TRANSMIT_SCALAR_ mpp_transmit_int8_scalar
600 #undef MPP_TRANSMIT_2D_
601 #define MPP_TRANSMIT_2D_ mpp_transmit_int8_2d
602 #undef MPP_TRANSMIT_3D_
603 #define MPP_TRANSMIT_3D_ mpp_transmit_int8_3d
604 #undef MPP_TRANSMIT_4D_
605 #define MPP_TRANSMIT_4D_ mpp_transmit_int8_4d
606 #undef MPP_TRANSMIT_5D_
607 #define MPP_TRANSMIT_5D_ mpp_transmit_int8_5d
608 #undef MPP_RECV_
609 #define MPP_RECV_ mpp_recv_int8
610 #undef MPP_RECV_SCALAR_
611 #define MPP_RECV_SCALAR_ mpp_recv_int8_scalar
612 #undef MPP_RECV_2D_
613 #define MPP_RECV_2D_ mpp_recv_int8_2d
614 #undef MPP_RECV_3D_
615 #define MPP_RECV_3D_ mpp_recv_int8_3d
616 #undef MPP_RECV_4D_
617 #define MPP_RECV_4D_ mpp_recv_int8_4d
618 #undef MPP_RECV_5D_
619 #define MPP_RECV_5D_ mpp_recv_int8_5d
620 #undef MPP_SEND_
621 #define MPP_SEND_ mpp_send_int8
622 #undef MPP_SEND_SCALAR_
623 #define MPP_SEND_SCALAR_ mpp_send_int8_scalar
624 #undef MPP_SEND_2D_
625 #define MPP_SEND_2D_ mpp_send_int8_2d
626 #undef MPP_SEND_3D_
627 #define MPP_SEND_3D_ mpp_send_int8_3d
628 #undef MPP_SEND_4D_
629 #define MPP_SEND_4D_ mpp_send_int8_4d
630 #undef MPP_SEND_5D_
631 #define MPP_SEND_5D_ mpp_send_int8_5d
632 #undef MPP_BROADCAST_
633 #define MPP_BROADCAST_ mpp_broadcast_int8
634 #undef MPP_BROADCAST_SCALAR_
635 #define MPP_BROADCAST_SCALAR_ mpp_broadcast_int8_scalar
636 #undef MPP_BROADCAST_2D_
637 #define MPP_BROADCAST_2D_ mpp_broadcast_int8_2d
638 #undef MPP_BROADCAST_3D_
639 #define MPP_BROADCAST_3D_ mpp_broadcast_int8_3d
640 #undef MPP_BROADCAST_4D_
641 #define MPP_BROADCAST_4D_ mpp_broadcast_int8_4d
642 #undef MPP_BROADCAST_5D_
643 #define MPP_BROADCAST_5D_ mpp_broadcast_int8_5d
644 #undef MPP_TYPE_
645 #define MPP_TYPE_ integer(i8_kind)
646 #undef MPP_TYPE_BYTELEN_
647 #define MPP_TYPE_BYTELEN_ 8
648 #undef MPI_TYPE_
649 #define MPI_TYPE_ MPI_INTEGER8
650 #include <mpp_transmit_mpi.fh>
651 
652 #undef MPP_TRANSMIT_
653 #define MPP_TRANSMIT_ mpp_transmit_int4
654 #undef MPP_TRANSMIT_SCALAR_
655 #define MPP_TRANSMIT_SCALAR_ mpp_transmit_int4_scalar
656 #undef MPP_TRANSMIT_2D_
657 #define MPP_TRANSMIT_2D_ mpp_transmit_int4_2d
658 #undef MPP_TRANSMIT_3D_
659 #define MPP_TRANSMIT_3D_ mpp_transmit_int4_3d
660 #undef MPP_TRANSMIT_4D_
661 #define MPP_TRANSMIT_4D_ mpp_transmit_int4_4d
662 #undef MPP_TRANSMIT_5D_
663 #define MPP_TRANSMIT_5D_ mpp_transmit_int4_5d
664 #undef MPP_RECV_
665 #define MPP_RECV_ mpp_recv_int4
666 #undef MPP_RECV_SCALAR_
667 #define MPP_RECV_SCALAR_ mpp_recv_int4_scalar
668 #undef MPP_RECV_2D_
669 #define MPP_RECV_2D_ mpp_recv_int4_2d
670 #undef MPP_RECV_3D_
671 #define MPP_RECV_3D_ mpp_recv_int4_3d
672 #undef MPP_RECV_4D_
673 #define MPP_RECV_4D_ mpp_recv_int4_4d
674 #undef MPP_RECV_5D_
675 #define MPP_RECV_5D_ mpp_recv_int4_5d
676 #undef MPP_SEND_
677 #define MPP_SEND_ mpp_send_int4
678 #undef MPP_SEND_SCALAR_
679 #define MPP_SEND_SCALAR_ mpp_send_int4_scalar
680 #undef MPP_SEND_2D_
681 #define MPP_SEND_2D_ mpp_send_int4_2d
682 #undef MPP_SEND_3D_
683 #define MPP_SEND_3D_ mpp_send_int4_3d
684 #undef MPP_SEND_4D_
685 #define MPP_SEND_4D_ mpp_send_int4_4d
686 #undef MPP_SEND_5D_
687 #define MPP_SEND_5D_ mpp_send_int4_5d
688 #undef MPP_BROADCAST_
689 #define MPP_BROADCAST_ mpp_broadcast_int4
690 #undef MPP_BROADCAST_SCALAR_
691 #define MPP_BROADCAST_SCALAR_ mpp_broadcast_int4_scalar
692 #undef MPP_BROADCAST_2D_
693 #define MPP_BROADCAST_2D_ mpp_broadcast_int4_2d
694 #undef MPP_BROADCAST_3D_
695 #define MPP_BROADCAST_3D_ mpp_broadcast_int4_3d
696 #undef MPP_BROADCAST_4D_
697 #define MPP_BROADCAST_4D_ mpp_broadcast_int4_4d
698 #undef MPP_BROADCAST_5D_
699 #define MPP_BROADCAST_5D_ mpp_broadcast_int4_5d
700 #undef MPP_TYPE_
701 #define MPP_TYPE_ integer(i4_kind)
702 #undef MPP_TYPE_BYTELEN_
703 #define MPP_TYPE_BYTELEN_ 4
704 #undef MPI_TYPE_
705 #define MPI_TYPE_ MPI_INTEGER4
706 #include <mpp_transmit_mpi.fh>
707 
708 #undef MPP_TYPE_INIT_VALUE
709 #define MPP_TYPE_INIT_VALUE .false.
710 #undef MPP_TRANSMIT_
711 #define MPP_TRANSMIT_ mpp_transmit_logical8
712 #undef MPP_TRANSMIT_SCALAR_
713 #define MPP_TRANSMIT_SCALAR_ mpp_transmit_logical8_scalar
714 #undef MPP_TRANSMIT_2D_
715 #define MPP_TRANSMIT_2D_ mpp_transmit_logical8_2d
716 #undef MPP_TRANSMIT_3D_
717 #define MPP_TRANSMIT_3D_ mpp_transmit_logical8_3d
718 #undef MPP_TRANSMIT_4D_
719 #define MPP_TRANSMIT_4D_ mpp_transmit_logical8_4d
720 #undef MPP_TRANSMIT_5D_
721 #define MPP_TRANSMIT_5D_ mpp_transmit_logical8_5d
722 #undef MPP_RECV_
723 #define MPP_RECV_ mpp_recv_logical8
724 #undef MPP_RECV_SCALAR_
725 #define MPP_RECV_SCALAR_ mpp_recv_logical8_scalar
726 #undef MPP_RECV_2D_
727 #define MPP_RECV_2D_ mpp_recv_logical8_2d
728 #undef MPP_RECV_3D_
729 #define MPP_RECV_3D_ mpp_recv_logical8_3d
730 #undef MPP_RECV_4D_
731 #define MPP_RECV_4D_ mpp_recv_logical8_4d
732 #undef MPP_RECV_5D_
733 #define MPP_RECV_5D_ mpp_recv_logical8_5d
734 #undef MPP_SEND_
735 #define MPP_SEND_ mpp_send_logical8
736 #undef MPP_SEND_SCALAR_
737 #define MPP_SEND_SCALAR_ mpp_send_logical8_scalar
738 #undef MPP_SEND_2D_
739 #define MPP_SEND_2D_ mpp_send_logical8_2d
740 #undef MPP_SEND_3D_
741 #define MPP_SEND_3D_ mpp_send_logical8_3d
742 #undef MPP_SEND_4D_
743 #define MPP_SEND_4D_ mpp_send_logical8_4d
744 #undef MPP_SEND_5D_
745 #define MPP_SEND_5D_ mpp_send_logical8_5d
746 #undef MPP_BROADCAST_
747 #define MPP_BROADCAST_ mpp_broadcast_logical8
748 #undef MPP_BROADCAST_SCALAR_
749 #define MPP_BROADCAST_SCALAR_ mpp_broadcast_logical8_scalar
750 #undef MPP_BROADCAST_2D_
751 #define MPP_BROADCAST_2D_ mpp_broadcast_logical8_2d
752 #undef MPP_BROADCAST_3D_
753 #define MPP_BROADCAST_3D_ mpp_broadcast_logical8_3d
754 #undef MPP_BROADCAST_4D_
755 #define MPP_BROADCAST_4D_ mpp_broadcast_logical8_4d
756 #undef MPP_BROADCAST_5D_
757 #define MPP_BROADCAST_5D_ mpp_broadcast_logical8_5d
758 #undef MPP_TYPE_
759 #define MPP_TYPE_ logical(l8_kind)
760 #undef MPP_TYPE_BYTELEN_
761 #define MPP_TYPE_BYTELEN_ 8
762 #undef MPI_TYPE_
763 #define MPI_TYPE_ MPI_INTEGER8
764 #include <mpp_transmit_mpi.fh>
765 
766 #undef MPP_TRANSMIT_
767 #define MPP_TRANSMIT_ mpp_transmit_logical4
768 #undef MPP_TRANSMIT_SCALAR_
769 #define MPP_TRANSMIT_SCALAR_ mpp_transmit_logical4_scalar
770 #undef MPP_TRANSMIT_2D_
771 #define MPP_TRANSMIT_2D_ mpp_transmit_logical4_2d
772 #undef MPP_TRANSMIT_3D_
773 #define MPP_TRANSMIT_3D_ mpp_transmit_logical4_3d
774 #undef MPP_TRANSMIT_4D_
775 #define MPP_TRANSMIT_4D_ mpp_transmit_logical4_4d
776 #undef MPP_TRANSMIT_5D_
777 #define MPP_TRANSMIT_5D_ mpp_transmit_logical4_5d
778 #undef MPP_RECV_
779 #define MPP_RECV_ mpp_recv_logical4
780 #undef MPP_RECV_SCALAR_
781 #define MPP_RECV_SCALAR_ mpp_recv_logical4_scalar
782 #undef MPP_RECV_2D_
783 #define MPP_RECV_2D_ mpp_recv_logical4_2d
784 #undef MPP_RECV_3D_
785 #define MPP_RECV_3D_ mpp_recv_logical4_3d
786 #undef MPP_RECV_4D_
787 #define MPP_RECV_4D_ mpp_recv_logical4_4d
788 #undef MPP_RECV_5D_
789 #define MPP_RECV_5D_ mpp_recv_logical4_5d
790 #undef MPP_SEND_
791 #define MPP_SEND_ mpp_send_logical4
792 #undef MPP_SEND_SCALAR_
793 #define MPP_SEND_SCALAR_ mpp_send_logical4_scalar
794 #undef MPP_SEND_2D_
795 #define MPP_SEND_2D_ mpp_send_logical4_2d
796 #undef MPP_SEND_3D_
797 #define MPP_SEND_3D_ mpp_send_logical4_3d
798 #undef MPP_SEND_4D_
799 #define MPP_SEND_4D_ mpp_send_logical4_4d
800 #undef MPP_SEND_5D_
801 #define MPP_SEND_5D_ mpp_send_logical4_5d
802 #undef MPP_BROADCAST_
803 #define MPP_BROADCAST_ mpp_broadcast_logical4
804 #undef MPP_BROADCAST_SCALAR_
805 #define MPP_BROADCAST_SCALAR_ mpp_broadcast_logical4_scalar
806 #undef MPP_BROADCAST_2D_
807 #define MPP_BROADCAST_2D_ mpp_broadcast_logical4_2d
808 #undef MPP_BROADCAST_3D_
809 #define MPP_BROADCAST_3D_ mpp_broadcast_logical4_3d
810 #undef MPP_BROADCAST_4D_
811 #define MPP_BROADCAST_4D_ mpp_broadcast_logical4_4d
812 #undef MPP_BROADCAST_5D_
813 #define MPP_BROADCAST_5D_ mpp_broadcast_logical4_5d
814 #undef MPP_TYPE_
815 #define MPP_TYPE_ logical(l4_kind)
816 #undef MPP_TYPE_BYTELEN_
817 #define MPP_TYPE_BYTELEN_ 4
818 #undef MPI_TYPE_
819 #define MPI_TYPE_ MPI_INTEGER4
820 #include <mpp_transmit_mpi.fh>
821 #undef MPP_TYPE_INIT_VALUE
822 
823 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
824 ! !
825 ! GLOBAL REDUCTION ROUTINES: mpp_max, mpp_sum, mpp_min !
826 ! !
827 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
828 #undef MPP_REDUCE_0D_
829 #define MPP_REDUCE_0D_ mpp_max_real8_0d
830 #undef MPP_REDUCE_1D_
831 #define MPP_REDUCE_1D_ mpp_max_real8_1d
832 #undef MPP_TYPE_
833 #define MPP_TYPE_ real(r8_kind)
834 #undef MPP_TYPE_BYTELEN_
835 #define MPP_TYPE_BYTELEN_ 8
836 #undef MPI_TYPE_
837 #define MPI_TYPE_ MPI_REAL8
838 #undef MPI_REDUCE_
839 #define MPI_REDUCE_ MPI_MAX
840 #include <mpp_reduce_mpi.fh>
841 
842 #undef MPP_REDUCE_0D_
843 #define MPP_REDUCE_0D_ mpp_max_real4_0d
844 #undef MPP_REDUCE_1D_
845 #define MPP_REDUCE_1D_ mpp_max_real4_1d
846 #undef MPP_TYPE_
847 #define MPP_TYPE_ real(r4_kind)
848 #undef MPP_TYPE_BYTELEN_
849 #define MPP_TYPE_BYTELEN_ 4
850 #undef MPI_TYPE_
851 #define MPI_TYPE_ MPI_REAL4
852 #undef MPI_REDUCE_
853 #define MPI_REDUCE_ MPI_MAX
854 #include <mpp_reduce_mpi.fh>
855 
856 #undef MPP_REDUCE_0D_
857 #define MPP_REDUCE_0D_ mpp_max_int8_0d
858 #undef MPP_REDUCE_1D_
859 #define MPP_REDUCE_1D_ mpp_max_int8_1d
860 #undef MPP_TYPE_
861 #define MPP_TYPE_ integer(i8_kind)
862 #undef MPP_TYPE_BYTELEN_
863 #define MPP_TYPE_BYTELEN_ 8
864 #undef MPI_TYPE_
865 #define MPI_TYPE_ MPI_INTEGER8
866 #undef MPI_REDUCE_
867 #define MPI_REDUCE_ MPI_MAX
868 #include <mpp_reduce_mpi.fh>
869 
870 #undef MPP_REDUCE_0D_
871 #define MPP_REDUCE_0D_ mpp_max_int4_0d
872 #undef MPP_REDUCE_1D_
873 #define MPP_REDUCE_1D_ mpp_max_int4_1d
874 #undef MPP_TYPE_
875 #define MPP_TYPE_ integer(i4_kind)
876 #undef MPP_TYPE_BYTELEN_
877 #define MPP_TYPE_BYTELEN_ 4
878 #undef MPI_TYPE_
879 #define MPI_TYPE_ MPI_INTEGER4
880 #undef MPI_REDUCE_
881 #define MPI_REDUCE_ MPI_MAX
882 #include <mpp_reduce_mpi.fh>
883 
884 #undef MPP_REDUCE_0D_
885 #define MPP_REDUCE_0D_ mpp_min_real8_0d
886 #undef MPP_REDUCE_1D_
887 #define MPP_REDUCE_1D_ mpp_min_real8_1d
888 #undef MPP_TYPE_
889 #define MPP_TYPE_ real(r8_kind)
890 #undef MPP_TYPE_BYTELEN_
891 #define MPP_TYPE_BYTELEN_ 8
892 #undef MPI_TYPE_
893 #define MPI_TYPE_ MPI_REAL8
894 #undef MPI_REDUCE_
895 #define MPI_REDUCE_ MPI_MIN
896 #include <mpp_reduce_mpi.fh>
897 
898 #undef MPP_REDUCE_0D_
899 #define MPP_REDUCE_0D_ mpp_min_real4_0d
900 #undef MPP_REDUCE_1D_
901 #define MPP_REDUCE_1D_ mpp_min_real4_1d
902 #undef MPP_TYPE_
903 #define MPP_TYPE_ real(r4_kind)
904 #undef MPP_TYPE_BYTELEN_
905 #define MPP_TYPE_BYTELEN_ 4
906 #undef MPI_TYPE_
907 #define MPI_TYPE_ MPI_REAL4
908 #undef MPI_REDUCE_
909 #define MPI_REDUCE_ MPI_MIN
910 #include <mpp_reduce_mpi.fh>
911 
912 #undef MPP_REDUCE_0D_
913 #define MPP_REDUCE_0D_ mpp_min_int8_0d
914 #undef MPP_REDUCE_1D_
915 #define MPP_REDUCE_1D_ mpp_min_int8_1d
916 #undef MPP_TYPE_
917 #define MPP_TYPE_ integer(i8_kind)
918 #undef MPP_TYPE_BYTELEN_
919 #define MPP_TYPE_BYTELEN_ 8
920 #undef MPI_TYPE_
921 #define MPI_TYPE_ MPI_INTEGER8
922 #undef MPI_REDUCE_
923 #define MPI_REDUCE_ MPI_MIN
924 #include <mpp_reduce_mpi.fh>
925 
926 #undef MPP_REDUCE_0D_
927 #define MPP_REDUCE_0D_ mpp_min_int4_0d
928 #undef MPP_REDUCE_1D_
929 #define MPP_REDUCE_1D_ mpp_min_int4_1d
930 #undef MPP_TYPE_
931 #define MPP_TYPE_ integer(i4_kind)
932 #undef MPP_TYPE_BYTELEN_
933 #define MPP_TYPE_BYTELEN_ 4
934 #undef MPI_TYPE_
935 #define MPI_TYPE_ MPI_INTEGER4
936 #undef MPI_REDUCE_
937 #define MPI_REDUCE_ MPI_MIN
938 #include <mpp_reduce_mpi.fh>
939 
940 #undef MPP_SUM_
941 #define MPP_SUM_ mpp_sum_real8
942 #undef MPP_SUM_SCALAR_
943 #define MPP_SUM_SCALAR_ mpp_sum_real8_scalar
944 #undef MPP_SUM_2D_
945 #define MPP_SUM_2D_ mpp_sum_real8_2d
946 #undef MPP_SUM_3D_
947 #define MPP_SUM_3D_ mpp_sum_real8_3d
948 #undef MPP_SUM_4D_
949 #define MPP_SUM_4D_ mpp_sum_real8_4d
950 #undef MPP_SUM_5D_
951 #define MPP_SUM_5D_ mpp_sum_real8_5d
952 #undef MPP_TYPE_
953 #define MPP_TYPE_ real(r8_kind)
954 #undef MPI_TYPE_
955 #define MPI_TYPE_ MPI_REAL8
956 #undef MPP_TYPE_BYTELEN_
957 #define MPP_TYPE_BYTELEN_ 8
958 #include <mpp_sum_mpi.fh>
959 
960 #ifdef OVERLOAD_C8
961 #undef MPP_SUM_
962 #define MPP_SUM_ mpp_sum_cmplx8
963 #undef MPP_SUM_SCALAR_
964 #define MPP_SUM_SCALAR_ mpp_sum_cmplx8_scalar
965 #undef MPP_SUM_2D_
966 #define MPP_SUM_2D_ mpp_sum_cmplx8_2d
967 #undef MPP_SUM_3D_
968 #define MPP_SUM_3D_ mpp_sum_cmplx8_3d
969 #undef MPP_SUM_4D_
970 #define MPP_SUM_4D_ mpp_sum_cmplx8_4d
971 #undef MPP_SUM_5D_
972 #define MPP_SUM_5D_ mpp_sum_cmplx8_5d
973 #undef MPP_TYPE_
974 #define MPP_TYPE_ complex(c8_kind)
975 #undef MPI_TYPE_
976 #define MPI_TYPE_ MPI_DOUBLE_COMPLEX
977 #undef MPP_TYPE_BYTELEN_
978 #define MPP_TYPE_BYTELEN_ 16
979 #include <mpp_sum_mpi.fh>
980 #endif
981 
982 #undef MPP_SUM_
983 #define MPP_SUM_ mpp_sum_real4
984 #undef MPP_SUM_SCALAR_
985 #define MPP_SUM_SCALAR_ mpp_sum_real4_scalar
986 #undef MPP_SUM_2D_
987 #define MPP_SUM_2D_ mpp_sum_real4_2d
988 #undef MPP_SUM_3D_
989 #define MPP_SUM_3D_ mpp_sum_real4_3d
990 #undef MPP_SUM_4D_
991 #define MPP_SUM_4D_ mpp_sum_real4_4d
992 #undef MPP_SUM_5D_
993 #define MPP_SUM_5D_ mpp_sum_real4_5d
994 #undef MPP_TYPE_
995 #define MPP_TYPE_ real(r4_kind)
996 #undef MPI_TYPE_
997 #define MPI_TYPE_ MPI_REAL4
998 #undef MPP_TYPE_BYTELEN_
999 #define MPP_TYPE_BYTELEN_ 4
1000 #include <mpp_sum_mpi.fh>
1001 
1002 #ifdef OVERLOAD_C4
1003 #undef MPP_SUM_
1004 #define MPP_SUM_ mpp_sum_cmplx4
1005 #undef MPP_SUM_SCALAR_
1006 #define MPP_SUM_SCALAR_ mpp_sum_cmplx4_scalar
1007 #undef MPP_SUM_2D_
1008 #define MPP_SUM_2D_ mpp_sum_cmplx4_2d
1009 #undef MPP_SUM_3D_
1010 #define MPP_SUM_3D_ mpp_sum_cmplx4_3d
1011 #undef MPP_SUM_4D_
1012 #define MPP_SUM_4D_ mpp_sum_cmplx4_4d
1013 #undef MPP_SUM_5D_
1014 #define MPP_SUM_5D_ mpp_sum_cmplx4_5d
1015 #undef MPP_TYPE_
1016 #define MPP_TYPE_ complex(c4_kind)
1017 #undef MPI_TYPE_
1018 #define MPI_TYPE_ MPI_COMPLEX
1019 #undef MPP_TYPE_BYTELEN_
1020 #define MPP_TYPE_BYTELEN_ 8
1021 #include <mpp_sum_mpi.fh>
1022 #endif
1023 
1024 #undef MPP_SUM_
1025 #define MPP_SUM_ mpp_sum_int8
1026 #undef MPP_SUM_SCALAR_
1027 #define MPP_SUM_SCALAR_ mpp_sum_int8_scalar
1028 #undef MPP_SUM_2D_
1029 #define MPP_SUM_2D_ mpp_sum_int8_2d
1030 #undef MPP_SUM_3D_
1031 #define MPP_SUM_3D_ mpp_sum_int8_3d
1032 #undef MPP_SUM_4D_
1033 #define MPP_SUM_4D_ mpp_sum_int8_4d
1034 #undef MPP_SUM_5D_
1035 #define MPP_SUM_5D_ mpp_sum_int8_5d
1036 #undef MPP_TYPE_
1037 #define MPP_TYPE_ integer(i8_kind)
1038 #undef MPI_TYPE_
1039 #define MPI_TYPE_ MPI_INTEGER8
1040 #undef MPP_TYPE_BYTELEN_
1041 #define MPP_TYPE_BYTELEN_ 8
1042 #include <mpp_sum_mpi.fh>
1043 
1044 #undef MPP_SUM_
1045 #define MPP_SUM_ mpp_sum_int4
1046 #undef MPP_SUM_SCALAR_
1047 #define MPP_SUM_SCALAR_ mpp_sum_int4_scalar
1048 #undef MPP_SUM_2D_
1049 #define MPP_SUM_2D_ mpp_sum_int4_2d
1050 #undef MPP_SUM_3D_
1051 #define MPP_SUM_3D_ mpp_sum_int4_3d
1052 #undef MPP_SUM_4D_
1053 #define MPP_SUM_4D_ mpp_sum_int4_4d
1054 #undef MPP_SUM_5D_
1055 #define MPP_SUM_5D_ mpp_sum_int4_5d
1056 #undef MPP_TYPE_
1057 #define MPP_TYPE_ integer(i4_kind)
1058 #undef MPI_TYPE_
1059 #define MPI_TYPE_ MPI_INTEGER4
1060 #undef MPP_TYPE_BYTELEN_
1061 #define MPP_TYPE_BYTELEN_ 4
1062 #include <mpp_sum_mpi.fh>
1063 !--------------------------------
1064 #undef MPP_SUM_AD_
1065 #define MPP_SUM_AD_ mpp_sum_real8_ad
1066 #undef MPP_SUM_SCALAR_AD_
1067 #define MPP_SUM_SCALAR_AD_ mpp_sum_real8_scalar_ad
1068 #undef MPP_SUM_2D_AD_
1069 #define MPP_SUM_2D_AD_ mpp_sum_real8_2d_ad
1070 #undef MPP_SUM_3D_AD_
1071 #define MPP_SUM_3D_AD_ mpp_sum_real8_3d_ad
1072 #undef MPP_SUM_4D_AD_
1073 #define MPP_SUM_4D_AD_ mpp_sum_real8_4d_ad
1074 #undef MPP_SUM_5D_AD_
1075 #define MPP_SUM_5D_AD_ mpp_sum_real8_5d_ad
1076 #undef MPP_TYPE_
1077 #define MPP_TYPE_ real(r8_kind)
1078 #undef MPI_TYPE_
1079 #define MPI_TYPE_ MPI_REAL8
1080 #undef MPP_TYPE_BYTELEN_
1081 #define MPP_TYPE_BYTELEN_ 8
1082 #include <mpp_sum_mpi_ad.fh>
1083 
1084 #ifdef OVERLOAD_C8
1085 #undef MPP_SUM_AD_
1086 #define MPP_SUM_AD_ mpp_sum_cmplx8_ad
1087 #undef MPP_SUM_SCALAR_AD_
1088 #define MPP_SUM_SCALAR_AD_ mpp_sum_cmplx8_scalar_ad
1089 #undef MPP_SUM_2D_AD_
1090 #define MPP_SUM_2D_AD_ mpp_sum_cmplx8_2d_ad
1091 #undef MPP_SUM_3D_AD_
1092 #define MPP_SUM_3D_AD_ mpp_sum_cmplx8_3d_ad
1093 #undef MPP_SUM_4D_AD_
1094 #define MPP_SUM_4D_AD_ mpp_sum_cmplx8_4d_ad
1095 #undef MPP_SUM_5D_AD_
1096 #define MPP_SUM_5D_AD_ mpp_sum_cmplx8_5d_ad
1097 #undef MPP_TYPE_
1098 #define MPP_TYPE_ complex(c8_kind)
1099 #undef MPI_TYPE_
1100 #define MPI_TYPE_ MPI_DOUBLE_COMPLEX
1101 #undef MPP_TYPE_BYTELEN_
1102 #define MPP_TYPE_BYTELEN_ 16
1103 #include <mpp_sum_mpi_ad.fh>
1104 #endif
1105 
1106 #undef MPP_SUM_AD_
1107 #define MPP_SUM_AD_ mpp_sum_real4_ad
1108 #undef MPP_SUM_SCALAR_AD_
1109 #define MPP_SUM_SCALAR_AD_ mpp_sum_real4_scalar_ad
1110 #undef MPP_SUM_2D_AD_
1111 #define MPP_SUM_2D_AD_ mpp_sum_real4_2d_ad
1112 #undef MPP_SUM_3D_AD_
1113 #define MPP_SUM_3D_AD_ mpp_sum_real4_3d_ad
1114 #undef MPP_SUM_4D_AD_
1115 #define MPP_SUM_4D_AD_ mpp_sum_real4_4d_ad
1116 #undef MPP_SUM_5D_AD_
1117 #define MPP_SUM_5D_AD_ mpp_sum_real4_5d_ad
1118 #undef MPP_TYPE_
1119 #define MPP_TYPE_ real(r4_kind)
1120 #undef MPI_TYPE_
1121 #define MPI_TYPE_ MPI_REAL4
1122 #undef MPP_TYPE_BYTELEN_
1123 #define MPP_TYPE_BYTELEN_ 4
1124 #include <mpp_sum_mpi_ad.fh>
1125 
1126 #ifdef OVERLOAD_C4
1127 #undef MPP_SUM_AD_
1128 #define MPP_SUM_AD_ mpp_sum_cmplx4_ad
1129 #undef MPP_SUM_SCALAR_AD_
1130 #define MPP_SUM_SCALAR_AD_ mpp_sum_cmplx4_scalar_ad
1131 #undef MPP_SUM_2D_AD_
1132 #define MPP_SUM_2D_AD_ mpp_sum_cmplx4_2d_ad
1133 #undef MPP_SUM_3D_AD_
1134 #define MPP_SUM_3D_AD_ mpp_sum_cmplx4_3d_ad
1135 #undef MPP_SUM_4D_AD_
1136 #define MPP_SUM_4D_AD_ mpp_sum_cmplx4_4d_ad
1137 #undef MPP_SUM_5D_AD_
1138 #define MPP_SUM_5D_AD_ mpp_sum_cmplx4_5d_ad
1139 #undef MPP_TYPE_
1140 #define MPP_TYPE_ complex(c4_kind)
1141 #undef MPI_TYPE_
1142 #define MPI_TYPE_ MPI_COMPLEX
1143 #undef MPP_TYPE_BYTELEN_
1144 #define MPP_TYPE_BYTELEN_ 8
1145 #include <mpp_sum_mpi_ad.fh>
1146 #endif
1147 
1148 #undef MPP_SUM_AD_
1149 #define MPP_SUM_AD_ mpp_sum_int8_ad
1150 #undef MPP_SUM_SCALAR_AD_
1151 #define MPP_SUM_SCALAR_AD_ mpp_sum_int8_scalar_ad
1152 #undef MPP_SUM_2D_AD_
1153 #define MPP_SUM_2D_AD_ mpp_sum_int8_2d_ad
1154 #undef MPP_SUM_3D_AD_
1155 #define MPP_SUM_3D_AD_ mpp_sum_int8_3d_ad
1156 #undef MPP_SUM_4D_AD_
1157 #define MPP_SUM_4D_AD_ mpp_sum_int8_4d_ad
1158 #undef MPP_SUM_5D_AD_
1159 #define MPP_SUM_5D_AD_ mpp_sum_int8_5d_ad
1160 #undef MPP_TYPE_
1161 #define MPP_TYPE_ integer(i8_kind)
1162 #undef MPI_TYPE_
1163 #define MPI_TYPE_ MPI_INTEGER8
1164 #undef MPP_TYPE_BYTELEN_
1165 #define MPP_TYPE_BYTELEN_ 8
1166 #include <mpp_sum_mpi_ad.fh>
1167 
1168 #undef MPP_SUM_AD_
1169 #define MPP_SUM_AD_ mpp_sum_int4_ad
1170 #undef MPP_SUM_SCALAR_AD_
1171 #define MPP_SUM_SCALAR_AD_ mpp_sum_int4_scalar_ad
1172 #undef MPP_SUM_2D_AD_
1173 #define MPP_SUM_2D_AD_ mpp_sum_int4_2d_ad
1174 #undef MPP_SUM_3D_AD_
1175 #define MPP_SUM_3D_AD_ mpp_sum_int4_3d_ad
1176 #undef MPP_SUM_4D_AD_
1177 #define MPP_SUM_4D_AD_ mpp_sum_int4_4d_ad
1178 #undef MPP_SUM_5D_AD_
1179 #define MPP_SUM_5D_AD_ mpp_sum_int4_5d_ad
1180 #undef MPP_TYPE_
1181 #define MPP_TYPE_ integer(i4_kind)
1182 #undef MPI_TYPE_
1183 #define MPI_TYPE_ MPI_INTEGER4
1184 #undef MPP_TYPE_BYTELEN_
1185 #define MPP_TYPE_BYTELEN_ 4
1186 #include <mpp_sum_mpi_ad.fh>
1187 
1188 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1189 ! !
1190 ! SCATTER AND GATHER ROUTINES: mpp_alltoall !
1191 ! !
1192 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1193 
1194 #undef MPP_ALLTOALL_
1195 #undef MPP_ALLTOALLV_
1196 #undef MPP_ALLTOALLW_
1197 #undef MPP_TYPE_
1198 #undef MPP_TYPE_BYTELEN_
1199 #undef MPI_TYPE_
1200 #define MPP_ALLTOALL_ mpp_alltoall_int4
1201 #define MPP_ALLTOALLV_ mpp_alltoall_int4_v
1202 #define MPP_ALLTOALLW_ mpp_alltoall_int4_w
1203 #define MPP_TYPE_ integer(i4_kind)
1204 #define MPP_TYPE_BYTELEN_ 4
1205 #define MPI_TYPE_ MPI_INTEGER4
1206 #include <mpp_alltoall_mpi.fh>
1207 
1208 #undef MPP_ALLTOALL_
1209 #undef MPP_ALLTOALLV_
1210 #undef MPP_ALLTOALLW_
1211 #undef MPP_TYPE_
1212 #undef MPP_TYPE_BYTELEN_
1213 #undef MPI_TYPE_
1214 #define MPP_ALLTOALL_ mpp_alltoall_int8
1215 #define MPP_ALLTOALLV_ mpp_alltoall_int8_v
1216 #define MPP_ALLTOALLW_ mpp_alltoall_int8_w
1217 #define MPP_TYPE_ integer(i8_kind)
1218 #define MPP_TYPE_BYTELEN_ 8
1219 #define MPI_TYPE_ MPI_INTEGER8
1220 #include <mpp_alltoall_mpi.fh>
1221 
1222 #undef MPP_ALLTOALL_
1223 #undef MPP_ALLTOALLV_
1224 #undef MPP_ALLTOALLW_
1225 #undef MPP_TYPE_
1226 #undef MPP_TYPE_BYTELEN_
1227 #undef MPI_TYPE_
1228 #define MPP_ALLTOALL_ mpp_alltoall_real4
1229 #define MPP_ALLTOALLV_ mpp_alltoall_real4_v
1230 #define MPP_ALLTOALLW_ mpp_alltoall_real4_w
1231 #define MPP_TYPE_ real(r4_kind)
1232 #define MPP_TYPE_BYTELEN_ 4
1233 #define MPI_TYPE_ MPI_REAL4
1234 #include <mpp_alltoall_mpi.fh>
1235 
1236 #undef MPP_ALLTOALL_
1237 #undef MPP_ALLTOALLV_
1238 #undef MPP_ALLTOALLW_
1239 #undef MPP_TYPE_
1240 #undef MPP_TYPE_BYTELEN_
1241 #undef MPI_TYPE_
1242 #define MPP_ALLTOALL_ mpp_alltoall_real8
1243 #define MPP_ALLTOALLV_ mpp_alltoall_real8_v
1244 #define MPP_ALLTOALLW_ mpp_alltoall_real8_w
1245 #define MPP_TYPE_ real(r8_kind)
1246 #define MPP_TYPE_BYTELEN_ 8
1247 #define MPI_TYPE_ MPI_REAL8
1248 #include <mpp_alltoall_mpi.fh>
1249 
1250 #ifdef OVERLOAD_C4
1251 #undef MPP_ALLTOALL_
1252 #undef MPP_ALLTOALLV_
1253 #undef MPP_ALLTOALLW_
1254 #undef MPP_TYPE_
1255 #undef MPP_TYPE_BYTELEN_
1256 #undef MPI_TYPE_
1257 #define MPP_ALLTOALL_ mpp_alltoall_cmplx4
1258 #define MPP_ALLTOALLV_ mpp_alltoall_cmplx4_v
1259 #define MPP_ALLTOALLW_ mpp_alltoall_cmplx4_w
1260 #define MPP_TYPE_ complex(c4_kind)
1261 #define MPP_TYPE_BYTELEN_ 8
1262 #define MPI_TYPE_ MPI_COMPLEX8
1263 #include <mpp_alltoall_mpi.fh>
1264 #endif
1265 
1266 #ifdef OVERLOAD_C8
1267 #undef MPP_ALLTOALL_
1268 #undef MPP_ALLTOALLV_
1269 #undef MPP_ALLTOALLW_
1270 #undef MPP_TYPE_
1271 #undef MPP_TYPE_BYTELEN_
1272 #undef MPI_TYPE_
1273 #define MPP_ALLTOALL_ mpp_alltoall_cmplx8
1274 #define MPP_ALLTOALLV_ mpp_alltoall_cmplx8_v
1275 #define MPP_ALLTOALLW_ mpp_alltoall_cmplx8_w
1276 #define MPP_TYPE_ complex(c8_kind)
1277 #define MPP_TYPE_BYTELEN_ 16
1278 #define MPI_TYPE_ MPI_COMPLEX16
1279 #include <mpp_alltoall_mpi.fh>
1280 #endif
1281 
1282 #undef MPP_ALLTOALL_
1283 #undef MPP_ALLTOALLV_
1284 #undef MPP_ALLTOALLW_
1285 #undef MPP_TYPE_
1286 #undef MPP_TYPE_BYTELEN_
1287 #undef MPI_TYPE_
1288 #define MPP_ALLTOALL_ mpp_alltoall_logical4
1289 #define MPP_ALLTOALLV_ mpp_alltoall_logical4_v
1290 #define MPP_ALLTOALLW_ mpp_alltoall_logical4_w
1291 #define MPP_TYPE_ logical(l4_kind)
1292 #define MPP_TYPE_BYTELEN_ 4
1293 #define MPI_TYPE_ MPI_INTEGER4
1294 #include <mpp_alltoall_mpi.fh>
1295 
1296 #undef MPP_ALLTOALL_
1297 #undef MPP_ALLTOALLV_
1298 #undef MPP_ALLTOALLW_
1299 #undef MPP_TYPE_
1300 #undef MPP_TYPE_BYTELEN_
1301 #undef MPI_TYPE_
1302 #define MPP_ALLTOALL_ mpp_alltoall_logical8
1303 #define MPP_ALLTOALLV_ mpp_alltoall_logical8_v
1304 #define MPP_ALLTOALLW_ mpp_alltoall_logical8_w
1305 #define MPP_TYPE_ logical(l8_kind)
1306 #define MPP_TYPE_BYTELEN_ 8
1307 #define MPI_TYPE_ MPI_INTEGER8
1308 #include <mpp_alltoall_mpi.fh>
1309 
1310 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1311 ! !
1312 ! DATA TRANSFER TYPES: mpp_type_create, mpp_type_free !
1313 ! !
1314 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1315 
1316 #undef MPP_TYPE_CREATE_
1317 #undef MPP_TYPE_
1318 #undef MPI_TYPE_
1319 #define MPP_TYPE_CREATE_ mpp_type_create_int4
1320 #define MPP_TYPE_ integer(i4_kind)
1321 #define MPI_TYPE_ MPI_INTEGER4
1322 #include <mpp_type_mpi.fh>
1323 
1324 #undef MPP_TYPE_CREATE_
1325 #undef MPP_TYPE_
1326 #undef MPI_TYPE_
1327 #define MPP_TYPE_CREATE_ mpp_type_create_int8
1328 #define MPP_TYPE_ integer(i8_kind)
1329 #define MPI_TYPE_ MPI_INTEGER8
1330 #include <mpp_type_mpi.fh>
1331 
1332 #undef MPP_TYPE_CREATE_
1333 #undef MPP_TYPE_
1334 #undef MPI_TYPE_
1335 #define MPP_TYPE_CREATE_ mpp_type_create_real4
1336 #define MPP_TYPE_ real(r4_kind)
1337 #define MPI_TYPE_ MPI_REAL4
1338 #include <mpp_type_mpi.fh>
1339 
1340 #undef MPP_TYPE_CREATE_
1341 #undef MPP_TYPE_
1342 #undef MPI_TYPE_
1343 #define MPP_TYPE_CREATE_ mpp_type_create_real8
1344 #define MPP_TYPE_ real(r8_kind)
1345 #define MPI_TYPE_ MPI_REAL8
1346 #include <mpp_type_mpi.fh>
1347 
1348 #undef MPP_TYPE_CREATE_
1349 #undef MPP_TYPE_
1350 #undef MPI_TYPE_
1351 #define MPP_TYPE_CREATE_ mpp_type_create_cmplx4
1352 #define MPP_TYPE_ complex(c4_kind)
1353 #define MPI_TYPE_ MPI_COMPLEX8
1354 #include <mpp_type_mpi.fh>
1355 
1356 #undef MPP_TYPE_CREATE_
1357 #undef MPP_TYPE_
1358 #undef MPI_TYPE_
1359 #define MPP_TYPE_CREATE_ mpp_type_create_cmplx8
1360 #define MPP_TYPE_ complex(c8_kind)
1361 #define MPI_TYPE_ MPI_COMPLEX16
1362 #include <mpp_type_mpi.fh>
1363 
1364 #undef MPP_TYPE_CREATE_
1365 #undef MPP_TYPE_
1366 #undef MPI_TYPE_
1367 #define MPP_TYPE_CREATE_ mpp_type_create_logical4
1368 #define MPP_TYPE_ logical(l4_kind)
1369 #define MPI_TYPE_ MPI_INTEGER4
1370 #include <mpp_type_mpi.fh>
1371 
1372 #undef MPP_TYPE_CREATE_
1373 #undef MPP_TYPE_
1374 #undef MPI_TYPE_
1375 #define MPP_TYPE_CREATE_ mpp_type_create_logical8
1376 #define MPP_TYPE_ logical(l8_kind)
1377 #define MPI_TYPE_ MPI_INTEGER8
1378 #include <mpp_type_mpi.fh>
1379 
1380 ! Clear preprocessor flags
1381 #undef MPI_TYPE_
1382 #undef MPP_TYPE_
1383 #undef MPP_TYPE_CREATE_
1384 
1385 !> Deallocates memory for mpp_type objects
1386 !! @TODO This should probably not take a pointer, but for now we do this.
1387 subroutine mpp_type_free(dtype)
1388  type(mpp_type), pointer, intent(inout) :: dtype
1389 
1390  if (.NOT. module_is_initialized) &
1391  call mpp_error(fatal, 'MPP_TYPE_FREE: You must first call mpp_init.')
1392 
1393  if (current_clock .NE. 0) &
1394  call system_clock(start_tick)
1395 
1396  if (verbose) &
1397  call mpp_error(note, 'MPP_TYPE_FREE: using MPI_Type_free...')
1398 
1399  ! Decrement the reference counter
1400  dtype%counter = dtype%counter - 1
1401 
1402  if (dtype%counter < 1) then
1403  ! Remove from list
1404  dtype%prev => dtype%next
1405  datatypes%length = datatypes%length - 1
1406 
1407  ! Free resources
1408  deallocate(dtype%sizes)
1409  deallocate(dtype%subsizes)
1410  deallocate(dtype%starts)
1411 
1412  ! User-defined datatype cleanup
1413  if (dtype%id /= mpi_byte) then
1414  call mpi_type_free(dtype%id, error)
1415  deallocate(dtype)
1416  endif
1417  end if
1418 
1419  if (current_clock .NE. 0) &
1420  call increment_current_clock(event_type_free, mpp_type_bytelen_)
1421 
1422 end subroutine mpp_type_free
1423 !> @}
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:490
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:1219
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:705
subroutine mpp_broadcast_char(char_data, length, from_pe, pelist)
Broadcasts a character string from the given pe to it's pelist.