Skip to content

Commit

Permalink
Merge branch 'main' into ascii_io
Browse files Browse the repository at this point in the history
  • Loading branch information
rem1776 authored Mar 26, 2021
2 parents 72f06af + 1d7d2f4 commit a85eca0
Show file tree
Hide file tree
Showing 41 changed files with 2,969 additions and 3,420 deletions.
6 changes: 5 additions & 1 deletion amip_interp/amip_interp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -544,7 +544,11 @@ subroutine get_amip_sst (Time, Interp, sst, err_msg, lon_model, lat_model)
lon_model, lat_model, interp_method="bilinear" )

if (use_mpp_io) then
the_file_exists = fms_io_file_exists(ncfilename)
!! USE_MPP_IO_WARNING
call mpp_error ('amip_interp_mod', &
'MPP_IO is no longer supported. Please remove from namelist',&
WARNING)
the_file_exists = fms_io_file_exists(ncfilename)
else
the_file_exists = fms2_io_file_exists(ncfilename)
endif !if (use_mpp_io)
Expand Down
1 change: 1 addition & 0 deletions configure.ac
Original file line number Diff line number Diff line change
Expand Up @@ -355,6 +355,7 @@ AC_CONFIG_FILES([
test_fms/axis_utils/Makefile
test_fms/mosaic/Makefile
test_fms/affinity/Makefile
test_fms/coupler/Makefile
FMS.pc
])

Expand Down
503 changes: 477 additions & 26 deletions coupler/coupler_types.F90

Large diffs are not rendered by default.

8 changes: 6 additions & 2 deletions coupler/ensemble_manager.F90
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,8 @@ 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 fms_io_mod, only : set_filename_appendix
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

IMPLICIT NONE

Expand Down Expand Up @@ -400,7 +401,10 @@ subroutine ensemble_pelist_setup(concurrent, atmos_npes, ocean_npes, land_npes,
if (ensemble_size > 1) then
write( text,'(a,i2.2)' ) 'ens_', ensemble_id
!Append ensemble_id to the restart filenames
call set_filename_appendix(trim(text))

!< 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))
endif

