Skip to content

Commit

Permalink
minor documentation updates, typo in set_weight, and renames some _mo…
Browse files Browse the repository at this point in the history
…dern variables
  • Loading branch information
uramirez8707 committed Aug 10, 2023
1 parent 17e0ab0 commit 91a249a
Show file tree
Hide file tree
Showing 4 changed files with 49 additions and 22 deletions.
22 changes: 11 additions & 11 deletions diag_manager/diag_manager.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1675,9 +1675,9 @@ LOGICAL FUNCTION diag_send_data(diag_field_id, field, time, is_in, js_in, ks_in,
CHARACTER(len=128) :: error_string, error_string1

REAL, ALLOCATABLE, DIMENSION(:,:,:) :: field_out !< Local copy of field
class(*), pointer, dimension(:,:,:,:) :: field_modern !< 4d remapped pointer
logical, pointer, dimension(:,:,:,:) :: mask_modern !< 4d remapped pointer
class(*), pointer, dimension(:,:,:,:) :: rmask_modern !< 4d remapped pointer
class(*), pointer, dimension(:,:,:,:) :: field_remap !< 4d remapped pointer
logical, pointer, dimension(:,:,:,:) :: mask_remap !< 4d remapped pointer
class(*), pointer, dimension(:,:,:,:) :: rmask_remap !< 4d remapped pointer
REAL(kind=r4_kind), POINTER, DIMENSION(:,:,:) :: rmask_ptr_r4 !< A pointer to r4 type of rmask
REAL(kind=r8_kind), POINTER, DIMENSION(:,:,:) :: rmask_ptr_r8 !<A pointer to r8 type of rmask

Expand Down Expand Up @@ -1718,15 +1718,15 @@ LOGICAL FUNCTION diag_send_data(diag_field_id, field, time, is_in, js_in, ks_in,
IF ( fms_error_handler('diag_manager_mod::send_data_3d', err_msg_local, err_msg) ) RETURN
END IF
if (use_modern_diag) then !> Set up array lengths for remapping
field_modern => null()
mask_modern => null()
rmask_modern => null()
field_remap => null()
mask_remap => null()
rmask_remap => null()
ie = SIZE(field,1)
je = SIZE(field,2)
ke = SIZE(field,3)
field_modern(1:ie,1:je,1:ke,1:1) => field
if (present(mask)) mask_modern(1:ie,1:je,1:ke,1:1) => mask
if (present(rmask)) rmask_modern(1:ie,1:je,1:ke,1:1) => rmask
field_remap(1:ie,1:je,1:ke,1:1) => field
if (present(mask)) mask_remap(1:ie,1:je,1:ke,1:1) => mask
if (present(rmask)) rmask_remap(1:ie,1:je,1:ke,1:1) => rmask
endif
SELECT TYPE (field)
TYPE IS (real(kind=r4_kind))
Expand All @@ -1740,10 +1740,10 @@ LOGICAL FUNCTION diag_send_data(diag_field_id, field, time, is_in, js_in, ks_in,
END SELECT
! Split old and modern2023 here
modern_if: iF (use_modern_diag) then
diag_send_data = fms_diag_object%fms_diag_accept_data(diag_field_id, field_modern, mask_modern, rmask_modern, &
diag_send_data = fms_diag_object%fms_diag_accept_data(diag_field_id, field_remap, mask_remap, rmask_remap, &
time, is_in, js_in, ks_in, ie_in, je_in, ke_in, weight, &
err_msg)
nullify (field_modern)
nullify (field_remap)
elSE ! modern_if
! oor_mask is only used for checking out of range values.
ALLOCATE(oor_mask(SIZE(field,1),SIZE(field,2),SIZE(field,3)), STAT=status)
Expand Down
4 changes: 2 additions & 2 deletions diag_manager/fms_diag_axis_object.F90
Original file line number Diff line number Diff line change
Expand Up @@ -769,15 +769,15 @@ function axis_length(this) &
end function

!> @brief Accesses its member starting_index
!! @return Returns a copy of the starting_index
!! @return a copy of the starting_index
function get_starting_index(this) result(indx)
class(fmsDiagSubAxis_type), intent(in) :: this !< diag_sub_axis object
integer :: indx !< Result to return
indx = this%starting_index
end function get_starting_index

!> @brief Accesses its member ending_index
!! @return Returns a copy of the ending_index
!! @return a copy of the ending_index
function get_ending_index(this) result(indx)
class(fmsDiagSubAxis_type), intent(in) :: this !< diag_sub_axis object
integer :: indx !< Result to return
Expand Down
2 changes: 1 addition & 1 deletion diag_manager/fms_diag_object.F90
Original file line number Diff line number Diff line change
Expand Up @@ -505,7 +505,7 @@ logical function fms_diag_accept_data (this, diag_field_id, field_data, mask, rm
CHARACTER(len=*), INTENT(out), OPTIONAL :: err_msg !< An error message returned

integer :: is, js, ks !< Starting indicies of the field_data
integer :: ie, je, ke !< Ending indicied of the field_data
integer :: ie, je, ke !< Ending indicies of the field_data
integer :: n1, n2, n3 !< Size of the 3 indicies of the field data
integer :: omp_num_threads !< Number of openmp threads
integer :: omp_level !< The openmp active level
Expand Down
43 changes: 35 additions & 8 deletions diag_manager/fms_diag_reduction_methods.F90
Original file line number Diff line number Diff line change
@@ -1,8 +1,32 @@
!> \author Ganga Purja Pun
!> \email [email protected]
!! \brief Contains routines for the modern diag manager
!! These routines are meant to be used for checks and in reduction methods.
!***********************************************************************
!* GNU Lesser General Public License
!*
!* This file is part of the GFDL Flexible Modeling System (FMS).
!*
!* FMS is free software: you can redistribute it and/or modify it under
!* the terms of the GNU Lesser General Public License as published by
!* the Free Software Foundation, either version 3 of the License, or (at
!* your option) any later version.
!*
!* FMS is distributed in the hope that it will be useful, but WITHOUT
!* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
!* FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
!* for more details.
!*
!* You should have received a copy of the GNU Lesser General Public
!* License along with FMS. If not, see <http://www.gnu.org/licenses/>.
!***********************************************************************

!> @defgroup fms_diag_reduction_methods_mod fms_diag_reduction_methods_mod
!> @ingroup diag_manager
!! @brief fms_diag_reduction_methods_mod contains routines that are meant to be used for
!! error checking and setting up to do the reduction methods

!> @file
!> @brief File for @ref fms_diag_reduction_methods_mod

!> @addtogroup fms_diag_reduction_methods_mod
!> @{
module fms_diag_reduction_methods_mod
use platform_mod, only: r8_kind, r4_kind
implicit none
Expand Down Expand Up @@ -81,10 +105,11 @@ function init_mask(rmask, mask, field) &
end function init_mask

!> @brief Sets the weight based on the weight passed into send_data (1.0_r8_kind if the weight is not passed in)
!> @return weight to used when averaging
!! The weight will be saved as an r8 and converted to r4 as needed
!! @return weight to use when averaging
pure function set_weight(weight) &
result(out_weight)
CLASS(*), INTENT(in), OPTIONAL :: weight !< The weight used for averaging
CLASS(*), INTENT(in), OPTIONAL :: weight !< The weight use when averaging

real(kind=r8_kind) :: out_weight

Expand All @@ -94,9 +119,11 @@ pure function set_weight(weight) &
type is (real(kind=r8_kind))
out_weight = real(weight, kind = r8_kind)
type is (real(kind=r4_kind))
out_Weight = real(weight, kind = r4_kind)
out_Weight = real(weight, kind = r8_kind)
end select
endif
end function set_weight

end module fms_diag_reduction_methods_mod
end module fms_diag_reduction_methods_mod
!> @}
! close documentation grouping

0 comments on commit 91a249a

Please sign in to comment.