Skip to content

Commit

Permalink
documentation updates
Browse files Browse the repository at this point in the history
  • Loading branch information
uramirez8707 committed Mar 12, 2024
1 parent 72d123f commit 6a315e8
Show file tree
Hide file tree
Showing 4 changed files with 68 additions and 41 deletions.
20 changes: 9 additions & 11 deletions diag_manager/fms_diag_field_object.F90
Original file line number Diff line number Diff line change
Expand Up @@ -74,8 +74,8 @@ module fms_diag_field_object_mod
class(*), allocatable, private :: data_RANGE(:) !< The range of the variable data
type(fmsDiagInputBuffer_t), allocatable :: input_data_buffer !< Input buffer object for when buffering
!! data
logical, allocatable, private :: multiple_send_data!< .True. if multiple send data calls
!! made for the field
logical, allocatable, private :: multiple_send_data!< .True. if send_data is called multiple
!! times for the same model time
logical, allocatable, private :: data_buffer_is_allocated !< True if the buffer has
!! been allocated
logical, allocatable, private :: math_needs_to_be_done !< If true, do math
Expand Down Expand Up @@ -372,7 +372,6 @@ subroutine fms_register_diag_field_obj &
this%do_not_log = do_not_log
endif

!TODO restrict to only averaging fields
if (present(multiple_send_data)) then
this%multiple_send_data = multiple_send_data
else
Expand Down Expand Up @@ -442,26 +441,23 @@ function get_send_data_time(this) &
rslt = this%input_data_buffer%get_send_data_time()
end function get_send_data_time

!> @brief Prepare the input_data_buffer to do the reduction method
subroutine prepare_data_buffer(this)
class (fmsDiagField_type) , intent(inout):: this !< The field object

