dump_tem_BC_prop Subroutine

public subroutine dump_tem_BC_prop(me, offset, nElems, basename, myPart, comm)

dump bc properties

Mpi IO

Arguments

Type IntentOptional Attributes Name
type(tem_BC_prop_type), intent(in) :: me

Boundary condition construct to load the data into

integer(kind=long_k), intent(in) :: offset

Offset of the local set of elements in the global list

integer, intent(in) :: nElems

Local number of elements with this property

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 dump

integer, intent(in) :: comm

Communicator to use


Calls

proc~~dump_tem_bc_prop~~CallsGraph proc~dump_tem_bc_prop dump_tem_BC_prop mpi_file_close mpi_file_close proc~dump_tem_bc_prop->mpi_file_close mpi_file_open mpi_file_open proc~dump_tem_bc_prop->mpi_file_open mpi_file_set_view mpi_file_set_view proc~dump_tem_bc_prop->mpi_file_set_view mpi_file_write_all mpi_file_write_all proc~dump_tem_bc_prop->mpi_file_write_all mpi_type_commit mpi_type_commit proc~dump_tem_bc_prop->mpi_type_commit mpi_type_contiguous mpi_type_contiguous proc~dump_tem_bc_prop->mpi_type_contiguous mpi_type_free mpi_type_free proc~dump_tem_bc_prop->mpi_type_free mpi_type_size mpi_type_size proc~dump_tem_bc_prop->mpi_type_size proc~check_mpi_error check_mpi_error proc~dump_tem_bc_prop->proc~check_mpi_error proc~dump_tem_bc_propheader dump_tem_BC_propHeader proc~dump_tem_bc_prop->proc~dump_tem_bc_propheader proc~tem_create_endiansuffix tem_create_EndianSuffix proc~dump_tem_bc_prop->proc~tem_create_endiansuffix 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 aot_out_close aot_out_close proc~dump_tem_bc_propheader->aot_out_close aot_out_close_table aot_out_close_table proc~dump_tem_bc_propheader->aot_out_close_table aot_out_open aot_out_open proc~dump_tem_bc_propheader->aot_out_open aot_out_open_table aot_out_open_table proc~dump_tem_bc_propheader->aot_out_open_table aot_out_val aot_out_val proc~dump_tem_bc_propheader->aot_out_val mpi_abort mpi_abort proc~tem_abort->mpi_abort

Source Code

  subroutine dump_tem_BC_prop( me, offset, nElems, basename, myPart, comm )
    ! ---------------------------------------------------------------------------
    !> Boundary condition construct to load the data into
    type(tem_BC_prop_type), intent(in) :: me
    !> Offset of the local set of elements in the global list
    integer(kind=long_k), intent(in) :: offset
    !> Local number of elements with this property
    integer, intent(in) :: 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 dump
    integer, intent(in) :: myPart
    !> Communicator to use
    integer, intent(in) :: comm
    ! ---------------------------------------------------------------------------
    integer :: root
    integer :: locomm
    character(len=256) :: headerfile
    character(len=256) :: datafile
    character(len=4) :: EndianSuffix
    ! ---------------------------------------------------------------------------
    integer(kind=MPI_OFFSET_KIND)     :: displacement
    integer :: fh, etype, ftype, ierror, iostatus( MPI_STATUS_SIZE ), typesize
    ! ---------------------------------------------------------------------------

    root = 0

    locomm = comm

    headerfile = trim(basename)//'.lua'
    EndianSuffix = tem_create_EndianSuffix()
    datafile = trim(basename)//trim(EndianSuffix)

    if (myPart == root) then
      ! Only root partition needs to write the header
      !open up the mesh header lua file to dump the stuff using aotus library
      call dump_tem_BC_propHeader( me, headerfile )
    end if

    if (nElems > 0) then
      !> Mpi IO
      write(logUnit(1),*) 'Write boundary ID to file: ' // trim(datafile)

      ! Open the binary file for MPI I/O (Write)
      call MPI_FILE_OPEN( comm, trim(datafile),                  &
        &                 ior(MPI_MODE_WRONLY,MPI_MODE_CREATE),  &
        &                 MPI_INFO_NULL, fh, iError              )
      call check_mpi_error( iError,'Open File in dump_tem_BC_prop')

      ! Create a contiguous type to describe the vector per element
      call MPI_TYPE_CONTIGUOUS( me%nSides, long_k_mpi, etype, iError )
      call check_mpi_error(iError,'contiguous etype in dump_tem_BC_prop')
      call MPI_TYPE_COMMIT( etype, iError )
      call check_mpi_error( iError,'commit etype in dump_tem_BC_prop')
      call MPI_TYPE_SIZE(etype, typesize, iError )
      call check_mpi_error(iError,'typesize in dump_tem_BC_prop')

      ! 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 dump_tem_BC_prop')
      call MPI_TYPE_COMMIT( ftype, iError )
      call check_mpi_error( iError,'commit ftype in dump_tem_BC_prop')

      ! 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 dump_tem_BC_prop')

      ! Read data from the file
      call MPI_FILE_WRITE_ALL( fh, me%boundary_ID, nElems, etype, iostatus, iError )
      call check_mpi_error( iError,'File write all in dump_tem_BC_prop')

      !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 dump_tem_BC_prop')
      call MPI_TYPE_FREE (ftype, iError)
      call check_mpi_error(iError,'free ftype in dump_tem_BC_prop')
      call MPI_FILE_CLOSE(fh,    iError)
      call check_mpi_error(iError,'close file in dump_tem_BC_prop')
      ! END IO-part
    end if

  end subroutine dump_tem_BC_prop