Skip to content

Commit

Permalink
Removal of mpp_open
Browse files Browse the repository at this point in the history
Commit #1
---------

Removes calls to mpp_open, and replaces then with FATAL MOM_error calls
when present.

This also introduces the idea where only domain-decomposed files are
used with infra IO.  I've floated this idea a few times and people seem
supportive, but it may not necessarily be embraced by everyone.

Also moves Vertical_coordinate.nc from infra to native netCDF.

This is primarily a trial balloon to see how the regression suite holds
up.

Commit #2
---------

mpp_open removal

This formally removes the mpp_open functions, along with the FMS_writes
control flag.  Hopefully there is nothing much interesting here.

Also removed open_file_unit since it's no longer used, and renamed
open_file_type to open_file since the interface serves no purpose.
  • Loading branch information
marshallward committed Feb 23, 2023
1 parent 8035a35 commit ef2b86b
Show file tree
Hide file tree
Showing 4 changed files with 50 additions and 94 deletions.
1 change: 0 additions & 1 deletion config_src/drivers/nuopc_cap/mom_cap.F90
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,6 @@ module MOM_cap_mod
use mpp_domains_mod, only: domain2d, mpp_get_compute_domain, mpp_get_compute_domains
use mpp_domains_mod, only: mpp_get_ntile_count, mpp_get_pelist, mpp_get_global_domain
use mpp_domains_mod, only: mpp_get_domain_npes
use mpp_io_mod, only: mpp_open, MPP_RDONLY, MPP_ASCII, MPP_OVERWR, MPP_APPEND, mpp_close, MPP_SINGLE
use mpp_mod, only: stdlog, stdout, mpp_root_pe, mpp_clock_id
use mpp_mod, only: mpp_clock_begin, mpp_clock_end, MPP_CLOCK_SYNC
use mpp_mod, only: MPP_CLOCK_DETAILED, CLOCK_COMPONENT, MAXPES
Expand Down
134 changes: 44 additions & 90 deletions config_src/infra/FMS2/MOM_io_infra.F90
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ module MOM_io_infra
use fms_io_mod, only : file_exist, field_exist, field_size, read_data
use fms_io_mod, only : fms_io_exit, get_filename_appendix
use mpp_domains_mod, only : mpp_get_compute_domain, mpp_get_global_domain
use mpp_io_mod, only : mpp_open, mpp_close, mpp_flush
use mpp_io_mod, only : mpp_close, mpp_flush
use mpp_io_mod, only : mpp_write_meta, mpp_write
use mpp_io_mod, only : mpp_get_atts, mpp_attribute_exist
use mpp_io_mod, only : mpp_get_axes, mpp_axistype=>axistype, mpp_get_axis_data
Expand Down Expand Up @@ -63,11 +63,6 @@ module MOM_io_infra
module procedure MOM_file_exists
end interface

!> Open a file (or fileset) for parallel or single-file I/O.
interface open_file
module procedure open_file_type, open_file_unit
end interface open_file

!> Read a data field from a file
interface read_field
module procedure read_field_4d
Expand Down Expand Up @@ -142,8 +137,8 @@ module MOM_io_infra
end type axistype

!> For now, these module-variables are hard-coded to exercise the new FMS2 interfaces.
! TODO: Delete these
logical :: FMS2_reads = .true.
logical :: FMS2_writes = .true.

contains

Expand Down Expand Up @@ -212,13 +207,6 @@ subroutine close_file_unit(iounit)

logical :: unit_is_open

! NOTE: Files opened by `mpp_open` must be closed by `mpp_close`. Otherwise,
! an error will occur during `fms_io_exit`.
!
! Since there is no way to check if `fms_io_init` was called, we are forced
! to visually confirm that the input unit was not created by `mpp_open`.
!
! After `mpp_open` has been removed, this message can be deleted.
inquire(iounit, opened=unit_is_open)
if (unit_is_open) close(iounit)
end subroutine close_file_unit
Expand Down Expand Up @@ -299,35 +287,7 @@ subroutine write_version(version, tag, unit)
end subroutine write_version

!> open_file opens a file for parallel or single-file I/O.
subroutine open_file_unit(unit, filename, action, form, threading, fileset, nohdrs, domain, MOM_domain)
integer, intent(out) :: unit !< The I/O unit for the opened file
character(len=*), intent(in) :: filename !< The name of the file being opened
integer, optional, intent(in) :: action !< A flag indicating whether the file can be read
!! or written to and how to handle existing files.
integer, optional, intent(in) :: form !< A flag indicating the format of a new file. The
!! default is ASCII_FILE, but NETCDF_FILE is also common.
integer, optional, intent(in) :: threading !< A flag indicating whether one (SINGLE_FILE)
!! or multiple PEs (MULTIPLE) participate in I/O.
!! With the default, the root PE does I/O.
integer, optional, intent(in) :: fileset !< A flag indicating whether multiple PEs doing I/O due
!! to threading=MULTIPLE write to the same file (SINGLE_FILE)
!! or to one file per PE (MULTIPLE, the default).
logical, optional, intent(in) :: nohdrs !< If nohdrs is .TRUE., headers are not written to
!! ASCII files. The default is .false.
type(domain2d), optional, intent(in) :: domain !< A domain2d type that describes the decomposition
type(MOM_domain_type), optional, intent(in) :: MOM_Domain !< A MOM_Domain that describes the decomposition

