!***********************************************************************
!* 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 .
!***********************************************************************
MODULE diag_data_mod
#include
!
! Seth Underwood
!
!
! Type descriptions and global variables for the diag_manager modules.
!
!
! Notation:
!
! - input field
! - The data structure describing the field as
! registered by the model code.
!
! - output field
! - The data structure describing the actual
! diagnostic output with requested frequency and
! other options.
!
!
! Input fields, output fields, and output files are gathered in arrays called
! "input_fields", "output_fields", and "files", respectively. Indices in these
! arrays are used as pointers to create associations between various data
! structures.
!
! Each input field associated with one or several output fields via array of
! indices output_fields; each output field points to the single "parent" input
! field with the input_field index, and to the output file with the output_file
! index
!
USE time_manager_mod, ONLY: time_type
USE mpp_domains_mod, ONLY: domain1d, domain2d, domainUG
USE mpp_io_mod, ONLY: fieldtype
USE fms_mod, ONLY: WARNING, write_version_number
#ifdef use_netCDF
! NF90_FILL_REAL has value of 9.9692099683868690e+36.
USE netcdf, ONLY: NF_FILL_REAL => NF90_FILL_REAL
#endif
IMPLICIT NONE
PUBLIC
!
!
! Maximum number of fields per file.
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
! Value used in the region specification of the diag_table to indicate to use the full axis instead of a sub-axis
!
!
! Alternate value used in the region specification of the diag_table to indicate to use the full axis instead of a sub-axis
!
!
! Return value for a diag_field that isn't found in the diag_table
!
! Specify storage limits for fixed size tables used for pointers, etc.
INTEGER, PARAMETER :: MAX_FIELDS_PER_FILE = 300 !< Maximum number of fields per file.
INTEGER, PARAMETER :: DIAG_OTHER = 0
INTEGER, PARAMETER :: DIAG_OCEAN = 1
INTEGER, PARAMETER :: DIAG_ALL = 2
INTEGER, PARAMETER :: VERY_LARGE_FILE_FREQ = 100000
INTEGER, PARAMETER :: VERY_LARGE_AXIS_LENGTH = 10000
INTEGER, PARAMETER :: EVERY_TIME = 0
INTEGER, PARAMETER :: END_OF_RUN = -1
INTEGER, PARAMETER :: DIAG_SECONDS = 1, DIAG_MINUTES = 2, DIAG_HOURS = 3
INTEGER, PARAMETER :: DIAG_DAYS = 4, DIAG_MONTHS = 5, DIAG_YEARS = 6
INTEGER, PARAMETER :: MAX_SUBAXES = 10
INTEGER, PARAMETER :: GLO_REG_VAL = -999
INTEGER, PARAMETER :: GLO_REG_VAL_ALT = -1
REAL, PARAMETER :: CMOR_MISSING_VALUE = 1.0e20 !< CMOR standard missing value
INTEGER, PARAMETER :: DIAG_FIELD_NOT_FOUND = -1
!
!
! Contains the coordinates of the local domain to output.
!
!
! Start coordinates (Lat, Lon, Depth) of the local domain to output.
!
!
! End coordinates (Lat, Lon, Depth) of the local domain to output.
!
!
! Start indices at each local PE.
!
!
! End indices at each local PE.
!
!
! ID returned from diag_subaxes_init of 3 subaces.
!
TYPE diag_grid
REAL, DIMENSION(3) :: start, END ! start and end coordinates (lat,lon,depth) of local domain to output
INTEGER, DIMENSION(3) :: l_start_indx, l_end_indx ! start and end indices at each LOCAL PE
INTEGER, DIMENSION(3) :: subaxes ! id returned from diag_subaxes_init of 3 subaxes
END TYPE diag_grid
!
!
!
! Diagnostic field type
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
TYPE diag_fieldtype
TYPE(fieldtype) :: Field
TYPE(domain2d) :: Domain
TYPE(domainUG) :: DomainU
REAL :: miss, miss_pack
LOGICAL :: miss_present, miss_pack_present
INTEGER :: tile_count
END TYPE diag_fieldtype
!
!
!
! Attribute type for diagnostic fields
!
!
! Data type of attribute values (NF_INT, NF_FLOAT, NF_CHAR)
!
!
! Number of values in attribute, or if a character string then
! length of the string.
!
!
! Name of the attribute
!
!
! Character string to hold character value of attribute
!
!
! REAL array to hold value of REAL attributes.
!
!
! INTEGER array to hold value of INTEGER attributes.
!
type :: diag_atttype
INTEGER :: type
INTEGER :: len
CHARACTER(len=128) :: name
CHARACTER(len=1280) :: catt
REAL, _ALLOCATABLE, DIMENSION(:) :: fatt _NULL
INTEGER, _ALLOCATABLE, DIMENSION(:) :: iatt _NULL
end type diag_atttype
!
!
!
! Define the region for field output.
!
!
!
!
!
!
!
!
!
!
!
!
!
TYPE coord_type
REAL :: xbegin
REAL :: xend
REAL :: ybegin
REAL :: yend
REAL :: zbegin
REAL :: zend
END TYPE coord_type
!
!
!
! Type to define the diagnostic files that will be written as defined by the diagnostic table.
!
!
! Name of the output file.
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
! Frequency to create a new file.
!
!
! Time units of new_file_freq ( days, hours, years, ...)
!
!
!
!
!
!
!
!
!
!
!
!
! Time to open next file.
!
!
! Time file opened
!
!
! Time file closed. File does not allow data after close time
!
!
!
!
!
!
!
!
!
!
! Array to hold user definable attributes
!
!
! Number of defined attibutes
!
TYPE file_type
CHARACTER(len=128) :: name !< Name of the output file.
CHARACTER(len=128) :: long_name
INTEGER, DIMENSION(max_fields_per_file) :: fields
INTEGER :: num_fields
INTEGER :: output_freq
INTEGER :: output_units
INTEGER :: FORMAT
INTEGER :: time_units
INTEGER :: file_unit
INTEGER :: bytes_written
INTEGER :: time_axis_id, time_bounds_id
INTEGER :: new_file_freq !< frequency to create new file
INTEGER :: new_file_freq_units !< time units of new_file_freq (days, hours, years, ...)
INTEGER :: duration
INTEGER :: duration_units
INTEGER :: tile_count
LOGICAL :: local !< .TRUE. if fields are output in a region instead of global.
TYPE(time_type) :: last_flush
TYPE(time_type) :: next_open !< Time to open a new file.
TYPE(time_type) :: start_time !< Time file opened.
TYPE(time_type) :: close_time !< Time file closed. File does not allow data after close time
TYPE(diag_fieldtype):: f_avg_start, f_avg_end, f_avg_nitems, f_bounds
TYPE(diag_atttype), _ALLOCATABLE, dimension(:) :: attributes _NULL
INTEGER :: num_attributes
!----------
!ug support
logical(INT_KIND) :: use_domainUG = .false.
logical(INT_KIND) :: use_domain2D = .false.
!----------
END TYPE file_type
!
!
!
! Type to hold the input field description
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
! The current level of OpenMP nesting
!
!
!
!
!
!
!
!
! Indicates if the mask_ignore_warning has been issued for this input
! field. Once .TRUE. the warning message is suppressed on all subsequent
! send_data calls.
!
TYPE input_field_type
CHARACTER(len=128) :: module_name, field_name, long_name, units
CHARACTER(len=256) :: standard_name
CHARACTER(len=64) :: interp_method
INTEGER, DIMENSION(3) :: axes
INTEGER :: num_axes
LOGICAL :: missing_value_present, range_present
REAL :: missing_value
REAL, DIMENSION(2) :: range
INTEGER, _ALLOCATABLE, dimension(:) :: output_fields _NULL
INTEGER :: num_output_fields
INTEGER, DIMENSION(3) :: size
LOGICAL :: static, register, mask_variant, local
INTEGER :: numthreads
INTEGER :: active_omp_level
INTEGER :: tile_count
TYPE(coord_type) :: local_coord
TYPE(time_type) :: time
LOGICAL :: issued_mask_ignore_warning
END TYPE input_field_type
!
!
!
! Type to hold the output field description.
!
!
! Index of the corresponding input field in the table
!
!
! Index of the output file in the table
!
!
!
!
!
!
! .TRUE. if the output field is maximum over time interval
!
!
! .TRUE. if the output field is minimum over time interval
!
!
! .TRUE. if the output field is averaged over time interval.
!
!
! .TRUE. if the output field is the rms. In this case, time_average will also be true.
!
!
! .TRUE. if any of time_min, time_max, time_rms, or time_average is true
!
!
!
!
! Power to use When calculating the mean_pow(n)
!
!
! Time method field from the input file
!
!
! Coordinates of buffer are (x, y, z, time-of-day)
!
!
! Coordinates of buffer are (x, y, z, time-of-day)
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
! Number of diurnal sample intervals, 1 or more
!
!
!
!
! .TRUE. if this field is written out on a region and not globally.
!
!
! .TRUE. if this field is written out on a region, not global.
!
!
!
!
!
!
! .TRUE. if dealing with vertical sub-level output.
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
! Array to hold user definable attributes
!
!
! Number of defined attibutes
!
TYPE output_field_type
INTEGER :: input_field ! index of the corresponding input field in the table
INTEGER :: output_file ! index of the output file in the table
CHARACTER(len=128) :: output_name
LOGICAL :: time_average ! true if the output field is averaged over time interval
LOGICAL :: time_rms ! true if the output field is the rms. If true, then time_average is also
LOGICAL :: static
LOGICAL :: time_max ! true if the output field is maximum over time interval
LOGICAL :: time_min ! true if the output field is minimum over time interval
LOGICAL :: time_sum ! true if the output field is summed over time interval
LOGICAL :: time_ops ! true if any of time_min, time_max, time_rms or time_average is true
INTEGER :: pack
INTEGER :: pow_value !< Power value to use for mean_pow(n) calculations
CHARACTER(len=50) :: time_method ! time method field from the input file
! coordinates of the buffer and counter are (x, y, z, time-of-day)
REAL, _ALLOCATABLE, DIMENSION(:,:,:,:) :: buffer _NULL
REAL, _ALLOCATABLE, DIMENSION(:,:,:,:) :: counter _NULL
! the following two counters are used in time-averaging for some
! combination of the field options. Their size is the length of the
! diurnal axis; the counters must be tracked separately for each of
! the diurnal interval, because the number of time slices accumulated
! in each can be different, depending on time step and the number of
! diurnal samples.
REAL, _ALLOCATABLE, DIMENSION(:) :: count_0d
INTEGER, _ALLOCATABLE, dimension(:) :: num_elements
TYPE(time_type) :: last_output, next_output, next_next_output
TYPE(diag_fieldtype) :: f_type
INTEGER, DIMENSION(4) :: axes
INTEGER :: num_axes, total_elements, region_elements
INTEGER :: n_diurnal_samples ! number of diurnal sample intervals, 1 or more
TYPE(diag_grid) :: output_grid
LOGICAL :: local_output, need_compute, phys_window, written_once
LOGICAL :: reduced_k_range
INTEGER :: imin, imax, jmin, jmax, kmin, kmax
TYPE(time_type) :: Time_of_prev_field_data
TYPE(diag_atttype), _ALLOCATABLE, dimension(:) :: attributes _NULL
INTEGER :: num_attributes
!----------
!ug support
logical :: reduced_k_unstruct = .false.
!----------
END TYPE output_field_type
!
!
!
! Type to hold the diagnostic axis description.
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
!
! Array to hold user definable attributes
!
!
! Number of defined attibutes
!
TYPE diag_axis_type
CHARACTER(len=128) :: name
CHARACTER(len=256) :: units, long_name
CHARACTER(len=1) :: cart_name
REAL, DIMENSION(:), POINTER :: data
INTEGER, DIMENSION(MAX_SUBAXES) :: start
INTEGER, DIMENSION(MAX_SUBAXES) :: end
CHARACTER(len=128), DIMENSION(MAX_SUBAXES) :: subaxis_name
INTEGER :: length, direction, edges, set, shift
TYPE(domain1d) :: Domain
TYPE(domain2d) :: Domain2
TYPE(domain2d), dimension(MAX_SUBAXES) :: subaxis_domain2
type(domainUG) :: DomainUG
CHARACTER(len=128) :: aux, req
INTEGER :: tile_count
TYPE(diag_atttype), _ALLOCATABLE, dimension(:) :: attributes _NULL
INTEGER :: num_attributes
END TYPE diag_axis_type
!
!
!
!
!
!
!
!
TYPE diag_global_att_type
CHARACTER(len=128) :: grid_type='regular'
CHARACTER(len=128) :: tile_name='N/A'
END TYPE diag_global_att_type
!
! Include variable "version" to be written to log file.
#include
!
!
! Number of output files currenly in use by the diag_manager.
!
!
! Number of input fields in use.
!
!
! Number of output fields in use.
!
!
INTEGER :: num_files = 0
INTEGER :: num_input_fields = 0
INTEGER :: num_output_fields = 0
INTEGER :: null_axis_id
!
!
!
!
! Maximum number of output files allowed. Increase via the diag_manager_nml namelist.
!
!
! Maximum number of output fields. Increase via the diag_manager_nml namelist.
!
!
! Maximum number of input fields. Increase via the diag_manager_nml namelist.
!
!
! Maximum number of output_fields per input_field.
!
!
! Maximum number of independent axes.
!
!
!
!
! Indicate if diag_manager should force the flush of the netCDF diagnostic
! files to disk Note: changing this to .TRUE. can greatly reduce the model
! performance as at each write to the netCDF diagnostic file, the model must
! wait until the flush to disk finishes.
!
!
!
!
! Indicates if we should overwrite the MISSING_VALUE to use the CMOR missing value.
!
!
! Issue warnings if the output field has values outside the given
! range for a variable.
!
!
! Cause a fatal error if the output field has a value outside the
! given range for a variable.
!
!
! Maximum number of user definable attributes per field.
!
!
! Maximum number of user definable global attributes per file.
!
!
! Maximum number of user definable attributes per axis.
!
!
! Indicates if the file start date will be prepended to the file name. .TRUE. is
! only supported if the diag_manager_init routine is called with the optional time_init parameter.
! This was usually done by FRE after the model run.
!
!
! Will determine which value to use when checking a regional output if the region is the full axis or a sub-axis.
! The values are defined as GLO_REG_VAL (-999) and GLO_REG_VAL_ALT (-1) in diag_data_mod.
!
LOGICAL :: append_pelist_name = .FALSE.
LOGICAL :: mix_snapshot_average_fields =.FALSE.
INTEGER :: max_files = 31 !< Maximum number of output files allowed. Increase via diag_manager_nml.
INTEGER :: max_output_fields = 300 !< Maximum number of output fields. Increase via diag_manager_nml.
INTEGER :: max_input_fields = 600 !< Maximum number of input fields. Increase via diag_manager_nml.
INTEGER :: max_out_per_in_field = 150 !< Maximum number of output_fields per input_field. Increase via diag_manager_nml.
INTEGER :: max_axes = 60 !< Maximum number of independent axes.
LOGICAL :: do_diag_field_log = .FALSE.
LOGICAL :: write_bytes_in_file = .FALSE.
LOGICAL :: debug_diag_manager = .FALSE.
LOGICAL :: flush_nc_files = .FALSE. !< Control if diag_manager will force a
!! flush of the netCDF file on each write.
!! Note: changing this to .TRUE. can greatly
!! reduce the performance of the model, as the
!! model must wait until the flush to disk has
!! completed.
INTEGER :: max_num_axis_sets = 25
LOGICAL :: use_cmor = .FALSE.
LOGICAL :: issue_oor_warnings = .TRUE.
LOGICAL :: oor_warnings_fatal = .FALSE.
LOGICAL :: region_out_use_alt_value = .TRUE.
INTEGER :: max_field_attributes = 4 !< Maximum number of user definable attributes per field. Liptak: Changed from 2 to 4 20170718
INTEGER :: max_file_attributes = 2 !< Maximum number of user definable global attributes per file.
INTEGER :: max_axis_attributes = 4 !< Maximum number of user definable attributes per axis.
LOGICAL :: prepend_date = .TRUE. !< Should the history file have the start date prepended to the file name
LOGICAL :: write_manifest_file = .FALSE. !< Indicates if the manifest file should be written. If writing many
!! regional files, then the termination time may increase causing job to time out.
!
!
! Fill value used. Value will be NF90_FILL_REAL if using the
! netCDF module, otherwise will be 9.9692099683868690e+36.
!
#ifdef use_netCDF
REAL :: FILL_VALUE = NF_FILL_REAL ! from file /usr/local/include/netcdf.inc
#else
REAL :: FILL_VALUE = 9.9692099683868690e+36
#endif
INTEGER :: pack_size = 1 ! 1 for double and 2 for float
!
!
!
!
REAL :: EMPTY = 0.0
REAL :: MAX_VALUE, MIN_VALUE
!
!
! Time diag_manager_init called. If init_time not included in
! diag_manager_init call, then same as base_time
!
!
!
!
!
!
!
!
!
TYPE(time_type) :: diag_init_time
TYPE(time_type) :: base_time
INTEGER :: base_year, base_month, base_day, base_hour, base_minute, base_second
CHARACTER(len = 256):: global_descriptor
!
!
!
!
TYPE(file_type), SAVE, ALLOCATABLE :: files(:)
TYPE(input_field_type), ALLOCATABLE :: input_fields(:)
TYPE(output_field_type), ALLOCATABLE :: output_fields(:)
!
!
!
!
! Indicate if diag_manager has been initialized
!
!
!
!
TYPE(time_type) :: time_zero
LOGICAL :: first_send_data_call = .TRUE.
LOGICAL :: module_is_initialized = .FALSE.
INTEGER :: diag_log_unit
CHARACTER(len=10), DIMENSION(6) :: time_unit_list = (/'seconds ', 'minutes ',&
& 'hours ', 'days ', 'months ', 'years '/)
CHARACTER(len=32) :: pelist_name
INTEGER :: oor_warning = WARNING
CONTAINS
!
!
! Write the version number of this file
!
!
! SUBROUTINE diag_util_init
!
!
! Write the version number of this file to the log file.
!
SUBROUTINE diag_data_init()
IF (module_is_initialized) THEN
RETURN
END IF
! Write version number out to log file
call write_version_number("DIAG_DATA_MOD", version)
END SUBROUTINE diag_data_init
!
END MODULE diag_data_mod