Hi Nehemiah

The OpenMPI mailing list searchable archive:

http://www.open-mpi.org/community/lists/users/

Several Fortran 90 compilers reject any module that was compiled
with a different compiler (even when they can find it).

One possibility is to build OpenMPI again with SunStudio.
Another is to compile the program with gfortran, or much better,
with the corresponding OpenMPI wrapper mpif90.

I hope this helps.
Gus Correa

Nehemiah Dacres wrote:
is there a searchable archive of this mailing list?

I am helping someone use Openmpi with Sun's compilers that came with SolarisStudio. I used the --showme with mpif90 and got this

gfortran -I/opt/openmpi/include -pthread -I/opt/openmpi/lib ring_f90.f90 -L/opt/openmpi/lib -lmpi_f90 -lmpi_f77 -lmpi -lopen-rte -lopen-pal -ldl -Wl,--export-dynamic -lnsl -lutil -lm -ldl

that line compiles fine and so does the mpif90 command but when I replace gfortran with sunf90 or the absoulute path to my solaris studio compilers I get this

$ f90 -I/opt/openmpi/include -pthread -I/opt/openmpi/lib ring_f90.f90 -L/opt/openmpi/lib -lmpi_f90 -lmpi_f77 -lmpi -lopen-rte -lopen-pal -ldl -Wl,--export-dynamic -lnsl -lutil -lm -ldl f90: Warning: Option -pthread passed to ld, if ld is invoked, ignored otherwise f90: Warning: Option -Wl,--export-dynamic passed to ld, if ld is invoked, ignored otherwise

  use mpi
^ "ring_f90.f90", Line = 10, Column = 7: ERROR: "MPI" is specified as the module name on a USE statement, but the compiler cannot find it.

  call MPI_COMM_RANK(MPI_COMM_WORLD, rank, ierr)
^ "ring_f90.f90", Line = 17, Column = 22: ERROR: IMPLICIT NONE is specified in the local scope, therefore an explicit type must be specified for data object "MPI_COMM_WORLD".

     call MPI_SEND(message, 1, MPI_INTEGER, next, tag, MPI_COMM_WORLD, ierr)
^ "ring_f90.f90", Line = 34, Column = 32: ERROR: IMPLICIT NONE is specified in the local scope, therefore an explicit type must be specified for data object "MPI_INTEGER".

        MPI_STATUS_IGNORE, ierr)
^ "ring_f90.f90", Line = 46, Column = 9: ERROR: IMPLICIT NONE is specified in the local scope, therefore an explicit type must be specified for data object "MPI_STATUS_IGNORE".

f90comp: 73 SOURCE LINES
f90comp: 4 ERRORS, 0 WARNINGS, 0 OTHER MESSAGES, 0 ANSI

and the file contains this (from cat ring_f90.f90 ):

!
! Copyright (c) 2004-2006 The Trustees of Indiana University and Indiana
!                         University Research and Technology
!                         Corporation.  All rights reserved.
! Copyright (c) 2006      Cisco Systems, Inc.  All rights reserved.
!
! Simple ring test program
!
program ring
  use mpi
  implicit none
  integer :: rank, size, tag, next, from, message, ierr

! Start up MPI

  call MPI_INIT(ierr)
  call MPI_COMM_RANK(MPI_COMM_WORLD, rank, ierr)
  call MPI_COMM_SIZE(MPI_COMM_WORLD, size, ierr)

! Calculate the rank of the next process in the ring.  Use the modulus
! operator so that the last process "wraps around" to rank zero.

  tag = 201
  next = mod((rank + 1), size)
  from = mod((rank + size - 1), size)
! If we are the "master" process (i.e., MPI_COMM_WORLD rank 0), put
! the number of times to go around the ring in the message.

  if (rank .eq. 0) then
     message = 10

print *, 'Process 0 sending ', message, ' to ', next, ' tag ', tag, ' (', size, ' processes in ring)'
     call MPI_SEND(message, 1, MPI_INTEGER, next, tag, MPI_COMM_WORLD, ierr)
     print *, 'Process 0 sent to ', next
  endif

! Pass the message around the ring.  The exit mechanism works as
! follows: the message (a positive integer) is passed around the ring.
! Each time it passes rank 0, it is decremented.  When each processes
! receives a message containing a 0 value, it passes the message on to
! the next process and then quits.  By passing the 0 message first,
! every process gets the 0 message and can quit normally.

10 call MPI_RECV(message, 1, MPI_INTEGER, from, tag, MPI_COMM_WORLD, &
        MPI_STATUS_IGNORE, ierr)

  if (rank .eq. 0) then
     message = message - 1
     print *, 'Process 0 decremented value:', message
  endif

  call MPI_SEND(message, 1, MPI_INTEGER, next, tag, MPI_COMM_WORLD, ierr)
if (message .eq. 0) then
     print *, 'Process ', rank, ' exiting'
     goto 20
  endif
  goto 10

! The last process does one extra send to process 0, which needs to be
! received before the program can exit

 20 if (rank .eq. 0) then
     call MPI_RECV(message, 1, MPI_INTEGER, from, tag, MPI_COMM_WORLD, &
          MPI_STATUS_IGNORE, ierr)
  endif

! All done

  call MPI_FINALIZE(ierr)
end program


Now, i must warn you, I don't know FORTRAN but I am supporting someone who does. I have them CC

--
Nehemiah I. Dacres
System Administrator Advanced Technology Group Saint Louis University


------------------------------------------------------------------------

_______________________________________________
users mailing list
us...@open-mpi.org
http://www.open-mpi.org/mailman/listinfo.cgi/users

Reply via email to