Blame test/mpi/f90/util/mtestf90.f90

Packit 0848f5
! This file created from test/mpi/f77/util/mtestf.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 MTest_Init( ierr )
Packit 0848f5
!       Place the include first so that we can automatically create a
Packit 0848f5
!       Fortran 90 version that uses the mpi module instead.  If
Packit 0848f5
!       the module is in a different place, the compiler can complain
Packit 0848f5
!       about out-of-order statements
Packit 0848f5
        use mpi
Packit 0848f5
        integer ierr
Packit 0848f5
        logical flag
Packit 0848f5
        logical dbgflag
Packit 0848f5
        integer wrank
Packit 0848f5
        common /mtest/ dbgflag, wrank
Packit 0848f5
Packit 0848f5
        call MPI_Initialized( flag, ierr )
Packit 0848f5
        if (.not. flag) then
Packit 0848f5
           call MPI_Init( ierr )
Packit 0848f5
        endif
Packit 0848f5
Packit 0848f5
        dbgflag = .false.
Packit 0848f5
        call MPI_Comm_rank( MPI_COMM_WORLD, wrank, ierr )
Packit 0848f5
        end
Packit 0848f5
!
Packit 0848f5
        subroutine MTest_Finalize( errs )
Packit 0848f5
        use mpi
Packit 0848f5
        integer errs
Packit 0848f5
        integer rank, toterrs, ierr
Packit 0848f5
        
Packit 0848f5
        call MPI_Comm_rank( MPI_COMM_WORLD, rank, ierr )
Packit 0848f5
Packit 0848f5
        call MPI_Allreduce( errs, toterrs, 1, MPI_INTEGER, MPI_SUM,  &
Packit 0848f5
      &        MPI_COMM_WORLD, ierr ) 
Packit 0848f5
        
Packit 0848f5
        if (rank .eq. 0) then
Packit 0848f5
           if (toterrs .gt. 0) then 
Packit 0848f5
                print *, " Found ", toterrs, " errors"
Packit 0848f5
           else
Packit 0848f5
                print *, " No Errors"
Packit 0848f5
           endif
Packit 0848f5
        endif
Packit 0848f5
        end
Packit 0848f5
!
Packit 0848f5
! A simple get intracomm for now
Packit 0848f5
        logical function MTestGetIntracomm( comm, min_size, qsmaller )
Packit 0848f5
        use mpi
Packit 0848f5
        integer ierr
Packit 0848f5
        integer comm, min_size, size, rank
Packit 0848f5
        logical qsmaller
Packit 0848f5
        integer myindex
Packit 0848f5
        save myindex
Packit 0848f5
        data myindex /0/
Packit 0848f5
Packit 0848f5
        comm = MPI_COMM_NULL
Packit 0848f5
        if (myindex .eq. 0) then
Packit 0848f5
           comm = MPI_COMM_WORLD
Packit 0848f5
        else if (myindex .eq. 1) then
Packit 0848f5
           call mpi_comm_dup( MPI_COMM_WORLD, comm, ierr )
Packit 0848f5
        else if (myindex .eq. 2) then
Packit 0848f5
           call mpi_comm_size( MPI_COMM_WORLD, size, ierr )
Packit 0848f5
           call mpi_comm_rank( MPI_COMM_WORLD, rank, ierr )
Packit 0848f5
           call mpi_comm_split( MPI_COMM_WORLD, 0, size - rank, comm,  &
Packit 0848f5
      &                                 ierr )
Packit 0848f5
        else
Packit 0848f5
           if (min_size .eq. 1 .and. myindex .eq. 3) then
Packit 0848f5
              comm = MPI_COMM_SELF
Packit 0848f5
           endif
Packit 0848f5
        endif
Packit 0848f5
        myindex = mod( myindex, 4 ) + 1
Packit 0848f5
        MTestGetIntracomm = comm .ne. MPI_COMM_NULL
Packit 0848f5
        end
Packit 0848f5
!
Packit 0848f5
        subroutine MTestFreeComm( comm )
