save_string_parameter Subroutine

public subroutine save_string_parameter(h5file_id, dset, string_array)

Arguments

Type IntentOptional AttributesName
integer(kind=HID_T), intent(in) :: h5file_id
character(len=MAX_STRING_LENGTH), intent(in) :: dset
character(len=MAX_STRING_LENGTH), intent(in), DIMENSION(:):: string_array

Calls

proc~~save_string_parameter~~CallsGraph proc~save_string_parameter save_string_parameter h5dwrite_vl_f h5dwrite_vl_f proc~save_string_parameter->h5dwrite_vl_f h5dclose_f h5dclose_f proc~save_string_parameter->h5dclose_f h5tcopy_f h5tcopy_f proc~save_string_parameter->h5tcopy_f h5screate_simple_f h5screate_simple_f proc~save_string_parameter->h5screate_simple_f h5sclose_f h5sclose_f proc~save_string_parameter->h5sclose_f h5tset_strpad_f h5tset_strpad_f proc~save_string_parameter->h5tset_strpad_f

Called by

proc~~save_string_parameter~~CalledByGraph proc~save_string_parameter save_string_parameter proc~save_params_ms save_params_ms proc~save_params_ms->proc~save_string_parameter proc~save_simulation_parameters save_simulation_parameters proc~save_simulation_parameters->proc~save_string_parameter proc~save_params_ss save_params_ss proc~save_params_ss->proc~save_string_parameter program~main main program~main->proc~save_simulation_parameters proc~save_collision_params save_collision_params program~main->proc~save_collision_params proc~save_collision_params->proc~save_params_ms proc~save_collision_params->proc~save_params_ss

Contents

Source Code


Source Code

  subroutine save_string_parameter(h5file_id,dset,string_array)
    INTEGER(HID_T), INTENT(IN) 								:: h5file_id
    CHARACTER(MAX_STRING_LENGTH), INTENT(IN) 				:: dset
    CHARACTER(MAX_STRING_LENGTH), DIMENSION(:), INTENT(IN) 	:: string_array
    INTEGER(HID_T) 											:: dset_id
    INTEGER(HID_T) 											:: dspace_id
    INTEGER(HSIZE_T), DIMENSION(1) 							:: dims
    INTEGER(HSIZE_T), DIMENSION(2) 							:: data_dims
    INTEGER(SIZE_T), DIMENSION(:), ALLOCATABLE 				:: str_len
    INTEGER(HID_T) 											:: string_type
    INTEGER 												:: h5error

    ALLOCATE(str_len(SIZE(string_array)))

    dims = (/SIZE(string_array)/)
    data_dims = (/MAX_STRING_LENGTH,SIZE(string_array)/)
    str_len = (/LEN_TRIM(string_array)/)

    call h5tcopy_f(H5T_STRING,string_type,h5error)
    call h5tset_strpad_f(string_type,H5T_STR_SPACEPAD_F,h5error)

    call h5screate_simple_f(1,dims,dspace_id,h5error)

    call h5dcreate_f(h5file_id,TRIM(dset),string_type,dspace_id,dset_id,h5error)

    call h5dwrite_vl_f(dset_id,string_type,string_array,data_dims,str_len,h5error,dspace_id)

    call h5sclose_f(dspace_id, h5error)
    call h5dclose_f(dset_id, h5error)

    DEALLOCATE(str_len)
  end subroutine save_string_parameter