load_tem_BC_realArray Subroutine

private subroutine load_tem_BC_realArray(offset, propname, arraylen, nElems, propdat, basename, myPart, comm)

load bc realarray data from disk

Arguments

Type IntentOptional Attributes Name
integer(kind=long_k), intent(in) :: offset

Offset of the local set of elements in the global list

character(len=*), intent(in) :: propname

Name of the property to load

integer, intent(in) :: arraylen

Length of the real data array to read per element

integer, intent(in) :: nElems

Local number of elements with this property

real(kind=rk), intent(out) :: propdat(arraylen,nElems)

real array data to fill

character(len=*), intent(in) :: basename

Name of the file, the data is stored in, will be appended with ".lua" for the header information and ".lsb" or ".msb" for the binary data.

integer, intent(in) :: myPart

Partition to load

integer, intent(in) :: comm

Communicator to use


Calls

proc~~load_tem_bc_realarray~~CallsGraph proc~load_tem_bc_realarray load_tem_BC_realArray proc~tem_create_endiansuffix tem_create_EndianSuffix proc~load_tem_bc_realarray->proc~tem_create_endiansuffix mpi_comm_split mpi_comm_split proc~load_tem_bc_realarray->mpi_comm_split mpi_type_contiguous mpi_type_contiguous proc~load_tem_bc_realarray->mpi_type_contiguous mpi_type_size mpi_type_size proc~load_tem_bc_realarray->mpi_type_size mpi_type_commit mpi_type_commit proc~load_tem_bc_realarray->mpi_type_commit mpi_file_read_all mpi_file_read_all proc~load_tem_bc_realarray->mpi_file_read_all mpi_file_close mpi_file_close proc~load_tem_bc_realarray->mpi_file_close mpi_file_open mpi_file_open proc~load_tem_bc_realarray->mpi_file_open proc~check_mpi_error check_mpi_error proc~load_tem_bc_realarray->proc~check_mpi_error mpi_file_set_view mpi_file_set_view proc~load_tem_bc_realarray->mpi_file_set_view mpi_type_free mpi_type_free proc~load_tem_bc_realarray->mpi_type_free mpi_error_string mpi_error_string proc~check_mpi_error->mpi_error_string proc~tem_abort tem_abort proc~check_mpi_error->proc~tem_abort mpi_abort mpi_abort proc~tem_abort->mpi_abort

Called by

proc~~load_tem_bc_realarray~~CalledByGraph proc~load_tem_bc_realarray load_tem_BC_realArray proc~load_tem_bc_qval load_tem_BC_qVal proc~load_tem_bc_qval->proc~load_tem_bc_realarray proc~load_tem_bc_normal load_tem_BC_normal proc~load_tem_bc_normal->proc~load_tem_bc_realarray

Contents

Source Code


Source Code

  subroutine load_tem_BC_realArray( offset, propname, arraylen, nElems, &
    &                               propdat, basename, myPart, comm     )
    ! ---------------------------------------------------------------------------
    !> Offset of the local set of elements in the global list
    integer(kind=long_k), intent(in)      :: offset
    !> Name of the property to load
    character(len=*), intent(in)          :: propname
    !> Length of the real data array to read per element
    integer, intent(in)                   :: arraylen
    !> Local number of elements with this property
    integer, intent(in)                   :: nElems
    !> real array data to fill
    real(kind=rk), intent(out)            :: propdat(arraylen, nElems)
    !> Name of the file, the data is stored in, will be appended with
    !! ".lua" for the header information and ".lsb" or ".msb" for the
    !! binary data.
    character(len=*), intent(in)          :: basename
    !> Partition to load
    integer, intent(in)                   :: myPart
    !> Communicator to use
    integer, intent(in)                   :: comm
    ! ---------------------------------------------------------------------------
    integer :: i
    integer, parameter :: root = 0
    integer :: propcomm
    integer :: color, iError
    logical :: participant !< If the local rank is a participant in Qval
    character(len=4) :: EndianSuffix
    character(len=256) :: datafile
    real(kind=rk), allocatable :: buffer(:)
    integer(kind=MPI_OFFSET_KIND)     :: displacement
    integer :: fh, etype, ftype, iostatus( MPI_STATUS_SIZE ), typesize
    ! ---------------------------------------------------------------------------

    ! set binary file name
    EndianSuffix = tem_create_EndianSuffix()
    datafile = trim(basename)//trim(EndianSuffix)

    participant = ( nElems > 0 )

    If( participant ) then
      color = 1
    else
      color = MPI_UNDEFINED
    end if

    ! Split the communicator
    call MPI_COMM_SPLIT(comm, color, myPart, propcomm, iError)

    if (nElems > 0) then
      write(logUnit(1), *) 'Load '//propname//' from file: '//trim(datafile)

      allocate( buffer( arraylen * nElems ) )

      ! Open the binary file for MPI I/O (Write)
      call MPI_FILE_OPEN( propcomm, trim(datafile), MPI_MODE_RDONLY, &
        &                 MPI_INFO_NULL, fh, iError                  )
      call check_mpi_error( iError,'File open in load_tem_BC_realarray')

      ! Create a contiguous type to describe the vector per element
      call MPI_TYPE_CONTIGUOUS( arraylen, rk_mpi, etype, iError )
      call check_mpi_error( iError,'contiguous etype in load_tem_BC_realarray')
      call MPI_TYPE_COMMIT(     etype, iError )
      call check_mpi_error( iError,'commit etype in load_tem_BC_realarray')
      call MPI_TYPE_SIZE(etype, typesize, iError )
      call check_mpi_error(iError,'typesize in load_tem_BC_realarray')

      ! Calculate displacement for file view
      displacement = offset * typesize * 1_MPI_OFFSET_KIND


      ! Create a MPI CONTIGUOUS as ftype for file view
      call MPI_TYPE_CONTIGUOUS(nElems, etype, ftype, iError)
      call check_mpi_error( iError,'contiguous ftype in load_tem_BC_realarray')
      call MPI_TYPE_COMMIT( ftype, iError )
      call check_mpi_error( iError,'commit ftype in load_tem_BC_realarray')

      ! Set the view for each process on the file above
      call MPI_FILE_SET_VIEW( fh, displacement, etype, ftype, "native",  &
        &                     MPI_INFO_NULL, iError )
      call check_mpi_error( iError,'set File view in load_tem_BC_realarray' )

      ! Read data from the file
      call MPI_FILE_READ_ALL( fh, buffer, nElems, etype, iostatus, iError )
      call check_mpi_error( iError,'File read all in load_tem_BC_realarray')

      !Free the MPI_Datatypes which were created and close the file
      call MPI_TYPE_FREE (etype, iError)
      call check_mpi_error( iError,'free etype in load_tem_BC_realarray')
      call MPI_TYPE_FREE (ftype, iError)
      call check_mpi_error( iError,'free ftype in load_tem_BC_realarray')
      call MPI_FILE_CLOSE(fh,    iError)
      call check_mpi_error( iError,'close file in load_tem_BC_realarray')
      ! END IO-part

      do i=1,nElems
        propdat(:,i) = buffer( ((i-1)*arraylen+1) : (i*arraylen) )
      end do
      deallocate( buffer )

    end if

  end subroutine load_tem_BC_realarray