Blame test/mpi/f90/io/miscfilef90.f90

Packit 0848f5
! This file created from test/mpi/f77/io/miscfilef.f with f77tof90
Packit 0848f5
! -*- Mode: Fortran; -*-
Packit 0848f5
!
Packit 0848f5
!  (C) 2004 by Argonne National Laboratory.
Packit 0848f5
!      See COPYRIGHT in top-level directory.
Packit 0848f5
!
Packit 0848f5
      program main
Packit 0848f5
      use mpi
Packit 0848f5
! iooffset.h provides a variable "offset" that is of type MPI_Offset
Packit 0848f5
! (in Fortran 90, kind=MPI_OFFSET_KIND)
Packit 0848f5
      integer (kind=MPI_OFFSET_KIND) offset
Packit 0848f5
Packit 0848f5
! iodisp.h declares disp as an MPI_Offset integer
Packit 0848f5
      integer (kind=MPI_OFFSET_KIND) disp
Packit 0848f5
Packit 0848f5
      integer rank, size
Packit 0848f5
      integer fh, i, group, worldgroup, result
Packit 0848f5
      integer ierr, errs
Packit 0848f5
      integer BUFSIZE
Packit 0848f5
      parameter (BUFSIZE=1024)
Packit 0848f5
      integer buf(BUFSIZE)
Packit 0848f5
      character*(50) filename
Packit 0848f5
      character*(MPI_MAX_DATAREP_STRING) datarep
Packit 0848f5
      integer amode
Packit 0848f5
      logical atomicity
Packit 0848f5
      integer newtype, etype, filetype
Packit 0848f5
      integer integer_size, type_size
Packit 0848f5
!      
Packit 0848f5
      errs = 0
Packit 0848f5
      call mtest_init( ierr )
Packit 0848f5
      call mpi_comm_rank( MPI_COMM_WORLD, rank, ierr )
Packit 0848f5
      call mpi_comm_size( MPI_COMM_WORLD, size, ierr )
Packit 0848f5
!
Packit 0848f5
! Create a file that we'll then query properties
Packit 0848f5
      filename = "testfile.txt"
Packit 0848f5
      call mpi_file_open( MPI_COMM_WORLD, filename, MPI_MODE_CREATE +       &
Packit 0848f5
      &     MPI_MODE_RDWR, MPI_INFO_NULL, fh, ierr ) 
Packit 0848f5
      if (ierr .ne. MPI_SUCCESS) then
Packit 0848f5
         print *, "Unable to create file ", filename
Packit 0848f5
         call mpi_abort( MPI_COMM_WORLD, 1, ierr )
Packit 0848f5
      endif
Packit 0848f5
!
Packit 0848f5
! Fill in some data
Packit 0848f5
      do i=1, BUFSIZE
Packit 0848f5
         buf(i) = i
Packit 0848f5
      enddo
Packit 0848f5
      call mpi_file_write( fh, buf, BUFSIZE, MPI_INTEGER,                &
Packit 0848f5
      &     MPI_STATUS_IGNORE, ierr ) 
Packit 0848f5
      call MPI_File_sync( fh, ierr )
Packit 0848f5
!
Packit 0848f5
! Now, query properties of the file and the file handle
Packit 0848f5
      call MPI_File_get_amode(fh, amode, ierr )
Packit 0848f5
      if (amode .ne. MPI_MODE_CREATE + MPI_MODE_RDWR) then
Packit 0848f5
         errs = errs + 1
Packit 0848f5
         print *, " Amode was different than expected"
Packit 0848f5
      endif
Packit 0848f5
!
Packit 0848f5
      call MPI_File_get_atomicity( fh, atomicity, ierr )
Packit 0848f5
      if (atomicity) then
Packit 0848f5
         errs = errs + 1
Packit 0848f5
         print *, " Atomicity was true but should be false"
Packit 0848f5
      endif
Packit 0848f5
!
Packit 0848f5
      call MPI_File_set_atomicity( fh, .true., ierr )
Packit 0848f5
      call MPI_File_get_atomicity( fh, atomicity, ierr )
Packit 0848f5
      if (.not. atomicity) then
Packit 0848f5
         errs = errs + 1
Packit 0848f5
         print *, " Atomicity was set to true but ",                    &
Packit 0848f5
      &        "get_atomicity returned false" 