end subroutine ensemble_pelist_setup
Expand Down
2 changes: 2 additions & 0 deletions data_override/data_override.F90
Original file line number Diff line number Diff line change
Expand Up @@ -262,6 +262,8 @@ subroutine data_override_init(Atm_domain_in, Ocean_domain_in, Ice_domain_in, Lan

! Read coupler_table
if(use_mpp_bug) then
call mpp_error(WARNING, 'data_override_mod:' &
//'MPP_IO is no longer supported. Please remove "use_mpp_bug" from namelist')
call mpp_open(iunit, 'data_table', action=MPP_RDONLY)
else
iunit = get_unit()
Expand Down
3 changes: 3 additions & 0 deletions diag_manager/diag_manager.F90
Original file line number Diff line number Diff line change
Expand Up @@ -3943,6 +3943,9 @@ SUBROUTINE diag_manager_init(diag_model_subset, time_init, err_msg)
else
CALL error_mesg('diag_manager_mod::diag_manager_init',&
& 'diag_manager is using mpp_io', NOTE)
CALL error_mesg('diag_manager_mod::diag_manager_init',&
&'MPP_IO is no longer supported. Please remove from namelist',&
&WARNING)
endif
ALLOCATE(pelist(mpp_npes()))
CALL mpp_get_current_pelist(pelist, pelist_name)
Expand Down
12 changes: 9 additions & 3 deletions diag_manager/diag_util.F90
Original file line number Diff line number Diff line change
Expand Up @@ -76,7 +76,9 @@ MODULE diag_util_mod
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, get_instance_filename
USE fms_io_mod, ONLY: get_tile_string, return_domain, string
USE fms2_io_mod, ONLY: fms2_io_get_instance_filename => get_instance_filename
USE fms_io_mod, ONLY: mpp_io_get_instance_filename => get_instance_filename
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 @@ -86,7 +88,7 @@ MODULE diag_util_mod
& OPERATOR(<), OPERATOR(>=), OPERATOR(<=), OPERATOR(==)
USE mpp_io_mod, ONLY: mpp_close
USE mpp_mod, ONLY: mpp_npes
USE fms_io_mod, ONLY: get_instance_filename, get_mosaic_tile_file_ug
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
#ifdef use_netCDF
Expand Down Expand Up @@ -1601,7 +1603,11 @@ SUBROUTINE opening_file(file, time, use_mpp_io, filename_time)

! Add ensemble ID to filename
fname=base_name
call get_instance_filename(fname, base_name)
if (use_mpp_io) then
call mpp_io_get_instance_filename(fname, base_name)
else
call fms2_io_get_instance_filename(fname, base_name)
endif

! Set the filename
filename = TRIM(base_name)//TRIM(suffix)
Expand Down
6 changes: 5 additions & 1 deletion exchange/xgrid.F90
Original file line number Diff line number Diff line change
Expand Up @@ -142,6 +142,7 @@ module xgrid_mod

use fms_mod, only: check_nml_error, &
error_mesg, FATAL, NOTE, stdlog, &
WARNING, & !!! use_mpp_io removal
write_version_number, lowercase, string
use mpp_mod, only: mpp_npes, mpp_pe, mpp_root_pe, mpp_send, mpp_recv, &
mpp_sync_self, stdout, mpp_max, EVENT_RECV, &
Expand Down Expand Up @@ -623,7 +624,10 @@ subroutine xgrid_init(remap_method)
if (use_mpp_io) then
! Tell user which IO they are using
call error_mesg('xgrid_init', "Using mpp_io in xgrid_mod",NOTE)
if ( mpp_pe() == mpp_root_pe() ) write (unit,'(a)')"Using mpp_io in xgrid_mod"
call error_mesg('xgrid_init', &
'MPP_IO is no longer supported. Please remove from namelist',&
WARNING)
if ( mpp_pe() == mpp_root_pe() ) write (unit,'(a)')"Using mpp_io in xgrid_mod"
else
call error_mesg('xgrid_init',"Using fms2_io in xgrid_mod",NOTE)
if ( mpp_pe() == mpp_root_pe() ) write (unit,'(a)')"Using fms2_io in xgrid_mod"
Expand Down
48 changes: 40 additions & 8 deletions fms/fms.F90
Original file line number Diff line number Diff line change
Expand Up @@ -182,10 +182,10 @@ module fms_mod
use fms_io_mod, only : fms_io_init, fms_io_exit, field_size, &
read_data, write_data, read_compressed, read_distributed, &
open_namelist_file, open_restart_file, open_ieee32_file, close_file, &
set_domain, get_domain_decomp, nullify_domain, &
open_file, open_direct_file, string, get_mosaic_tile_grid, &
get_domain_decomp, &
open_file, open_direct_file, get_mosaic_tile_grid, &
get_mosaic_tile_file, get_global_att_value, file_exist, field_exist, &
write_version_number
write_version_number, set_domain, nullify_domain
use fms2_io_mod, only: fms2_io_init
use memutils_mod, only: print_memuse_stats, memutils_init

Expand All @@ -202,8 +202,8 @@ module fms_mod
open_file, open_direct_file

! routines for reading/writing distributed data
public :: set_domain, read_data, write_data, read_compressed, read_distributed
public :: get_domain_decomp, field_size, nullify_domain
public :: read_data, write_data, read_compressed, read_distributed
public :: get_domain_decomp, field_size
public :: get_global_att_value

! routines for get mosaic information
Expand All @@ -216,8 +216,9 @@ module fms_mod
public :: write_version_number

! miscellaneous utilities (non i/o)
public :: lowercase, uppercase, string, &
string_array_index, monotonic_array
public :: lowercase, uppercase, &
string_array_index, monotonic_array, &
set_domain, nullify_domain

! public mpp interfaces
public :: mpp_error, NOTE, WARNING, FATAL, &
Expand All @@ -231,6 +232,9 @@ module fms_mod
public :: CLOCK_COMPONENT, CLOCK_SUBCOMPONENT, &
CLOCK_MODULE_DRIVER, CLOCK_MODULE, &
CLOCK_ROUTINE, CLOCK_LOOP, CLOCK_INFRA
!public from the old fms_io but not exists here
public :: string

! public mpp-io interfaces
public :: do_cf_compliance

Expand Down Expand Up @@ -330,6 +334,11 @@ module fms_mod

logical :: module_is_initialized = .FALSE.

!> Converts a number to a string
interface string
module procedure string_from_integer
module procedure string_from_real
end interface

contains

Expand Down Expand Up @@ -998,7 +1007,30 @@ function monotonic_array ( array, direction )

end function monotonic_array
! </FUNCTION>

!! Functions from the old fms_io
!> \brief Converts an integer to a string
!! This has been updated from the fms_io function.
function string_from_integer(i) result (res)
integer, intent(in) :: i !< Integer to be converted to a string
character(:),allocatable :: res !< String converted frominteger
character(range(i)+2) :: tmp !< Temp string that is set to correct size
write(tmp,'(i0)') i
res = trim(tmp)
return

end function string_from_integer

!#######################################################################
!> \brief Converts a real to a string
function string_from_real(a)
real, intent(in) :: a
character(len=32) :: string_from_real

write(string_from_real,*) a

return

end function string_from_real
end module fms_mod
! <INFO>
! <BUG>
Expand Down
17 changes: 13 additions & 4 deletions fms/fms_io.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2491,7 +2491,8 @@ subroutine save_restart(fileObj, time_stamp, directory, append, time_level)
character(len=256) :: dir
character(len=80) :: restartname ! The restart file name (no dir).
character(len=336) :: restartpath ! The restart file path (dir/file).

integer :: i !< For looping
logical :: has_dot !< For determining if the time_stamp has a .
! This approach is taken rather than interface overloading in order to preserve
! use of the register_restart_field infrastructure

Expand All @@ -2506,7 +2507,15 @@ subroutine save_restart(fileObj, time_stamp, directory, append, time_level)
if (PRESENT(time_stamp)) then
if(len_trim(restartname)+len_trim(time_stamp) > 79) call mpp_error(FATAL, "fms_io(save_restart): " // &
"Length of restart file name + time_stamp is greater than allowed character length of 79")
restartname = trim(time_stamp)//"."//trim(restartname)
has_dot = .false.
do i=1,len(time_stamp)
if (time_stamp(i:i) == ".") has_dot = .true.
enddo
if (has_dot) then
restartname = trim(time_stamp)//trim(restartname)
else
restartname = trim(time_stamp)//"."//trim(restartname)
endif
endif
end if
if(len_trim(dir) > 0) then
Expand Down Expand Up @@ -7411,7 +7420,6 @@ end subroutine close_file
subroutine set_domain (Domain2)

type(domain2D), intent(in), target :: Domain2

if (.NOT.module_is_initialized) call fms_io_init ( )

! --- set_domain must be called before a read_data or write_data ---
Expand Down Expand Up @@ -7701,7 +7709,7 @@ end function open_file
function string_from_integer(n)
integer, intent(in) :: n
character(len=16) :: string_from_integer

call mpp_error(WARNING, "function string has been moved to fms_mod. Please update.")
if(n<0) then
call mpp_error(FATAL, 'fms_io_mod: n should be non-negative integer, contact developer')
else if( n<10 ) then
Expand Down Expand Up @@ -7732,6 +7740,7 @@ end function string_from_integer
function string_from_real(a)
real, intent(in) :: a
character(len=32) :: string_from_real
call mpp_error(WARNING, "function string has been moved to fms_mod. Please update.")

write(string_from_real,*) a

Expand Down
7 changes: 5 additions & 2 deletions fms2_io/Makefile.am
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,9 @@ libfms2_io_la_SOURCES = \
include/netcdf_write_data.inc \
include/register_global_attribute.inc \
include/register_variable_attribute.inc \
include/unstructured_domain_write.inc
include/unstructured_domain_write.inc \
include/gather_data_bc.inc \
include/scatter_data_bc.inc

# Some mods are dependant on other mods in this dir.
fms2_io_mod.$(FC_MODEXT): fms_io_utils_mod.$(FC_MODEXT) netcdf_io_mod.$(FC_MODEXT) fms_netcdf_domain_io_mod.$(FC_MODEXT) \
Expand All @@ -63,7 +65,8 @@ fms_io_utils_mod.$(FC_MODEXT): include/array_utils.inc include/array_utils_char.
netcdf_io_mod.$(FC_MODEXT): fms_io_utils_mod.$(FC_MODEXT) include/netcdf_add_restart_variable.inc include/netcdf_read_data.inc \
include/netcdf_write_data.inc include/register_global_attribute.inc \
include/register_variable_attribute.inc include/get_global_attribute.inc \
include/get_variable_attribute.inc include/compressed_write.inc include/compressed_read.inc
include/get_variable_attribute.inc include/compressed_write.inc include/compressed_read.inc \
include/gather_data_bc.inc include/scatter_data_bc.inc
fms_netcdf_domain_io_mod.$(FC_MODEXT): fms_io_utils_mod.$(FC_MODEXT) netcdf_io_mod.$(FC_MODEXT) include/register_domain_restart_variable.inc \
include/domain_read.inc include/domain_write.inc include/compute_global_checksum.inc
fms_netcdf_unstructured_domain_io_mod.$(FC_MODEXT): fms_io_utils_mod.$(FC_MODEXT) netcdf_io_mod.$(FC_MODEXT) \
Expand Down
11 changes: 9 additions & 2 deletions fms2_io/fms2_io.F90
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,6 @@ module fms2_io_mod
implicit none
private


public :: unlimited
public :: FmsNetcdfFile_t
public :: FmsNetcdfDomainFile_t
Expand Down Expand Up @@ -84,10 +83,16 @@ module fms2_io_mod
public :: set_fileobj_time_name
public :: is_dimension_registered
public :: fms2_io_init
public :: write_restart_bc
public :: read_restart_bc
public :: get_mosaic_tile_grid
public :: ascii_read
public :: get_mosaic_tile_file
public :: parse_mask_table
public :: get_filename_appendix
public :: set_filename_appendix
public :: get_instance_filename
public :: nullify_filename_appendix

interface open_file
module procedure netcdf_file_open_wrap
Expand Down Expand Up @@ -144,6 +149,8 @@ module fms2_io_mod
module procedure register_unstructured_domain_restart_variable_3d
module procedure register_unstructured_domain_restart_variable_4d
module procedure register_unstructured_domain_restart_variable_5d
module procedure register_restart_region_2d
module procedure register_restart_region_3d
end interface register_restart_field


Expand Down Expand Up @@ -217,6 +224,7 @@ module fms2_io_mod
end interface read_new_restart

logical, private :: fms2_io_is_initialized = .false. !< True after fms2_io_init is run

!< Namelist variables
integer :: ncchksz = 64*1024 !< User defined chunksize (in bytes) argument in netcdf file
!! creation calls. Replaces setting the NC_CHKSZ environment variable.
Expand Down Expand Up @@ -254,5 +262,4 @@ subroutine fms2_io_init ()
fms2_io_is_initialized = .true.
end subroutine fms2_io_init


end module fms2_io_mod
Loading

0 comments on commit a85eca0

Please sign in to comment.