Blame test/mpi/f90/rma/winattrf90.f90

Packit Service c5cf8c
! This file created from f77/rma/winattrf.f with f77tof90
Packit Service c5cf8c
! -*- Mode: Fortran; -*- 
Packit Service c5cf8c
!
Packit Service c5cf8c
!  (C) 2003 by Argonne National Laboratory.
Packit Service c5cf8c
!      See COPYRIGHT in top-level directory.
Packit Service c5cf8c
!
Packit Service c5cf8c
      program main
Packit Service c5cf8c
      use mpi
Packit Service c5cf8c
      integer errs, ierr
Packit Service c5cf8c
      integer (kind=MPI_ADDRESS_KIND) extrastate, valin, valout, val
Packit Service c5cf8c
Packit Service c5cf8c
      integer comm, win, buf(10)
Packit Service c5cf8c
      integer curcount, keyval
Packit Service c5cf8c
      logical flag
Packit Service c5cf8c
      external mycopyfn, mydelfn
Packit Service c5cf8c
      integer callcount, delcount
Packit Service c5cf8c
      common /myattr/ callcount, delcount
Packit Service c5cf8c
!
Packit Service c5cf8c
! The only difference between the MPI-2 and MPI-1 attribute caching
Packit Service c5cf8c
! routines in Fortran is that the take an address-sized integer
Packit Service c5cf8c
! instead of a simple integer.  These still are not pointers,
Packit Service c5cf8c
! so the values are still just integers. 
Packit Service c5cf8c
!
Packit Service c5cf8c
      errs      = 0
Packit Service c5cf8c
      callcount = 0
Packit Service c5cf8c
      delcount  = 0
Packit Service c5cf8c
      call mtest_init( ierr )
Packit Service c5cf8c
      call mpi_comm_dup( MPI_COMM_WORLD, comm, ierr )
Packit Service c5cf8c
! Create a new window; use val for an address-sized int
Packit Service c5cf8c
      val = 10
Packit Service c5cf8c
      call mpi_win_create( buf, val, 1, &
Packit Service c5cf8c
      &                        MPI_INFO_NULL, comm, win, ierr )
Packit Service c5cf8c
! 
Packit Service c5cf8c
      extrastate = 1001
Packit Service c5cf8c
      call mpi_win_create_keyval( mycopyfn, mydelfn, keyval,  &
Packit Service c5cf8c
      &                             extrastate, ierr )
Packit Service c5cf8c
      flag = .true.
Packit Service c5cf8c
      call mpi_win_get_attr( win, keyval, valout, flag, ierr )
Packit Service c5cf8c
      if (flag) then
Packit Service c5cf8c
         errs = errs + 1
Packit Service c5cf8c
         print *, ' get attr returned true when no attr set'
Packit Service c5cf8c
      endif
Packit Service c5cf8c
Packit Service c5cf8c
      valin = 2003
Packit Service c5cf8c
      call mpi_win_set_attr( win, keyval, valin, ierr )
Packit Service c5cf8c
      flag = .false.
Packit Service c5cf8c
      valout = -1
Packit Service c5cf8c
      call mpi_win_get_attr( win, keyval, valout, flag, ierr )
Packit Service c5cf8c
      if (valout .ne. 2003) then
Packit Service c5cf8c
         errs = errs + 1
Packit Service c5cf8c
         print *, 'Unexpected value (should be 2003)', valout,  &
Packit Service c5cf8c
      &            ' from attr'
Packit Service c5cf8c
      endif
Packit Service c5cf8c
      
Packit Service c5cf8c
      valin = 2001
Packit Service c5cf8c
      call mpi_win_set_attr( win, keyval, valin, ierr )
Packit Service c5cf8c
      flag = .false.
Packit Service c5cf8c
      valout = -1
Packit Service c5cf8c
      call mpi_win_get_attr( win, keyval, valout, flag, ierr )
Packit Service c5cf8c
      if (valout .ne. 2001) then
