tem_restart_openWrite Subroutine

public subroutine tem_restart_openWrite(me, tree, timing, varSys, subTree, label, suffix)

open the restart dump file and write out the 'normal' restart header as well as the mesh.

Arguments

Type IntentOptional Attributes Name
type(tem_restart_type) :: me

the restart infotmation

type(treelmesh_type) :: tree

mesh, provided in treelm format

type(tem_time_type), intent(in) :: timing

current simulation time information

type(tem_varSys_type), intent(in) :: varSys

the used var systeme

type(tem_subTree_type), intent(inout), optional :: subTree

optional subTree of the given tree

character(len=*), intent(in), optional :: label

additional label for the filename (needed for tracking in harvester format)

character(len=*), intent(in), optional :: suffix

optional suffix (if present NO timestamp will be added!!!!)


Calls

proc~~tem_restart_openwrite~~CallsGraph proc~tem_restart_openwrite tem_restart_openWrite mpi_allreduce mpi_allreduce proc~tem_restart_openwrite->mpi_allreduce mpi_file_open mpi_file_open proc~tem_restart_openwrite->mpi_file_open mpi_file_set_view mpi_file_set_view proc~tem_restart_openwrite->mpi_file_set_view proc~check_mpi_error check_mpi_error proc~tem_restart_openwrite->proc~check_mpi_error proc~dump_treelmesh dump_treelmesh proc~tem_restart_openwrite->proc~dump_treelmesh proc~tem_create_endiansuffix tem_create_EndianSuffix proc~tem_restart_openwrite->proc~tem_create_endiansuffix proc~tem_dump_subtree tem_dump_subTree proc~tem_restart_openwrite->proc~tem_dump_subtree proc~tem_restart_writeheader tem_restart_writeHeader proc~tem_restart_openwrite->proc~tem_restart_writeheader proc~tem_time_sim_stamp tem_time_sim_stamp proc~tem_restart_openwrite->proc~tem_time_sim_stamp 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 proc~dump_treelmesh->mpi_file_open proc~dump_treelmesh->mpi_file_set_view proc~dump_treelmesh->proc~check_mpi_error proc~dump_treelmesh->proc~tem_create_endiansuffix mpi_exscan mpi_exscan proc~dump_treelmesh->mpi_exscan mpi_file_close mpi_file_close proc~dump_treelmesh->mpi_file_close mpi_file_write_all mpi_file_write_all proc~dump_treelmesh->mpi_file_write_all mpi_type_commit mpi_type_commit proc~dump_treelmesh->mpi_type_commit mpi_type_contiguous mpi_type_contiguous proc~dump_treelmesh->mpi_type_contiguous mpi_type_free mpi_type_free proc~dump_treelmesh->mpi_type_free mpi_type_size mpi_type_size proc~dump_treelmesh->mpi_type_size proc~dump_tem_global dump_tem_global proc~dump_treelmesh->proc~dump_tem_global proc~tem_dump_subtree->proc~dump_treelmesh aot_out_close aot_out_close proc~tem_restart_writeheader->aot_out_close aot_out_close_table aot_out_close_table proc~tem_restart_writeheader->aot_out_close_table aot_out_open aot_out_open proc~tem_restart_writeheader->aot_out_open aot_out_open_table aot_out_open_table proc~tem_restart_writeheader->aot_out_open_table aot_out_val aot_out_val proc~tem_restart_writeheader->aot_out_val interface~tem_varsys_out tem_varSys_out proc~tem_restart_writeheader->interface~tem_varsys_out proc~newunit newunit proc~tem_restart_writeheader->proc~newunit proc~tem_mesh_out tem_mesh_out proc~tem_restart_writeheader->proc~tem_mesh_out proc~tem_open tem_open proc~tem_restart_writeheader->proc~tem_open proc~tem_time_out tem_time_out proc~tem_restart_writeheader->proc~tem_time_out

Called by

proc~~tem_restart_openwrite~~CalledByGraph proc~tem_restart_openwrite tem_restart_openWrite proc~hvs_output_open hvs_output_open proc~hvs_output_open->proc~tem_restart_openwrite proc~tem_tracker tem_tracker proc~tem_tracker->proc~hvs_output_open

