Skip to content

Commit

Permalink
lite purge updated to 2022.01-alpha2
Browse files Browse the repository at this point in the history
  • Loading branch information
GFDL-Eric committed Mar 3, 2022
1 parent f19c926 commit d7f5a42
Show file tree
Hide file tree
Showing 6 changed files with 15 additions and 356 deletions.
330 changes: 1 addition & 329 deletions coupler/coupler_types.F90

Large diffs are not rendered by default.

6 changes: 2 additions & 4 deletions coupler/ensemble_manager.F90
Original file line number Diff line number Diff line change
Expand Up @@ -32,8 +32,7 @@ module ensemble_manager_mod
use mpp_mod, only : mpp_npes, stdout, stdlog, mpp_error, FATAL
use mpp_mod, only : mpp_pe, mpp_declare_pelist
use mpp_mod, only : input_nml_file
use fms2_io_mod, only : fms2_io_set_filename_appendix=>set_filename_appendix
use fms_io_mod, only : fms_io_set_filename_appendix=>set_filename_appendix
use fms2_io_mod, only : set_filename_appendix

IMPLICIT NONE

Expand Down Expand Up @@ -409,8 +408,7 @@ subroutine ensemble_pelist_setup(concurrent, atmos_npes, ocean_npes, land_npes,
!Append ensemble_id to the restart filenames

!< Both calls are needed for cases where both fms2io/fmsio are used
call fms2_io_set_filename_appendix(trim(text))
call fms_io_set_filename_appendix(trim(text))
call set_filename_appendix(trim(text))
endif

end subroutine ensemble_pelist_setup
Expand Down
3 changes: 1 addition & 2 deletions data_override/data_override.F90
Original file line number Diff line number Diff line change
Expand Up @@ -54,8 +54,7 @@ module data_override_mod
reset_src_data_region, &
NO_REGION, INSIDE_REGION, OUTSIDE_REGION, &
get_external_fileobj
use fms_mod, only: write_version_number, field_exist, lowercase, check_nml_error
use axis_utils_mod, only: get_axis_bounds
use fms_mod, only: write_version_number, lowercase, check_nml_error
use axis_utils2_mod, only : nearest_index, axis_edges
use mpp_domains_mod, only : domain2d, mpp_get_compute_domain, NULL_DOMAIN2D,operator(.NE.),operator(.EQ.)
use mpp_domains_mod, only : mpp_get_global_domain, mpp_get_data_domain
Expand Down
5 changes: 3 additions & 2 deletions diag_integral/diag_integral.F90
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,7 @@ module diag_integral_mod
operator(==), operator(>=), &
operator(/=)
use mpp_mod, only: input_nml_file
use fms_mod, only: open_file, error_mesg, &
use fms_mod, only: error_mesg, &
check_nml_error, &
fms_init, &
mpp_pe, mpp_root_pe,&
Expand Down Expand Up @@ -379,7 +379,7 @@ subroutine diag_integral_init (Time_init, Time, blon, blat, area_in)
file_name = ensemble_file_name(file_name)
endif
nc = len_trim(file_name)
diag_unit = open_file (file_name(1:nc), action='write')
open(newunit=diag_unit, file=file_name(1:nc), action='write')
endif

!-------------------------------------------------------------------------------
Expand Down Expand Up @@ -952,6 +952,7 @@ subroutine diag_integral_end (Time)
! deallocate module variables.
!-------------------------------------------------------------------------------
deallocate (area)
if (diag_unit /= 0) close(diag_unit)

!-------------------------------------------------------------------------------
! mark the module as uninitialized.
Expand Down
1 change: 0 additions & 1 deletion diag_manager/diag_manager.F90
Original file line number Diff line number Diff line change
Expand Up @@ -201,7 +201,6 @@ MODULE diag_manager_mod

USE fms_mod, ONLY: error_mesg, FATAL, WARNING, NOTE, stdout, stdlog, write_version_number,&
& fms_error_handler, check_nml_error, lowercase
USE fms_io_mod, ONLY: get_instance_filename
USE diag_axis_mod, ONLY: diag_axis_init, get_axis_length, get_axis_num, get_domain2d, get_tile_count,&
& diag_axis_add_attribute, axis_compatible_check, CENTER, NORTH, EAST
USE diag_util_mod, ONLY: get_subfield_size, log_diag_field_info, update_bounds,&
Expand Down
26 changes: 8 additions & 18 deletions diag_manager/diag_util.F90
Original file line number Diff line number Diff line change
Expand Up @@ -62,8 +62,8 @@ MODULE diag_util_mod
USE diag_output_mod, ONLY: diag_field_write, diag_write_time !<fms2_io use_mpp_io=.false.
USE diag_grid_mod, ONLY: get_local_indexes
USE fms_mod, ONLY: error_mesg, FATAL, WARNING, NOTE, mpp_pe, mpp_root_pe, lowercase, fms_error_handler,&
& write_version_number, do_cf_compliance
USE fms_io_mod, ONLY: get_tile_string, return_domain, string
& string, write_version_number
USE fms2_io_mod, ONLY: get_instance_filename, FmsNetcdfFile_t, check_if_open
USE mpp_domains_mod,ONLY: domain1d, domain2d, mpp_get_compute_domain, null_domain1d, null_domain2d,&
& OPERATOR(.NE.), OPERATOR(.EQ.), mpp_modify_domain, mpp_get_domain_components,&
& mpp_get_ntile_count, mpp_get_current_ntile, mpp_get_tile_id, mpp_mosaic_defined, mpp_get_tile_npes,&
Expand All @@ -72,9 +72,7 @@ MODULE diag_util_mod
& increment_time, get_calendar_type, get_date, get_time, leap_year, OPERATOR(-),&
& OPERATOR(<), OPERATOR(>=), OPERATOR(<=), OPERATOR(==)
USE mpp_mod, ONLY: mpp_npes
USE fms_io_mod, ONLY: get_mosaic_tile_file_ug
USE constants_mod, ONLY: SECONDS_PER_DAY, SECONDS_PER_HOUR, SECONDS_PER_MINUTE
USE fms2_io_mod, fms2_io_get_instance_filename => get_instance_filename
#ifdef use_netCDF
USE netcdf, ONLY: NF90_CHAR
#endif
Expand Down Expand Up @@ -1587,7 +1585,7 @@ SUBROUTINE opening_file(file, time, filename_time)

! Add ensemble ID to filename
fname=base_name
call fms2_io_get_instance_filename(fname, base_name)
call get_instance_filename(fname, base_name)

! Set the filename
filename = TRIM(base_name)//TRIM(suffix)
Expand Down Expand Up @@ -1912,19 +1910,11 @@ SUBROUTINE opening_file(file, time, filename_time)
& cart_name, dir, edges, Domain, domainU, DATA)
CALL get_diag_axis( time_bounds_id(1), timeb_name, timeb_units, timeb_longname,&
& cart_name, dir, edges, Domain, domainU, DATA)
IF ( do_cf_compliance() ) THEN
! CF Compliance requires the unit on the _bnds axis is the same as 'time'
files(file)%f_bounds = write_field_meta_data(files(file)%file_unit,&
& TRIM(time_name)//'_bnds', (/time_bounds_id,time_axis_id/),&
& time_units, TRIM(time_name)//' axis boundaries', pack=pack_size , &
& fileob=fileob)
ELSE
files(file)%f_bounds = write_field_meta_data(files(file)%file_unit,&
& TRIM(time_name)//'_bnds', (/time_bounds_id,time_axis_id/),&
& TRIM(time_unit_list(files(file)%time_units)),&
& TRIM(time_name)//' axis boundaries', pack=pack_size, &
& fileob=fileob)
END IF
! CF Compliance requires the unit on the _bnds axis is the same as 'time'
files(file)%f_bounds = write_field_meta_data(files(file)%file_unit,&
& TRIM(time_name)//'_bnds', (/time_bounds_id,time_axis_id/),&
& time_units, TRIM(time_name)//' axis boundaries', pack=pack_size , &
& fileob=fileob)
END IF
! Let lower levels know that all meta data has been sent
call done_meta_data(files(file)%file_unit)
Expand Down

0 comments on commit d7f5a42

Please sign in to comment.