|
Packit |
0848f5 |
! This file created from test/mpi/f77/spawn/spawnf.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, err
|
|
Packit |
0848f5 |
integer rank, size, rsize, i
|
|
Packit |
0848f5 |
integer np
|
|
Packit |
0848f5 |
integer errcodes(2)
|
|
Packit |
0848f5 |
integer parentcomm, intercomm
|
|
Packit |
0848f5 |
integer status(MPI_STATUS_SIZE)
|
|
Packit |
0848f5 |
integer ierr
|
|
Packit |
0848f5 |
integer can_spawn
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
errs = 0
|
|
Packit |
0848f5 |
np = 2
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
call MTest_Init( ierr )
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
call MTestSpawnPossible( can_spawn, errs )
|
|
Packit |
0848f5 |
if ( can_spawn .eq. 0 ) then
|
|
Packit |
0848f5 |
call MTest_Finalize( errs )
|
|
Packit |
0848f5 |
goto 300
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
call MPI_Comm_get_parent( parentcomm, ierr )
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
if (parentcomm .eq. MPI_COMM_NULL) then
|
|
Packit |
0848f5 |
! Create 2 more processes
|
|
Packit |
0848f5 |
call MPI_Comm_spawn( "./spawnf90", MPI_ARGV_NULL, np, &
|
|
Packit |
0848f5 |
& MPI_INFO_NULL, 0, MPI_COMM_WORLD, intercomm, errcodes &
|
|
Packit |
0848f5 |
& ,ierr )
|
|
Packit |
0848f5 |
else
|
|
Packit |
0848f5 |
intercomm = parentcomm
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
! We now have a valid intercomm
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
call MPI_Comm_remote_size( intercomm, rsize, ierr )
|
|
Packit |
0848f5 |
call MPI_Comm_size( intercomm, size, ierr )
|
|
Packit |
0848f5 |
call MPI_Comm_rank( intercomm, rank, ierr )
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
if (parentcomm .eq. MPI_COMM_NULL) then
|
|
Packit |
0848f5 |
! Master
|
|
Packit |
0848f5 |
if (rsize .ne. np) then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
print *, "Did not create ", np, " processes (got ", rsize, &
|
|
Packit |
0848f5 |
& ")"
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
if (rank .eq. 0) then
|
|
Packit |
0848f5 |
do i=0,rsize-1
|
|
Packit |
0848f5 |
call MPI_Send( i, 1, MPI_INTEGER, i, 0, intercomm, ierr &
|
|
Packit |
0848f5 |
& )
|
|
Packit |
0848f5 |
enddo
|
|
Packit |
0848f5 |
! We could use intercomm reduce to get the errors from the
|
|
Packit |
0848f5 |
! children, but we'll use a simpler loop to make sure that
|
|
Packit |
0848f5 |
! we get valid data
|
|
Packit |
0848f5 |
do i=0, rsize-1
|
|
Packit |
0848f5 |
call MPI_Recv( err, 1, MPI_INTEGER, i, 1, intercomm, &
|
|
Packit |
0848f5 |
& MPI_STATUS_IGNORE, ierr )
|
|
Packit |
0848f5 |
errs = errs + err
|
|
Packit |
0848f5 |
enddo
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
else
|
|
Packit |
0848f5 |
! Child
|
|
Packit |
0848f5 |
if (size .ne. np) then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
print *, "(Child) Did not create ", np, " processes (got " &
|
|
Packit |
0848f5 |
& ,size, ")"
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
call MPI_Recv( i, 1, MPI_INTEGER, 0, 0, intercomm, status, &
|
|
Packit |
0848f5 |
& ierr )
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
if (i .ne. rank) then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
print *, "Unexpected rank on child ", rank, "(",i,")"
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
! Send the errs back to the master process
|
|
Packit |
0848f5 |
call MPI_Ssend( errs, 1, MPI_INTEGER, 0, 1, intercomm, ierr )
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
! It isn't necessary to free the intercomm, but it should not hurt
|
|
Packit |
0848f5 |
call MPI_Comm_free( intercomm, ierr )
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
! Note that the MTest_Finalize get errs only over COMM_WORLD
|
|
Packit |
0848f5 |
! Note also that both the parent and child will generate "No
|
|
Packit |
0848f5 |
! Errors" if both call MTest_Finalize
|
|
Packit |
0848f5 |
if (parentcomm .eq. MPI_COMM_NULL) then
|
|
Packit |
0848f5 |
call MTest_Finalize( errs )
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
300 continue
|
|
Packit |
0848f5 |
call MPI_Finalize( ierr )
|
|
Packit |
0848f5 |
end
|