Logo AND Algorithmique Numérique Distribuée

Public GIT Repository
add F90 rma tests
[simgrid.git] / teshsuite / smpi / mpich3-test / f90 / rma / winscale2f90.f90
1 ! This file created from test/mpi/f77/rma/winscale2f.f with f77tof90
2 ! -*- Mode: Fortran; -*- 
3 !
4 !  (C) 2003 by Argonne National Laboratory.
5 !      See COPYRIGHT in top-level directory.
6 !
7       program main
8       use mpi
9       integer ierr, errs
10       integer win, intsize
11       integer left, right, rank, size
12       integer nrows, ncols
13       parameter (nrows=25,ncols=10)
14       integer buf(1:nrows,0:ncols+1)
15       integer comm, group, group2, ans
16       integer nneighbors, nbrs(2), i, j
17       logical mtestGetIntraComm
18       logical flag
19 ! Include addsize defines asize as an address-sized integer
20       integer (kind=MPI_ADDRESS_KIND) asize
21
22       
23       errs = 0
24       call mtest_init( ierr )
25
26       call mpi_type_size( MPI_INTEGER, intsize, ierr )
27       do while( mtestGetIntraComm( comm, 2, .false. ) ) 
28          asize = nrows * (ncols + 2) * intsize
29          call mpi_win_create( buf, asize, intsize * nrows,  &
30       &                        MPI_INFO_NULL, comm, win, ierr )
31          
32 ! Create the group for the neighbors
33          call mpi_comm_size( comm, size, ierr )
34          call mpi_comm_rank( comm, rank, ierr )
35          nneighbors = 0
36          left = rank - 1
37          if (left .lt. 0) then
38             left = MPI_PROC_NULL
39          else
40             nneighbors = nneighbors + 1
41             nbrs(nneighbors) = left
42          endif
43          right = rank + 1
44          if (right .ge. size) then
45             right = MPI_PROC_NULL
46          else
47             nneighbors = nneighbors + 1
48             nbrs(nneighbors) = right
49          endif
50          call mpi_comm_group( comm, group, ierr )
51          call mpi_group_incl( group, nneighbors, nbrs, group2, ierr )
52          call mpi_group_free( group, ierr )
53 !
54 ! Initialize the buffer 
55          do i=1,nrows
56             buf(i,0)       = -1
57             buf(i,ncols+1) = -1
58          enddo
59          do j=1,ncols
60             do i=1,nrows
61                buf(i,j) = rank * (ncols * nrows) + i + (j-1) * nrows
62             enddo
63          enddo
64          call mpi_win_post( group2, 0, win, ierr )
65          call mpi_win_start( group2, 0, win, ierr )
66 !         
67          asize = ncols+1
68          call mpi_put( buf(1,1), nrows, MPI_INTEGER, left, asize, &
69       &                 nrows, MPI_INTEGER, win, ierr )
70          asize = 0
71          call mpi_put( buf(1,ncols), nrows, MPI_INTEGER, right, asize,  &
72       &                 nrows, MPI_INTEGER, win, ierr )
73 !         
74          call mpi_win_complete( win, ierr )
75          flag = .false.
76          do while (.not. flag)
77             call mpi_win_test( win, flag, ierr )
78          enddo
79 !
80 ! Check the results
81          if (left .ne. MPI_PROC_NULL) then
82             do i=1, nrows
83                ans = rank * (ncols * nrows) - nrows + i
84                if (buf(i,0) .ne. ans) then
85                   errs = errs + 1
86                   if (errs .le. 10) then
87                      print *, ' buf(',i,',0) = ', buf(i,0),  &
88       &    'expected ', ans
89                   endif
90                endif
91             enddo
92          endif
93          if (right .ne. MPI_PROC_NULL) then
94             do i=1, nrows
95                ans = (rank+1) * (ncols * nrows) + i
96                if (buf(i,ncols+1) .ne. ans) then
97                   errs = errs + 1
98                   if (errs .le. 10) then
99                      print *, ' buf(',i,',',ncols+1,') = ',  &
100       &                          buf(i,ncols+1), ' expected ', ans
101                   endif
102                endif
103             enddo
104          endif
105          call mpi_group_free( group2, ierr )
106          call mpi_win_free( win, ierr )
107          call mtestFreeComm( comm )
108       enddo
109
110       call mtest_finalize( errs )
111       call mpi_finalize( ierr )
112       end