I've got a strange problem with Fortran90 and MPI_BCAST call on a large
application. I've isolated the problem in this short program samples.
With fortran we can use subarrays in functions calls. Example, with passing a subarray to
the "change" procedure:
MODULE mymod
IMPLICIT NONE
CONTAINS
SUBROUTINE change(tab,i)
IMPLICIT NONE
INTEGER, INTENT(INOUT),DIMENSION(:)::tab
INTEGER, INTENT(IN) :: i
tab(:)=i
END SUBROUTINE change
END MODULE mymod
PROGRAM toto
USE mymod
IMPLICIT NONE
INTEGER, PARAMETER::nx=6, ny=4
INTEGER, DIMENSION(nx,ny):: tab
INTEGER::i
tab=-1
DO i=1,nx
CALL change(tab(i,:),i)
ENDDO
PRINT*,tab
END PROGRAM toto
But If I use subarrays with MPI_BCAST() like in this example:
PROGRAM bide
USE mpi
IMPLICIT NONE
INTEGER :: nbcpus
INTEGER :: my_rank
INTEGER :: ierr,i,buf
INTEGER, ALLOCATABLE:: tab(:,:)
CALL MPI_INIT(ierr)
CALL MPI_COMM_RANK(MPI_COMM_WORLD,my_rank,ierr)
CALL MPI_COMM_SIZE(MPI_COMM_WORLD,nbcpus,ierr)
ALLOCATE (tab(0:nbcpus-1,4))
tab(:,:)=-1
tab(my_rank,:)=my_rank
DO i=0,nbcpus-1
CALL MPI_BCAST(tab(i,:),4,MPI_INTEGER,i,MPI_COMM_WORLD,ierr)
ENDDO
IF (my_rank .EQ. 0) print*,tab
CALL MPI_FINALIZE(ierr)
END PROGRAM bide
It doesn't work! With openMPI 1.2.8 (OpenSuse 11.4 X86_64) I have random
segfault: it works sometime, with few cpus (2, 4, 8...) and does'nt work
sometime with a larger number of cpus (32, 48, 64...). With OpenMPI 1.4.4
(build from sources) it hangs (most of the array tab remains at the -1
initialization value).
Such procedure calls are allowed with fortran90 so I do not understand why they
fail here. I have to use a buffer array (called tabl in the following program)
to solve the problem.
PROGRAM bide
USE mpi
IMPLICIT NONE
INTEGER :: nbcpus
INTEGER :: my_rank
INTEGER :: ierr,i,buf
INTEGER, ALLOCATABLE:: tab(:,:)
INTEGER::tab1(4)
CALL MPI_INIT(ierr)
CALL MPI_COMM_RANK(MPI_COMM_WORLD,my_rank,ierr)
CALL MPI_COMM_SIZE(MPI_COMM_WORLD,nbcpus,ierr)
ALLOCATE (tab(0:nbcpus-1,4))
tab=-1
tab1=-1
DO i=0,nbcpus-1
IF(my_rank.EQ.i) tab1=my_rank
CALL MPI_BCAST(tab1,4,MPI_INTEGER,i,MPI_COMM_WORLD,ierr)
tab(i,:)=tab1
ENDDO
IF (my_rank .EQ. 0) print*,tab
CALL MPI_FINALIZE(ierr)
END PROGRAM bide
Any idea about this behavior ?
Patrick
--
===============================================================
| Equipe M.O.S.T. |
http://most.hmg.inpg.fr
|
| Patrick BEGOU | ------------ |
| LEGI |
mailto:patrick.be...@hmg.inpg.fr
|
| BP 53 X | Tel 04 76 82 51 35 |
| 38041 GRENOBLE CEDEX | Fax 04 76 82 52 71 |
===============================================================
_______________________________________________
users mailing list
us...@open-mpi.org
http://www.open-mpi.org/mailman/listinfo.cgi/users