[MPI3 Fortran] Deprecate mpif.h?

Rolf Rabenseifner rabenseifner at hlrs.de
Sat Mar 6 15:37:09 CST 2010


I want to point here to a technical problem with the nice section
MPI-2.2 482:39-484:18 "Problems Due to Data Copying and Sequence Association"

I've done a test with assumed-shape and assumed-size formal
arguments as buffer and using a strided actual argument when calling the
routine (e.g. MPI_IRECV).

With assumed-size, the compiler did call-by-in-and-out-copy,
with assumed-shape, the compiler did call-by-reference.

To overcome the restrictions shown in "Problems Due to Data Copying",
one needs call-by-reference.

With assumed-shape, we have also assumed-rank (is this correct?)
and therefore we have to 15 times overload a function with one buffer
and 225 times with two buffers?

And we cannot use our wrappers to current C routines, because now,
the array descriptor is handed over, and the extracting of
the data from the strided input must be done by MPI.

If the user itself uses additionally a strided datatype handle,
then both mechanisms must be applied to the unstrided array
handed over by Fortran to C.

Do I miss something? Or is it such complicated?
Do we want this implementation effort?

Attached is a small test-routine, to be compiled with mpif90,
but started directly (there is no MPI_Init inside).

Best regards
Rolf

----- "N.M. Maclaren" <nmm1 at cam.ac.uk> wrote:

...
> 
> > The TR features can be implemented on top of an 
> >existing Fortran 2003 compiler - it is not necessary for the vendor
> to 
> >implement the new features of Fortran 2008 first.  It is not even 
> >required that all of Fortran 2003 be implemented before the TR.  You
> 
> >really just need the support for C interoperability and allocatable 
> >dummy arguments from Fortran 2003, and most compilers already support
> 
> >those features.
> 
> Yes.  That's not the problem.
> 
> A bigger one is how to bind the various models together.  For
> example,
> with the current TR's approach, you cannot have a single MPI function
> that takes both assumed-size array arguments (which are heavily used)
> and assumed-shape/assumed-rank ones.  MPI is going to have to decide
> how to handle that one.
> 
> Similarly, MPI is going to have to address the fact that the TR
> doesn't
> help with using Fortran derived types on heterogeneous clusters.  And
> what to do about one-sided transfers (ugh) - actually, those are
> going
> to be a BIG semantic problem with the forthcoming C++ and C standards
> as well.
> 
> Regards,
> Nick Maclaren.
> 
> _______________________________________________
> mpi3-fortran mailing list
> mpi3-fortran at lists.mpi-forum.org
> http://lists.mpi-forum.org/mailman/listinfo.cgi/mpi3-fortran

_____________________________________________________________________

module test_mpi
contains
 
  subroutine TEST_RECV_ASSUMED_SIZE(buf,cnt,dt,src,tag,comm,status)
    use mpi 
    implicit none 
 
    REAL, dimension(*) :: buf
    integer :: cnt
    integer :: dt
    integer :: src
    integer*8 :: tag
    integer :: comm
    integer, dimension(MPI_STATUS_SIZE) :: status
    
    integer i
    integer*8 :: base

    base = tag 
    do i=1,cnt
      write(*,'(A,I1,A,F5.1,A,I1,A,I)') '  buf(',i,')=',buf(i), ',  loc(buf(',i,'))-base=', loc(buf(i))-base 
    end do
    return 
  end subroutine TEST_RECV_ASSUMED_SIZE
 
  subroutine TEST_RECV_ASSUMED_SHAPE(buf,cnt,dt,src,tag,comm,status)
    use mpi 
    implicit none 
 
    REAL, dimension(1:) :: buf
    integer :: cnt
    integer :: dt
    integer :: src
    integer*8 :: tag
    integer :: comm
    integer, dimension(MPI_STATUS_SIZE) :: status
    
    integer i
    integer*8 :: base

    base = tag 
    do i=1,cnt
      write(*,'(A,I1,A,F5.1,A,I1,A,I)') '  buf(',i,')=',buf(i), ',  loc(buf(',i,'))-base=', loc(buf(i))-base 
    end do
    return 
  end subroutine TEST_RECV_ASSUMED_SHAPE

end module test_mpi

