Blame test/mpi/f90/attr/commattrf90.f90

Packit 0848f5
! This file created from test/mpi/f77/attr/commattrf.f with f77tof90
Packit 0848f5
! -*- Mode: Fortran; -*- 
Packit 0848f5
!
Packit 0848f5
!  (C) 2003 by Argonne National Laboratory.
Packit 0848f5
!      See COPYRIGHT in top-level directory.
Packit 0848f5
!
Packit 0848f5
      program main
Packit 0848f5
      use mpi
Packit 0848f5
      integer errs, ierr
Packit 0848f5
      integer (kind=MPI_ADDRESS_KIND) extrastate, valin, valout, val
Packit 0848f5
Packit 0848f5
      integer comm1, comm2
Packit 0848f5
      integer curcount, keyval
Packit 0848f5
      logical flag
Packit 0848f5
      external mycopyfn, mydelfn
Packit 0848f5
      integer callcount, delcount
Packit 0848f5
      common /myattr/ callcount, delcount
Packit 0848f5
!
Packit 0848f5
! The only difference between the MPI-2 and MPI-1 attribute caching
Packit 0848f5
! routines in Fortran is that the take an address-sized integer
Packit 0848f5
! instead of a simple integer.  These still are not pointers,
Packit 0848f5
! so the values are still just integers. 
Packit 0848f5
!
Packit 0848f5
      errs      = 0
Packit 0848f5
      callcount = 0
Packit 0848f5
      delcount  = 0
Packit 0848f5
      call mtest_init( ierr )
Packit 0848f5
      call mpi_comm_dup( MPI_COMM_WORLD, comm1, ierr )
Packit 0848f5
! 
Packit 0848f5
      extrastate = 1001
Packit 0848f5
      call mpi_comm_create_keyval( mycopyfn, mydelfn, keyval,  &
Packit 0848f5
      &                             extrastate, ierr )
Packit 0848f5
      flag = .true.
Packit 0848f5
      call mpi_comm_get_attr( comm1, keyval, valout, flag, ierr )
Packit 0848f5
      if (flag) then
Packit 0848f5
         errs = errs + 1
Packit 0848f5
         print *, ' get attr returned true when no attr set'
Packit 0848f5
      endif
Packit 0848f5
Packit 0848f5
      valin = 2003
Packit 0848f5
      call mpi_comm_set_attr( comm1, keyval, valin, ierr )
Packit 0848f5
      flag = .false.
Packit 0848f5
      valout = -1
Packit 0848f5
      call mpi_comm_get_attr( comm1, keyval, valout, flag, ierr )
Packit 0848f5
      if (valout .ne. 2003) then
Packit 0848f5
         errs = errs + 1
Packit 0848f5
         print *, 'Unexpected value (should be 2003)', valout,  &
Packit 0848f5
      &            ' from attr'
Packit 0848f5
      endif
Packit 0848f5
      
Packit 0848f5
      valin = 2001
Packit 0848f5
      call mpi_comm_set_attr( comm1, keyval, valin, ierr )
Packit 0848f5
      flag = .false.
Packit 0848f5
      valout = -1
Packit 0848f5
      call mpi_comm_get_attr( comm1, keyval, valout, flag, ierr )
Packit 0848f5
      if (valout .ne. 2001) then
Packit 0848f5
         errs = errs + 1
Packit 0848f5
         print *, 'Unexpected value (should be 2001)', valout,  &
Packit 0848f5
      &            ' from attr'
Packit 0848f5
      endif
Packit 0848f5
      
Packit 0848f5
!
Packit 0848f5
! Test the copy function
Packit 0848f5
      valin = 5001
Packit 0848f5
      call mpi_comm_set_attr( comm1, keyval, valin, ierr )
Packit 0848f5
      call mpi_comm_dup( comm1, comm2, ierr )
Packit 0848f5
      flag = .false.
Packit 0848f5
      call mpi_comm_get_attr( comm1, keyval, valout, flag, ierr )
Packit 0848f5
      if (valout .ne. 5001) then
Packit 0848f5
         errs = errs + 1
Packit 0848f5
         print *, 'Unexpected output value in comm ', valout
Packit 0848f5
      endif
Packit 0848f5
      flag = .false.
Packit 0848f5
      call mpi_comm_get_attr( comm2, keyval, valout, flag, ierr )
Packit 0848f5
      if (valout .ne. 5003) then
Packit 0848f5
         errs = errs + 1
