33 subroutine mpp_init( flags, localcomm, test_level, alt_input_nml_path )
34 integer,
optional,
intent(in) :: flags
35 integer,
optional,
intent(in) :: localcomm
36 integer,
optional,
intent(in) :: test_level
38 character(len=*),
optional,
intent(in) :: alt_input_nml_path
40 logical :: opened, existed
44 if( module_is_initialized )
return
46 call mpi_initialized( opened, error )
47 if(opened .and. .NOT.
PRESENT(localcomm))
call mpp_error( fatal,
'MPP_INIT: communicator is required' )
48 if( .NOT.opened )
then
50 mpp_comm_private = mpi_comm_world
52 mpp_comm_private = localcomm
54 call mpi_comm_rank( mpp_comm_private, pe, error )
55 call mpi_comm_size( mpp_comm_private, npes, error )
57 module_is_initialized = .true.
58 if (
present(test_level))
then
63 if (t_level == 0)
return
66 allocate(peset(0:current_peset_max))
71 peset(:)%log2stride = -1
75 allocate( peset(0)%list(1) )
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
82 if (t_level == 1)
return
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
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
99 mpp_byte%prev => null()
100 mpp_byte%next => null()
103 datatypes%head => mpp_byte
104 datatypes%tail => mpp_byte
107 if(
PRESENT(flags) )
then
108 debug = flags.EQ.mpp_debug
109 verbose = flags.EQ.mpp_verbose .OR. debug
111 if (t_level == 3)
return
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)
120 if (t_level == 4)
return
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')
127 if (t_level == 5)
return
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.")
134 if(etc_unit_is_stderr)
then
137 if (trim(etcfile) /=
'/dev/null')
then
138 write( etcfile,
'(a,i6.6)' )trim(etcfile)//
'.', pe
140 inquire(file=etcfile, exist=existed)
142 open( newunit=etc_unit, file=trim(etcfile), status=
'REPLACE' )
144 open( newunit=etc_unit, file=trim(etcfile) )
148 if (t_level == 6)
return
151 max_request = max(max_request_min, mpp_npes()*request_multiply)
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
162 if (t_level == 7)
return
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)
179 stdout_unit = stdout()
181 call mpp_clock_begin(clock0)
184end subroutine mpp_init
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
194 type(mpp_type),
pointer :: dtype, next_dtype
196 if( .NOT.module_is_initialized )
return
197 call mpp_set_current_pelist()
198 call mpp_clock_end(clock0)
199 t_total = clocks(clock0)%total_ticks*tick_rate
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
208 call flush( out_unit )
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'
218 write( log_unit,
'(/37x,a)' )
'time'
220 call flush( out_unit )
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 )
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
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'
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 )
249 do j = 1,max_event_types
250 n = clocks(i)%events(j)%calls; nmax = n
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() )
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
275 call flush( out_unit )
277 inquire(unit=etc_unit, opened=opened)
279 call flush (etc_unit)
284 dtype => datatypes%head
285 do while (
associated(dtype))
286 next_dtype => dtype%next
287 call mpp_type_free(dtype)
291 call mpp_set_current_pelist()
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)
298end subroutine mpp_exit
302 subroutine mpp_set_stack_size(n)
303 integer,
intent(in) :: n
304 character(len=8) :: text
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) )
312 write( text,
'(i8)' )n
313 if( pe.EQ.root_pe )
call mpp_error( note,
'MPP_SET_STACK_SIZE: stack size set to '//text//
'.' )
316 end subroutine mpp_set_stack_size
324 subroutine mpp_broadcast_char(char_data, length, from_pe, pelist )
325 character(len=*),
intent(inout) :: char_data(:)
326 integer,
intent(in) :: length
327 integer,
intent(in) :: from_pe
328 integer,
intent(in),
optional :: pelist(:)
329 integer :: n, i, from_rank
330 character :: str1D(length*size(char_data(:)))
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
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
345 if( .NOT.any(from_pe.EQ.peset(current_peset_num)%list) ) &
346 call mpp_error( fatal,
'mpp_broadcast_text: broadcasting from invalid PE.' )
348 if( debug .and. (current_clock.NE.0) )
call system_clock(start_tick)
351 if(peset(n)%list(i) == from_pe)
then
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 )
361 end subroutine mpp_broadcast_char
364#define MPP_TYPE_INIT_VALUE 0.
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
379#define MPP_RECV_ mpp_recv_real8
380#undef MPP_RECV_SCALAR_
381#define MPP_RECV_SCALAR_ mpp_recv_real8_scalar
383#define MPP_RECV_2D_ mpp_recv_real8_2d
385#define MPP_RECV_3D_ mpp_recv_real8_3d
387#define MPP_RECV_4D_ mpp_recv_real8_4d
389#define MPP_RECV_5D_ mpp_recv_real8_5d
391#define MPP_SEND_ mpp_send_real8
392#undef MPP_SEND_SCALAR_
393#define MPP_SEND_SCALAR_ mpp_send_real8_scalar
395#define MPP_SEND_2D_ mpp_send_real8_2d
397#define MPP_SEND_3D_ mpp_send_real8_3d
399#define MPP_SEND_4D_ mpp_send_real8_4d
401#define MPP_SEND_5D_ mpp_send_real8_5d
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
415#define MPP_TYPE_ real(r8_kind)
416#undef MPP_TYPE_BYTELEN_
417#define MPP_TYPE_BYTELEN_ 8
419#define MPI_TYPE_ MPI_REAL8
420#include <mpp_transmit_mpi.fh>
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
436#define MPP_RECV_ mpp_recv_cmplx8
437#undef MPP_RECV_SCALAR_
438#define MPP_RECV_SCALAR_ mpp_recv_cmplx8_scalar
440#define MPP_RECV_2D_ mpp_recv_cmplx8_2d
442#define MPP_RECV_3D_ mpp_recv_cmplx8_3d
444#define MPP_RECV_4D_ mpp_recv_cmplx8_4d
446#define MPP_RECV_5D_ mpp_recv_cmplx8_5d
448#define MPP_SEND_ mpp_send_cmplx8
449#undef MPP_SEND_SCALAR_
450#define MPP_SEND_SCALAR_ mpp_send_cmplx8_scalar
452#define MPP_SEND_2D_ mpp_send_cmplx8_2d
454#define MPP_SEND_3D_ mpp_send_cmplx8_3d
456#define MPP_SEND_4D_ mpp_send_cmplx8_4d
458#define MPP_SEND_5D_ mpp_send_cmplx8_5d
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
472#define MPP_TYPE_ complex(c8_kind)
473#undef MPP_TYPE_BYTELEN_
474#define MPP_TYPE_BYTELEN_ 16
476#define MPI_TYPE_ MPI_DOUBLE_COMPLEX
477#include <mpp_transmit_mpi.fh>
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
493#define MPP_RECV_ mpp_recv_real4
494#undef MPP_RECV_SCALAR_
495#define MPP_RECV_SCALAR_ mpp_recv_real4_scalar
497#define MPP_RECV_2D_ mpp_recv_real4_2d
499#define MPP_RECV_3D_ mpp_recv_real4_3d
501#define MPP_RECV_4D_ mpp_recv_real4_4d
503#define MPP_RECV_5D_ mpp_recv_real4_5d
505#define MPP_SEND_ mpp_send_real4
506#undef MPP_SEND_SCALAR_
507#define MPP_SEND_SCALAR_ mpp_send_real4_scalar
509#define MPP_SEND_2D_ mpp_send_real4_2d
511#define MPP_SEND_3D_ mpp_send_real4_3d
513#define MPP_SEND_4D_ mpp_send_real4_4d
515#define MPP_SEND_5D_ mpp_send_real4_5d
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
529#define MPP_TYPE_ real(r4_kind)
530#undef MPP_TYPE_BYTELEN_
531#define MPP_TYPE_BYTELEN_ 4
533#define MPI_TYPE_ MPI_REAL4
534#include <mpp_transmit_mpi.fh>
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
550#define MPP_RECV_ mpp_recv_cmplx4
551#undef MPP_RECV_SCALAR_
552#define MPP_RECV_SCALAR_ mpp_recv_cmplx4_scalar
554#define MPP_RECV_2D_ mpp_recv_cmplx4_2d
556#define MPP_RECV_3D_ mpp_recv_cmplx4_3d
558#define MPP_RECV_4D_ mpp_recv_cmplx4_4d
560#define MPP_RECV_5D_ mpp_recv_cmplx4_5d
562#define MPP_SEND_ mpp_send_cmplx4
563#undef MPP_SEND_SCALAR_
564#define MPP_SEND_SCALAR_ mpp_send_cmplx4_scalar
566#define MPP_SEND_2D_ mpp_send_cmplx4_2d
568#define MPP_SEND_3D_ mpp_send_cmplx4_3d
570#define MPP_SEND_4D_ mpp_send_cmplx4_4d
572#define MPP_SEND_5D_ mpp_send_cmplx4_5d
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
586#define MPP_TYPE_ complex(c4_kind)
587#undef MPP_TYPE_BYTELEN_
588#define MPP_TYPE_BYTELEN_ 8
590#define MPI_TYPE_ MPI_COMPLEX
591#include <mpp_transmit_mpi.fh>
594#undef MPP_TYPE_INIT_VALUE
595#define MPP_TYPE_INIT_VALUE 0
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
609#define MPP_RECV_ mpp_recv_int8
610#undef MPP_RECV_SCALAR_
611#define MPP_RECV_SCALAR_ mpp_recv_int8_scalar
613#define MPP_RECV_2D_ mpp_recv_int8_2d
615#define MPP_RECV_3D_ mpp_recv_int8_3d
617#define MPP_RECV_4D_ mpp_recv_int8_4d
619#define MPP_RECV_5D_ mpp_recv_int8_5d
621#define MPP_SEND_ mpp_send_int8
622#undef MPP_SEND_SCALAR_
623#define MPP_SEND_SCALAR_ mpp_send_int8_scalar
625#define MPP_SEND_2D_ mpp_send_int8_2d
627#define MPP_SEND_3D_ mpp_send_int8_3d
629#define MPP_SEND_4D_ mpp_send_int8_4d
631#define MPP_SEND_5D_ mpp_send_int8_5d
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
645#define MPP_TYPE_ integer(i8_kind)
646#undef MPP_TYPE_BYTELEN_
647#define MPP_TYPE_BYTELEN_ 8
649#define MPI_TYPE_ MPI_INTEGER8
650#include <mpp_transmit_mpi.fh>
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
665#define MPP_RECV_ mpp_recv_int4
666#undef MPP_RECV_SCALAR_
667#define MPP_RECV_SCALAR_ mpp_recv_int4_scalar
669#define MPP_RECV_2D_ mpp_recv_int4_2d
671#define MPP_RECV_3D_ mpp_recv_int4_3d
673#define MPP_RECV_4D_ mpp_recv_int4_4d
675#define MPP_RECV_5D_ mpp_recv_int4_5d
677#define MPP_SEND_ mpp_send_int4
678#undef MPP_SEND_SCALAR_
679#define MPP_SEND_SCALAR_ mpp_send_int4_scalar
681#define MPP_SEND_2D_ mpp_send_int4_2d
683#define MPP_SEND_3D_ mpp_send_int4_3d
685#define MPP_SEND_4D_ mpp_send_int4_4d
687#define MPP_SEND_5D_ mpp_send_int4_5d
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
701#define MPP_TYPE_ integer(i4_kind)
702#undef MPP_TYPE_BYTELEN_
703#define MPP_TYPE_BYTELEN_ 4
705#define MPI_TYPE_ MPI_INTEGER4
706#include <mpp_transmit_mpi.fh>
708#undef MPP_TYPE_INIT_VALUE
709#define MPP_TYPE_INIT_VALUE .false.
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
723#define MPP_RECV_ mpp_recv_logical8
724#undef MPP_RECV_SCALAR_
725#define MPP_RECV_SCALAR_ mpp_recv_logical8_scalar
727#define MPP_RECV_2D_ mpp_recv_logical8_2d
729#define MPP_RECV_3D_ mpp_recv_logical8_3d
731#define MPP_RECV_4D_ mpp_recv_logical8_4d
733#define MPP_RECV_5D_ mpp_recv_logical8_5d
735#define MPP_SEND_ mpp_send_logical8
736#undef MPP_SEND_SCALAR_
737#define MPP_SEND_SCALAR_ mpp_send_logical8_scalar
739#define MPP_SEND_2D_ mpp_send_logical8_2d
741#define MPP_SEND_3D_ mpp_send_logical8_3d
743#define MPP_SEND_4D_ mpp_send_logical8_4d
745#define MPP_SEND_5D_ mpp_send_logical8_5d
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
759#define MPP_TYPE_ logical(l8_kind)
760#undef MPP_TYPE_BYTELEN_
761#define MPP_TYPE_BYTELEN_ 8
763#define MPI_TYPE_ MPI_INTEGER8
764#include <mpp_transmit_mpi.fh>
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
779#define MPP_RECV_ mpp_recv_logical4
780#undef MPP_RECV_SCALAR_
781#define MPP_RECV_SCALAR_ mpp_recv_logical4_scalar
783#define MPP_RECV_2D_ mpp_recv_logical4_2d
785#define MPP_RECV_3D_ mpp_recv_logical4_3d
787#define MPP_RECV_4D_ mpp_recv_logical4_4d
789#define MPP_RECV_5D_ mpp_recv_logical4_5d
791#define MPP_SEND_ mpp_send_logical4
792#undef MPP_SEND_SCALAR_
793#define MPP_SEND_SCALAR_ mpp_send_logical4_scalar
795#define MPP_SEND_2D_ mpp_send_logical4_2d
797#define MPP_SEND_3D_ mpp_send_logical4_3d
799#define MPP_SEND_4D_ mpp_send_logical4_4d
801#define MPP_SEND_5D_ mpp_send_logical4_5d
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
815#define MPP_TYPE_ logical(l4_kind)
816#undef MPP_TYPE_BYTELEN_
817#define MPP_TYPE_BYTELEN_ 4
819#define MPI_TYPE_ MPI_INTEGER4
820#include <mpp_transmit_mpi.fh>
821#undef MPP_TYPE_INIT_VALUE
829#define MPP_REDUCE_0D_ mpp_max_real8_0d
831#define MPP_REDUCE_1D_ mpp_max_real8_1d
833#define MPP_TYPE_ real(r8_kind)
834#undef MPP_TYPE_BYTELEN_
835#define MPP_TYPE_BYTELEN_ 8
837#define MPI_TYPE_ MPI_REAL8
839#define MPI_REDUCE_ MPI_MAX
840#include <mpp_reduce_mpi.fh>
843#define MPP_REDUCE_0D_ mpp_max_real4_0d
845#define MPP_REDUCE_1D_ mpp_max_real4_1d
847#define MPP_TYPE_ real(r4_kind)
848#undef MPP_TYPE_BYTELEN_
849#define MPP_TYPE_BYTELEN_ 4
851#define MPI_TYPE_ MPI_REAL4
853#define MPI_REDUCE_ MPI_MAX
854#include <mpp_reduce_mpi.fh>
857#define MPP_REDUCE_0D_ mpp_max_int8_0d
859#define MPP_REDUCE_1D_ mpp_max_int8_1d
861#define MPP_TYPE_ integer(i8_kind)
862#undef MPP_TYPE_BYTELEN_
863#define MPP_TYPE_BYTELEN_ 8
865#define MPI_TYPE_ MPI_INTEGER8
867#define MPI_REDUCE_ MPI_MAX
868#include <mpp_reduce_mpi.fh>
871#define MPP_REDUCE_0D_ mpp_max_int4_0d
873#define MPP_REDUCE_1D_ mpp_max_int4_1d
875#define MPP_TYPE_ integer(i4_kind)
876#undef MPP_TYPE_BYTELEN_
877#define MPP_TYPE_BYTELEN_ 4
879#define MPI_TYPE_ MPI_INTEGER4
881#define MPI_REDUCE_ MPI_MAX
882#include <mpp_reduce_mpi.fh>
885#define MPP_REDUCE_0D_ mpp_min_real8_0d
887#define MPP_REDUCE_1D_ mpp_min_real8_1d
889#define MPP_TYPE_ real(r8_kind)
890#undef MPP_TYPE_BYTELEN_
891#define MPP_TYPE_BYTELEN_ 8
893#define MPI_TYPE_ MPI_REAL8
895#define MPI_REDUCE_ MPI_MIN
896#include <mpp_reduce_mpi.fh>
899#define MPP_REDUCE_0D_ mpp_min_real4_0d
901#define MPP_REDUCE_1D_ mpp_min_real4_1d
903#define MPP_TYPE_ real(r4_kind)
904#undef MPP_TYPE_BYTELEN_
905#define MPP_TYPE_BYTELEN_ 4
907#define MPI_TYPE_ MPI_REAL4
909#define MPI_REDUCE_ MPI_MIN
910#include <mpp_reduce_mpi.fh>
913#define MPP_REDUCE_0D_ mpp_min_int8_0d
915#define MPP_REDUCE_1D_ mpp_min_int8_1d
917#define MPP_TYPE_ integer(i8_kind)
918#undef MPP_TYPE_BYTELEN_
919#define MPP_TYPE_BYTELEN_ 8
921#define MPI_TYPE_ MPI_INTEGER8
923#define MPI_REDUCE_ MPI_MIN
924#include <mpp_reduce_mpi.fh>
927#define MPP_REDUCE_0D_ mpp_min_int4_0d
929#define MPP_REDUCE_1D_ mpp_min_int4_1d
931#define MPP_TYPE_ integer(i4_kind)
932#undef MPP_TYPE_BYTELEN_
933#define MPP_TYPE_BYTELEN_ 4
935#define MPI_TYPE_ MPI_INTEGER4
937#define MPI_REDUCE_ MPI_MIN
938#include <mpp_reduce_mpi.fh>
941#define MPP_SUM_ mpp_sum_real8
942#undef MPP_SUM_SCALAR_
943#define MPP_SUM_SCALAR_ mpp_sum_real8_scalar
945#define MPP_SUM_2D_ mpp_sum_real8_2d
947#define MPP_SUM_3D_ mpp_sum_real8_3d
949#define MPP_SUM_4D_ mpp_sum_real8_4d
951#define MPP_SUM_5D_ mpp_sum_real8_5d
953#define MPP_TYPE_ real(r8_kind)
955#define MPI_TYPE_ MPI_REAL8
956#undef MPP_TYPE_BYTELEN_
957#define MPP_TYPE_BYTELEN_ 8
958#include <mpp_sum_mpi.fh>
962#define MPP_SUM_ mpp_sum_cmplx8
963#undef MPP_SUM_SCALAR_
964#define MPP_SUM_SCALAR_ mpp_sum_cmplx8_scalar
966#define MPP_SUM_2D_ mpp_sum_cmplx8_2d
968#define MPP_SUM_3D_ mpp_sum_cmplx8_3d
970#define MPP_SUM_4D_ mpp_sum_cmplx8_4d
972#define MPP_SUM_5D_ mpp_sum_cmplx8_5d
974#define MPP_TYPE_ complex(c8_kind)
976#define MPI_TYPE_ MPI_DOUBLE_COMPLEX
977#undef MPP_TYPE_BYTELEN_
978#define MPP_TYPE_BYTELEN_ 16
979#include <mpp_sum_mpi.fh>
983#define MPP_SUM_ mpp_sum_real4
984#undef MPP_SUM_SCALAR_
985#define MPP_SUM_SCALAR_ mpp_sum_real4_scalar
987#define MPP_SUM_2D_ mpp_sum_real4_2d
989#define MPP_SUM_3D_ mpp_sum_real4_3d
991#define MPP_SUM_4D_ mpp_sum_real4_4d
993#define MPP_SUM_5D_ mpp_sum_real4_5d
995#define MPP_TYPE_ real(r4_kind)
997#define MPI_TYPE_ MPI_REAL4
998#undef MPP_TYPE_BYTELEN_
999#define MPP_TYPE_BYTELEN_ 4
1000#include <mpp_sum_mpi.fh>
1004#define MPP_SUM_ mpp_sum_cmplx4
1005#undef MPP_SUM_SCALAR_
1006#define MPP_SUM_SCALAR_ mpp_sum_cmplx4_scalar
1008#define MPP_SUM_2D_ mpp_sum_cmplx4_2d
1010#define MPP_SUM_3D_ mpp_sum_cmplx4_3d
1012#define MPP_SUM_4D_ mpp_sum_cmplx4_4d
1014#define MPP_SUM_5D_ mpp_sum_cmplx4_5d
1016#define MPP_TYPE_ complex(c4_kind)
1018#define MPI_TYPE_ MPI_COMPLEX
1019#undef MPP_TYPE_BYTELEN_
1020#define MPP_TYPE_BYTELEN_ 8
1021#include <mpp_sum_mpi.fh>
1025#define MPP_SUM_ mpp_sum_int8
1026#undef MPP_SUM_SCALAR_
1027#define MPP_SUM_SCALAR_ mpp_sum_int8_scalar
1029#define MPP_SUM_2D_ mpp_sum_int8_2d
1031#define MPP_SUM_3D_ mpp_sum_int8_3d
1033#define MPP_SUM_4D_ mpp_sum_int8_4d
1035#define MPP_SUM_5D_ mpp_sum_int8_5d
1037#define MPP_TYPE_ integer(i8_kind)
1039#define MPI_TYPE_ MPI_INTEGER8
1040#undef MPP_TYPE_BYTELEN_
1041#define MPP_TYPE_BYTELEN_ 8
1042#include <mpp_sum_mpi.fh>
1045#define MPP_SUM_ mpp_sum_int4
1046#undef MPP_SUM_SCALAR_
1047#define MPP_SUM_SCALAR_ mpp_sum_int4_scalar
1049#define MPP_SUM_2D_ mpp_sum_int4_2d
1051#define MPP_SUM_3D_ mpp_sum_int4_3d
1053#define MPP_SUM_4D_ mpp_sum_int4_4d
1055#define MPP_SUM_5D_ mpp_sum_int4_5d
1057#define MPP_TYPE_ integer(i4_kind)
1059#define MPI_TYPE_ MPI_INTEGER4
1060#undef MPP_TYPE_BYTELEN_
1061#define MPP_TYPE_BYTELEN_ 4
1062#include <mpp_sum_mpi.fh>
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
1077#define MPP_TYPE_ real(r8_kind)
1079#define MPI_TYPE_ MPI_REAL8
1080#undef MPP_TYPE_BYTELEN_
1081#define MPP_TYPE_BYTELEN_ 8
1082#include <mpp_sum_mpi_ad.fh>
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
1098#define MPP_TYPE_ complex(c8_kind)
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>
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
1119#define MPP_TYPE_ real(r4_kind)
1121#define MPI_TYPE_ MPI_REAL4
1122#undef MPP_TYPE_BYTELEN_
1123#define MPP_TYPE_BYTELEN_ 4
1124#include <mpp_sum_mpi_ad.fh>
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
1140#define MPP_TYPE_ complex(c4_kind)
1142#define MPI_TYPE_ MPI_COMPLEX
1143#undef MPP_TYPE_BYTELEN_
1144#define MPP_TYPE_BYTELEN_ 8
1145#include <mpp_sum_mpi_ad.fh>
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
1161#define MPP_TYPE_ integer(i8_kind)
1163#define MPI_TYPE_ MPI_INTEGER8
1164#undef MPP_TYPE_BYTELEN_
1165#define MPP_TYPE_BYTELEN_ 8
1166#include <mpp_sum_mpi_ad.fh>
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
1181#define MPP_TYPE_ integer(i4_kind)
1183#define MPI_TYPE_ MPI_INTEGER4
1184#undef MPP_TYPE_BYTELEN_
1185#define MPP_TYPE_BYTELEN_ 4
1186#include <mpp_sum_mpi_ad.fh>
1195#undef MPP_ALLTOALLV_
1196#undef MPP_ALLTOALLW_
1198#undef MPP_TYPE_BYTELEN_
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>
1209#undef MPP_ALLTOALLV_
1210#undef MPP_ALLTOALLW_
1212#undef MPP_TYPE_BYTELEN_
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>
1223#undef MPP_ALLTOALLV_
1224#undef MPP_ALLTOALLW_
1226#undef MPP_TYPE_BYTELEN_
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>
1237#undef MPP_ALLTOALLV_
1238#undef MPP_ALLTOALLW_
1240#undef MPP_TYPE_BYTELEN_
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>
1252#undef MPP_ALLTOALLV_
1253#undef MPP_ALLTOALLW_
1255#undef MPP_TYPE_BYTELEN_
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>
1268#undef MPP_ALLTOALLV_
1269#undef MPP_ALLTOALLW_
1271#undef MPP_TYPE_BYTELEN_
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>
1283#undef MPP_ALLTOALLV_
1284#undef MPP_ALLTOALLW_
1286#undef MPP_TYPE_BYTELEN_
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>
1297#undef MPP_ALLTOALLV_
1298#undef MPP_ALLTOALLW_
1300#undef MPP_TYPE_BYTELEN_
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>
1316#undef MPP_TYPE_CREATE_
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>
1324#undef MPP_TYPE_CREATE_
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>
1332#undef MPP_TYPE_CREATE_
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>
1340#undef MPP_TYPE_CREATE_
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>
1348#undef MPP_TYPE_CREATE_
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>
1356#undef MPP_TYPE_CREATE_
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>
1364#undef MPP_TYPE_CREATE_
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>
1372#undef MPP_TYPE_CREATE_
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>
1383#undef MPP_TYPE_CREATE_
1387subroutine mpp_type_free(dtype)
1388 type(mpp_type),
pointer,
intent(inout) :: dtype
1390 if (.NOT. module_is_initialized) &
1391 call mpp_error(fatal,
'MPP_TYPE_FREE: You must first call mpp_init.')
1393 if (current_clock .NE. 0) &
1394 call system_clock(start_tick)
1397 call mpp_error(note,
'MPP_TYPE_FREE: using MPI_Type_free...')
1400 dtype%counter = dtype%counter - 1
1402 if (dtype%counter < 1)
then
1404 dtype%prev => dtype%next
1405 datatypes%length = datatypes%length - 1
1408 deallocate(dtype%sizes)
1409 deallocate(dtype%subsizes)
1410 deallocate(dtype%starts)
1413 if (dtype%id /= mpi_byte)
then
1414 call mpi_type_free(dtype%id, error)
1419 if (current_clock .NE. 0) &
1420 call increment_current_clock(event_type_free, mpp_type_bytelen_)
1422end subroutine mpp_type_free
integer function get_peset(pelist)
Makes a PE set out of a PE list. A PE list is an ordered list of PEs a PE set is a triad (start,...
subroutine mpp_sync(pelist, do_self)
Synchronize PEs in list.