Logo AND Algorithmique Numérique Distribuée

Public GIT Repository
add F90 rma tests
[simgrid.git] / teshsuite / smpi / mpich3-test / f90 / rma / winaccf90.f90
1 ! This file created from test/mpi/f77/rma/winaccf.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, ans
16       integer i, j
17       logical mtestGetIntraComm
18 ! Include addsize defines asize as an address-sized integer
19       integer (kind=MPI_ADDRESS_KIND) asize
20
21       
22       errs = 0
23       call mtest_init( ierr )
24
25       call mpi_type_size( MPI_INTEGER, intsize, ierr )
26       do while( mtestGetIntraComm( comm, 2, .false. ) ) 
27          asize  = nrows * (ncols + 2) * intsize
28          call mpi_win_create( buf, asize, intsize * nrows,  &
29       &                        MPI_INFO_NULL, comm, win, ierr )
30          
31          call mpi_comm_size( comm, size, ierr )
32          call mpi_comm_rank( comm, rank, ierr )
33          left = rank - 1
34          if (left .lt. 0) then
35             left = MPI_PROC_NULL
36          endif
37          right = rank + 1
38          if (right .ge. size) then
39             right = MPI_PROC_NULL
40          endif
41 !
42 ! Initialize the buffer 
43          do i=1,nrows
44             buf(i,0)       = -1
45             buf(i,ncols+1) = -1
46          enddo
47          do j=1,ncols
48             do i=1,nrows
49                buf(i,j) = rank * (ncols * nrows) + i + (j-1) * nrows
50             enddo
51          enddo
52          call mpi_win_fence( MPI_MODE_NOPRECEDE, win, ierr )
53 !         
54          asize = ncols + 1
55          call mpi_accumulate( buf(1,1), nrows, MPI_INTEGER,  &
56       &                 left, asize,  &
57       &                 nrows, MPI_INTEGER, MPI_SUM, win, ierr )
58          asize = 0
59          call mpi_accumulate( buf(1,ncols), nrows, MPI_INTEGER, right, &
60       &                 asize, nrows, MPI_INTEGER, MPI_SUM, win, ierr )
61 !         
62          call mpi_win_fence( MPI_MODE_NOSTORE + MPI_MODE_NOPUT +  &
63       &                       MPI_MODE_NOSUCCEED, win, ierr )
64 !
65 ! Check the results
66          if (left .ne. MPI_PROC_NULL) then
67             do i=1, nrows
68                ans = rank * (ncols * nrows) - nrows + i - 1
69                if (buf(i,0) .ne. ans) then
70                   errs = errs + 1
71                   if (errs .le. 10) then
72                      print *, ' buf(',i,',0) = ', buf(i,0)
73                   endif
74                endif
75             enddo
76          endif
77          if (right .ne. MPI_PROC_NULL) then
78             do i=1, nrows
79                ans = (rank + 1) * (ncols * nrows) + i - 1
80                if (buf(i,ncols+1) .ne. ans) then
81                   errs = errs + 1
82                   if (errs .le. 10) then
83                      print *, ' buf(',i,',',ncols+1,') = ',  &
84       &                         buf(i,ncols+1)
85                   endif
86                endif
87             enddo
88          endif
89          call mpi_win_free( win, ierr )
90          call mtestFreeComm( comm )
91       enddo
92
93       call mtest_finalize( errs )
94       call mpi_finalize( ierr )
95       end