if (.not. this%multiple_send_data) return
if (this%mask_variant) return
call this%input_data_buffer%prepare_input_buffer_object(this%modname//":"//this%varname)
end subroutine prepare_data_buffer

call this%input_data_buffer%prepare_input_buffer_object()

end subroutine

!> @brief Initialize the input_data_buffer
subroutine init_data_buffer(this)
class (fmsDiagField_type) , intent(inout):: this !< The field object

if (.not. this%multiple_send_data) return
if (this%mask_variant) return

call this%input_data_buffer%init_input_buffer_object()

end subroutine

end subroutine init_data_buffer

!> @brief Adds the input data to the buffered data.
subroutine set_data_buffer (this, input_data, mask, weight, is, js, ks, ie, je, ke)
Expand Down Expand Up @@ -1073,6 +1069,8 @@ pure function get_var_skind(this, field_yaml) &

end function get_var_skind

!> @brief Get the multiple_send_data member of the field object
!! @return multiple_send_data of the field
pure function get_multiple_send_data(this) &
result(rslt)
class (fmsDiagField_type), intent(in) :: this !< diag field
Expand Down
3 changes: 2 additions & 1 deletion diag_manager/fms_diag_file_object.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1399,7 +1399,8 @@ subroutine write_time_data(this)
fms2io_fileobj => diag_file%fms2io_fileobj

!< If data has not been written for the current unlimited dimension
!! ignore this
!! ignore this. The diag_file%unlim_dimension_level .ne. 1 is there to ensure
!! that at least one time level is written (this is needed for the combiner)
if (.not. diag_file%data_has_been_written .and. diag_file%unlim_dimension_level .ne. 1) return

if (diag_file%time_ops) then
Expand Down
62 changes: 44 additions & 18 deletions diag_manager/fms_diag_input_buffer.F90
Original file line number Diff line number Diff line change
Expand Up @@ -26,13 +26,16 @@ module fms_diag_input_buffer_mod
use platform_mod, only: r8_kind, r4_kind, i4_kind, i8_kind
use fms_diag_axis_object_mod, only: fmsDiagAxisContainer_type, fmsDiagFullAxis_type
use time_manager_mod, only: time_type
use mpp_mod, only: mpp_error, FATAL
implicit NONE
private

!> @brief Appends the input_data_buffer and the mask (only when the mask is set to .True.)
interface append_data_buffer
module procedure append_data_buffer_r4, append_data_buffer_r8
end interface

!> @brief Sums the data in the input_data_buffer
interface sum_data_buffer
module procedure sum_data_buffer_r4, sum_data_buffer_r8
end interface
Expand Down Expand Up @@ -140,6 +143,7 @@ function allocate_input_buffer_object(this, input_data, axis_ids, diag_axis) &
this%counter = 0
end function allocate_input_buffer_object

!> @brief Initiliazes an input data buffer and the counter
subroutine init_input_buffer_object(this)
class(fmsDiagInputBuffer_t), intent(inout) :: this !< input buffer object

Expand All @@ -149,7 +153,6 @@ subroutine init_input_buffer_object(this)
type is (real(kind=r4_kind))
buffer = 0.0_r4_kind
end select

this%counter = 0
end subroutine init_input_buffer_object

Expand All @@ -171,6 +174,8 @@ function get_send_data_time(this) &
rslt = this%send_data_time
end function get_send_data_time

!> @brief Updates the input data buffer object for the current send_data call
!! @return Error message (if an error occurs)
function update_input_buffer_object(this, input_data, is, js, ks, ie, je, ke, mask_in, mask_out, &
mask_variant, var_is_masked) &
result(err_msg)
Expand All @@ -186,36 +191,47 @@ function update_input_buffer_object(this, input_data, is, js, ks, ie, je, ke, ma

character(len=128) :: err_msg

err_msg = ""
if (mask_variant) then
call append_data_buffer_wrapper(mask_out(is:ie,js:je,ks:ke,:), mask_in, &
err_msg = append_data_buffer_wrapper(mask_out(is:ie,js:je,ks:ke,:), mask_in, &
this%buffer(is:ie,js:je,ks:ke,:), input_data)
else
mask_out(is:ie,js:je,ks:ke,:) = mask_in
call sum_data_buffer_wrapper(mask_in, this%buffer(is:ie,js:je,ks:ke,:), input_data, &
err_msg = sum_data_buffer_wrapper(mask_in, this%buffer(is:ie,js:je,ks:ke,:), input_data, &
this%counter(is:ie,js:je,ks:ke,:), &
var_is_masked)
endif

end function update_input_buffer_object

subroutine prepare_input_buffer_object(this)
!> @brief Prepare the input data buffer to do the reduction methods (i.e divide by the number of times
!! send data has been called)
subroutine prepare_input_buffer_object(this, field_info)
class(fmsDiagInputBuffer_t), intent(inout) :: this !< input buffer object
character(len=*), intent(in) :: field_info !< Field info to append to error message

select type (input_data => this%buffer)
type is (real(kind=r4_kind))
input_data = input_data / this%counter(1,1,1,1)
type is (real(kind=r8_kind))
input_data = input_data / this%counter(1,1,1,1)
class default
call mpp_error(FATAL, "prepare_input_buffer_object::"//trim(field_info)//&
" has only been implemented for real variables. Contact developers.")
end select
end subroutine prepare_input_buffer_object

subroutine sum_data_buffer_wrapper(mask, data_out, data_in, counter, var_is_masked)
logical, intent(in) :: mask(:,:,:,:)
class(*), intent(inout) :: data_out(:,:,:,:)
class(*), intent(in) :: data_in(:,:,:,:)
integer, intent(inout) :: counter(:,:,:,:)
logical, intent(in) :: var_is_masked
!> @brief Sums the data in the input_data_buffer
!! @return Error message (if an error occurs)
function sum_data_buffer_wrapper(mask, data_out, data_in, counter, var_is_masked) &
result(err_msg)

logical, intent(in) :: mask(:,:,:,:) !< Mask passed into send_data
class(*), intent(inout) :: data_out(:,:,:,:) !< Data currently saved in the input_data_buffer
class(*), intent(in) :: data_in(:,:,:,:) !< Data passed into send_data
integer, intent(inout) :: counter(:,:,:,:) !< Number of times data has been summed
logical, intent(in) :: var_is_masked !< .True. if the variable is masked

character(len=128) :: err_msg

select type(data_out)
type is (real(kind=r8_kind))
Expand All @@ -228,15 +244,22 @@ subroutine sum_data_buffer_wrapper(mask, data_out, data_in, counter, var_is_mask
type is (real(kind=r4_kind))
call sum_data_buffer(mask, data_out, data_in, counter, var_is_masked)
end select
class default
err_msg = "sum_data_buffer_wrapper:: has only been implemented for real. Contact developers"
end select
end subroutine sum_data_buffer_wrapper
end function sum_data_buffer_wrapper

subroutine append_data_buffer_wrapper(mask_out, mask_in, data_out, data_in)
logical, intent(inout) :: mask_out(:,:,:,:)
logical, intent(in) :: mask_in(:,:,:,:)
class(*), intent(inout) :: data_out(:,:,:,:)
class(*), intent(in) :: data_in(:,:,:,:)
!> @brief Appends the input_data_buffer and the mask (only when the mask is set to .True.)
!! @return Error message (if an error occurs)
function append_data_buffer_wrapper(mask_out, mask_in, data_out, data_in) &
result(err_msg)
logical, intent(inout) :: mask_out(:,:,:,:) !< Mask currently in the input_data_buffer
logical, intent(in) :: mask_in(:,:,:,:) !< Mask passed in to send_data
class(*), intent(inout) :: data_out(:,:,:,:) !< Data currently in the input_data_buffer
class(*), intent(in) :: data_in(:,:,:,:) !< Data passed in to send_data

character(len=128) :: err_msg

select type(data_out)
type is (real(kind=r8_kind))
select type (data_in)
Expand All @@ -248,8 +271,11 @@ subroutine append_data_buffer_wrapper(mask_out, mask_in, data_out, data_in)
type is (real(kind=r4_kind))
call append_data_buffer(mask_out, mask_in, data_out, data_in)
end select
class default
err_msg = "append_data_buffer:: has only been implemented for real. Contact developers"
end select
end subroutine
end function append_data_buffer_wrapper

!> @brief Sets the members of the input buffer object
!! @return Error message if something went wrong
function set_input_buffer_object(this, input_data, weight, is, js, ks, ie, je, ke) &
Expand Down
24 changes: 13 additions & 11 deletions diag_manager/include/fms_diag_input_buffer.inc
Original file line number Diff line number Diff line change
Expand Up @@ -17,13 +17,14 @@
!* License along with FMS. If not, see <http://www.gnu.org/licenses/>.
!***********************************************************************

!> @brief Appends the input_data_buffer and the mask (only when the mask is set to .True.)
subroutine APPEND_DATA_BUFFER_(mask_out, mask_in, data_out, data_in)
logical, intent(inout) :: mask_out(:,:,:,:)
logical, intent(in) :: mask_in(:,:,:,:)
real(FMS_TRM_KIND_), intent(inout) :: data_out(:,:,:,:)
real(FMS_TRM_KIND_), intent(in) :: data_in(:,:,:,:)
logical, intent(inout) :: mask_out(:,:,:,:) !< Mask currently in the input_data_buffer
logical, intent(in) :: mask_in(:,:,:,:) !< Mask passed in to send_data
real(FMS_TRM_KIND_), intent(inout) :: data_out(:,:,:,:) !< Data currently in the input_data_buffer
real(FMS_TRM_KIND_), intent(in) :: data_in(:,:,:,:) !< Data passed in to send_data

integer :: i, j, k, l
integer :: i, j, k, l !< For looping through the input_data_buffer

do l = 1, size(data_out, 4)
do k = 1, size(data_out, 3)
Expand All @@ -38,14 +39,15 @@ subroutine APPEND_DATA_BUFFER_(mask_out, mask_in, data_out, data_in)
enddo
enddo

end subroutine
end subroutine APPEND_DATA_BUFFER_

!> @brief Sums the data in the input_data_buffer
subroutine SUM_DATA_BUFFER_(mask, data_out, data_in, counter, var_is_masked)
logical, intent(in) :: mask(:,:,:,:)
real(FMS_TRM_KIND_), intent(inout) :: data_out(:,:,:,:)
real(FMS_TRM_KIND_), intent(in) :: data_in(:,:,:,:)
integer, intent(inout) :: counter(:,:,:,:)
logical, intent(in) :: var_is_masked
logical, intent(in) :: mask(:,:,:,:) !< Mask passed into send_data
real(FMS_TRM_KIND_), intent(inout) :: data_out(:,:,:,:) !< Data currently saved in the input_data_buffer
real(FMS_TRM_KIND_), intent(in) :: data_in(:,:,:,:) !< Data passed into send_data
integer, intent(inout) :: counter(:,:,:,:) !< Number of times data has been summed
logical, intent(in) :: var_is_masked !< .True. if the variable is masked

if (var_is_masked) then
where (mask)
Expand Down

0 comments on commit 6a315e8

Please sign in to comment.