Blame test/mpi/f90/attr/commattr4f90.f90

Packit 0848f5
! This file created from test/mpi/f77/attr/commattr4f.f with f77tof90
Packit 0848f5
! -*- Mode: Fortran; -*- 
Packit 0848f5
!
Packit 0848f5
!  (C) 2015 by Argonne National Laboratory.
Packit 0848f5
!      See COPYRIGHT in top-level directory.
Packit 0848f5
!
Packit 0848f5
      program main
Packit 0848f5
!
Packit 0848f5
      use mpi
Packit 0848f5
Packit 0848f5
      integer    ierr
Packit 0848f5
      integer    errs
Packit 0848f5
      logical    found
Packit 0848f5
      integer    comm2
Packit 0848f5
      integer    key
Packit 0848f5
      integer (kind=MPI_ADDRESS_KIND) extrastate, valin, valout, val
Packit 0848f5
Packit 0848f5
Packit 0848f5
      errs = 0
Packit 0848f5
!
Packit 0848f5
!  initialize the mpi environment
Packit 0848f5
!
Packit 0848f5
      call mpi_init(ierr)
Packit 0848f5
Packit 0848f5
      call mpi_comm_create_keyval(MPI_COMM_DUP_FN, &
Packit 0848f5
      &     MPI_NULL_DELETE_FN, &
Packit 0848f5
      &     key, &
Packit 0848f5
      &     extrastate, &
Packit 0848f5
      &     ierr)
Packit 0848f5
!
Packit 0848f5
!  set a value for the attribute
Packit 0848f5
!
Packit 0848f5
      valin = huge(valin)
Packit 0848f5
!
Packit 0848f5
!  set attr in comm_world
Packit 0848f5
!
Packit 0848f5
      call mpi_comm_set_attr(MPI_COMM_WORLD, &
Packit 0848f5
      &     key, &
Packit 0848f5
      &     valin, &
Packit 0848f5
      &     ierr)
Packit 0848f5
      call mpi_comm_get_attr(MPI_COMM_WORLD, &
Packit 0848f5
      &     key, &
Packit 0848f5
      &     valout, &
Packit 0848f5
      &     found, &
Packit 0848f5
      &     ierr)
Packit 0848f5
      if (found .neqv. .true.) then
Packit 0848f5
         print *, "mpi_comm_set_attr reported key, but not found on ", &
Packit 0848f5
      &        "mpi_comm_world"
Packit 0848f5
         errs = errs + 1
Packit 0848f5
      else if (valout .ne. valin) then
Packit 0848f5
         print *, "key found, but valin does not match valout"
Packit 0848f5
         print *, valout, " != ", valin
Packit 0848f5
         errs = errs + 1
Packit 0848f5
      end if
Packit 0848f5
!
Packit 0848f5
!  dup the communicator, attribute should follow
Packit 0848f5
!
Packit 0848f5
      call mpi_comm_dup(MPI_COMM_WORLD, &
Packit 0848f5
      &     comm2, &
Packit 0848f5
      &     ierr)
Packit 0848f5
!
Packit 0848f5
!  get the value for the attribute
Packit 0848f5
!
Packit 0848f5
      call mpi_comm_get_attr(comm2, &
Packit 0848f5
      &     key, &
Packit 0848f5
      &     valout, &
Packit 0848f5
      &     found, &
Packit 0848f5
      &     ierr)
Packit 0848f5
      if (found .neqv. .true.) then
Packit 0848f5
         print *, "mpi_comm_set_attr reported key, but not found on ", &
Packit 0848f5
      &        "duped comm"
Packit 0848f5
         errs = errs + 1
Packit 0848f5
      else if (valout .ne. valin) then
Packit 0848f5
         print *, "key found, but value does not match that on ", &
Packit 0848f5
      &        "mpi_comm_world"
Packit 0848f5
         print *, valout, " != ", valin
Packit 0848f5
         errs = errs + 1
Packit 0848f5
      end if
Packit 0848f5
!
Packit 0848f5
!     free the duped communicator
Packit 0848f5
!
Packit 0848f5
      call mpi_comm_free(comm2, ierr)
Packit 0848f5
!
Packit 0848f5
!     free keyval
Packit 0848f5
!
Packit 0848f5
      call mpi_comm_delete_attr(MPI_COMM_WORLD, &
Packit 0848f5
      &     key, ierr)
Packit 0848f5
      call mpi_comm_free_keyval(key, &
Packit 0848f5
      &     ierr)
Packit 0848f5
      call mpi_finalize(ierr)
Packit 0848f5
Packit 0848f5
      if (errs .eq. 0) then
Packit 0848f5
         print *, " No Errors"
Packit 0848f5
      end if
Packit 0848f5
Packit 0848f5
      end