[mpich-discuss] MPI_FILE_read and derived types in fortran.

Rajeev Thakur thakur at mcs.anl.gov
Tue Mar 11 13:06:47 CDT 2014


Use MPI_Type_create_struct instead of MPI_Type_struct, which has been deprecated since 1997 and removed in MPI-3 in 2012 because of Fortran binding issues. For MPI_Type_create_struct, the offsets array needs to be declared as integer (kind=MPI_ADDRESS_KIND). See if that helps.

Rajeev


On Mar 11, 2014, at 11:25 AM, Scot Breitenfeld <brtnfld at hdfgroup.org> wrote:

> Hi,
> 
> I created a file in fortran using (which I compiled with mpif90):
> 
> PROGRAM writeUstream
> 
>  IMPLICIT NONE
>  INTEGER :: i, ii
>  INTEGER, DIMENSION(1:3,1:25) :: buf
> 
>  OPEN(UNIT=11, FILE="ustream.demo", FORM="unformatted", STATUS="UNKNOWN", ACCESS="STREAM")
> 
>  ii = 1
> 
>  DO i=1, 25
>     buf(1,i) = ii
>     buf(2,i) = ii+1
>     buf(3,i) = ii+2
>     WRITE(11) buf(1:3,i)
>     ii = ii + 3
>  ENDDO
>  CLOSE(UNIT=11)
> 
> END PROGRAM writeUstream
> 
> And I’ve made a simple program to read the file (on the same machine) using MPI_FILE_read:
> 
> PROGRAM struct
> 
>  USE mpi
> 
>  IMPLICIT NONE
> 
>  INTEGER, PARAMETER :: NELEM = 2
>  INTEGER :: numtasks, rank, source, dest, tag, i,  ierr 
>  INTEGER :: stat(MPI_STATUS_SIZE) 
>  INTEGER :: fh
>  INTEGER :: status
>  INTEGER(kind=MPI_OFFSET_KIND) :: disp
> 
>  INTEGER, DIMENSION(1:3) :: iiaux
> 
>  TYPE Particle
>     SEQUENCE
>     INTEGER, DIMENSION(1:3) :: indx
>  END TYPE Particle
> 
>  TYPE(Particle), DIMENSION(1:nelem) ::  particles
>  INTEGER particletype, oldtypes(1:1), blockcounts(1:1), offsets(1:1), extent 
> 
>  CALL MPI_INIT(ierr)
>  CALL MPI_COMM_RANK(MPI_COMM_WORLD, rank, ierr)
>  CALL MPI_COMM_SIZE(MPI_COMM_WORLD, numtasks, ierr)
> 
>  !  Setup description of the 3 MPI_INTEGERS fields x, y, z
>  offsets(1) = 0
>  oldtypes(1) = MPI_INTEGER
>  blockcounts(1) = 3
> 
>  !  Now define structured TYPE and commit it  
>  CALL MPI_TYPE_STRUCT(1, blockcounts, offsets, oldtypes, particletype, ierr)
>  CALL MPI_TYPE_COMMIT(particletype, ierr)
> 
>  CALL MPI_File_open(MPI_COMM_WORLD, "ustream.demo", MPI_MODE_RDONLY, MPI_INFO_NULL, fh, ierr)
> 
>  disp = 0
> 
>  CALL MPI_File_set_view(fh, disp, MPI_INTEGER, particletype, "native", MPI_INFO_NULL, ierr)
> 
>  particles(1:nelem)%indx = -1
> 
>  CALL MPI_File_read(fh, particles, nelem, particletype, status, ierr) 
> 
>  PRINT*,"derived type"
>  DO i=1,nelem
>     PRINT*,particles(i)%indx
>  ENDDO
> 
>  CALL MPI_File_close(fh, ierr)
> 
>  CALL MPI_File_open(MPI_COMM_WORLD, "ustream.demo", MPI_MODE_RDONLY, &
>                  MPI_INFO_NULL, fh, ierr)
> 
>  CALL MPI_FILE_read(fh,iiaux,3,MPI_INTEGER,status,ierr)
> 
>  PRINT*,"No derived type"
> 
>  PRINT*,iiaux
>  CALL MPI_FILE_read(fh,iiaux,3,MPI_INTEGER,status,ierr)
>  PRINT*,iiaux
> 
>  CALL MPI_File_close(fh, ierr)
> 
>  CALL MPI_FINALIZE(ierr) 
> END PROGRAM struct
> 
> 
> When I run this program to read the file using just one process, the first two integers of the derived type are not correct, but all the remaining values are correct. All the values when reading them into an integer array is correct. Here is the output:
> 
> derived type
>          24           0           3
>           4           5           6
> No derived type
>           1           2           3
>           4           5           6
> 
> I don’t get any error from the MPI calls and I used gcc 4.8.1 to compile mpich 3.0.4 on Linux  2.6.18-308.13.1.el5PAE #1 SMP Tue Aug 21 17:50:26 EDT 2012 i686 i686 i386 GNU/Linux
> I not exactly sure what is going on.
> 
> Thanks,
> Scot
> 
> 
> 
> 
> 
> 
> _______________________________________________
> discuss mailing list     discuss at mpich.org
> To manage subscription options or unsubscribe:
> https://lists.mpich.org/mailman/listinfo/discuss




More information about the discuss mailing list