[mvapich-discuss] Output large files using MPI-IO

Madhusudan Pai mpai at stanford.edu
Thu Mar 4 14:14:00 EST 2010


Hi Sayantan,

I have included the code below. I'll try with the MPICH2 versions and let
you know.

Thanks!
Madhu

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

program file_set_view

  implicit none
  include 'mpif.h'

  integer, parameter :: str_medium = 64

!!! ------------------------------------------------------------

  integer, dimension (:), pointer :: map, blocklength
  integer, dimension (:), pointer :: hexa_

  character(len=str_medium) :: file
  integer :: ierr, irank, nproc, iunit, i
  integer  :: ncells_hexa_,ncells_hexa

  integer(kind=MPI_OFFSET_KIND) :: disp
  integer :: fileview_hexa_conn
  integer :: iroot, status
  integer :: comm = MPI_COMM_WORLD

  logical :: file_is_there

  integer, dimension(:), pointer :: nhexas_proc

  integer :: mpi_info

!!! ------------------------------------------------------------

  call MPI_INIT(ierr)
  call MPI_COMM_RANK(MPI_COMM_WORLD,irank,ierr)
  call MPI_COMM_SIZE(MPI_COMM_WORLD,nproc,ierr)
  irank = irank+1
  iroot = 1

  call MPI_INFO_CREATE(mpi_info,ierr)
  call MPI_INFO_SET(mpi_info,"romio_ds_write","disable",ierr)
!  mpi_info = MPI_INFO_NULL

 !!! ----------------------------------------------------------------
 !! in practice, a communicator with specified topology is created here
 !! with MPI_CART_CREATE

 !! -----------------------------------------------------------------
  !!! problem size determined by ncells_hexa

  ncells_hexa = 2**29-1
  if(irank.eq.iroot)print*,'ncells_hexa...',ncells_hexa

  ncells_hexa_ = ncells_hexa/nproc

  allocate(hexa_(ncells_hexa_))
  allocate(nhexas_proc (nproc))
  call
MPI_allgather(ncells_hexa_,1,MPI_INTEGER,nhexas_proc,1,MPI_INTEGER,comm,ierr)

  !! global numbering of hexahedral cells in the domain
  !! for large domains, the integer value in hexa_(:) can exceed 2^31-1
(integer*4)

  do i=1,ncells_hexa_
     hexa_(i) = i + sum(nhexas_proc(1:irank-1))
  end do

  allocate(blocklength(ncells_hexa_))
  allocate(map(ncells_hexa_))

  blocklength(1:ncells_hexa_) = 4
  map(1:ncells_hexa_) = (hexa_(1:ncells_hexa_)-1)*8

  !!
------------------------------------------------------------------------
  !! create view for output later
  !!
------------------------------------------------------------------------

  call
MPI_TYPE_INDEXED(ncells_hexa_,blocklength,map,MPI_INTEGER,fileview_hexa_conn,ierr)
  call MPI_TYPE_COMMIT(fileview_hexa_conn,ierr)

  !! open file

  file="geometry"
  inquire(file=file,exist=file_is_there)
  if (file_is_there .and. irank.eq.iroot) call
MPI_FILE_DELETE(file,mpi_info,ierr)
  call
MPI_FILE_OPEN(comm,file,IOR(MPI_MODE_WRONLY,MPI_MODE_CREATE),mpi_info,iunit,ierr)

  !! output file
  disp = 0
  call
MPI_FILE_SET_VIEW(iunit,disp,MPI_INTEGER,fileview_hexa_conn,"native",mpi_info,ierr)
  call MPI_FILE_WRITE_ALL(iunit,hexa_,ncells_hexa_,MPI_INTEGER,status,ierr)

  ! Close the file
  call MPI_FILE_CLOSE(iunit,ierr)

end program file_set_view

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


On Thu, Mar 4, 2010 at 6:13 AM, Sayantan Sur <surs at cse.ohio-state.edu>wrote:

> Hi Madhu,
>
> Thanks for the report. Would it be possible for you to post the
> snippet of code, so that we may reproduce the error at our end?
>
> The problem seems to be something related with ROMIO. We were
> wondering if you could try MVAPICH2-1.4 on TACC to see if the problem
> has been fixed in more recent versions. There is a 'hecura' module on
> Ranger that has MVAPICH2-1.4. Does the bug show up even with the
> hecura module?
>
>
> http://www.tacc.utexas.edu/software_modules.php?app=softwareModule&isTest=&machine=Ranger#version
>
> Thanks.
>
> On Wed, Mar 3, 2010 at 7:16 PM, Madhusudan Pai <mpai at stanford.edu> wrote:
> > Hello,
> >
> > This is probably a novice MPI question but I can't seem to figure out the
> > reason behind an error I get when I try to output a large array on
> Ranger. I
> > have created a snippet of my code that can reproduce this error, although
> I
> > have pasted only portions here. I can post the entire code (about 117
> lines
> > if needed).
> >
> > Essentially, I use MPI_TYPE_INDEXED to create a view, then I use
> > MPI_FILE_SET_VIEW and MPI_FILE_WRITE_ALL to output my file.
> >
> >  call MPI_TYPE_INDEXED(ncells,blocklength,map,MPI_INTEGER,fileview,ierr)
> >  call MPI_TYPE_COMMIT(fileview,ierr)
> >
> > blocklength and map are 1-d arrays of size ncells, and ncells,
> blocklength
> > and map are declared as integer (kind=4).
> >
> > Then I set the view and output an array called hexa as
> >
> >  disp = 0
> >  call
> > MPI_FILE_SET_VIEW(iunit,disp,MPI_INTEGER,fileview,"native",mpi_info,ierr)
> >  call MPI_FILE_WRITE_ALL(iunit,hexa,ncells,MPI_INTEGER,status,ierr)
> >
> > where hexa is a 1-d array of size ncells. The array hexa contains the
> global
> > node numbering of my mesh (so the last cell contains a value of order
> > (ncells*nproc)).
> >
> > For small problem sizes the code works just fine. But the problem arises
> > when ncells is close to the integer*4 limit. And since the array map is a
> > function of hexa (specifically, map = hexa * 8), the entries of map also
> > cross the integer*4 limit. The routine stalls at MPI_FILE_WRITE_ALL with
> the
> > error "*io Invalid argument**io Invalid argument**io Invalid
> argument**io...
> > " on several processes.
> >
> > 1) I can't seem to figure out which "argument" is causing this error.
> >
> > 2) I also changed the type declaration of map and ncells to integer
> > (kind=8), but this did not seem to correct the problem. I have also tried
> > with MPI_INTEGER8 in the WRITE_ALL routine.
> >
> > I am using mvapich 1.0.1 and intel 10.1 fortran for compilation.
> >
> > Any help greatly appreciated!
> >
> > Thanks,
> > Madhu Pai
> > Stanford University
> >
> > _______________________________________________
> > mvapich-discuss mailing list
> > mvapich-discuss at cse.ohio-state.edu
> > http://mail.cse.ohio-state.edu/mailman/listinfo/mvapich-discuss
> >
> >
>
>
>
> --
> Sayantan Sur
>
> Research Scientist
> Department of Computer Science
> The Ohio State University.
>



-- 
_________________________________________________
Madhusudan G. Pai, Ph.D.
Center for Turbulence Research
Building 02-250
481 Panama Mall
Stanford University
Stanford, CA 94305-3035
Ph: (650) 736-0900
Fax: (650) 723-9617
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://mail.cse.ohio-state.edu/pipermail/mvapich-discuss/attachments/20100304/bdab65e7/attachment-0001.html


More information about the mvapich-discuss mailing list