Blame test/mpi/f08/pt2pt/greqf08.f90

Packit 0848f5
! This file created from test/mpi/f77/pt2pt/greqf.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
      subroutine query_fn( extrastate, status, ierr )
Packit 0848f5
      use mpi_f08
Packit 0848f5
      TYPE(MPI_Status) status
Packit 0848f5
      integer ierr
Packit 0848f5
      integer (kind=MPI_ADDRESS_KIND) extrastate, valin, valout, val
Packit 0848f5
      logical flag
Packit 0848f5
Packit 0848f5
!
Packit 0848f5
!    set a default status
Packit 0848f5
      status%MPI_SOURCE = MPI_UNDEFINED
Packit 0848f5
      status%MPI_TAG    = MPI_UNDEFINED
Packit 0848f5
      flag = .false.
Packit 0848f5
      call mpi_status_set_cancelled( status, flag, ierr)
Packit 0848f5
      call mpi_status_set_elements( status, MPI_BYTE, 0, ierr )
Packit 0848f5
      ierr = MPI_SUCCESS
Packit 0848f5
      end
Packit 0848f5
!
Packit 0848f5
      subroutine free_fn( extrastate, ierr )
Packit 0848f5
      use mpi_f08
Packit 0848f5
      integer value, ierr
Packit 0848f5
      integer (kind=MPI_ADDRESS_KIND) extrastate, valin, valout, val
Packit 0848f5
Packit 0848f5
      integer freefncall
Packit 0848f5
      common /fnccalls/ freefncall
Packit 0848f5
!
Packit 0848f5
!   For testing purposes, the following print can be used to check whether
Packit 0848f5
!   the free_fn is called
Packit 0848f5
!      print *, 'Free_fn called'
Packit 0848f5
!
Packit 0848f5
      extrastate = extrastate - 1
Packit 0848f5
!   The value returned by the free function is the error code
Packit 0848f5
!   returned by the wait/test function
Packit 0848f5
      ierr = MPI_SUCCESS
Packit 0848f5
      end
Packit 0848f5
!
Packit 0848f5
      subroutine cancel_fn( extrastate, complete, ierr )
Packit 0848f5
      use mpi_f08
Packit 0848f5
      integer ierr
Packit 0848f5
      logical complete
Packit 0848f5
      integer (kind=MPI_ADDRESS_KIND) extrastate, valin, valout, val
Packit 0848f5
Packit 0848f5
Packit 0848f5
      ierr = MPI_SUCCESS
Packit 0848f5
      end
Packit 0848f5
!
Packit 0848f5
!
Packit 0848f5
! This is a very simple test of generalized requests.  Normally, the
Packit 0848f5
! MPI_Grequest_complete function would be called from another routine,
Packit 0848f5
! often running in a separate thread.  This simple code allows us to
Packit 0848f5
! check that requests can be created, tested, and waited on in the
Packit 0848f5
! case where the request is complete before the wait is called.
Packit 0848f5
!
Packit 0848f5
! Note that MPI did *not* define a routine that can be called within
Packit 0848f5
! test or wait to advance the state of a generalized request.
Packit 0848f5
! Most uses of generalized requests will need to use a separate thread.
Packit 0848f5
!
Packit 0848f5
       program main
Packit 0848f5
       use mpi_f08
Packit 0848f5
       integer errs, ierr
Packit 0848f5
       logical flag
Packit 0848f5
       TYPE(MPI_Status) status
Packit 0848f5
       TYPE(MPI_Request) request
Packit 0848f5
       external query_fn, free_fn, cancel_fn
Packit 0848f5
       integer (kind=MPI_ADDRESS_KIND) extrastate, valin, valout, val
Packit 0848f5
Packit 0848f5
       integer freefncall
Packit 0848f5
       common /fnccalls/ freefncall
Packit 0848f5
Packit 0848f5
       errs = 0
Packit 0848f5
       freefncall = 0
Packit 0848f5
Packit 0848f5
       call MTest_Init( ierr )
Packit 0848f5
Packit 0848f5
       extrastate = 0
Packit 0848f5
       call mpi_grequest_start( query_fn, free_fn, cancel_fn,  &
Packit 0848f5
      &            extrastate, request, ierr )
Packit 0848f5
       call mpi_test( request, flag, status, ierr )
Packit 0848f5
       if (flag) then
Packit 0848f5
          errs = errs + 1
Packit 0848f5
          print *, 'Generalized request marked as complete'
Packit 0848f5
       endif
Packit 0848f5
Packit 0848f5
       call mpi_grequest_complete( request, ierr )
Packit 0848f5
Packit 0848f5
       call MPI_Wait( request, status, ierr )
Packit 0848f5
Packit 0848f5
       extrastate = 1
Packit 0848f5
       call mpi_grequest_start( query_fn, free_fn, cancel_fn,  &
Packit 0848f5
      &                          extrastate, request, ierr )
Packit 0848f5
       call mpi_grequest_complete( request, ierr )
Packit 0848f5
       call mpi_wait( request, MPI_STATUS_IGNORE, ierr )
Packit 0848f5
!
Packit 0848f5
!      The following routine may prevent an optimizing compiler from
Packit 0848f5
!      just remembering that extrastate was set in grequest_start
Packit 0848f5
       call dummyupdate(extrastate)
Packit 0848f5
       if (extrastate .ne. 0) then
Packit 0848f5
          errs = errs + 1
Packit 0848f5
          if (freefncall .eq. 0) then
Packit 0848f5
              print *, 'Free routine not called'
Packit 0848f5
          else
Packit 0848f5
              print *, 'Free routine did not update extra_data'
Packit 0848f5
              print *, 'extrastate = ', extrastate
Packit 0848f5
          endif
Packit 0848f5
       endif
Packit 0848f5
!
Packit 0848f5
       call MTest_Finalize( errs )
Packit 0848f5
       call mpi_finalize( ierr )
Packit 0848f5
       end
Packit 0848f5
!