File: packef08.f90

package info (click to toggle)
mpich 4.0.2-3
  • links: PTS, VCS
  • area: main
  • in suites: bookworm
  • size: 423,384 kB
  • sloc: ansic: 1,088,434; cpp: 71,364; javascript: 40,763; f90: 22,829; sh: 17,463; perl: 14,773; xml: 14,418; python: 10,265; makefile: 9,246; fortran: 8,008; java: 4,355; asm: 324; ruby: 176; lisp: 19; php: 8; sed: 4
file content (188 lines) | stat: -rw-r--r-- 6,828 bytes parent folder | download | duplicates (4)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
!
! Copyright (C) by Argonne National Laboratory
!     See COPYRIGHT in top-level directory
!

! This file created from test/mpi/f77/datatype/packef.f with f77tof90

       program main
       use mpi_f08
       integer ierr, errs
       integer inbuf(10), ioutbuf(10), inbuf2(10), ioutbuf2(10)
       integer i, insize, rsize, csize, insize2
       character*(16) cbuf, coutbuf
       double precision rbuf(10), routbuf(10)
       integer packbuf(1000), pbufsize, intsize
       integer max_asizev
       parameter (max_asizev = 3)
       integer (kind=MPI_ADDRESS_KIND) aint, aintv(max_asizev)


       errs = 0
       call mtest_init( ierr )

       call mpi_type_size( MPI_INTEGER, intsize, ierr )
       pbufsize = 1000 * intsize

       call mpi_pack_external_size( 'external32', 10, MPI_INTEGER,  &
      &                              aint, ierr )
       if (aint .ne. 10 * 4) then
          errs = errs + 1
          print *, 'Expected 40 for size of 10 external32 integers', &
      &       ', got ', aint
       endif
       call mpi_pack_external_size( 'external32', 10, MPI_LOGICAL,  &
      &                              aint, ierr )
       if (aint .ne. 10 * 4) then
          errs = errs + 1
          print *, 'Expected 40 for size of 10 external32 logicals', &
      &       ', got ', aint
       endif
       call mpi_pack_external_size( 'external32', 10, MPI_CHARACTER,  &
      &                              aint, ierr )
       if (aint .ne. 10 * 1) then
          errs = errs + 1
          print *, 'Expected 10 for size of 10 external32 characters', &
      &       ', got ', aint
       endif

       call mpi_pack_external_size( 'external32', 3, MPI_INTEGER2, &
      &                              aint, ierr )
       if (aint .ne. 3 * 2) then
          errs = errs + 1
          print *, 'Expected 6 for size of 3 external32 INTEGER*2', &
      &       ', got ', aint
       endif
       call mpi_pack_external_size( 'external32', 3, MPI_INTEGER4, &
      &                              aint, ierr )
       if (aint .ne. 3 * 4) then
          errs = errs + 1
          print *, 'Expected 12 for size of 3 external32 INTEGER*4', &
      &       ', got ', aint
       endif
       call mpi_pack_external_size( 'external32', 3, MPI_REAL4, &
      &                              aint, ierr )
       if (aint .ne. 3 * 4) then
          errs = errs + 1
          print *, 'Expected 12 for size of 3 external32 REAL*4', &
      &       ', got ', aint
       endif
       call mpi_pack_external_size( 'external32', 3, MPI_REAL8, &
      &                              aint, ierr )
       if (aint .ne. 3 * 8) then
          errs = errs + 1
          print *, 'Expected 24 for size of 3 external32 REAL*8', &
      &       ', got ', aint
       endif
       if (MPI_INTEGER1 .ne. MPI_DATATYPE_NULL) then
          call mpi_pack_external_size( 'external32', 3, MPI_INTEGER1, &
      &                              aint, ierr )
          if (aint .ne. 3 * 1) then
             errs = errs + 1
             print *, 'Expected 3 for size of 3 external32 INTEGER*1', &
      &            ', got ', aint
          endif
       endif
       if (MPI_INTEGER8 .ne. MPI_DATATYPE_NULL) then
          call mpi_pack_external_size( 'external32', 3, MPI_INTEGER8, &
      &                              aint, ierr )
          if (aint .ne. 3 * 8) then
             errs = errs + 1
             print *, 'Expected 24 for size of 3 external32 INTEGER*8', &
      &            ', got ', aint
          endif
       endif

