shelf_read_data Subroutine

private subroutine shelf_read_data(this, file_id, group_name, error)

Reads the state of the ice shelf object from the specified group in an HDF5 file. This sets the thickness, the velocity, and parameter values.

Arguments

Type IntentOptional AttributesName
class(ice_shelf), intent(inout) :: this
integer(kind=hid_t), intent(in) :: file_id

The identifier for the HDF5 file/group in which this data is meant to be written.

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

The name to give the group in the HDF5 file storing the ice shelf's data.

integer, intent(out) :: error

Flag indicating whether routine ran without error. If no error occurs then has value 0.


Calls

proc~~shelf_read_data~~CallsGraph proc~shelf_read_data shelf_read_data h5gopen_f h5gopen_f proc~shelf_read_data->h5gopen_f str str proc~shelf_read_data->str h5ltget_attribute_int_f h5ltget_attribute_int_f proc~shelf_read_data->h5ltget_attribute_int_f h5ltget_attribute_string_f h5ltget_attribute_string_f proc~shelf_read_data->h5ltget_attribute_string_f h5ltget_attribute_double_f h5ltget_attribute_double_f proc~shelf_read_data->h5ltget_attribute_double_f h5gclose_f h5gclose_f proc~shelf_read_data->h5gclose_f

Contents

Source Code


Source Code

  subroutine shelf_read_data(this,file_id,group_name,error)
    !* Author: Chris MacMackin
    !  Date: April 2017
    !
    ! Reads the state of the ice shelf object from the specified group
    ! in an HDF5 file. This sets the thickness, the velocity, and
    ! parameter values.
    !
    class(ice_shelf), intent(inout) :: this
    integer(hid_t), intent(in)      :: file_id
      !! The identifier for the HDF5 file/group in which this data is
      !! meant to be written.
    character(len=*), intent(in)    :: group_name
      !! The name to give the group in the HDF5 file storing the
      !! ice shelf's data.
    integer, intent(out)            :: error
      !! Flag indicating whether routine ran without error. If no
      !! error occurs then has value 0.
    integer(hid_t) :: group_id
    integer :: ret_err, i, nkap
    real(r8), dimension(1) :: param
    integer, dimension(1) :: iparam
    character(len=20) :: fieldname
    character(len=50) :: ice_type

    ret_err = 0
    call h5gopen_f(file_id, group_name, group_id, error)
    if (error /= 0) then
      call logger%error('ice_shelf%read_data','Could not open HDF group "'// &
                        group_name//'", so no IO performed.')
      return
    end if

    call h5ltget_attribute_string_f(file_id, group_name, hdf_type_attr, &
                                    ice_type, error)
    if (trim(ice_type) /= hdf_type_name) then
      call logger%error('ice_shelf%read_data','Trying to read data from '// &
                        'glacier of type other than ice_shelf.')
      error = -1
      return
    end if
    call h5ltget_attribute_double_f(file_id, group_name, hdf_lambda, &
                                    param, error)
    this%lambda = param(1)
    call h5ltget_attribute_double_f(file_id, group_name, hdf_chi, &
                                    param, error)
    this%chi = param(1)
    call h5ltget_attribute_double_f(file_id, group_name, hdf_zeta, &
                                    param, error)
    this%zeta = param(1)
    if (error /= 0) then
      call logger%warning('ice_shelf%read_data','Error code '//  &
                          trim(str(error))//' returned when '//  &
                          'reading attributes from HDF group '// &
                          group_name)
      ret_err = error
    end if
    call h5ltget_attribute_int_f(file_id, group_name, hdf_n_kappa, &
                                 iparam, error)
    if (error /= 0) then
      ! For backwards compatibility, don't crash if this attribute is
      ! not present. Instead just realise there is no internal layer
      ! data in the HDF file.
      nkap = 0
    else
      nkap = iparam(1)
    end if

    call this%thickness%read_hdf(group_id, hdf_thickness, error)
    if (error /= 0) then
      call logger%warning('ice_shelf%read_data','Error code '//        &
                          trim(str(error))//' returned when reading '// &
                          'ice shelf thickness field from HDF file')
      if (ret_err == 0) ret_err = error
    end if

    call this%velocity%read_hdf(group_id, hdf_velocity, error)
    if (error /= 0) then
      call logger%warning('ice_shelf%read_data','Error code '// &
                          trim(str(error))//' returned when '//  &
                          'reading ice shelf velocity field '//  &
                          'from HDF file')
      if (ret_err == 0) ret_err = error
    end if

    if (nkap > 0) allocate(this%kappa(nkap))
    do i = 1, nkap
      write(fieldname , hdf_kappa) i
      call this%kappa(i)%read_hdf(group_id, fieldname, error)
      if (error /= 0) then
        call logger%warning('ice_shelf%read_data','Error code '//        &
                            trim(str(error))//' returned when reading '// &
                            'ice shelf kappa field from HDF file')
        if (ret_err == 0) ret_err = error
      end if
    end do

    call h5gclose_f(group_id, error)
    if (error /= 0) then
      call logger%warning('ice_shelf%read_data','Error code '// &
                          trim(str(error))//' returned when '//  &
                          'closing HDF group '//group_name)
      if (ret_err == 0) ret_err = error
    end if
    error = ret_err
#ifdef DEBUG
    call logger%debug('ice_shelf%read_data','Read ice shelf data from '// &
                      'HDF group '//group_name)
#endif
  end subroutine shelf_read_data