21 #include <fms_platform.h> 57 USE fms_mod,
ONLY: warning, write_version_number
60 USE netcdf,
ONLY: nf_fill_real => nf90_fill_real
133 REAL,
DIMENSION(3) :: start, end
134 INTEGER,
DIMENSION(3) :: l_start_indx, l_end_indx
135 INTEGER,
DIMENSION(3) :: subaxes
161 REAL :: miss, miss_pack
162 LOGICAL :: miss_present, miss_pack_present
163 INTEGER :: tile_count
193 CHARACTER(len=128) :: name
194 CHARACTER(len=1280) :: catt
195 REAL, _allocatable,
DIMENSION(:) :: fatt _null
196 INTEGER, _allocatable,
DIMENSION(:) :: iatt _null
294 CHARACTER(len=128) :: name
295 CHARACTER(len=128) :: long_name
296 INTEGER,
DIMENSION(max_fields_per_file) :: fields
297 INTEGER :: num_fields
298 INTEGER :: output_freq
299 INTEGER :: output_units
301 INTEGER :: time_units
303 INTEGER :: bytes_written
304 INTEGER :: time_axis_id, time_bounds_id
305 INTEGER :: new_file_freq
306 INTEGER :: new_file_freq_units
308 INTEGER :: duration_units
309 INTEGER :: tile_count
317 INTEGER :: num_attributes
320 logical(INT_KIND) :: use_domainug = .false.
321 logical(INT_KIND) :: use_domain2d = .false.
385 CHARACTER(len=128) :: module_name, field_name, long_name, units
386 CHARACTER(len=256) :: standard_name
387 CHARACTER(len=64) :: interp_method
388 INTEGER,
DIMENSION(3) :: axes
390 LOGICAL :: missing_value_present, range_present
391 REAL :: missing_value
392 REAL,
DIMENSION(2) :: range
396 LOGICAL :: static, register, mask_variant, local
397 INTEGER :: numthreads
398 INTEGER :: active_omp_level
399 INTEGER :: tile_count
402 LOGICAL :: issued_mask_ignore_warning
508 INTEGER :: input_field
509 INTEGER :: output_file
510 CHARACTER(len=128) :: output_name
511 LOGICAL :: time_average
520 CHARACTER(len=50) :: time_method
522 REAL, _allocatable,
DIMENSION(:,:,:,:) :: buffer _null
523 REAL, _allocatable,
DIMENSION(:,:,:,:) :: counter _null
530 REAL, _allocatable,
DIMENSION(:) :: count_0d
531 INTEGER, _allocatable,
dimension(:) :: num_elements
533 TYPE(
time_type) :: last_output, next_output, next_next_output
535 INTEGER,
DIMENSION(4) :: axes
536 INTEGER :: num_axes, total_elements, region_elements
537 INTEGER :: n_diurnal_samples
539 LOGICAL :: local_output, need_compute, phys_window, written_once
540 LOGICAL :: reduced_k_range
541 INTEGER :: imin, imax, jmin, jmax, kmin, kmax
544 INTEGER :: num_attributes
547 logical :: reduced_k_unstruct = .false.
601 CHARACTER(len=128) :: name
602 CHARACTER(len=256) :: units, long_name
603 CHARACTER(len=1) :: cart_name
604 REAL,
DIMENSION(:),
POINTER :: data
605 INTEGER,
DIMENSION(MAX_SUBAXES) :: start
606 INTEGER,
DIMENSION(MAX_SUBAXES) :: end
607 CHARACTER(len=128),
DIMENSION(MAX_SUBAXES) :: subaxis_name
608 INTEGER :: length, direction, edges, set, shift
611 TYPE(
domain2d),
dimension(MAX_SUBAXES) :: subaxis_domain2
613 CHARACTER(len=128) :: aux, req
614 INTEGER :: tile_count
616 INTEGER :: num_attributes
628 CHARACTER(len=128) :: grid_type=
'regular' 629 CHARACTER(len=128) :: tile_name=
'N/A' 634 #include<file_version.h> 799 &
'hours ',
'days ',
'months ',
'years '/)
821 call write_version_number(
"DIAG_DATA_MOD", version)
real, parameter cmor_missing_value
CMOR standard missing value.
logical write_manifest_file
Indicates if the manifest file should be written. If writing many regional files, then the terminatio...
integer, parameter every_time
character(len=256) global_descriptor
integer num_output_fields
integer, parameter diag_seconds
subroutine diag_data_init()
integer max_field_attributes
Maximum number of user definable attributes per field. Liptak: Changed from 2 to 4 20170718...
integer max_axis_attributes
Maximum number of user definable attributes per axis.
integer max_out_per_in_field
Maximum number of output_fields per input_field. Increase via diag_manager_nml.
character(len=10), dimension(6) time_unit_list
type(time_type) base_time
character(len=32) pelist_name
integer, parameter glo_reg_val
integer, parameter end_of_run
integer max_file_attributes
Maximum number of user definable global attributes per file.
integer, parameter diag_field_not_found
logical flush_nc_files
Control if diag_manager will force a flush of the netCDF file on each write. Note: changing this to ...
type(output_field_type), dimension(:), allocatable output_fields
logical write_bytes_in_file
integer, parameter diag_ocean
type(time_type) diag_init_time
type(file_type), dimension(:), allocatable, save files
integer, parameter very_large_axis_length
logical append_pelist_name
integer, parameter diag_hours
integer max_num_axis_sets
integer, parameter glo_reg_val_alt
logical oor_warnings_fatal
integer max_axes
Maximum number of independent axes.
type(input_field_type), dimension(:), allocatable input_fields
integer, parameter diag_minutes
integer, parameter max_fields_per_file
Maximum number of fields per file.
logical module_is_initialized
integer max_files
Maximum number of output files allowed. Increase via diag_manager_nml.
integer max_output_fields
Maximum number of output fields. Increase via diag_manager_nml.
integer, parameter diag_years
integer, parameter max_subaxes
integer, parameter diag_other
************************************************************************GNU Lesser General Public License **This file is part of the GFDL Flexible Modeling System(FMS). ! *! *FMS is free software 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 see< http:! ***********************************************************************subroutine READ_RECORD_CORE_(unit, field, nwords, data, start, axsiz) integer, intent(in) ::unit type(fieldtype), intent(in) ::field integer, intent(in) ::nwords MPP_TYPE_, intent(inout) ::data(nwords) integer, intent(in) ::start(:), axsiz(:) integer(SHORT_KIND) ::i2vals(nwords)!rab used in conjunction with transfer intrinsic to determine size of a variable integer(KIND=1) ::one_byte(8) integer ::word_sz!#ifdef __sgi integer(INT_KIND) ::ivals(nwords) real(FLOAT_KIND) ::rvals(nwords)!#else! integer ::ivals(nwords)! real ::rvals(nwords)!#endif real(DOUBLE_KIND) ::r8vals(nwords) pointer(ptr1, i2vals) pointer(ptr2, ivals) pointer(ptr3, rvals) pointer(ptr4, r8vals) if(mpp_io_stack_size< nwords) call mpp_io_set_stack_size(nwords) call mpp_error(FATAL, 'MPP_READ currently requires use_netCDF option') end subroutine READ_RECORD_CORE_ subroutine READ_RECORD_(unit, field, nwords, data, time_level, domain, position, tile_count, start_in, axsiz_in)!routine that is finally called by all mpp_read routines to perform the read!a non-netCDF record contains:! field ID! a set of 4 coordinates(is:ie, js:je) giving the data subdomain! a timelevel and a timestamp(=NULLTIME if field is static)! 3D real data(stored as 1D)!if you are using direct access I/O, the RECL argument to OPEN must be large enough for the above!in a global direct access file, record position on PE is given by %record.!Treatment of timestamp:! We assume that static fields have been passed without a timestamp.! Here that is converted into a timestamp of NULLTIME.! For non-netCDF fields, field is treated no differently, but is written! with a timestamp of NULLTIME. There is no check in the code to prevent! the user from repeatedly writing a static field. integer, intent(in) ::unit, nwords type(fieldtype), intent(in) ::field MPP_TYPE_, intent(inout) ::data(nwords) integer, intent(in), optional ::time_level type(domain2D), intent(in), optional ::domain integer, intent(in), optional ::position, tile_count integer, intent(in), optional ::start_in(:), axsiz_in(:) integer, dimension(size(field%axes(:))) ::start, axsiz integer ::tlevel !, subdomain(4) integer ::i, error, is, ie, js, je, isg, ieg, jsg, jeg type(domain2d), pointer ::io_domain=> tlevel if(PRESENT(start_in) .AND. PRESENT(axsiz_in)) then if(size(start(! the data domain and compute domain must refer to the subdomain being passed ! In this ! since that attempts to gather all data on PE size(field%axes(:)) axsiz(i)
logical first_send_data_call
logical do_diag_field_log
logical mix_snapshot_average_fields
logical prepend_date
Should the history file have the start date prepended to the file name.
integer max_input_fields
Maximum number of input fields. Increase via diag_manager_nml.
type(time_type) time_zero
logical region_out_use_alt_value
integer, parameter diag_days
integer, parameter diag_all
logical issue_oor_warnings
integer, parameter very_large_file_freq
logical debug_diag_manager
integer, parameter diag_months