if (present(MOM_Domain)) then
call mpp_open(unit, filename, action=action, form=form, threading=threading, fileset=fileset, &
nohdrs=nohdrs, domain=MOM_Domain%mpp_domain)
else
call mpp_open(unit, filename, action=action, form=form, threading=threading, fileset=fileset, &
nohdrs=nohdrs, domain=domain)
endif
end subroutine open_file_unit

!> open_file opens a file for parallel or single-file I/O.
subroutine open_file_type(IO_handle, filename, action, MOM_domain, threading, fileset)
subroutine open_file(IO_handle, filename, action, MOM_domain, threading, fileset)
type(file_type), intent(inout) :: IO_handle !< The handle for the opened file
character(len=*), intent(in) :: filename !< The path name of the file being opened
integer, optional, intent(in) :: action !< A flag indicating whether the file can be read
Expand Down Expand Up @@ -355,63 +315,60 @@ subroutine open_file_type(IO_handle, filename, action, MOM_domain, threading, fi
integer :: index_nc

if (IO_handle%open_to_write) then
call MOM_error(WARNING, "open_file_type called for file "//trim(filename)//&
call MOM_error(WARNING, "open_file called for file "//trim(filename)//&
" with an IO_handle that is already open to to write.")
return
endif
if (IO_handle%open_to_read) then
call MOM_error(FATAL, "open_file_type called for file "//trim(filename)//&
call MOM_error(FATAL, "open_file called for file "//trim(filename)//&
" with an IO_handle that is already open to to read.")
endif

file_mode = WRITEONLY_FILE ; if (present(action)) file_mode = action

if (FMS2_writes .and. present(MOM_Domain)) then
if (.not.associated(IO_handle%fileobj)) allocate (IO_handle%fileobj)
! Domains are currently required to use FMS I/O.
! NOTE: This is required due to issues with string-based attributes in
! certain compilers, but could be relaxes if those issues are resolved.
if (.not. present(MOM_Domain)) &
call MOM_error(FATAL, 'open_file: FMS I/O requires a domain input.')

! The FMS1 interface automatically appends .nc if necessary, but FMS2 interface does not.
index_nc = index(trim(filename), ".nc")
if (index_nc > 0) then
filename_tmp = trim(filename)
else
filename_tmp = trim(filename)//".nc"
if (is_root_PE()) call MOM_error(WARNING, "Open_file is appending .nc to the filename "//trim(filename))
endif
if (.not.associated(IO_handle%fileobj)) allocate (IO_handle%fileobj)

if (file_mode == WRITEONLY_FILE) then ; mode = "write"
elseif (file_mode == APPEND_FILE) then ; mode = "append"
elseif (file_mode == OVERWRITE_FILE) then ; mode = "overwrite"
elseif (file_mode == READONLY_FILE) then ; mode = "read"
else
call MOM_error(FATAL, "open_file_type called with unrecognized action.")
endif

IO_handle%num_times = 0
IO_handle%file_time = 0.0
if ((file_mode == APPEND_FILE) .and. file_exists(filename_tmp, MOM_Domain)) then
! Determine the latest file time and number of records so far.
success = fms2_open_file(fileObj_read, trim(filename_tmp), "read", MOM_domain%mpp_domain)
call get_unlimited_dimension_name(fileObj_read, dim_unlim_name)
if (len_trim(dim_unlim_name) > 0) &
call get_dimension_size(fileObj_read, trim(dim_unlim_name), IO_handle%num_times)
if (IO_handle%num_times > 0) &
call fms2_read_data(fileObj_read, trim(dim_unlim_name), IO_handle%file_time, &
unlim_dim_level=IO_handle%num_times)
call fms2_close_file(fileObj_read)
endif
! The FMS1 interface automatically appends .nc if necessary, but FMS2 interface does not.
index_nc = index(trim(filename), ".nc")
if (index_nc > 0) then
filename_tmp = trim(filename)
else
filename_tmp = trim(filename)//".nc"
if (is_root_PE()) call MOM_error(WARNING, "Open_file is appending .nc to the filename "//trim(filename))
endif

success = fms2_open_file(IO_handle%fileobj, trim(filename_tmp), trim(mode), MOM_domain%mpp_domain)
if (.not.success) call MOM_error(FATAL, "Unable to open file "//trim(filename_tmp))
IO_handle%FMS2_file = .true.
elseif (present(MOM_Domain)) then
call mpp_open(IO_handle%unit, filename, action=file_mode, form=NETCDF_FILE, threading=threading, &
fileset=fileset, domain=MOM_Domain%mpp_domain)
IO_handle%FMS2_file = .false.
if (file_mode == WRITEONLY_FILE) then ; mode = "write"
elseif (file_mode == APPEND_FILE) then ; mode = "append"
elseif (file_mode == OVERWRITE_FILE) then ; mode = "overwrite"
elseif (file_mode == READONLY_FILE) then ; mode = "read"
else
call mpp_open(IO_handle%unit, filename, action=file_mode, form=NETCDF_FILE, threading=threading, &
fileset=fileset)
IO_handle%FMS2_file = .false.
call MOM_error(FATAL, "open_file called with unrecognized action.")
endif

IO_handle%num_times = 0
IO_handle%file_time = 0.0
if ((file_mode == APPEND_FILE) .and. file_exists(filename_tmp, MOM_Domain)) then
! Determine the latest file time and number of records so far.
success = fms2_open_file(fileObj_read, trim(filename_tmp), "read", MOM_domain%mpp_domain)
call get_unlimited_dimension_name(fileObj_read, dim_unlim_name)
if (len_trim(dim_unlim_name) > 0) &
call get_dimension_size(fileObj_read, trim(dim_unlim_name), IO_handle%num_times)
if (IO_handle%num_times > 0) &
call fms2_read_data(fileObj_read, trim(dim_unlim_name), IO_handle%file_time, &
unlim_dim_level=IO_handle%num_times)
call fms2_close_file(fileObj_read)
endif

success = fms2_open_file(IO_handle%fileobj, trim(filename_tmp), trim(mode), MOM_domain%mpp_domain)
if (.not.success) call MOM_error(FATAL, "Unable to open file "//trim(filename_tmp))
! TODO: Drop this
IO_handle%FMS2_file = .true.
IO_handle%filename = trim(filename)

if (file_mode == READONLY_FILE) then
Expand All @@ -420,7 +377,7 @@ subroutine open_file_type(IO_handle, filename, action, MOM_domain, threading, fi
IO_handle%open_to_read = .false. ; IO_handle%open_to_write = .true.
endif

end subroutine open_file_type
end subroutine open_file

!> open_file opens an ascii file for parallel or single-file I/O using Fortran read and write calls.
subroutine open_ASCII_file(unit, file, action, threading, fileset)
Expand Down Expand Up @@ -830,10 +787,7 @@ subroutine get_axis_data( axis, dat )
if (size(axis%ax_data) > size(dat)) call MOM_error(FATAL, &
"get_axis_data called with too small of an output data array for "//trim(axis%name))
do i=1,size(axis%ax_data) ; dat(i) = axis%ax_data(i) ; enddo
elseif (.not.FMS2_writes) then
call mpp_get_axis_data( axis%AT, dat )
endif

end subroutine get_axis_data

!> This routine uses the fms_io subroutine read_data to read a scalar named
Expand Down
4 changes: 2 additions & 2 deletions src/ALE/MOM_regridding.F90
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ module MOM_regridding
use MOM_file_parser, only : param_file_type, get_param, log_param
use MOM_io, only : file_exists, field_exists, field_size, MOM_read_data
use MOM_io, only : vardesc, var_desc, SINGLE_FILE
use MOM_io, only : MOM_infra_file, MOM_field
use MOM_io, only : MOM_netCDF_file, MOM_field
use MOM_io, only : create_MOM_file, MOM_write_field
use MOM_io, only : verify_variable_units, slasher
use MOM_unit_scaling, only : unit_scale_type
Expand Down Expand Up @@ -2214,7 +2214,7 @@ subroutine write_regrid_file( CS, GV, filepath )

type(vardesc) :: vars(2)
type(MOM_field) :: fields(2)
type(MOM_infra_file) :: IO_handle ! The I/O handle of the fileset
type(MOM_netCDF_file) :: IO_handle ! The I/O handle of the fileset
real :: ds(GV%ke), dsi(GV%ke+1)

if (CS%regridding_scheme == REGRIDDING_HYBGEN) then
Expand Down
5 changes: 4 additions & 1 deletion src/framework/MOM_io.F90
Original file line number Diff line number Diff line change
Expand Up @@ -333,12 +333,15 @@ subroutine create_MOM_file(IO_handle, filename, vars, novars, fields, &
IsgB = dG%IsgB ; IegB = dG%IegB ; JsgB = dG%JsgB ; JegB = dG%JegB
endif

if (domain_set .and. (num_PEs() == 1)) thread = SINGLE_FILE
! Previously, thread was set to SINGLE_FILE for single-PE jobs; we now
! base this solely on the presence of a domain.
if (domain_set) thread = MULTIPLE

one_file = .true.
if (domain_set) one_file = (thread == SINGLE_FILE)

if (one_file) then
! thread must equal SINGLE_FILE, so why pass the variable?
call IO_handle%open(filename, action=OVERWRITE_FILE, threading=thread)
else
call IO_handle%open(filename, action=OVERWRITE_FILE, MOM_domain=Domain)
Expand Down

0 comments on commit ef2b86b

Please sign in to comment.