Skip to content

Commit

Permalink
changes all fms2 fileobj instances to fms2io_fileobj (NOAA-GFDL#1333)
Browse files Browse the repository at this point in the history
* change `fileobj` to `fms2io_fileobj`
  • Loading branch information
mcallic2 authored and rem1776 committed May 1, 2024
1 parent 2f1c376 commit a5a6311
Show file tree
Hide file tree
Showing 4 changed files with 175 additions and 172 deletions.
77 changes: 39 additions & 38 deletions diag_manager/fms_diag_axis_object.F90
Original file line number Diff line number Diff line change
Expand Up @@ -291,9 +291,9 @@ subroutine add_axis_attribute(this, att_name, att_value)
end subroutine add_axis_attribute

!> @brief Write the axis meta data to an open fileobj
subroutine write_axis_metadata(this, fileobj, edges_in_file, parent_axis)
subroutine write_axis_metadata(this, fms2io_fileobj, edges_in_file, parent_axis)
class(fmsDiagAxis_type), target, INTENT(IN) :: this !< diag_axis obj
class(FmsNetcdfFile_t), INTENT(INOUT) :: fileobj !< Fms2_io fileobj to write the data to
class(FmsNetcdfFile_t), INTENT(INOUT) :: fms2io_fileobj!< Fms2_io fileobj to write the data to
logical, INTENT(IN) :: edges_in_file !< .True. if the edges to this axis are
!! already in the file
class(fmsDiagAxis_type), OPTIONAL, target, INTENT(IN) :: parent_axis !< If the axis is a subaxis, axis object
Expand Down Expand Up @@ -330,85 +330,86 @@ subroutine write_axis_metadata(this, fileobj, edges_in_file, parent_axis)
endif
type_of_domain = NO_DOMAIN !< All subaxes are treated as non-domain decomposed (each rank writes it own file)
type is (fmsDiagDiurnalAxis_type)
call this%write_diurnal_metadata(fileobj)
call this%write_diurnal_metadata(fms2io_fileobj)
return
end select

!< Add the axis as a dimension in the netcdf file based on the type of axis_domain and the fileobj type
select type (fileobj)
select type (fms2io_fileobj)
!< The register_field calls need to be inside the select type block so that it can go inside the correct
!! register_field interface
type is (FmsNetcdfFile_t)
!< Here the axis is not domain decomposed (i.e z_axis)
call register_axis(fileobj, axis_name, axis_length)
call register_field(fileobj, axis_name, diag_axis%type_of_data, (/axis_name/))
call register_axis(fms2io_fileobj, axis_name, axis_length)
call register_field(fms2io_fileobj, axis_name, diag_axis%type_of_data, (/axis_name/))
type is (FmsNetcdfDomainFile_t)
select case (type_of_domain)
case (NO_DOMAIN)
!< Here the fileobj is domain decomposed, but the axis is not
!< Here the fms2io_fileobj is domain decomposed, but the axis is not
!! Domain decomposed fileobjs can have axis that are not domain decomposed (i.e "Z" axis)
call register_axis(fileobj, axis_name, axis_length)
call register_field(fileobj, axis_name, diag_axis%type_of_data, (/axis_name/))
call register_axis(fms2io_fileobj, axis_name, axis_length)
call register_field(fms2io_fileobj, axis_name, diag_axis%type_of_data, (/axis_name/))
case (TWO_D_DOMAIN)
!< Here the axis is domain decomposed
call register_axis(fileobj, axis_name, diag_axis%cart_name, domain_position=diag_axis%domain_position)
call register_field(fileobj, axis_name, diag_axis%type_of_data, (/axis_name/))
call register_axis(fms2io_fileobj, axis_name, diag_axis%cart_name, domain_position=diag_axis%domain_position)
call register_field(fms2io_fileobj, axis_name, diag_axis%type_of_data, (/axis_name/))
end select
type is (FmsNetcdfUnstructuredDomainFile_t)
select case (type_of_domain)
case (UG_DOMAIN)
!< Here the axis is in a unstructured domain
call register_axis(fileobj, axis_name)
call register_field(fileobj, axis_name, diag_axis%type_of_data, (/axis_name/))
call register_axis(fms2io_fileobj, axis_name)
call register_field(fms2io_fileobj, axis_name, diag_axis%type_of_data, (/axis_name/))
case default
!< Here the fileobj is in the unstructured domain, but the axis is not
!< Here the fms2io_fileobj is in the unstructured domain, but the axis is not
!< Unstructured domain fileobjs can have axis that are not domain decomposed (i.e "Z" axis)
call register_axis(fileobj, axis_name, axis_length)
call register_field(fileobj, axis_name, diag_axis%type_of_data, (/axis_name/))
call register_axis(fms2io_fileobj, axis_name, axis_length)
call register_field(fms2io_fileobj, axis_name, diag_axis%type_of_data, (/axis_name/))
end select
end select

!< Write its metadata
call register_variable_attribute(fileobj, axis_name, "long_name", diag_axis%long_name, &
call register_variable_attribute(fms2io_fileobj, axis_name, "long_name", diag_axis%long_name, &
str_len=len_trim(diag_axis%long_name))

if (diag_axis%cart_name .NE. "N") &
call register_variable_attribute(fileobj, axis_name, "axis", diag_axis%cart_name, str_len=1)
call register_variable_attribute(fms2io_fileobj, axis_name, "axis", diag_axis%cart_name, str_len=1)

if (trim(diag_axis%units) .NE. "none") &
call register_variable_attribute(fileobj, axis_name, "units", diag_axis%units, str_len=len_trim(diag_axis%units))
call register_variable_attribute(fms2io_fileobj, axis_name, "units", diag_axis%units, &
str_len=len_trim(diag_axis%units))

select case (diag_axis%direction)
case (direction_up)
call register_variable_attribute(fileobj, axis_name, "positive", "up", str_len=2)
call register_variable_attribute(fms2io_fileobj, axis_name, "positive", "up", str_len=2)
case (direction_down)
call register_variable_attribute(fileobj, axis_name, "positive", "down", str_len=4)
call register_variable_attribute(fms2io_fileobj, axis_name, "positive", "down", str_len=4)
end select

!< Ignore the edges attribute, if the edges are already in the file or if it is subaxis
if (.not. edges_in_file .and. allocated(diag_axis%edges_name) .and. .not. is_subaxis) then
call register_variable_attribute(fileobj, axis_name, "edges", diag_axis%edges_name, &
call register_variable_attribute(fms2io_fileobj, axis_name, "edges", diag_axis%edges_name, &
str_len=len_trim(diag_axis%edges_name))
endif

if(allocated(diag_axis%attributes)) then
do i = 1, diag_axis%num_attributes
select type (att_value => diag_axis%attributes(i)%att_value)
type is (character(len=*))
call register_variable_attribute(fileobj, axis_name, diag_axis%attributes(i)%att_name, trim(att_value(1)), &
str_len=len_trim(att_value(1)))
call register_variable_attribute(fms2io_fileobj, axis_name, diag_axis%attributes(i)%att_name, &
trim(att_value(1)), str_len=len_trim(att_value(1)))
class default
call register_variable_attribute(fileobj, axis_name, diag_axis%attributes(i)%att_name, att_value)
call register_variable_attribute(fms2io_fileobj, axis_name, diag_axis%attributes(i)%att_name, att_value)
end select
enddo
endif

end subroutine write_axis_metadata

!> @brief Write the axis data to an open fileobj
subroutine write_axis_data(this, fileobj, parent_axis)
!> @brief Write the axis data to an open fms2io_fileobj
subroutine write_axis_data(this, fms2io_fileobj, parent_axis)
class(fmsDiagAxis_type), target, INTENT(IN) :: this !< diag_axis obj
class(FmsNetcdfFile_t), INTENT(INOUT) :: fileobj !< Fms2_io fileobj to write the data to
class(FmsNetcdfFile_t), INTENT(INOUT) :: fms2io_fileobj!< Fms2_io fileobj to write the data to
class(fmsDiagAxis_type), OPTIONAL, target, INTENT(IN) :: parent_axis !< The parent axis if this is a subaxis

integer :: i !< Starting index of a sub_axis
Expand All @@ -417,19 +418,19 @@ subroutine write_axis_data(this, fileobj, parent_axis)
select type(this)
type is (fmsDiagFullAxis_type)
call this%get_global_io_domain(global_io_index)
call write_data(fileobj, this%axis_name, this%axis_data(global_io_index(1):global_io_index(2)))
call write_data(fms2io_fileobj, this%axis_name, this%axis_data(global_io_index(1):global_io_index(2)))
type is (fmsDiagSubAxis_type)
i = this%starting_index
j = this%ending_index

if (present(parent_axis)) then
select type(parent_axis)
type is (fmsDiagFullAxis_type)
call write_data(fileobj, this%subaxis_name, parent_axis%axis_data(i:j))
call write_data(fms2io_fileobj, this%subaxis_name, parent_axis%axis_data(i:j))
end select
endif
type is (fmsDiagDiurnalAxis_type)
call write_data(fileobj, this%axis_name, this%diurnal_data)
call write_data(fms2io_fileobj, this%axis_name, this%diurnal_data)
end select
end subroutine write_axis_data

Expand Down Expand Up @@ -1263,18 +1264,18 @@ pure function get_diurnal_axis_samples(this) &
end function get_diurnal_axis_samples

!< @brief Writes out the metadata for a diurnal axis
subroutine write_diurnal_metadata(this, fileobj)
subroutine write_diurnal_metadata(this, fms2io_fileobj)
class(fmsDiagDiurnalAxis_type), intent(in) :: this !< Diurnal axis Object
class(FmsNetcdfFile_t), intent(inout) :: fileobj !< Fms2_io fileobj to write the data to
class(FmsNetcdfFile_t), intent(inout) :: fms2io_fileobj !< Fms2_io fileobj to write the data to

call register_axis(fileobj, this%axis_name, size(this%diurnal_data))
call register_field(fileobj, this%axis_name, pack_size_str, (/trim(this%axis_name)/))
call register_variable_attribute(fileobj, this%axis_name, "units", &
call register_axis(fms2io_fileobj, this%axis_name, size(this%diurnal_data))
call register_field(fms2io_fileobj, this%axis_name, pack_size_str, (/trim(this%axis_name)/))
call register_variable_attribute(fms2io_fileobj, this%axis_name, "units", &
&trim(this%units), str_len=len_trim(this%units))
call register_variable_attribute(fileobj, this%axis_name, "long_name", &
call register_variable_attribute(fms2io_fileobj, this%axis_name, "long_name", &
&trim(this%long_name), str_len=len_trim(this%long_name))
if (this%edges_id .ne. diag_null) &
call register_variable_attribute(fileobj, this%axis_name, "edges", &
call register_variable_attribute(fms2io_fileobj, this%axis_name, "edges", &
&trim(this%edges_name), str_len=len_trim(this%edges_name))
end subroutine write_diurnal_metadata

Expand Down
58 changes: 29 additions & 29 deletions diag_manager/fms_diag_field_object.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1105,27 +1105,27 @@ end subroutine get_dimnames

!> @brief Wrapper for the register_field call. The select types are needed so that the code can go
!! in the correct interface
subroutine register_field_wrap(fileobj, varname, vartype, dimensions)
class(FmsNetcdfFile_t), INTENT(INOUT) :: fileobj !< Fms2_io fileobj to write to
subroutine register_field_wrap(fms2io_fileobj, varname, vartype, dimensions)
class(FmsNetcdfFile_t), INTENT(INOUT) :: fms2io_fileobj!< Fms2_io fileobj to write to
character(len=*), INTENT(IN) :: varname !< Name of the variable
character(len=*), INTENT(IN) :: vartype !< The type of the variable
character(len=*), optional, INTENT(IN) :: dimensions(:) !< The dimension names of the field

select type(fileobj)
select type(fms2io_fileobj)
type is (FmsNetcdfFile_t)
call register_field(fileobj, varname, vartype, dimensions)
call register_field(fms2io_fileobj, varname, vartype, dimensions)
type is (FmsNetcdfDomainFile_t)
call register_field(fileobj, varname, vartype, dimensions)
call register_field(fms2io_fileobj, varname, vartype, dimensions)
type is (FmsNetcdfUnstructuredDomainFile_t)
call register_field(fileobj, varname, vartype, dimensions)
call register_field(fms2io_fileobj, varname, vartype, dimensions)
end select
end subroutine register_field_wrap

!> @brief Write the field's metadata to the file
subroutine write_field_metadata(this, fileobj, file_id, yaml_id, diag_axis, unlim_dimname, is_regional, &
subroutine write_field_metadata(this, fms2io_fileobj, file_id, yaml_id, diag_axis, unlim_dimname, is_regional, &
cell_measures)
class (fmsDiagField_type), target, intent(inout) :: this !< diag field
class(FmsNetcdfFile_t), INTENT(INOUT) :: fileobj !< Fms2_io fileobj to write to
class(FmsNetcdfFile_t), INTENT(INOUT) :: fms2io_fileobj!< Fms2_io fileobj to write to
integer, intent(in) :: file_id !< File id of the file to write to
integer, intent(in) :: yaml_id !< Yaml id of the yaml entry of this field
class(fmsDiagAxisContainer_type), intent(in) :: diag_axis(:) !< Diag_axis object
Expand All @@ -1147,50 +1147,50 @@ subroutine write_field_metadata(this, fileobj, file_id, yaml_id, diag_axis, unli

if (allocated(this%axis_ids)) then
call this%get_dimnames(diag_axis, field_yaml, unlim_dimname, dimnames, is_regional)
call register_field_wrap(fileobj, var_name, this%get_var_skind(field_yaml), dimnames)
call register_field_wrap(fms2io_fileobj, var_name, this%get_var_skind(field_yaml), dimnames)
else
if (this%is_static()) then
call register_field_wrap(fileobj, var_name, this%get_var_skind(field_yaml))
call register_field_wrap(fms2io_fileobj, var_name, this%get_var_skind(field_yaml))
else
!< In this case, the scalar variable is a function of time, so we need to pass in the
!! unlimited dimension as a dimension
call register_field_wrap(fileobj, var_name, this%get_var_skind(field_yaml), (/unlim_dimname/))
call register_field_wrap(fms2io_fileobj, var_name, this%get_var_skind(field_yaml), (/unlim_dimname/))
endif
endif

long_name = this%get_longname_to_write(field_yaml)
call register_variable_attribute(fileobj, var_name, "long_name", long_name, str_len=len_trim(long_name))
call register_variable_attribute(fms2io_fileobj, var_name, "long_name", long_name, str_len=len_trim(long_name))

units = this%get_units()
if (units .ne. diag_null_string) &
call register_variable_attribute(fileobj, var_name, "units", units, str_len=len_trim(units))
call register_variable_attribute(fms2io_fileobj, var_name, "units", units, str_len=len_trim(units))

if (this%has_missing_value()) then
call register_variable_attribute(fileobj, var_name, "missing_value", &
call register_variable_attribute(fms2io_fileobj, var_name, "missing_value", &
this%get_missing_value(field_yaml%get_var_kind()))
call register_variable_attribute(fileobj, var_name, "_FillValue", &
call register_variable_attribute(fms2io_fileobj, var_name, "_FillValue", &
this%get_missing_value(field_yaml%get_var_kind()))
else
call register_variable_attribute(fileobj, var_name, "missing_value", &
call register_variable_attribute(fms2io_fileobj, var_name, "missing_value", &
get_default_missing_value(field_yaml%get_var_kind()))
call register_variable_attribute(fileobj, var_name, "_FillValue", &
call register_variable_attribute(fms2io_fileobj, var_name, "_FillValue", &
get_default_missing_value(field_yaml%get_var_kind()))
endif

if (this%has_data_RANGE()) then
call register_variable_attribute(fileobj, var_name, "valid_range", &
call register_variable_attribute(fms2io_fileobj, var_name, "valid_range", &
this%get_data_range(field_yaml%get_var_kind()))
endif

if (this%has_interp_method()) then
call register_variable_attribute(fileobj, var_name, "interp_method", this%get_interp_method(), &
call register_variable_attribute(fms2io_fileobj, var_name, "interp_method", this%get_interp_method(), &
str_len=len_trim(this%get_interp_method()))
endif

if (.not. this%static) then
select case (field_yaml%get_var_reduction())
case (time_average, time_max, time_min, time_diurnal, time_power, time_rms, time_sum)
call register_variable_attribute(fileobj, var_name, "time_avg_info", &
call register_variable_attribute(fms2io_fileobj, var_name, "time_avg_info", &
trim(avg_name)//'_T1,'//trim(avg_name)//'_T2,'//trim(avg_name)//'_DT', &
str_len=len(trim(avg_name)//'_T1,'//trim(avg_name)//'_T2,'//trim(avg_name)//'_DT'))
end select
Expand All @@ -1200,34 +1200,34 @@ subroutine write_field_metadata(this, fileobj, file_id, yaml_id, diag_axis, unli
!< Check if any of the attributes defined via a "diag_field_add_attribute" call
!! are the cell_methods, if so add to the "cell_methods" variable:
do i = 1, this%num_attributes
call this%attributes(i)%write_metadata(fileobj, var_name, &
call this%attributes(i)%write_metadata(fms2io_fileobj, var_name, &
cell_methods=cell_methods)
enddo

!< Append the time cell methods based on the variable's reduction
call this%append_time_cell_methods(cell_methods, field_yaml)
if (trim(cell_methods) .ne. "") &
call register_variable_attribute(fileobj, var_name, "cell_methods", &
call register_variable_attribute(fms2io_fileobj, var_name, "cell_methods", &
trim(adjustl(cell_methods)), str_len=len_trim(adjustl(cell_methods)))

!< Write out the cell_measures attribute (i.e Area, Volume)
!! The diag field ids for the Area and Volume are sent in the register call
!! This was defined in file object and passed in here
if (trim(cell_measures) .ne. "") &
call register_variable_attribute(fileobj, var_name, "cell_measures", &
call register_variable_attribute(fms2io_fileobj, var_name, "cell_measures", &
trim(adjustl(cell_measures)), str_len=len_trim(adjustl(cell_measures)))

!< Write out the standard_name (this was defined in the register call)
if (this%has_standname()) &
call register_variable_attribute(fileobj, var_name, "standard_name", &
call register_variable_attribute(fms2io_fileobj, var_name, "standard_name", &
trim(this%get_standname()), str_len=len_trim(this%get_standname()))

call this%write_coordinate_attribute(fileobj, var_name, diag_axis)
call this%write_coordinate_attribute(fms2io_fileobj, var_name, diag_axis)

if (field_yaml%has_var_attributes()) then
yaml_field_attributes = field_yaml%get_var_attributes()
do i = 1, size(yaml_field_attributes,1)
call register_variable_attribute(fileobj, var_name, trim(yaml_field_attributes(i,1)), &
call register_variable_attribute(fms2io_fileobj, var_name, trim(yaml_field_attributes(i,1)), &
trim(yaml_field_attributes(i,2)), str_len=len_trim(yaml_field_attributes(i,2)))
enddo
deallocate(yaml_field_attributes)
Expand All @@ -1236,9 +1236,9 @@ end subroutine write_field_metadata

!> @brief Writes the coordinate attribute of a field if any of the field's axis has an
!! auxiliary axis
subroutine write_coordinate_attribute (this, fileobj, var_name, diag_axis)
subroutine write_coordinate_attribute (this, fms2io_fileobj, var_name, diag_axis)
CLASS(fmsDiagField_type), intent(in) :: this !< The field object
class(FmsNetcdfFile_t), INTENT(INOUT) :: fileobj !< Fms2_io fileobj to write to
class(FmsNetcdfFile_t), INTENT(INOUT) :: fms2io_fileobj!< Fms2_io fileobj to write to
character(len=*), intent(in) :: var_name !< Variable name
class(fmsDiagAxisContainer_type), intent(in) :: diag_axis(:) !< Diag_axis object

Expand All @@ -1262,7 +1262,7 @@ subroutine write_coordinate_attribute (this, fileobj, var_name, diag_axis)

if (trim(aux_coord) .eq. "") return

call register_variable_attribute(fileobj, var_name, "coordinates", &
call register_variable_attribute(fms2io_fileobj, var_name, "coordinates", &
trim(adjustl(aux_coord)), str_len=len_trim(adjustl(aux_coord)))

end subroutine write_coordinate_attribute
Expand Down
Loading

0 comments on commit a5a6311

Please sign in to comment.