Packit 0848f5
      endif
Packit 0848f5
      call MPI_File_set_atomicity( fh, .false., ierr )
Packit 0848f5
!
Packit 0848f5
! FIXME: original code use 10,10,20, and the following code 
Packit 0848f5
! assumed the original
Packit 0848f5
! 
Packit 0848f5
! Create a vector type of 10 elements, each of 20 elements, with a stride of
Packit 0848f5
! 30 elements
Packit 0848f5
      call mpi_type_vector( 10, 20, 30, MPI_INTEGER, newtype, ierr )
Packit 0848f5
      call mpi_type_commit( newtype, ierr )
Packit 0848f5
!
Packit 0848f5
! All processes are getting the same view, with a 1000 byte offset
Packit 0848f5
      offset = 1000
Packit 0848f5
      call mpi_file_set_view( fh, offset, MPI_INTEGER, newtype, "native"  &
Packit 0848f5
      &     , MPI_INFO_NULL, ierr )  
Packit 0848f5
Packit 0848f5
      call mpi_file_get_view( fh, offset, etype, filetype, datarep, ierr  &
Packit 0848f5
      &     ) 
Packit 0848f5
      if (offset .ne. 1000) then
Packit 0848f5
         print *, " displacement was ", offset, ", expected 1000"
Packit 0848f5
         errs = errs + 1
Packit 0848f5
      endif
Packit 0848f5
      if (datarep .ne. "native") then
Packit 0848f5
         print *, " data representation form was ", datarep,              &
Packit 0848f5
      &        ", expected native" 
Packit 0848f5
         errs = errs + 1
Packit 0848f5
      endif
Packit 0848f5
Packit 0848f5
! Find the byte offset, given an offset of 20 etypes relative to the
Packit 0848f5
! current view (the same as the blockcount of the filetype, which
Packit 0848f5
! places it at the beginning of the next block, hence a stride
Packit 0848f5
! distance away). 
Packit 0848f5
      offset = 20
Packit 0848f5
      call mpi_file_get_byte_offset( fh, offset, disp, ierr )
Packit 0848f5
      call mpi_type_size( MPI_INTEGER, integer_size, ierr )
Packit 0848f5
      if (disp .ne. 1000 + 30 * integer_size) then
Packit 0848f5
         errs = errs + 1
Packit 0848f5
         print *, " (offset20)Byte offset = ", disp, ", should be ",         &
Packit 0848f5
      &            1000+20*integer_size 
Packit 0848f5
      endif
Packit 0848f5
!
Packit 0848f5
!     We should also compare file and etypes.  We just look at the 
Packit 0848f5
!     sizes and extents for now
Packit 0848f5
Packit 0848f5
      call mpi_type_size( etype, type_size, ierr )
Packit 0848f5
      if (type_size .ne. integer_size) then
Packit 0848f5
         print *, " Etype has size ", type_size, ", but should be ",      &
Packit 0848f5
      &        integer_size 
Packit 0848f5
         errs = errs + 1
Packit 0848f5
      endif
Packit 0848f5
      call mpi_type_size( filetype, type_size, ierr )
Packit 0848f5
      if (type_size .ne. 10*20*integer_size) then
Packit 0848f5
         print *, " filetype has size ", type_size, ", but should be ",   &
Packit 0848f5
      &        10*20*integer_size 
Packit 0848f5
         errs = errs + 1
Packit 0848f5
      endif
Packit 0848f5
!
Packit 0848f5
! Only free derived type
Packit 0848f5
      call mpi_type_free( filetype, ierr )
Packit 0848f5
Packit 0848f5
      call mpi_file_get_group( fh, group, ierr )
Packit 0848f5
      call mpi_comm_group( MPI_COMM_WORLD, worldgroup, ierr )
Packit 0848f5
      call mpi_group_compare( group, worldgroup, result, ierr )
Packit 0848f5
      
Packit 0848f5
      if (result .ne. MPI_IDENT) then
Packit 0848f5
         print *, " Group of file does not match group of comm_world"
Packit 0848f5
         errs = errs + 1
Packit 0848f5
      endif
Packit 0848f5
      call mpi_group_free( group, ierr )
Packit 0848f5
      call mpi_group_free( worldgroup, ierr )
Packit 0848f5
Packit 0848f5
      offset = 1000+25*integer_size
