Skip to content

Commit

Permalink
update to use file length instead of path length where appropriate
Browse files Browse the repository at this point in the history
  • Loading branch information
rem1776 authored and rem1776 committed Aug 2, 2024
1 parent 480636a commit 1049e1d
Show file tree
Hide file tree
Showing 24 changed files with 51 additions and 50 deletions.
4 changes: 2 additions & 2 deletions amip_interp/amip_interp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -135,7 +135,7 @@ module amip_interp_mod
NOTE, mpp_error, fms_error_handler

use constants_mod, only: TFREEZE, pi
use platform_mod, only: r4_kind, r8_kind, i2_kind, FMS_PATH_LEN
use platform_mod, only: r4_kind, r8_kind, i2_kind, FMS_FILE_LEN
use mpp_mod, only: input_nml_file
use fms2_io_mod, only: FmsNetcdfFile_t, fms2_io_file_exists=>file_exists, open_file, close_file, &
get_dimension_size, fms2_io_read_data=>read_data
Expand Down Expand Up @@ -304,7 +304,7 @@ module amip_interp_mod
! ---- global unit & date ----

integer :: iunit
character(len=FMS_PATH_LEN) :: file_name_sst, file_name_ice
character(len=FMS_FILE_LEN) :: file_name_sst, file_name_ice
type(FmsNetcdfFile_t), target :: fileobj_sst, fileobj_ice

type (date_type) :: Curr_date = date_type( -99, -99, -99 )
Expand Down
4 changes: 2 additions & 2 deletions amip_interp/include/amip_interp.inc
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@ subroutine GET_AMIP_SST_ (Time, Interp, sst, err_msg, lon_model, lat_model)
integer, dimension(:), allocatable :: ryr, rmo, rdy
character(len=30) :: time_unit
real(FMS_AMIP_INTERP_KIND_), dimension(:), allocatable :: timeval
character(len=FMS_PATH_LEN) :: ncfilename
character(len=FMS_FILE_LEN) :: ncfilename
type(FmsNetcdfFile_t) :: fileobj
logical :: the_file_exists
! end add by JHC
Expand Down Expand Up @@ -652,7 +652,7 @@ endif
integer(I2_KIND) :: idat(mobs,nobs)
integer :: nrecords, yr, mo, dy, ierr, k
integer, dimension(:), allocatable :: ryr, rmo, rdy
character(len=FMS_PATH_LEN) :: ncfilename
character(len=FMS_FILE_LEN) :: ncfilename
character(len=NF90_MAX_NAME) :: ncfieldname
type(FmsNetcdfFile_t), pointer :: fileobj
integer, parameter :: lkind = FMS_AMIP_INTERP_KIND_
Expand Down
2 changes: 1 addition & 1 deletion column_diagnostics/column_diagnostics.F90
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ module column_diagnostics_mod
get_date, time_type
use constants_mod, only: constants_init, PI, RADIAN
use mpp_mod, only: input_nml_file
use platform_mod, only: r4_kind, r8_kind
use platform_mod, only: r4_kind, r8_kind, FMS_FILE_LEN
!-------------------------------------------------------------------

