Skip to content

Commit

Permalink
feat: finish register diag field routines (NOAA-GFDL#984)
Browse files Browse the repository at this point in the history
  • Loading branch information
uramirez8707 authored and rem1776 committed May 1, 2024
1 parent 839e4cb commit 0dc70d7
Show file tree
Hide file tree
Showing 9 changed files with 280 additions and 184 deletions.
1 change: 1 addition & 0 deletions diag_manager/diag_data.F90
Original file line number Diff line number Diff line change
Expand Up @@ -101,6 +101,7 @@ MODULE diag_data_mod
INTEGER, PARAMETER :: NO_DOMAIN = 1 !< Use the FmsNetcdfFile_t fileobj
INTEGER, PARAMETER :: TWO_D_DOMAIN = 2 !< Use the FmsNetcdfDomainFile_t fileobj
INTEGER, PARAMETER :: UG_DOMAIN = 3 !< Use the FmsNetcdfUnstructuredDomainFile_t fileobj
INTEGER, PARAMETER :: SUB_REGIONAL = 4 !< This is a file with a sub_region use the FmsNetcdfFile_t fileobj
INTEGER, PARAMETER :: DIRECTION_UP = 1 !< The axis points up if positive
INTEGER, PARAMETER :: DIRECTION_DOWN = -1 !< The axis points down if positive
INTEGER, PARAMETER :: GLO_REG_VAL = -999 !< Value used in the region specification of the diag_table
Expand Down
32 changes: 20 additions & 12 deletions diag_manager/diag_manager.F90
Original file line number Diff line number Diff line change
Expand Up @@ -473,21 +473,25 @@ INTEGER FUNCTION register_diag_field_scalar_modern(module_name, field_name, init
CHARACTER(len=*), OPTIONAL, INTENT(in) :: realm !< String to set as the modeling_realm attribute

#ifdef use_yaml
integer, allocatable :: diag_file_indices(:) !< indices where the field was found
integer, allocatable :: diag_field_indices(:) !< indices where the field was found

diag_file_indices = find_diag_field(field_name)
if (diag_file_indices(1) .eq. diag_null) then
diag_field_indices = find_diag_field(field_name)
if (diag_field_indices(1) .eq. diag_null) then
!< The field was not found in the table, so return diag_null
register_diag_field_scalar_modern = diag_null
deallocate(diag_file_indices)
deallocate(diag_field_indices)
return
endif

registered_variables = registered_variables + 1
register_diag_field_scalar_modern = registered_variables

!< TO DO: Fill in the diag_obj
deallocate(diag_file_indices)
call diag_objs(registered_variables)%setID(registered_variables)
call diag_objs(registered_variables)%register(module_name, field_name, init_time, diag_field_indices, &
& longname=long_name, units=units, missing_value=missing_value, varrange=var_range, &
& standname=standard_name, do_not_log=do_not_log, err_msg=err_msg, &
& area=area, volume=volume, realm=realm)
deallocate(diag_field_indices)
#endif

end function register_diag_field_scalar_modern
Expand Down Expand Up @@ -520,21 +524,25 @@ INTEGER FUNCTION register_diag_field_array_modern(module_name, field_name, axes,
CHARACTER(len=*), OPTIONAL, INTENT(in) :: realm !< String to set as the modeling_realm attribute

#ifdef use_yaml
integer, allocatable :: diag_file_indices(:) !< indices where the field was found
integer, allocatable :: diag_field_indices(:) !< indices of diag_field yaml where the field was found

diag_file_indices = find_diag_field(field_name)
if (diag_file_indices(1) .eq. diag_null) then
diag_field_indices = find_diag_field(field_name)
if (diag_field_indices(1) .eq. diag_null) then
!< The field was not found in the table, so return diag_null
register_diag_field_array_modern = diag_null
deallocate(diag_file_indices)
deallocate(diag_field_indices)
return
endif

registered_variables = registered_variables + 1
register_diag_field_array_modern = registered_variables

!< TO DO: Fill in the diag_obj
deallocate(diag_file_indices)
call diag_objs(registered_variables)%setID(registered_variables)
call diag_objs(registered_variables)%register(module_name, field_name, init_time, diag_field_indices, axes, &
& longname=long_name, units=units, missing_value=missing_value, varrange=var_range, &
& mask_variant=mask_variant, standname=standard_name, do_not_log=do_not_log, err_msg=err_msg, &
& interp_method=interp_method, tile_count=tile_count, area=area, volume=volume, realm=realm)
deallocate(diag_field_indices)
#endif

end function register_diag_field_array_modern
Expand Down
19 changes: 15 additions & 4 deletions diag_manager/fms_diag_axis_object.F90
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ module fms_diag_axis_object_mod
PRIVATE

public :: diagAxis_t, set_subaxis, fms_diag_axis_init, fms_diag_axis_object_init, fms_diag_axis_object_end, &
& get_domain_and_domain_type, axis_obj
& get_domain_and_domain_type, axis_obj, diagDomain_t, sub_axis_objs
!> @}

!> @brief Type to hold the domain info for an axis
Expand Down Expand Up @@ -76,6 +76,7 @@ module fms_diag_axis_object_mod
INTEGER :: starting_index !< Starting index of the subaxis relative to the parent axis
INTEGER :: ending_index !< Ending index of the subaxis relative to the parent axis
class(*) , ALLOCATABLE :: bounds !< Bounds of the subaxis (lat/lon or indices)
INTEGER :: parent_axis_id !< Id of the parent_axis
contains
procedure :: exists => check_if_subaxis_exists
END TYPE subaxis_t
Expand Down Expand Up @@ -121,6 +122,8 @@ module fms_diag_axis_object_mod
integer :: number_of_axis !< Number of axis that has been registered
type(diagAxis_t), ALLOCATABLE, TARGET :: axis_obj(:) !< Diag_axis objects
logical :: module_is_initialized !< Flag indicating if the module is initialized
integer :: nsubaxis_objs !< Number of sub_axis that has been registered
type(subaxis_t), ALLOCATABLE, Target :: sub_axis_objs(:) !< Registered sub_axis objects

!> @addtogroup fms_diag_yaml_mod
!> @{
Expand Down Expand Up @@ -319,10 +322,14 @@ function get_axis_length(obj) &
end function

!> @brief Set the subaxis of the axis obj
subroutine set_subaxis(obj, bounds)
class(diagAxis_t), INTENT(INOUT) :: obj !< diag_axis obj
!> @return A sub_axis id corresponding to the indices of the sub_axes in the sub_axes_objs array
function set_subaxis(obj, bounds) &
result(sub_axes_id)
class(diagAxis_t), INTENT(INOUT) :: obj !< diag_axis obj
class(*), INTENT(INOUT) :: bounds(:) !< bound of the subaxis

integer :: sub_axes_id

integer :: i !< For do loops

!< Check if the subaxis for this bouds already exists
Expand All @@ -332,7 +339,11 @@ subroutine set_subaxis(obj, bounds)

!< TO DO: everything
obj%nsubaxis = obj%nsubaxis + 1
end subroutine

nsubaxis_objs = nsubaxis_objs + 1
sub_axes_id = nsubaxis_objs
!< TO DO: set the parent_axis_id
end function

!!!!!!!!!!!!!!!!!! SUB AXIS PROCEDURES !!!!!!!!!!!!!!!!!
!> @brief Check if a subaxis was already defined
Expand Down
100 changes: 88 additions & 12 deletions diag_manager/fms_diag_file_object.F90
Original file line number Diff line number Diff line change
Expand Up @@ -26,11 +26,12 @@
module fms_diag_file_object_mod
!use mpp_mod, only: mpp_error, FATAL
use fms2_io_mod, only: FmsNetcdfFile_t, FmsNetcdfUnstructuredDomainFile_t, FmsNetcdfDomainFile_t
use diag_data_mod, only: DIAG_NULL
use diag_data_mod, only: DIAG_NULL, NO_DOMAIN, max_axes, SUB_REGIONAL
#ifdef use_yaml
use fms_diag_yaml_mod, only: diag_yaml, diagYamlObject_type, diagYamlFiles_type
#endif

use fms_diag_axis_object_mod, only: diagDomain_t
use mpp_mod, only: mpp_error, FATAL
implicit none
private

Expand All @@ -44,10 +45,13 @@ module fms_diag_file_object_mod
private
integer :: id !< The number associated with this file in the larger array of files
class(FmsNetcdfFile_t), allocatable :: fileobj !< fms2_io file object for this history file
character(len=1) :: file_domain_type !< (I don't think we will need this)
#ifdef use_yaml
type(diagYamlFiles_type), pointer :: diag_yaml_file => null() !< Pointer to the diag_yaml_file data
#endif
integer :: type_of_domain !< The type of domain to use to open the file
!! NO_DOMAIN, TWO_D_DOMAIN, UG_DOMAIN, SUB_REGIONAL
class(diagDomain_t), pointer :: domain !< The domain to use,
!! null if NO_DOMAIN or SUB_REGIONAL
character(len=:) , dimension(:), allocatable :: file_metadata_from_model !< File metadata that comes from
!! the model.
integer, dimension(:), allocatable :: var_ids !< Variable IDs corresponding to file_varlist
Expand All @@ -57,18 +61,21 @@ module fms_diag_file_object_mod
logical, dimension(:), private, allocatable :: var_reg !< Array corresponding to `file_varlist`, .true.
!! if the variable has been registered and
!! `file_var_index` has been set for the variable
integer, dimension(:), allocatable :: axis_ids !< Array of axis ids in the file
integer, dimension(:), allocatable :: sub_axis_ids !< Array of axis ids in the file
integer :: number_of_axis !< Number of axis in the file

contains

procedure, public :: has_file_metadata_from_model
procedure, public :: has_fileobj
#ifdef use_yaml
procedure, public :: has_diag_yaml_file
procedure, public :: set_file_domain
procedure, public :: add_axes
#endif
procedure, public :: has_var_ids
procedure, public :: get_id
! TODO procedure, public :: get_fileobj ! TODO
procedure, public :: get_file_domain_type
! TODO procedure, public :: get_diag_yaml_file ! TODO
procedure, public :: get_file_metadata_from_model
procedure, public :: get_var_ids
Expand Down Expand Up @@ -128,6 +135,23 @@ logical function fms_diag_files_object_init ()
FMS_diag_files(i)%var_ids = DIAG_NULL
FMS_diag_files(i)%var_reg = .FALSE.
FMS_diag_files(i)%var_index = DIAG_NULL

!> These will be set in a set_file_domain
FMS_diag_files(i)%type_of_domain = NO_DOMAIN
FMS_diag_files(i)%domain => null()

!> This will be set in a add_axes
allocate(FMS_diag_files(i)%axis_ids(max_axes))

!> If the file has a sub_regional, define it as one and allocate the sub_axis_ids array.
!! This will be set in a add_axes
if (FMS_diag_files(i)%has_file_sub_region()) then
FMS_diag_files(i)%type_of_domain = SUB_REGIONAL
allocate(FMS_diag_files(i)%sub_axis_ids(max_axes))
FMS_diag_files(i)%sub_axis_ids = diag_null
endif

FMS_diag_files(i)%number_of_axis = 0
enddo set_ids_loop
fms_diag_files_object_init = .true.
else
Expand Down Expand Up @@ -181,13 +205,6 @@ end function get_id
! class(FmsNetcdfFile_t) :: res
! res = obj%fileobj
!end function get_fileobj
!> \brief Returns a copy of the value of file_domain_type
!! \return A copy of file_domain_type
pure function get_file_domain_type (obj) result (res)
class(fmsDiagFile_type), intent(in) :: obj !< The file object
character(1) :: res
res = obj%file_domain_type
end function get_file_domain_type
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!! TODO
!!> \brief Returns a copy of the value of diag_yaml_file
Expand Down Expand Up @@ -399,5 +416,64 @@ pure function has_file_global_meta (obj) result(res)
logical :: res
res = obj%diag_yaml_file%has_file_global_meta()
end function has_file_global_meta

!> @brief Set the domain and the type_of_domain for a file
!> @details This subroutine is going to be called once by every variable in the file
!! in register_diag_field. It will update the domain and the type_of_domain if needed and verify that
!! all the variables are in the same domain
subroutine set_file_domain(obj, domain, type_of_domain)
class(fmsDiagFile_type), intent(inout) :: obj !< The file object
integer, INTENT(in) :: type_of_domain !< fileobj_type to use
CLASS(diagDomain_t), INTENT(in), target :: domain !< Domain

!! If this a sub_regional, don't do anything here
if (obj%type_of_domain .eq. SUB_REGIONAL) return

if (type_of_domain .ne. obj%type_of_domain) then
!! If the current type_of_domain in the file obj is not the same as the variable calling this subroutine

if (type_of_domain .eq. NO_DOMAIN .or. obj%type_of_domain .eq. NO_DOMAIN) then
!! If they are not the same then one of them can be NO_DOMAIN
!! (i.e a file can have variables that are not domain decomposed and variables that are)

if (type_of_domain .ne. NO_DOMAIN) then
!! Update the file's type_of_domain and domain if needed
obj%type_of_domain = type_of_domain
obj%domain => domain
endif

else
!! If they are not the same and of them is not NO_DOMAIN, then crash because the variables don't have the
!! same domain (i.e a file has a variable is that in a 2D domain and one that is in a UG domain)

call mpp_error(FATAL, "The file: "//obj%get_file_fname()//" has variables that are not in the same domain")
endif
endif

end subroutine set_file_domain

!> @brief Loops through a variable's axis_ids and adds them to the FMSDiagFile object if they don't exist
subroutine add_axes(obj, axis_ids)
class(fmsDiagFile_type), intent(inout) :: obj !< The file object
integer, INTENT(in) :: axis_ids(:) !< Array of axes_ids

integer :: i, j !< For do loops

do i = 1, size(axis_ids)
do j = 1, obj%number_of_axis
!> Check if the axis already exists, if it does leave this do loop
if (axis_ids(i) .eq. obj%axis_ids(j)) exit
enddo

!> If the axis does not exist add it to the list
obj%number_of_axis = obj%number_of_axis + 1
obj%axis_ids(obj%number_of_axis) = axis_ids(i)

!> If this is a sub_regional file, set up the sub_axes
!> TO DO:
!!
enddo

end subroutine add_axes
#endif
end module fms_diag_file_object_mod
Loading

0 comments on commit 0dc70d7

Please sign in to comment.