Packit 0848f5
      call mpi_file_set_size(fh, offset, ierr )
Packit 0848f5
      call mpi_barrier(MPI_COMM_WORLD, ierr )
Packit 0848f5
      call mpi_file_sync(fh, ierr )
Packit 0848f5
      call mpi_file_get_size( fh, offset, ierr )
Packit 0848f5
Packit 0848f5
      if (offset .ne. 1000+25*integer_size) then
Packit 0848f5
         errs = errs + 1
Packit 0848f5
         print *, " File size is ", offset, ", should be ", 1000 + 25     &
Packit 0848f5
      &        * integer_size 
Packit 0848f5
      endif
Packit 0848f5
!
Packit 0848f5
! File size is 1000+25ints.  Seek to end.  Note that the file size
Packit 0848f5
! places the end of the file into the gap in the view, so seeking
Packit 0848f5
! to the end, which is relative to the view, needs to give the end
Packit 0848f5
! of the first block of 20 ints)
Packit 0848f5
      offset = 0
Packit 0848f5
      call mpi_file_seek( fh, offset, MPI_SEEK_END, ierr )
Packit 0848f5
      call mpi_file_get_position( fh, disp, ierr )
Packit 0848f5
      if (disp .ne. 20) then
Packit 0848f5
         errs = errs + 1
Packit 0848f5
         print *, "File pointer position = ", disp, ", should be 20"
Packit 0848f5
         if (disp .eq. 25) then
Packit 0848f5
! See MPI 2.1, section 13.4, page 399, lines 7-8. The disp must be
Packit 0848f5
! relative to the current view, in the etype units of the current view
Packit 0848f5
             print *, " MPI implementation failed to position the "//      &
Packit 0848f5
      &                "displacement within the current file view"
Packit 0848f5
         endif
Packit 0848f5
! Make sure we use the expected position in the next step.
Packit 0848f5
         disp = 20
Packit 0848f5
      endif
Packit 0848f5
      call mpi_file_get_byte_offset(fh, disp, offset, ierr )
Packit 0848f5
      if (offset .ne. 1000+30*integer_size) then
Packit 0848f5
         errs = errs + 1
Packit 0848f5
         print *, " (seek)Byte offset = ", offset, ", should be ", 1000     &
Packit 0848f5
      &        +30*integer_size  
Packit 0848f5
      endif
Packit 0848f5
Packit 0848f5
      call mpi_barrier(MPI_COMM_WORLD, ierr )
Packit 0848f5
Packit 0848f5
      offset = -20
Packit 0848f5
      call mpi_file_seek(fh, offset, MPI_SEEK_CUR, ierr )
Packit 0848f5
      call mpi_file_get_position(fh, disp, ierr )
Packit 0848f5
      call mpi_file_get_byte_offset(fh, disp, offset, ierr )
Packit 0848f5
      if (offset .ne. 1000) then
Packit 0848f5
         errs = errs + 1
Packit 0848f5
         print *, " File pointer position in bytes = ", offset,           &
Packit 0848f5
      &        ", should be 1000"
Packit 0848f5
      endif
Packit 0848f5
      
Packit 0848f5
      offset = 8192
Packit 0848f5
      call mpi_file_preallocate(fh, offset, ierr )
Packit 0848f5
      offset = 0
Packit 0848f5
      call mpi_file_get_size( fh, offset, ierr )
Packit 0848f5
      if (offset .lt. 8192) then
Packit 0848f5
         errs = errs + 1
Packit 0848f5
         print *, " Size after preallocate is ", offset,                  &
Packit 0848f5
      &        ", should be at least 8192" 
Packit 0848f5
      endif
Packit 0848f5
      call mpi_file_close( fh, ierr )
Packit 0848f5
Packit 0848f5
      call mpi_barrier(MPI_COMM_WORLD, ierr )
Packit 0848f5
      
Packit 0848f5
      if (rank .eq. 0) then
Packit 0848f5
         call MPI_File_delete(filename, MPI_INFO_NULL, ierr )
Packit 0848f5
      endif
Packit 0848f5
Packit 0848f5
      call mpi_type_free( newtype, ierr )
Packit 0848f5
Packit 0848f5
      call mtest_finalize( errs )
Packit 0848f5
      call mpi_finalize( ierr )
Packit 0848f5
      end