Packit Service c5cf8c
         errs = errs + 1
Packit Service c5cf8c
         print *, 'Unexpected value (should be 2001)', valout,  &
Packit Service c5cf8c
      &            ' from attr'
Packit Service c5cf8c
      endif
Packit Service c5cf8c
!
Packit Service c5cf8c
! Test the attr delete function
Packit Service c5cf8c
      delcount   = 0
Packit Service c5cf8c
      call mpi_win_delete_attr( win, keyval, ierr )
Packit Service c5cf8c
      if (delcount .ne. 1) then
Packit Service c5cf8c
         errs = errs + 1
Packit Service c5cf8c
         print *, ' Delete_attr did not call delete function'
Packit Service c5cf8c
      endif
Packit Service c5cf8c
      flag = .true.
Packit Service c5cf8c
      call mpi_win_get_attr( win, keyval, valout, flag, ierr )
Packit Service c5cf8c
      if (flag) then
Packit Service c5cf8c
         errs = errs + 1
Packit Service c5cf8c
         print *, ' Delete_attr did not delete attribute'
Packit Service c5cf8c
      endif
Packit Service c5cf8c
      
Packit Service c5cf8c
! Test the delete function on window free
Packit Service c5cf8c
      valin = 2001
Packit Service c5cf8c
      call mpi_win_set_attr( win, keyval, valin, ierr )
Packit Service c5cf8c
      curcount = delcount
Packit Service c5cf8c
      call mpi_win_free( win, ierr )
Packit Service c5cf8c
      if (delcount .ne. curcount + 1) then
Packit Service c5cf8c
         errs = errs + 1
Packit Service c5cf8c
         print *, ' did not get expected value of delcount ',  &
Packit Service c5cf8c
      &          delcount, curcount + 1
Packit Service c5cf8c
      endif
Packit Service c5cf8c
Packit Service c5cf8c
      ierr = -1
Packit Service c5cf8c
      call mpi_win_free_keyval( keyval, ierr )
Packit Service c5cf8c
      if (ierr .ne. MPI_SUCCESS) then
Packit Service c5cf8c
         errs = errs + 1
Packit Service c5cf8c
         call mtestprinterror( ierr )
Packit Service c5cf8c
      endif
Packit Service c5cf8c
!
Packit Service c5cf8c
! The MPI standard defines null copy and duplicate functions.
Packit Service c5cf8c
! However, are only used when an object is duplicated.  Since
Packit Service c5cf8c
! MPI_Win objects cannot be duplicated, so under normal circumstances,
Packit Service c5cf8c
! these will not be called.  Since they are defined, they should behave
Packit Service c5cf8c
! as defined.  To test them, we simply call them here
Packit Service c5cf8c
      flag   = .false.
Packit Service c5cf8c
      valin  = 7001
Packit Service c5cf8c
      valout = -1
Packit Service c5cf8c
      ierr   = -1
Packit Service c5cf8c
      call MPI_WIN_DUP_FN( win, keyval, extrastate, valin, valout, &
Packit Service c5cf8c
      &     flag, ierr ) 
Packit Service c5cf8c
      if (.not. flag) then
Packit Service c5cf8c
         errs = errs + 1
Packit Service c5cf8c
         print *, " Flag was false after MPI_WIN_DUP_FN"
Packit Service c5cf8c
      else if (valout .ne. 7001) then
Packit Service c5cf8c
         errs = errs + 1
Packit Service c5cf8c
         if (valout .eq. -1 ) then
Packit Service c5cf8c
          print *, " output attr value was not copied in MPI_WIN_DUP_FN" 
Packit Service c5cf8c
         endif
Packit Service c5cf8c
         print *, " value was ", valout, " but expected 7001"
Packit Service c5cf8c
      else if (ierr .ne. MPI_SUCCESS) then
Packit Service c5cf8c
         errs = errs + 1
Packit Service c5cf8c
         print *, " MPI_WIN_DUP_FN did not return MPI_SUCCESS"