implicit none
Expand Down
2 changes: 1 addition & 1 deletion column_diagnostics/include/column_diagnostics.inc
Original file line number Diff line number Diff line change
Expand Up @@ -99,7 +99,7 @@ integer, dimension(:), intent(out) :: diag_units !< unit number for
real(FMS_CD_KIND_) :: ref_lat
real(FMS_CD_KIND_) :: current_distance
character(len=8) :: char !< character string for diaganostic column index
character(len=FMS_PATH_LEN) :: filename !< filename for output file for diagnostic column
character(len=FMS_FILE_LEN) :: filename !< filename for output file for diagnostic column
logical :: allow_ij_input
logical :: open_file
integer :: io
Expand Down
4 changes: 2 additions & 2 deletions coupler/atmos_ocean_fluxes.F90
Original file line number Diff line number Diff line change
Expand Up @@ -135,8 +135,8 @@ function aof_set_coupler_flux(name, flux_type, implementation, atm_tr_index, par
integer :: length
integer :: num_parameters
integer :: outunit
character(len=FMS_PATH_LEN) :: coupler_list
character(len=FMS_PATH_LEN) :: current_list
character(len=FMS_PATH_LEN) :: coupler_list
character(len=FMS_PATH_LEN) :: current_list
character(len=fm_string_len) :: flux_type_test
character(len=fm_string_len) :: implementation_test
character(len=256) :: error_header
Expand Down
2 changes: 1 addition & 1 deletion data_override/get_grid_version.F90
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@
!> @{
module get_grid_version_mod
use constants_mod, only: DEG_TO_RAD
use platform_mod, only: r4_kind, r8_kind
use platform_mod, only: r4_kind, r8_kind, FMS_PATH_LEN
use mpp_mod, only : mpp_error,FATAL,NOTE, mpp_min, mpp_max
use mpp_domains_mod, only : domain2d, operator(.NE.),operator(.EQ.)
use mpp_domains_mod, only : mpp_get_global_domain, mpp_get_data_domain
Expand Down
2 changes: 1 addition & 1 deletion data_override/include/data_override.inc
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@
! modules. These modules are not intended to be used directly - they should be
! used through the data_override_mod API. See data_override.F90 for details.

use platform_mod, only: r4_kind, r8_kind
use platform_mod, only: r4_kind, r8_kind, FMS_PATH_LEN
use yaml_parser_mod
use constants_mod, only: DEG_TO_RAD
use mpp_mod, only : mpp_error, FATAL, WARNING, NOTE, stdout, stdlog, mpp_max
Expand Down
10 changes: 5 additions & 5 deletions diag_integral/diag_integral.F90
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ module diag_integral_mod

!###############################################################################

use platform_mod, only: i8_kind, FMS_PATH_LEN
use platform_mod, only: i8_kind, FMS_FILE_LEN
use time_manager_mod, only: time_type, get_time, set_time, &
time_manager_init, &
operator(+), operator(-), &
Expand Down Expand Up @@ -141,7 +141,7 @@ module diag_integral_mod
character(len=8) :: &
time_units = 'hours' !< time units associated with
!! output_interval
character(len=FMS_PATH_LEN) :: &
character(len=FMS_FILE_LEN) :: &
file_name = ' ' !< optional integrals output file name
logical :: &
print_header = .true. !< print a header for the integrals
Expand Down Expand Up @@ -1079,13 +1079,13 @@ end function vert_diag_integral
!! @return character array updated_file_name
function ensemble_file_name(fname) result(updated_file_name)
character (len=*), intent(inout) :: fname
character (len=FMS_PATH_LEN) :: updated_file_name
character (len=FMS_FILE_LEN) :: updated_file_name
integer :: ensemble_id_int
character(len=7) :: ensemble_suffix
character(len=2) :: ensemble_id_char
integer :: i
!> Make sure the file name short enough to handle adding the ensemble number
if (len(trim(fname)) > FMS_PATH_LEN-7) call error_mesg ('diag_integral_mod :: ensemble_file_name', &
if (len(trim(fname)) > FMS_FILE_LEN-7) call error_mesg ('diag_integral_mod :: ensemble_file_name', &
trim(fname)//" is too long and can not support adding ens_XX. Please shorten the "//&
"file_name in the diag_integral_nml", FATAL)
!> Get the ensemble ID and convert it to a string
Expand All @@ -1104,7 +1104,7 @@ function ensemble_file_name(fname) result(updated_file_name)
!> Loop through to find the last period
do i=len(trim(fname)),2,-1
if (fname(i:i) == ".") then
updated_file_name = fname(1:i-1)//trim(ensemble_suffix)//fname(i:FMS_PATH_LEN)
updated_file_name = fname(1:i-1)//trim(ensemble_suffix)//fname(i:len(fname))
return
endif
enddo
Expand Down
2 changes: 1 addition & 1 deletion diag_manager/diag_data.F90
Original file line number Diff line number Diff line change
Expand Up @@ -180,7 +180,7 @@ MODULE diag_data_mod
!> @brief Type to define the diagnostic files that will be written as defined by the diagnostic table.
!> @ingroup diag_data_mod
TYPE file_type
CHARACTER(len=FMS_PATH_LEN) :: name !< Name of the output file.
CHARACTER(len=FMS_FILE_LEN) :: name !< Name of the output file.
CHARACTER(len=128) :: long_name
INTEGER, DIMENSION(max_fields_per_file) :: fields
INTEGER :: num_fields
Expand Down
2 changes: 1 addition & 1 deletion diag_manager/diag_manager.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1415,7 +1415,7 @@ SUBROUTINE add_associated_files(file_num, cm_file_num, cm_ind)
INTEGER :: year, month, day, hour, minute, second
INTEGER :: n
CHARACTER(len=25) :: date_prefix
CHARACTER(len=FMS_PATH_LEN) :: asso_file_name
CHARACTER(len=FMS_FILE_LEN) :: asso_file_name

! Create the date_string
IF ( prepend_date ) THEN
Expand Down
2 changes: 1 addition & 1 deletion diag_manager/diag_output.F90
Original file line number Diff line number Diff line change
Expand Up @@ -109,7 +109,7 @@ SUBROUTINE diag_output_init (file_name, file_title, file_unit,&
integer, allocatable, dimension(:) :: current_pelist
integer :: mype !< The pe you are on
character(len=9) :: mype_string !< a string to store the pe
character(len=FMS_PATH_LEN) :: filename_tile !< Filename with the tile number included
character(len=FMS_FILE_LEN) :: filename_tile !< Filename with the tile number included
!! It is needed for subregional diagnostics

!---- initialize mpp_io ----
Expand Down
4 changes: 2 additions & 2 deletions diag_manager/diag_table.F90
Original file line number Diff line number Diff line change
Expand Up @@ -255,7 +255,7 @@ MODULE diag_table_mod
USE diag_data_mod, ONLY: global_descriptor, get_base_time, set_base_time, &
& DIAG_OTHER, DIAG_OCEAN, DIAG_ALL, coord_type, append_pelist_name, pelist_name
USE diag_util_mod, ONLY: init_file, check_duplicate_output_fields, init_input_field, init_output_field
USE platform_mod, ONLY: FMS_PATH_LEN
USE platform_mod, ONLY: FMS_FILE_LEN

IMPLICIT NONE

Expand Down Expand Up @@ -284,7 +284,7 @@ MODULE diag_table_mod
INTEGER :: iOutput_freq_units
INTEGER :: iNew_file_freq_units
INTEGER :: iFile_duration_units
CHARACTER(len=FMS_PATH_LEN) :: file_name
CHARACTER(len=FMS_FILE_LEN) :: file_name
CHARACTER(len=10) :: output_freq_units
CHARACTER(len=10) :: time_units
CHARACTER(len=128) :: long_name
Expand Down
4 changes: 2 additions & 2 deletions diag_manager/diag_util.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1655,10 +1655,10 @@ SUBROUTINE opening_file(file, time, filename_time)
LOGICAL :: time_ops, aux_present, match_aux_name, req_present, match_req_fields
CHARACTER(len=7) :: avg_name = 'average'
CHARACTER(len=128) :: time_units, timeb_units, avg, error_string, aux_name, req_fields, fieldname
CHARACTER(len=FMS_PATH_LEN) :: filename
CHARACTER(len=FMS_FILE_LEN) :: filename
CHARACTER(len=128) :: suffix, base_name
CHARACTER(len=32) :: time_name, timeb_name,time_longname, timeb_longname, cart_name
CHARACTER(len=FMS_PATH_LEN) :: fname
CHARACTER(len=FMS_FILE_LEN) :: fname
CHARACTER(len=24) :: start_date
TYPE(domain1d) :: domain
TYPE(domain2d) :: domain2
Expand Down
2 changes: 1 addition & 1 deletion diag_manager/fms_diag_field_object.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1899,7 +1899,7 @@ subroutine generate_associated_files_att(this, att, start_time)
type(time_type), intent(in) :: start_time !< The start_time for the field's file

character(len=:), allocatable :: field_name !< Name of the area/volume field
character(len=FMS_PATH_LEN) :: file_name !< Name of the file the area/volume field is in!
character(len=FMS_FILE_LEN) :: file_name !< Name of the file the area/volume field is in!
character(len=128) :: start_date !< Start date to append to the begining of the filename

integer :: year, month, day, hour, minute, second
Expand Down
8 changes: 4 additions & 4 deletions diag_manager/fms_diag_file_object.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1115,10 +1115,10 @@ subroutine open_diag_file(this, time_step, file_is_opened)
class(fmsDiagFile_type), pointer :: diag_file !< Diag_file object to open
class(diagDomain_t), pointer :: domain !< The domain used in the file
character(len=:), allocatable :: diag_file_name !< The file name as defined in the yaml
character(len=FMS_PATH_LEN) :: base_name !< The file name as defined in the yaml
character(len=FMS_FILE_LEN) :: base_name !< The file name as defined in the yaml
!! without the wildcard definition
character(len=FMS_PATH_LEN) :: file_name !< The file name as it will be written to disk
character(len=FMS_PATH_LEN) :: temp_name !< Temp variable to store the file_name
character(len=FMS_FILE_LEN) :: file_name !< The file name as it will be written to disk
character(len=FMS_FILE_LEN) :: temp_name !< Temp variable to store the file_name
character(len=128) :: start_date !< The start_time as a string that will be added to
!! the begining of the filename (start_date.filename)
character(len=128) :: suffix !< The current time as a string that will be added to
Expand Down Expand Up @@ -1694,7 +1694,7 @@ subroutine write_field_metadata(this, diag_field, diag_axis)
logical :: is_regional !< Flag indicating if the field is in a regional file
character(len=255) :: cell_measures !< cell_measures attributes for the field
logical :: need_associated_files !< .True. if the 'associated_files' global attribute is needed
character(len=FMS_PATH_LEN) :: associated_files !< Associated files attribute to add
character(len=FMS_FILE_LEN) :: associated_files !< Associated files attribute to add

is_regional = this%is_regional()

Expand Down
6 changes: 3 additions & 3 deletions diag_manager/fms_diag_yaml.F90
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ module fms_diag_yaml_mod
use, intrinsic :: iso_c_binding, only : c_ptr, c_null_char
use fms_string_utils_mod, only: fms_array_to_pointer, fms_find_my_string, fms_sort_this, fms_find_unique, string, &
fms_f2c_string
use platform_mod, only: r4_kind, i4_kind, r8_kind, i8_kind, FMS_PATH_LEN
use platform_mod, only: r4_kind, i4_kind, r8_kind, i8_kind, FMS_FILE_LEN
use fms_mod, only: lowercase

implicit none
Expand Down Expand Up @@ -77,7 +77,7 @@ module fms_diag_yaml_mod

!> @brief type to hold an array of sorted diag_files
type fileList_type
character(len=FMS_PATH_LEN), allocatable :: file_name(:) !< Array of diag_field
character(len=FMS_FILE_LEN), allocatable :: file_name(:) !< Array of diag_field
type(c_ptr), allocatable :: file_pointer(:) !< Array of pointers
integer, allocatable :: diag_file_indices(:) !< Index of the file in the diag_file array
end type
Expand Down Expand Up @@ -1525,7 +1525,7 @@ function get_diag_files_id(indices) &

integer :: field_id !< Indices of the field in the diag_yaml field array
integer :: i !< For do loops
character(len=FMS_PATH_LEN) :: filename !< Filename of the field
character(len=FMS_FILE_LEN) :: filename !< Filename of the field
integer, allocatable :: file_indices(:) !< Indices of the file in the sorted variable_list

allocate(file_id(size(indices)))
Expand Down
1 change: 1 addition & 0 deletions drifters/drifters.F90
Original file line number Diff line number Diff line change
Expand Up @@ -95,6 +95,7 @@ module drifters_mod
drifters_comm_gather, drifters_comm_update

use cloud_interpolator_mod, only: cld_ntrp_linear_cell_interp, cld_ntrp_locate_cell, cld_ntrp_get_cell_values
use platform_mod, only: FMS_PATH_LEN
implicit none
private

Expand Down
11 changes: 6 additions & 5 deletions exchange/xgrid.F90
Original file line number Diff line number Diff line change
Expand Up @@ -129,7 +129,7 @@ module xgrid_mod
use fms2_io_mod, only: FmsNetcdfFile_t, open_file, variable_exists, close_file
use fms2_io_mod, only: FmsNetcdfDomainFile_t, read_data, get_dimension_size
use fms2_io_mod, only: get_variable_units, dimension_exists
use platform_mod, only: r8_kind, i8_kind, FMS_PATH_LEN
use platform_mod, only: r8_kind, i8_kind, FMS_FILE_LEN

implicit none
private
Expand Down Expand Up @@ -1530,11 +1530,12 @@ subroutine setup_xmap(xmap, grid_ids, grid_domains, grid_file, atm_grid, lnd_ug_
real(r8_kind), dimension(:,:), allocatable :: check_data
real(r8_kind), dimension(:,:,:), allocatable :: check_data_3D
real(r8_kind), allocatable :: tmp_2d(:,:), tmp_3d(:,:,:)
character(len=FMS_PATH_LEN) :: xgrid_file, xgrid_name
character(len=256) :: tile_file, mosaic_file, xgrid_dimname
character(len=256) :: mosaic1, mosaic2, contact
character(len=FMS_FILE_LEN) :: xgrid_file, xgrid_name
character(len=FMS_FILE_LEN) :: tile_file, mosaic_file
character(len=256) :: mosaic1, mosaic2, contact, xgrid_dimname
character(len=256) :: tile1_name, tile2_name
character(len=256), allocatable :: tile1_list(:), tile2_list(:), xgrid_filelist(:)
character(len=256), allocatable :: tile1_list(:), tile2_list(:)
character(len=FMS_FILE_LEN), allocatable :: xgrid_filelist(:)
integer :: npes, npes2
integer, allocatable :: pelist(:)
type(domain2d), save :: domain2
Expand Down
6 changes: 3 additions & 3 deletions field_manager/field_manager.F90
Original file line number Diff line number Diff line change
Expand Up @@ -191,7 +191,7 @@ module field_manager_mod
write_version_number, &
check_nml_error
use fms2_io_mod, only: file_exists
use platform_mod, only: r4_kind, r8_kind, FMS_PATH_LEN
use platform_mod, only: r4_kind, r8_kind, FMS_PATH_LEN, FMS_FILE_LEN
#ifdef use_yaml
use fm_yaml_mod
#endif
Expand Down Expand Up @@ -590,9 +590,9 @@ end subroutine field_manager_init
!> @brief Routine to read and parse the field table yaml
subroutine read_field_table_yaml(nfields, table_name)
integer, intent(out), optional :: nfields !< number of fields
character(len=FMS_PATH_LEN), intent(in), optional :: table_name !< Name of the field table file, default is 'field_table.yaml'
character(len=*), intent(in), optional :: table_name !< Name of the field table file, default is 'field_table.yaml'

character(len=FMS_PATH_LEN) :: tbl_name !< field_table yaml file
character(len=FMS_FILE_LEN) :: tbl_name !< field_table yaml file
character(len=fm_string_len) :: method_control !< field_table yaml file
integer :: h, i, j, k, l, m !< dummy integer buffer
type (fmTable_t) :: my_table !< the field table
Expand Down
6 changes: 3 additions & 3 deletions field_manager/fm_util.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1602,7 +1602,7 @@ subroutine fm_util_set_value_integer_array(name, ival, length, caller, no_overwr
integer, intent(in) :: ival(length)
character(len=*), intent(in), optional :: caller
logical, intent(in), optional :: no_overwrite
character(len=FMS_PATH_LEN), intent(in), optional :: good_name_list
character(len=*), intent(in), optional :: good_name_list

!
! Local parameters
Expand Down Expand Up @@ -1759,7 +1759,7 @@ subroutine fm_util_set_value_logical_array(name, lval, length, caller, no_overwr
logical, intent(in) :: lval(length)
character(len=*), intent(in), optional :: caller
logical, intent(in), optional :: no_overwrite
character(len=FMS_PATH_LEN), intent(in), optional :: good_name_list
character(len=*), intent(in), optional :: good_name_list

!
! Local parameters
Expand Down Expand Up @@ -1916,7 +1916,7 @@ subroutine fm_util_set_value_string_array(name, sval, length, caller, no_overwri
character(len=*), intent(in) :: sval(length)
character(len=*), intent(in), optional :: caller
logical, intent(in), optional :: no_overwrite
character(len=FMS_PATH_LEN), intent(in), optional :: good_name_list
character(len=*), intent(in), optional :: good_name_list

!
! Local parameters
Expand Down
2 changes: 1 addition & 1 deletion fms2_io/blackboxio.F90
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@ subroutine get_new_filename(path, new_path, directory, timestamp, new_name)

character(len=FMS_PATH_LEN) :: dir
character(len=FMS_FILE_LEN) :: tstamp
character(len=FMS_FILE_LEN) :: nname
character(len=FMS_PATH_LEN) :: nname

dir = ""
if (present(directory)) then
Expand Down
4 changes: 2 additions & 2 deletions fms2_io/fms_io_utils.F90
Original file line number Diff line number Diff line change
Expand Up @@ -678,7 +678,7 @@ subroutine get_mosaic_tile_file_sg(file_in, file_out, is_no_domain, domain, tile
type(domain2D), intent(in), optional, target :: domain !< domain provided
integer, intent(in), optional :: tile_count !< tile count

character(len=FMS_PATH_LEN) :: basefile
character(len=FMS_FILE_LEN) :: basefile
character(len=6) :: tilename
character(len=2) :: my_tile_str
integer :: lens, ntiles, ntileMe, tile, my_tile_id
Expand Down Expand Up @@ -736,7 +736,7 @@ subroutine get_mosaic_tile_file_ug(file_in, file_out, domain)
character(len=*), intent(out) :: file_out !< name of tile file
type(domainUG), intent(in), optional :: domain !< domain provided

character(len=FMS_PATH_LEN) :: basefile
character(len=FMS_FILE_LEN) :: basefile
character(len=6) :: tilename
character(len=2) :: my_tile_str
integer :: lens, ntiles, my_tile_id
Expand Down
1 change: 0 additions & 1 deletion mosaic2/mosaic2.F90
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,6 @@ module mosaic2_mod

integer, parameter :: &
MAX_NAME = 256, & !> max length of the variable names
FMS_PATH_LEN = 1024, & !> max length of the file names
X_REFINE = 2, & !> supergrid size/model grid size in x-direction
Y_REFINE = 2 !> supergrid size/model grid size in y-direction

Expand Down
Loading

0 comments on commit 1049e1d

Please sign in to comment.