program test
  use mpi 
  use test_mpi
  implicit none

  REAL, dimension(6) :: buffer
  REAL, dimension(3,2) :: buffer2dim
  integer*8 :: base
  integer, dimension(MPI_STATUS_SIZE) :: sts
  integer i,j

  do i=1,6
    buffer(i)=100*i
  end do 

  do i=1,3
   do j=1,2
    buffer2dim(i,j)=100*i+j
   end do 
  end do 

  base=loc(buffer(1))

  write (*,*) ; write (*,*) 'With 1-dim buffer'
 
  write (*,*) ; write (*,*) 'Assumed SIZE - calling with "buffer":' 
  call TEST_RECV_ASSUMED_SIZE(buffer,6,MPI_REAL,0,base,MPI_COMM_WORLD, sts)

! write (*,*) ; write (*,*) 'Assumed SIZE - calling with "buffer(1:6:1)":' 
! call TEST_RECV_ASSUMED_SIZE(buffer(1:6:1),6,MPI_REAL,0,base,MPI_COMM_WORLD, sts)

! write (*,*) ; write (*,*) 'Assumed SIZE - calling with "buffer(1:3:1)":' 
! call TEST_RECV_ASSUMED_SIZE(buffer(1:3:1),3,MPI_REAL,0,base,MPI_COMM_WORLD, sts)

  write (*,*) ; write (*,*) 'Assumed SIZE - calling with "buffer(1:6:2)":' 
  call TEST_RECV_ASSUMED_SIZE(buffer(1:6:2),3,MPI_REAL,0,base,MPI_COMM_WORLD, sts)

  write (*,*) ; write (*,*) 'Assumed SHAPE - calling with "buffer":' 
  call TEST_RECV_ASSUMED_SHAPE(buffer,6,MPI_REAL,0,base,MPI_COMM_WORLD, sts)

! write (*,*) ; write (*,*) 'Assumed SHAPE - calling with "buffer(1:6:1)":' 
! call TEST_RECV_ASSUMED_SHAPE(buffer(1:6:1),6,MPI_REAL,0,base,MPI_COMM_WORLD, sts)

! write (*,*) ; write (*,*) 'Assumed SHAPE - calling with "buffer(1:3:1)":' 
! call TEST_RECV_ASSUMED_SHAPE(buffer(1:3:1),3,MPI_REAL,0,base,MPI_COMM_WORLD, sts)

  write (*,*) ; write (*,*) 'Assumed SHAPE - calling with "buffer(1:6:2)":' 
  call TEST_RECV_ASSUMED_SHAPE(buffer(1:6:2),3,MPI_REAL,0,base,MPI_COMM_WORLD, sts)
 
  write (*,*) ; write (*,*) 'With 2-dim buffer2dim'

  write (*,*) ; write (*,*) 'Assumed SIZE - calling with "buffer2dim":' 
  call TEST_RECV_ASSUMED_SIZE(buffer2dim,6,MPI_REAL,0,base,MPI_COMM_WORLD, sts)

! write (*,*) ; write (*,*) 'Assumed SIZE - calling with "buffer2dim(1:3:1,1:2:1)":' 
! call TEST_RECV_ASSUMED_SIZE(buffer2dim(1:3:1,1:2:1),6,MPI_REAL,0,base,MPI_COMM_WORLD, sts)

! write (*,*) ; write (*,*) 'Assumed SIZE - calling with "buffer2dim(1:3:1,2:2:1)":' 
! call TEST_RECV_ASSUMED_SIZE(buffer2dim(1:3:1,2:2:1),3,MPI_REAL,0,base,MPI_COMM_WORLD, sts)

  write (*,*) ; write (*,*) 'Assumed SIZE - calling with "buffer2dim(1:3:2,1:2:1)":' 
  call TEST_RECV_ASSUMED_SIZE(buffer2dim(1:3:2,1:2:1),4,MPI_REAL,0,base,MPI_COMM_WORLD, sts)

  write (*,*) ; write (*,*) 'Assumed SHAPE - calling with "buffer":' 
!!!!  call TEST_RECV_ASSUMED_SHAPE(buffer2dim,6,MPI_REAL,0,base,MPI_COMM_WORLD, sts)
  write(*,*) '    ---- NOT ALLOWED' 

! write (*,*) ; write (*,*) 'Assumed SHAPE - calling with "buffer2dim(1:3:1,1:2:1)":' 
! call TEST_RECV_ASSUMED_SHAPE(buffer2dim(1:3:1,1:2:1),6,MPI_REAL,0,base,MPI_COMM_WORLD, sts)

