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