File: winaccf08.f90

package info (click to toggle)
mpich 3.3-3
  • links: PTS, VCS
  • area: main
  • in suites: buster
  • size: 131,836 kB
  • sloc: ansic: 975,868; cpp: 57,437; f90: 53,762; perl: 19,562; xml: 12,464; sh: 12,303; fortran: 7,875; makefile: 7,078; ruby: 126; java: 100; python: 98; lisp: 19; php: 8; sed: 4
file content (96 lines) | stat: -rw-r--r-- 3,082 bytes parent folder | download
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
! This file created from test/mpi/f77/rma/winaccf.f with f77tof90
! -*- Mode: Fortran; -*-
!
!  (C) 2003 by Argonne National Laboratory.
!      See COPYRIGHT in top-level directory.
!
      program main
      use mpi_f08
      integer ierr, errs
      integer intsize
      TYPE(MPI_Win) win
      integer left, right, rank, size
      integer nrows, ncols
      parameter (nrows=25,ncols=10)
      integer buf(1:nrows,0:ncols+1)
      integer ans
      TYPE(MPI_Comm) comm
      integer i, j
      logical mtestGetIntraComm
! Include addsize defines asize as an address-sized integer
      integer (kind=MPI_ADDRESS_KIND) asize


      errs = 0
      call mtest_init( ierr )

      call mpi_type_size( MPI_INTEGER, intsize, ierr )
      do while( mtestGetIntraComm( comm, 2, .false. ) )
         asize  = nrows * (ncols + 2) * intsize
         call mpi_win_create( buf, asize, intsize * nrows,  &
      &                        MPI_INFO_NULL, comm, win, ierr )

         call mpi_comm_size( comm, size, ierr )
         call mpi_comm_rank( comm, rank, ierr )
         left = rank - 1
         if (left .lt. 0) then
            left = MPI_PROC_NULL
         endif
         right = rank + 1
         if (right .ge. size) then
            right = MPI_PROC_NULL
         endif
!
! Initialize the buffer
         do i=1,nrows
            buf(i,0)       = -1
            buf(i,ncols+1) = -1
         enddo
         do j=1,ncols
            do i=1,nrows
               buf(i,j) = rank * (ncols * nrows) + i + (j-1) * nrows
            enddo
         enddo
         call mpi_win_fence( MPI_MODE_NOPRECEDE, win, ierr )
!
         asize = ncols + 1
         call mpi_accumulate( buf(1,1), nrows, MPI_INTEGER,  &
      &                 left, asize,  &
      &                 nrows, MPI_INTEGER, MPI_SUM, win, ierr )
         asize = 0
         call mpi_accumulate( buf(1,ncols), nrows, MPI_INTEGER, right, &
      &                 asize, nrows, MPI_INTEGER, MPI_SUM, win, ierr )
!
         call mpi_win_fence( MPI_MODE_NOSTORE + MPI_MODE_NOPUT +  &
      &                       MPI_MODE_NOSUCCEED, win, ierr )
!
! Check the results
         if (left .ne. MPI_PROC_NULL) then
            do i=1, nrows
               ans = rank * (ncols * nrows) - nrows + i - 1
               if (buf(i,0) .ne. ans) then
                  errs = errs + 1
                  if (errs .le. 10) then
                     print *, ' buf(',i,',0) = ', buf(i,0)
                  endif
               endif
            enddo
         endif
         if (right .ne. MPI_PROC_NULL) then
            do i=1, nrows
               ans = (rank + 1) * (ncols * nrows) + i - 1
               if (buf(i,ncols+1) .ne. ans) then
                  errs = errs + 1
                  if (errs .le. 10) then
                     print *, ' buf(',i,',',ncols+1,') = ',  &
      &                         buf(i,ncols+1)
                  endif
               endif
            enddo
         endif
         call mpi_win_free( win, ierr )
         call mtestFreeComm( comm )
      enddo

      call mtest_finalize( errs )
      end