tem_dump_weights Subroutine

public subroutine tem_dump_weights(me, filename, weights)

Arguments

Type IntentOptional Attributes Name
type(treelmesh_type), intent(in) :: me
character(len=*), intent(in) :: filename

Weights file name

real(kind=rk), intent(in) :: weights(me%nElems)

Calls

proc~~tem_dump_weights~~CallsGraph proc~tem_dump_weights tem_dump_weights mpi_file_close mpi_file_close proc~tem_dump_weights->mpi_file_close mpi_file_open mpi_file_open proc~tem_dump_weights->mpi_file_open mpi_file_set_size mpi_file_set_size proc~tem_dump_weights->mpi_file_set_size mpi_file_set_view mpi_file_set_view proc~tem_dump_weights->mpi_file_set_view mpi_file_write_all mpi_file_write_all proc~tem_dump_weights->mpi_file_write_all mpi_type_commit mpi_type_commit proc~tem_dump_weights->mpi_type_commit mpi_type_contiguous mpi_type_contiguous proc~tem_dump_weights->mpi_type_contiguous mpi_type_free mpi_type_free proc~tem_dump_weights->mpi_type_free mpi_type_size mpi_type_size proc~tem_dump_weights->mpi_type_size proc~check_mpi_error check_mpi_error proc~tem_dump_weights->proc~check_mpi_error 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

Source Code

  subroutine tem_dump_weights( me, filename, weights )
    ! -------------------------------------------------------------------- !
    type(treelmesh_type), intent(in) :: me
    !> Weights file name
    character(len=*), intent(in) :: filename
    real(kind=rk), intent(in)    :: weights(me%nElems)
    ! -------------------------------------------------------------------- !
    integer                       :: nElems
    integer                       :: comm
    integer(kind=long_k)          :: offset, globElems
    integer(kind=long_k)          :: filesize
    integer(kind=MPI_OFFSET_KIND) :: displacement
    integer                       :: fh, ftype, iError
    integer                       :: iostatus( MPI_STATUS_SIZE )
    integer                       :: typesize
    ! -------------------------------------------------------------------- !

    nElems = me%nElems
    comm = me%global%comm
    offset = me%elemOffset
    globElems = me%global%nElems

    ! Found a weights file, which is used to read a weight for each
    ! element.
    write(logUnit(1),*) 'Dumping Weights to file: '//trim(filename)
    ! Open the binary file for MPI I/O (Write)
    call MPI_File_open( comm, trim(filename),                 &
      &                 ior(MPI_MODE_WRONLY,MPI_MODE_CREATE), &
      &                 MPI_INFO_NULL, fh, iError             )
    call check_mpi_error(iError,'file_open in dump_weights')

    ! Create a MPI Subarray  as ftype for file view
    call MPI_Type_contiguous( nElems, rk_mpi , ftype, iError )
    call check_mpi_error(iError,'type ftype in dump_weights')
    call MPI_Type_commit( ftype, iError )
    call check_mpi_error(iError,'commit ftype in dump_weights')

    !get size of etype
    call MPI_Type_size(rk_mpi, typesize, iError )
    call check_mpi_error(iError,'typesize in dump_weights')

    ! calculate displacement
    displacement= offset * typesize * 1_MPI_OFFSET_KIND

    ! set filesize
    filesize = globElems * typesize
    call MPI_File_set_size( fh, filesize, iError )

    ! Set the view for each process on the file above
    call MPI_File_set_view( fh, displacement, rk_mpi, ftype, &
      &                     "native", MPI_INFO_NULL, iError  )
    call check_mpi_error(iError,'set_view in dump_weights')

    ! Read data from the file
    call MPI_File_write_all( fh, weights, nElems, rk_mpi, iostatus, iError )
    call check_mpi_error(iError,'read_all in dump_weights')

    !Free the MPI_Datatypes which were created and close the file
    call MPI_Type_free(ftype, iError)
    call check_mpi_error(iError,'free ftype in dump_weights')
    call MPI_File_close(fh,    iError)
    call check_mpi_error(iError,'close file in dump_weights')
    write(logUnit(1),*) 'Done dumping weights.'

  end subroutine tem_dump_weights