Packit 0848f5
        use mpi
Packit 0848f5
        integer comm, ierr
Packit 0848f5
        if (comm .ne. MPI_COMM_WORLD .and. &
Packit 0848f5
      &      comm .ne. MPI_COMM_SELF  .and. &
Packit 0848f5
      &      comm .ne. MPI_COMM_NULL) then
Packit 0848f5
           call mpi_comm_free( comm, ierr )
Packit 0848f5
        endif
Packit 0848f5
        end
Packit 0848f5
!
Packit 0848f5
        subroutine MTestPrintError( errcode )
Packit 0848f5
        use mpi
Packit 0848f5
        integer errcode
Packit 0848f5
        integer errclass, slen, ierr
Packit 0848f5
        character*(MPI_MAX_ERROR_STRING) string
Packit 0848f5
Packit 0848f5
        call MPI_Error_class( errcode, errclass, ierr )
Packit 0848f5
        call MPI_Error_string( errcode, string, slen, ierr )
Packit 0848f5
        print *, "Error class ", errclass, "(", string(1:slen), ")"
Packit 0848f5
        end
Packit 0848f5
!
Packit 0848f5
        subroutine MTestPrintErrorMsg( msg, errcode )
Packit 0848f5
        use mpi
Packit 0848f5
        character*(*) msg
Packit 0848f5
        integer errcode
Packit 0848f5
        integer errclass, slen, ierr
Packit 0848f5
        character*(MPI_MAX_ERROR_STRING) string
Packit 0848f5
Packit 0848f5
        call MPI_Error_class( errcode, errclass, ierr )
Packit 0848f5
        call MPI_Error_string( errcode, string, slen, ierr )
Packit 0848f5
        print *, msg, ": Error class ", errclass, " &
Packit 0848f5
      &       (", string(1:slen), ")" 
Packit 0848f5
        end
Packit 0848f5
Packit 0848f5
        subroutine MTestSpawnPossible( can_spawn, errs )
Packit 0848f5
        use mpi
Packit 0848f5
        integer can_spawn
Packit 0848f5
        integer errs
Packit 0848f5
        integer(kind=MPI_ADDRESS_KIND) val
Packit 0848f5
        integer ierror
Packit 0848f5
        logical flag
Packit 0848f5
        integer comm_size
Packit 0848f5
Packit 0848f5
        call mpi_comm_get_attr( MPI_COMM_WORLD, MPI_UNIVERSE_SIZE, val, &
Packit 0848f5
      &                          flag, ierror )
Packit 0848f5
        if ( ierror .ne. MPI_SUCCESS ) then
Packit 0848f5
!       MPI_UNIVERSE_SIZE keyval missing from MPI_COMM_WORLD attributes
Packit 0848f5
            can_spawn = -1
Packit 0848f5
            errs = errs + 1
Packit 0848f5
        else
Packit 0848f5
            if ( flag ) then
Packit 0848f5
                comm_size = -1
Packit 0848f5
Packit 0848f5
                call mpi_comm_size( MPI_COMM_WORLD, comm_size, ierror )
Packit 0848f5
                if ( ierror .ne. MPI_SUCCESS ) then
Packit 0848f5
!       MPI_COMM_SIZE failed for MPI_COMM_WORLD
Packit 0848f5
                    can_spawn = -1
Packit 0848f5
                    errs = errs + 1
Packit 0848f5
                    return
Packit 0848f5
                endif
Packit 0848f5
Packit 0848f5
                if ( val .le. comm_size ) then
Packit 0848f5
!       no additional processes can be spawned
Packit 0848f5
                    can_spawn = 0
Packit 0848f5
                else
Packit 0848f5
                    can_spawn = 1
Packit 0848f5
                endif
Packit 0848f5
            else
Packit 0848f5
!       No attribute associated with key MPI_UNIVERSE_SIZE of MPI_COMM_WORLD
Packit 0848f5
                can_spawn = -1
Packit 0848f5
            endif
Packit 0848f5
        endif
Packit 0848f5
        end