Source Code

  subroutine tem_restart_openWrite( me, tree, timing, varSys, subTree, label, &
    &                               suffix )
    ! -------------------------------------------------------------------- !
    !> the restart infotmation
    type(tem_restart_type)                          :: me
    !> mesh, provided in treelm format
    type(treelmesh_type)                            :: tree
    !> current simulation time information
    type(tem_time_type),intent(in)                  :: timing
    !> the used var systeme
    type(tem_varSys_type), intent(in)               :: varSys
    !> optional subTree of the given tree
    type(tem_subTree_type), optional, intent(inout) :: subTree
    !> additional label for the filename (needed for tracking in harvester
    !! format)
    character(len=*), optional, intent(in)          :: label
    !> optional suffix (if present NO timestamp will be added!!!!)
    character(len=*), optional, intent(in)          :: suffix
    ! -------------------------------------------------------------------- !
    ! variables to catch possible MPI I/O errors
    integer :: iError
    integer :: pos
    character(len=pathLen) :: prefix
    logical :: meshChange_loc
    type(tem_global_type) :: global_loc
    ! -------------------------------------------------------------------- !

    ! Update the timestamp
    me%header%timestamp = trim(tem_time_sim_stamp(timing))

    ! Set the iteration to know when the last restart file was written
    me%lastWritten = timing

    if ( present(subTree) ) then
      global_loc = subTree%global
    else
      global_loc = tree%global
    end if

    meshChange_loc = global_loc%meshChange

    ! communicate wether the mesh has changed since last time dumping it
    call MPI_ALLREDUCE( meshChange_loc, global_loc%meshChange, 1,     &
      &                 MPI_LOGICAL, MPI_LOR, global_loc%comm, iError )

    ! if the mesh has changed ...
    if (global_loc%meshChange) then
      ! ... set the meshChange to false
      global_loc%meshChange = .false.
      ! ... get the position of the last path seperator
      pos = INDEX(trim(global_loc%dirname), pathSep, .true.)
      if ( present(label) ) then
        prefix = trim(global_loc%dirname(1:pos))//trim(label)//'_'
      else
        prefix = trim(global_loc%dirname(1:pos))
      end if
      if ( present(suffix) ) then
        ! change the dirname using NO timestamp but the suffix
        write(global_loc%dirname,'(a)') trim(prefix)//trim(suffix)//'_'
      else
        ! ... change the dirname
        write(global_loc%dirname,'(a)') trim(prefix)                        &
          &                             // trim( me%header%timestamp ) // '_'
      end if
      ! ... remove a possible predefined tag
      global_loc%predefined = ''
      ! ... copy back the global information to the tree or subTree and dump it
      if ( present(subTree) ) then
        subTree%global = global_loc
        call tem_dump_subTree( subTree, tree )
      else
        tree%global = global_loc
        call dump_treelmesh( tree )
      end if
    end if

    if ( present(suffix) ) then
      ! define the name of the file to write the binary data to without
      ! timestamp but using the suffix
      write(me%header%binName,'(a)') trim( me%header%binPrefix )//'_'  &
        &                               // trim( suffix )              &
        &                               // tem_create_EndianSuffix()
    else
      ! define the name of the file to write the binary data to
      write(me%header%binName,'(a)') trim( me%header%binPrefix )//'_'  &
        &                               // trim( me%header%timestamp ) &
        &                               // tem_create_EndianSuffix()
    end if

    ! open the binary file for MPI I/O
    call MPI_FILE_OPEN( me%comm%comm,                    &
      &                 trim( me%header%binName ),       &
      &                 MPI_MODE_WRONLY+MPI_MODE_CREATE, &
      &                 MPI_INFO_NULL, me%binaryUnit,    &
      &                 iError                           )
    call check_mpi_error( iError, 'File open of '         &
      &                        // trim(me%header%binName) &
      &                        // ' for writing in '      &
      &                        // 'tem_restart_openWrite' )

    call MPI_FILE_SET_VIEW( me%binaryUnit, me%write_file%displacement,     &
      &                     me%write_file%vectype,                         &
      &                     me%write_file%ftype, "native",                 &
      &                     MPI_INFO_NULL, iError                          )
    call check_mpi_error( iError,'set File view in tem_restart_openWrite')

    ! write out a regular restart header
    ! @todo: if [[tem_restart_writeHeader]] is only called here, then it should
    !       not be public. It would be better not to call it here, but let user
    !       decide where to call it.
    call tem_restart_writeHeader( me      = me,      &
      &                           tree    = tree,    &
      &                           subTree = subTree, &
      &                           timing  = timing,  &
      &                           varSys  = varSys,  &
      &                           suffix  = suffix   )

  end subroutine tem_restart_openWrite