!
! Initialize values
!
       insize = 10
       do i=1, insize
          inbuf(i) = i
       enddo
       rsize = 3
       do i=1, rsize
          rbuf(i) = 1000.0 * i
       enddo
       cbuf  = 'This is a string'
       csize = 16
       insize2 = 7
       do i=1, insize2
          inbuf2(i) = 5000-i
       enddo
!
       aintv(1) = pbufsize
       aintv(2) = 0
       aintv(3) = 0
! One MPI implementation failed to increment the position; instead,
! it set the value with the amount of data packed in this call
! We use aintv(3) to detect and report this specific error
       call mpi_pack_external( 'external32', inbuf, insize, MPI_INTEGER, &
      &               packbuf, aintv(1), aintv(2), ierr )
       if (aintv(2) .le. aintv(3)) then
            print *, ' Position decreased after pack of integer!'
       endif
       aintv(3) = aintv(2)
       call mpi_pack_external( 'external32', rbuf, rsize,  &
      &               MPI_DOUBLE_PRECISION, packbuf, aintv(1),  &
      &               aintv(2), ierr )
       if (aintv(2) .le. aintv(3)) then
            print *, ' Position decreased after pack of real!'
       endif
       aintv(3) = aintv(2)
       call mpi_pack_external( 'external32', cbuf, csize,  &
      &               MPI_CHARACTER, packbuf, aintv(1),  &
      &               aintv(2), ierr )
       if (aintv(2) .le. aintv(3)) then
            print *, ' Position decreased after pack of character!'
       endif
       aintv(3) = aintv(2)
       call mpi_pack_external( 'external32', inbuf2, insize2,  &
      &               MPI_INTEGER, &
      &               packbuf, aintv(1), aintv(2), ierr )
       if (aintv(2) .le. aintv(3)) then
            print *, ' Position decreased after pack of integer (2nd)!'
       endif
       aintv(3) = aintv(2)
!
! We could try sending this with MPI_BYTE...
       aintv(2) = 0
       call mpi_unpack_external( 'external32', packbuf, aintv(1), &
      &  aintv(2), ioutbuf, insize, MPI_INTEGER, ierr )
       call mpi_unpack_external( 'external32', packbuf, aintv(1), &
      &  aintv(2), routbuf, rsize, MPI_DOUBLE_PRECISION, ierr )
       call mpi_unpack_external( 'external32', packbuf, aintv(1), &
      &  aintv(2), coutbuf, csize, MPI_CHARACTER, ierr )
       call mpi_unpack_external( 'external32', packbuf, aintv(1), &
      &  aintv(2), ioutbuf2, insize2, MPI_INTEGER, ierr )
!
! Now, test the values
!
       do i=1, insize
          if (ioutbuf(i) .ne. i) then
             errs = errs + 1
             print *, 'ioutbuf(',i,') = ', ioutbuf(i), ' expected ', i
          endif
       enddo
       do i=1, rsize
          if (routbuf(i) .ne. 1000.0 * i) then
             errs = errs + 1
             print *, 'routbuf(',i,') = ', routbuf(i), ' expected ',       &
      &                1000.0 * i
          endif
       enddo
       if (coutbuf(1:csize) .ne. 'This is a string') then
          errs = errs + 1
          print *, 'coutbuf = ', coutbuf(1:csize), ' expected ',           &
      &             'This is a string'
       endif
       do i=1, insize2
          if (ioutbuf2(i) .ne. 5000-i) then
             errs = errs + 1
             print *, 'ioutbuf2(',i,') = ', ioutbuf2(i), ' expected ',     &
      &              5000-i
          endif
       enddo
!
       call mtest_finalize( errs )
       end