Packit Service c5cf8c
      endif
Packit Service c5cf8c
Packit Service c5cf8c
      flag   = .true.
Packit Service c5cf8c
      valin  = 7001
Packit Service c5cf8c
      valout = -1
Packit Service c5cf8c
      ierr   = -1
Packit Service c5cf8c
      call MPI_WIN_NULL_COPY_FN( win, keyval, extrastate, valin, valout &
Packit Service c5cf8c
      &     ,flag, ierr ) 
Packit Service c5cf8c
      if (flag) then
Packit Service c5cf8c
         errs = errs + 1
Packit Service c5cf8c
         print *, " Flag was true after MPI_WIN_NULL_COPY_FN"
Packit Service c5cf8c
      else if (valout .ne. -1) then
Packit Service c5cf8c
         errs = errs + 1
Packit Service c5cf8c
         print *, &
Packit Service c5cf8c
      &        " output attr value was copied in MPI_WIN_NULL_COPY_FN" 
Packit Service c5cf8c
      else if (ierr .ne. MPI_SUCCESS) then
Packit Service c5cf8c
         errs = errs + 1
Packit Service c5cf8c
         print *, " MPI_WIN_NULL_COPY_FN did not return MPI_SUCCESS"
Packit Service c5cf8c
      endif
Packit Service c5cf8c
!
Packit Service c5cf8c
      call mpi_comm_free( comm, ierr )
Packit Service c5cf8c
      call mtest_finalize( errs )
Packit Service c5cf8c
      end
Packit Service c5cf8c
!
Packit Service c5cf8c
! Note that the copyfn is unused for MPI windows, since there is
Packit Service c5cf8c
! (and because of alias rules, can be) no MPI_Win_dup function
Packit Service c5cf8c
      subroutine mycopyfn( oldwin, keyval, extrastate, valin, valout, &
Packit Service c5cf8c
      &                     flag, ierr )
Packit Service c5cf8c
      use mpi
Packit Service c5cf8c
      integer oldwin, keyval, ierr
Packit Service c5cf8c
      integer (kind=MPI_ADDRESS_KIND) extrastate, valin, valout, val
Packit Service c5cf8c
Packit Service c5cf8c
      logical flag
Packit Service c5cf8c
      integer callcount, delcount
Packit Service c5cf8c
      common /myattr/ callcount, delcount
Packit Service c5cf8c
! increment the attribute by 2
Packit Service c5cf8c
      valout = valin + 2
Packit Service c5cf8c
      callcount = callcount + 1
Packit Service c5cf8c
!
Packit Service c5cf8c
! Since we should *never* call this, indicate an error
Packit Service c5cf8c
      print *, ' Unexpected use of mycopyfn'
Packit Service c5cf8c
      flag = .false.
Packit Service c5cf8c
      ierr = MPI_ERR_OTHER
Packit Service c5cf8c
      end
Packit Service c5cf8c
!
Packit Service c5cf8c
      subroutine mydelfn( win, keyval, val, extrastate, ierr )
Packit Service c5cf8c
      use mpi
Packit Service c5cf8c
      integer win, keyval, ierr
Packit Service c5cf8c
      integer (kind=MPI_ADDRESS_KIND) extrastate, valin, valout, val
Packit Service c5cf8c
Packit Service c5cf8c
      integer callcount, delcount
Packit Service c5cf8c
      common /myattr/ callcount, delcount
Packit Service c5cf8c
      delcount = delcount + 1
Packit Service c5cf8c
      if (extrastate .eq. 1001) then
Packit Service c5cf8c
         ierr = MPI_SUCCESS
Packit Service c5cf8c
      else
Packit Service c5cf8c
         print *, ' Unexpected value of extrastate = ', extrastate
Packit Service c5cf8c
         ierr = MPI_ERR_OTHER
Packit Service c5cf8c
      endif
Packit Service c5cf8c
      end