Packit 0848f5
         print *, 'Unexpected output value in comm2 ', valout
Packit 0848f5
      endif
Packit 0848f5
! Test the delete function      
Packit 0848f5
      curcount = delcount
Packit 0848f5
      call mpi_comm_free( comm2, ierr )
Packit 0848f5
      if (delcount .ne. curcount + 1) then
Packit 0848f5
         errs = errs + 1
Packit 0848f5
         print *, ' did not get expected value of delcount ',  &
Packit 0848f5
      &          delcount, curcount + 1
Packit 0848f5
      endif
Packit 0848f5
!
Packit 0848f5
! Test the attr delete function
Packit 0848f5
      call mpi_comm_dup( comm1, comm2, ierr )
Packit 0848f5
      valin      = 6001
Packit 0848f5
      extrastate = 1001
Packit 0848f5
      call mpi_comm_set_attr( comm2, keyval, valin, ierr )
Packit 0848f5
      delcount   = 0
Packit 0848f5
      call mpi_comm_delete_attr( comm2, keyval, ierr )
Packit 0848f5
      if (delcount .ne. 1) then
Packit 0848f5
         errs = errs + 1
Packit 0848f5
         print *, ' Delete_attr did not call delete function'
Packit 0848f5
      endif
Packit 0848f5
      flag = .true.
Packit 0848f5
      call mpi_comm_get_attr( comm2, keyval, valout, flag, ierr )
Packit 0848f5
      if (flag) then
Packit 0848f5
         errs = errs + 1
Packit 0848f5
         print *, ' Delete_attr did not delete attribute'
Packit 0848f5
      endif
Packit 0848f5
      call mpi_comm_free( comm2, ierr )
Packit 0848f5
!
Packit 0848f5
      ierr = -1
Packit 0848f5
      call mpi_comm_free_keyval( keyval, ierr )
Packit 0848f5
      if (ierr .ne. MPI_SUCCESS) then
Packit 0848f5
         errs = errs + 1
Packit 0848f5
         call mtestprinterror( ierr )
Packit 0848f5
      endif
Packit 0848f5
      call mpi_comm_free( comm1, ierr )
Packit 0848f5
Packit 0848f5
      call mtest_finalize( errs )
Packit 0848f5
      call mpi_finalize( ierr )
Packit 0848f5
      end
Packit 0848f5
!
Packit 0848f5
      subroutine mycopyfn( oldcomm, keyval, extrastate, valin, valout, &
Packit 0848f5
      &                     flag, ierr )
Packit 0848f5
      use mpi
Packit 0848f5
      integer oldcomm, keyval, ierr
Packit 0848f5
      integer (kind=MPI_ADDRESS_KIND) extrastate, valin, valout, val
Packit 0848f5
Packit 0848f5
      logical flag
Packit 0848f5
      integer callcount, delcount
Packit 0848f5
      common /myattr/ callcount, delcount
Packit 0848f5
! increment the attribute by 2
Packit 0848f5
      valout = valin + 2
Packit 0848f5
      callcount = callcount + 1
Packit 0848f5
      if (extrastate .eq. 1001) then
Packit 0848f5
         flag = .true.
Packit 0848f5
         ierr = MPI_SUCCESS
Packit 0848f5
      else
Packit 0848f5
         print *, ' Unexpected value of extrastate = ', extrastate
Packit 0848f5
         flag = .false.
Packit 0848f5
         ierr = MPI_ERR_OTHER
Packit 0848f5
      endif
Packit 0848f5
      end
Packit 0848f5
!
Packit 0848f5
      subroutine mydelfn( comm, keyval, val, extrastate, ierr )
Packit 0848f5
      use mpi
Packit 0848f5
      integer comm, keyval, ierr
Packit 0848f5
      integer (kind=MPI_ADDRESS_KIND) extrastate, valin, valout, val
Packit 0848f5
Packit 0848f5
      integer callcount, delcount
Packit 0848f5
      common /myattr/ callcount, delcount
Packit 0848f5
      delcount = delcount + 1
Packit 0848f5
      if (extrastate .eq. 1001) then
Packit 0848f5
         ierr = MPI_SUCCESS
Packit 0848f5
      else
Packit 0848f5
         print *, ' Unexpected value of extrastate = ', extrastate
Packit 0848f5
         ierr = MPI_ERR_OTHER
Packit 0848f5
      endif
Packit 0848f5
      end