! write (*,*) ; write (*,*) 'Assumed SHAPE - calling with "buffer2dim(1:3:1,2:2:1)":' 
! call TEST_RECV_ASSUMED_SHAPE(buffer2dim(1:3:1,2:2:1),3,MPI_REAL,0,base,MPI_COMM_WORLD, sts)

  write (*,*) ; write (*,*) 'Assumed SHAPE - calling with "buffer2dim(1:3:2,1:2:1)":' 
!!!!  call TEST_RECV_ASSUMED_SHAPE(buffer2dim(1:3:2,1:2:1),4,MPI_REAL,0,base,MPI_COMM_WORLD, sts)
  write(*,*) '    ---- NOT ALLOWED' 

end program test

_____________________________________________________________________
 
 With 1-dim buffer
 
 Assumed SIZE - calling with "buffer":
  buf(1)=100.0,  loc(buf(1))-base=                      0
  buf(2)=200.0,  loc(buf(2))-base=                      4
  buf(3)=300.0,  loc(buf(3))-base=                      8
  buf(4)=400.0,  loc(buf(4))-base=                     12
  buf(5)=500.0,  loc(buf(5))-base=                     16
  buf(6)=600.0,  loc(buf(6))-base=                     20
 
 Assumed SIZE - calling with "buffer(1:6:2)":
  buf(1)=100.0,  loc(buf(1))-base=         17592185944224
  buf(2)=300.0,  loc(buf(2))-base=         17592185944228
  buf(3)=500.0,  loc(buf(3))-base=         17592185944232
>>>>>> The result shows clearly call-by-in-and-out-copy !!!!!
 
 Assumed SHAPE - calling with "buffer":
  buf(1)=100.0,  loc(buf(1))-base=                      0
  buf(2)=200.0,  loc(buf(2))-base=                      4
  buf(3)=300.0,  loc(buf(3))-base=                      8
  buf(4)=400.0,  loc(buf(4))-base=                     12
  buf(5)=500.0,  loc(buf(5))-base=                     16
  buf(6)=600.0,  loc(buf(6))-base=                     20
 
 Assumed SHAPE - calling with "buffer(1:6:2)":
  buf(1)=100.0,  loc(buf(1))-base=                      0
  buf(2)=300.0,  loc(buf(2))-base=                      8
  buf(3)=500.0,  loc(buf(3))-base=                     16
 
 With 2-dim buffer2dim
 
 Assumed SIZE - calling with "buffer2dim":
  buf(1)=101.0,  loc(buf(1))-base=                     32
  buf(2)=201.0,  loc(buf(2))-base=                     36
  buf(3)=301.0,  loc(buf(3))-base=                     40
  buf(4)=102.0,  loc(buf(4))-base=                     44
  buf(5)=202.0,  loc(buf(5))-base=                     48
  buf(6)=302.0,  loc(buf(6))-base=                     52
 
 Assumed SIZE - calling with "buffer2dim(1:3:2,1:2:1)":
  buf(1)=101.0,  loc(buf(1))-base=         17592185944208
  buf(2)=301.0,  loc(buf(2))-base=         17592185944212
  buf(3)=102.0,  loc(buf(3))-base=         17592185944216
  buf(4)=302.0,  loc(buf(4))-base=         17592185944220
>>>>>> The result shows clearly call-by-in-and-out-copy !!!!!
  
 Assumed SHAPE - calling with "buffer":
     ---- NOT ALLOWED
 
 Assumed SHAPE - calling with "buffer2dim(1:3:2,1:2:1)":
     ---- NOT ALLOWED

_____________________________________________________________________

-- 
Dr. Rolf Rabenseifner . . . . . . . . . .. email rabenseifner at hlrs.de
High Performance Computing Center (HLRS) . phone ++49(0)711/685-65530
University of Stuttgart . . . . . . . . .. fax ++49(0)711 / 685-65832
Head of Dpmt Parallel Computing . . . www.hlrs.de/people/rabenseifner
Nobelstr. 19, D-70550 Stuttgart, Germany . (Office: Allmandring 30)
-------------- next part --------------
A non-text attachment was scrubbed...
Name: type-star-test.f90
Type: text/x-fortran
Size: 4301 bytes
Desc: not available
URL: <http://lists.mpi-forum.org/pipermail/mpiwg-fortran/attachments/20100306/0916af18/attachment-0001.bin>
-------------- next part --------------
An embedded and charset-unspecified text was scrubbed...
Name: type-star-test.out.txt
URL: <http://lists.mpi-forum.org/pipermail/mpiwg-fortran/attachments/20100306/0916af18/attachment-0001.txt>


More information about the mpiwg-fortran mailing list