File: alltoallvf08.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 (148 lines) | stat: -rw-r--r-- 4,645 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
!
! Copyright (C) by Argonne National Laboratory
!     See COPYRIGHT in top-level directory
!

! This file created from test/mpi/f77/coll/alltoallvf.f with f77tof90

      program main
      use mpi_f08
      integer ierr, errs
      integer i, ans, size, rank, color
      TYPE(MPI_Comm) comm, newcomm
      integer maxSize, displ
      parameter (maxSize=128)
      integer scounts(maxSize), sdispls(maxSize)
      integer rcounts(maxSize), rdispls(maxSize)
      TYPE(MPI_Datatype) stype, rtype
      integer sbuf(maxSize), rbuf(maxSize)

      errs = 0

      call mtest_init( ierr )

! Get a comm
      call mpi_comm_dup( MPI_COMM_WORLD, comm, ierr )
      call mpi_comm_size( comm, size, ierr )
      if (size .gt. maxSize) then
         call mpi_comm_rank( comm, rank, ierr )
         color = 1
         if (rank .lt. maxSize) color = 0
         call mpi_comm_split( comm, color, rank, newcomm, ierr )
         call mpi_comm_free( comm, ierr )
         comm = newcomm
         call mpi_comm_size( comm, size, ierr )
      endif
      call mpi_comm_rank( comm, rank, ierr )
!
      if (size .le. maxSize) then
! Initialize the data.  Just use this as an all to all
! Use the same test as alltoallwf.c , except displacements are in units of
! integers instead of bytes
         do i=1, size
            scounts(i) = 1
            sdispls(i) = (i-1)
            stype      = MPI_INTEGER
            sbuf(i) = rank * size + i
            rcounts(i) = 1
            rdispls(i) = (i-1)
            rtype      = MPI_INTEGER
            rbuf(i) = -1
         enddo
         call mpi_alltoallv( sbuf, scounts, sdispls, stype, &
      &        rbuf, rcounts, rdispls, rtype, comm, ierr )
!
! check rbuf(i) = data from the ith location of the ith send buf, or
!       rbuf(i) = (i-1) * size + i
         do i=1, size
            ans = (i-1) * size + rank + 1
            if (rbuf(i) .ne. ans) then
               errs = errs + 1
               print *, rank, ' rbuf(', i, ') = ', rbuf(i),  &
      &               ' expected ', ans
            endif
         enddo
!
!     A halo-exchange example - mostly zero counts
!
         do i=1, size
            scounts(i) = 0
            sdispls(i) = 0
            stype      = MPI_INTEGER
            sbuf(i) = -1
            rcounts(i) = 0
            rdispls(i) = 0
            rtype      = MPI_INTEGER
            rbuf(i) = -1
         enddo

!
!     Note that the arrays are 1-origin
         displ = 0
         if (rank .gt. 0) then
            scounts(1+rank-1) = 1
            rcounts(1+rank-1) = 1
            sdispls(1+rank-1) = displ
            rdispls(1+rank-1) = rank - 1
            sbuf(1+displ)     = rank
            displ             = displ + 1
         endif
         scounts(1+rank)   = 1
         rcounts(1+rank)   = 1
         sdispls(1+rank)   = displ
         rdispls(1+rank)   = rank
         sbuf(1+displ)     = rank
         displ           = displ + 1
         if (rank .lt. size-1) then
            scounts(1+rank+1) = 1
            rcounts(1+rank+1) = 1
            sdispls(1+rank+1) = displ
            rdispls(1+rank+1) = rank+1
            sbuf(1+displ)     = rank
            displ             = displ + 1
         endif

         call mpi_alltoallv( sbuf, scounts, sdispls, stype, &
      &        rbuf, rcounts, rdispls, rtype, comm, ierr )
!
!   Check the neighbor values are correctly moved
!
         if (rank .gt. 0) then
            if (rbuf(1+rank-1) .ne. rank-1) then
               errs = errs + 1
               print *, rank, ' rbuf(',1+rank-1, ') = ', rbuf(1+rank-1), &
      &              'expected ', rank-1
            endif
         endif
         if (rbuf(1+rank) .ne. rank) then
            errs = errs + 1
            print *, rank, ' rbuf(', 1+rank, ') = ', rbuf(1+rank), &
      &           'expected ', rank
         endif
         if (rank .lt. size-1) then
            if (rbuf(1+rank+1) .ne. rank+1) then
               errs = errs + 1
               print *, rank, ' rbuf(', 1+rank+1, ') = ',rbuf(1+rank+1), &
      &              'expected ', rank+1
            endif
         endif
         do i=0,rank-2
            if (rbuf(1+i) .ne. -1) then
               errs = errs + 1
               print *, rank, ' rbuf(', 1+i, ') = ', rbuf(1+i),  &
      &              'expected -1'
            endif
         enddo
         do i=rank+2,size-1
            if (rbuf(1+i) .ne. -1) then
               errs = errs + 1
               print *, rank, ' rbuf(', i, ') = ', rbuf(1+i),  &
      &              'expected -1'
            endif
         enddo
      endif
      call mpi_comm_free( comm, ierr )

      call mtest_finalize( errs )
      end