Skip to content

Commit

Permalink
+Use file_type as the handle for I/O
Browse files Browse the repository at this point in the history
  Added and used the file_type as the handle for input and output, changing from
using an integer.  This changes the type of one of the required arguments to
write_field, write_MOM_field, create_file, reopen_file, get_file_info,
get_file_times, get_file_fields, write_metadata_axis and write_metadata_field,
and added new variants of open_file, close_file and flush_file using this new
type.  Also added the new routine file_is_open.  All answers are bitwise
identical, but there are changes to multiple I/O interfaces.
  • Loading branch information
Hallberg-NOAA committed Feb 13, 2021
1 parent 76b9ffa commit 21c2696
Show file tree
Hide file tree
Showing 8 changed files with 282 additions and 206 deletions.
13 changes: 6 additions & 7 deletions src/ALE/MOM_ALE.F90
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ module MOM_ALE
use MOM_error_handler, only : callTree_enter, callTree_leave, callTree_waypoint
use MOM_file_parser, only : get_param, param_file_type, log_param
use MOM_io, only : vardesc, var_desc, fieldtype, SINGLE_FILE
use MOM_io, only : create_file, write_field, close_file
use MOM_io, only : create_file, write_field, close_file, file_type
use MOM_interface_heights,only : find_eta
use MOM_open_boundary, only : ocean_OBC_type, OBC_DIRECTION_E, OBC_DIRECTION_W
use MOM_open_boundary, only : OBC_DIRECTION_N, OBC_DIRECTION_S
Expand Down Expand Up @@ -1273,7 +1273,7 @@ subroutine ALE_writeCoordinateFile( CS, GV, directory )
character(len=240) :: filepath
type(vardesc) :: vars(2)
type(fieldtype) :: fields(2)
integer :: unit
type(file_type) :: IO_handle ! The I/O handle of the fileset
real :: ds(GV%ke), dsi(GV%ke+1)

filepath = trim(directory) // trim("Vertical_coordinate")
Expand All @@ -1287,14 +1287,13 @@ subroutine ALE_writeCoordinateFile( CS, GV, directory )
vars(2) = var_desc('ds_interface', getCoordinateUnits( CS%regridCS ), &
'Layer Center Coordinate Separation','1','i','1')

call create_file(unit, trim(filepath), vars, 2, fields, SINGLE_FILE, GV=GV)
call write_field(unit, fields(1), ds)
call write_field(unit, fields(2), dsi)
call close_file(unit)
call create_file(IO_handle, trim(filepath), vars, 2, fields, SINGLE_FILE, GV=GV)
call write_field(IO_handle, fields(1), ds)
call write_field(IO_handle, fields(2), dsi)
call close_file(IO_handle)

end subroutine ALE_writeCoordinateFile


!> Set h to coordinate values for fixed coordinate systems
subroutine ALE_initThicknessToCoord( CS, G, GV, h )
type(ALE_CS), intent(inout) :: CS !< module control structure
Expand Down
6 changes: 3 additions & 3 deletions src/diagnostics/MOM_sum_output.F90
Original file line number Diff line number Diff line change
Expand Up @@ -12,9 +12,9 @@ module MOM_sum_output
use MOM_forcing_type, only : forcing
use MOM_grid, only : ocean_grid_type
use MOM_interface_heights, only : find_eta
use MOM_io, only : create_file, fieldtype, flush_file, open_ASCII_file, reopen_file, stdout
use MOM_io, only : create_file, file_type, fieldtype, flush_file, reopen_file
use MOM_io, only : file_exists, slasher, vardesc, var_desc, write_field, get_filename_appendix
use MOM_io, only : field_size, read_variable, read_attribute
use MOM_io, only : field_size, read_variable, read_attribute, open_ASCII_file, stdout
use MOM_io, only : APPEND_FILE, SINGLE_FILE, WRITEONLY_FILE
use MOM_open_boundary, only : ocean_OBC_type, OBC_segment_type
use MOM_open_boundary, only : OBC_DIRECTION_E, OBC_DIRECTION_W, OBC_DIRECTION_N, OBC_DIRECTION_S
Expand Down Expand Up @@ -122,7 +122,7 @@ module MOM_sum_output
!! to stdout when the energy files are written.
integer :: previous_calls = 0 !< The number of times write_energy has been called.
integer :: prev_n = 0 !< The value of n from the last call.
integer :: fileenergy_nc !< NetCDF id of the energy file.
type(file_type) :: fileenergy_nc !< The file handle for the netCDF version of the energy file.
integer :: fileenergy_ascii !< The unit number of the ascii version of the energy file.
type(fieldtype), dimension(NUM_FIELDS+MAX_FIELDS_) :: &
fields !< fieldtype variables for the output fields.
Expand Down
116 changes: 58 additions & 58 deletions src/framework/MOM_io.F90

Large diffs are not rendered by default.

204 changes: 142 additions & 62 deletions src/framework/MOM_io_infra.F90

Large diffs are not rendered by default.

64 changes: 31 additions & 33 deletions src/framework/MOM_restart.F90
Original file line number Diff line number Diff line change
Expand Up @@ -8,11 +8,11 @@ module MOM_restart
use MOM_error_handler, only : MOM_error, FATAL, WARNING, NOTE, is_root_pe
use MOM_file_parser, only : get_param, log_param, log_version, param_file_type
use MOM_grid, only : ocean_grid_type
use MOM_io, only : create_file, fieldtype, file_exists, open_file, close_file
use MOM_io, only : create_file, file_type, fieldtype, file_exists, open_file, close_file
use MOM_io, only : MOM_read_data, read_data, MOM_write_field, read_field_chksum
use MOM_io, only : get_file_info, get_file_fields, get_field_atts, get_file_times
use MOM_io, only : vardesc, var_desc, query_vardesc, modify_vardesc, get_filename_appendix
use MOM_io, only : MULTIPLE, NETCDF_FILE, READONLY_FILE, SINGLE_FILE
use MOM_io, only : MULTIPLE, READONLY_FILE, SINGLE_FILE
use MOM_io, only : CENTER, CORNER, NORTH_FACE, EAST_FACE
use MOM_string_functions, only : lowercase
use MOM_time_manager, only : time_type, time_type_to_real, real_to_time
Expand Down Expand Up @@ -874,7 +874,7 @@ subroutine save_restart(directory, time, G, CS, time_stamped, filename, GV, num_
! this should be 2 Gb or less.
integer :: start_var, next_var ! The starting variables of the
! current and next files.
integer :: unit ! The I/O unit of the open file.
type(file_type) :: IO_handle ! The I/O handle of the open fileset
integer :: m, nz, num_files, var_periods
integer :: seconds, days, year, month, hour, minute
character(len=8) :: hor_grid, z_grid, t_grid ! Variable grid info.
Expand Down Expand Up @@ -1020,33 +1020,31 @@ subroutine save_restart(directory, time, G, CS, time_stamped, filename, GV, num_
enddo

if (CS%parallel_restartfiles) then
call create_file(unit, trim(restartpath), vars, (next_var-start_var), &
call create_file(IO_handle, trim(restartpath), vars, (next_var-start_var), &
fields, MULTIPLE, G=G, GV=GV, checksums=check_val)
else
call create_file(unit, trim(restartpath), vars, (next_var-start_var), &
call create_file(IO_handle, trim(restartpath), vars, (next_var-start_var), &
fields, SINGLE_FILE, G=G, GV=GV, checksums=check_val)
endif

do m=start_var,next_var-1
if (associated(CS%var_ptr3d(m)%p)) then
call MOM_write_field(unit,fields(m-start_var+1), G%Domain, &
call MOM_write_field(IO_handle, fields(m-start_var+1), G%Domain, &
CS%var_ptr3d(m)%p, restart_time, turns=-turns)
elseif (associated(CS%var_ptr2d(m)%p)) then
call MOM_write_field(unit,fields(m-start_var+1), G%Domain, &
call MOM_write_field(IO_handle, fields(m-start_var+1), G%Domain, &
CS%var_ptr2d(m)%p, restart_time, turns=-turns)
elseif (associated(CS%var_ptr4d(m)%p)) then
call MOM_write_field(unit,fields(m-start_var+1), G%Domain, &
call MOM_write_field(IO_handle, fields(m-start_var+1), G%Domain, &
CS%var_ptr4d(m)%p, restart_time, turns=-turns)
elseif (associated(CS%var_ptr1d(m)%p)) then
call MOM_write_field(unit, fields(m-start_var+1), CS%var_ptr1d(m)%p, &
restart_time)
call MOM_write_field(IO_handle, fields(m-start_var+1), CS%var_ptr1d(m)%p, restart_time)
elseif (associated(CS%var_ptr0d(m)%p)) then
call MOM_write_field(unit, fields(m-start_var+1), CS%var_ptr0d(m)%p, &
restart_time)
call MOM_write_field(IO_handle, fields(m-start_var+1), CS%var_ptr0d(m)%p, restart_time)
endif
enddo

call close_file(unit)
call close_file(IO_handle)

num_files = num_files+1

Expand Down Expand Up @@ -1086,7 +1084,7 @@ subroutine restore_state(filename, directory, day, G, CS)
integer :: sizes(7)
integer :: nvar, ntime, pos

integer :: unit(CS%max_fields) ! The I/O units of all open files.
type(file_type) :: IO_handles(CS%max_fields) ! The I/O units of all open files.
character(len=200) :: unit_path(CS%max_fields) ! The file names.
logical :: unit_is_global(CS%max_fields) ! True if the file is global.

Expand All @@ -1104,10 +1102,10 @@ subroutine restore_state(filename, directory, day, G, CS)

! Get NetCDF ids for all of the restart files.
if ((LEN_TRIM(filename) == 1) .and. (filename(1:1) == 'F')) then
num_file = open_restart_units('r', directory, G, CS, units=unit, &
num_file = open_restart_units('r', directory, G, CS, IO_handles=IO_handles, &
file_paths=unit_path, global_files=unit_is_global)
else
num_file = open_restart_units(filename, directory, G, CS, units=unit, &
num_file = open_restart_units(filename, directory, G, CS, IO_handles=IO_handles, &
file_paths=unit_path, global_files=unit_is_global)
endif

Expand All @@ -1119,7 +1117,7 @@ subroutine restore_state(filename, directory, day, G, CS)

! Get the time from the first file in the list that has one.
do n=1,num_file
call get_file_times(unit(n), time_vals, ntime)
call get_file_times(IO_handles(n), time_vals, ntime)
if (ntime < 1) cycle

t1 = time_vals(1)
Expand All @@ -1136,7 +1134,7 @@ subroutine restore_state(filename, directory, day, G, CS)
! if they differ from the first time.
if (is_root_pe()) then
do m = n+1,num_file
call get_file_times(unit(n), time_vals, ntime)
call get_file_times(IO_handles(n), time_vals, ntime)
if (ntime < 1) cycle

t2 = time_vals(1)
Expand All @@ -1153,10 +1151,10 @@ subroutine restore_state(filename, directory, day, G, CS)

! Read each variable from the first file in which it is found.
do n=1,num_file
call get_file_info(unit(n), nvar=nvar)
call get_file_info(IO_handles(n), nvar=nvar)

allocate(fields(nvar))
call get_file_fields(unit(n), fields(1:nvar))
call get_file_fields(IO_handles(n), fields(1:nvar))

do m=1, nvar
call get_field_atts(fields(m), name=varname)
Expand Down Expand Up @@ -1262,7 +1260,7 @@ subroutine restore_state(filename, directory, day, G, CS)
enddo

do n=1,num_file
call close_file(unit(n))
call close_file(IO_handles(n))
enddo

! Check whether any mandatory fields have not been found.
Expand Down Expand Up @@ -1355,16 +1353,16 @@ end function is_new_run

!> open_restart_units determines the number of existing restart files and optionally opens
!! them and returns unit ids, paths and whether the files are global or spatially decomposed.
function open_restart_units(filename, directory, G, CS, units, file_paths, &
function open_restart_units(filename, directory, G, CS, IO_handles, file_paths, &
global_files) result(num_files)
character(len=*), intent(in) :: filename !< The list of restart file names or a single
!! character 'r' to read automatically named files.
character(len=*), intent(in) :: directory !< The directory in which to find restart files
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
type(MOM_restart_CS), pointer :: CS !< The control structure returned by a previous
!! call to restart_init.
integer, dimension(:), &
optional, intent(out) :: units !< The I/O units of all opened files.
type(file_type), dimension(:), &
optional, intent(out) :: IO_handles !< The I/O handles of all opened files.
character(len=*), dimension(:), &
optional, intent(out) :: file_paths !< The full paths to open files.
logical, dimension(:), &
Expand Down Expand Up @@ -1444,22 +1442,22 @@ function open_restart_units(filename, directory, G, CS, units, file_paths, &
num_restart = num_restart + 1
inquire(file=filepath, exist=fexists)
if (fexists) then
if (present(units)) &
call open_file(units(n), trim(filepath), READONLY_FILE, NETCDF_FILE, &
if (present(IO_handles)) &
call open_file(IO_handles(n), trim(filepath), READONLY_FILE, &
threading=MULTIPLE, fileset=SINGLE_FILE)
if (present(global_files)) global_files(n) = .true.
elseif (CS%parallel_restartfiles) then
! Look for decomposed files using the I/O Layout.
fexists = file_exists(filepath, G%Domain)
if (fexists .and. (present(units))) &
call open_file(units(n), trim(filepath), READONLY_FILE, NETCDF_FILE, MOM_domain=G%Domain)
if (fexists .and. (present(IO_handles))) &
call open_file(IO_handles(n), trim(filepath), READONLY_FILE, MOM_domain=G%Domain)
if (fexists .and. present(global_files)) global_files(n) = .false.
endif

if (fexists) then
if (present(file_paths)) file_paths(n) = filepath
n = n + 1
if (is_root_pe() .and. (present(units))) &
if (is_root_pe() .and. (present(IO_handles))) &
call MOM_error(NOTE, "MOM_restart: MOM run restarted using : "//trim(filepath))
else
err = 1 ; exit
Expand All @@ -1472,16 +1470,16 @@ function open_restart_units(filename, directory, G, CS, units, file_paths, &

inquire(file=filepath, exist=fexists)
if (fexists) then
if (present(units)) &
call open_file(units(n), trim(filepath), READONLY_FILE, NETCDF_FILE, &
if (present(IO_handles)) &
call open_file(IO_handles(n), trim(filepath), READONLY_FILE, &
threading=MULTIPLE, fileset=SINGLE_FILE)
if (present(global_files)) global_files(n) = .true.
if (present(file_paths)) file_paths(n) = filepath
n = n + 1
if (is_root_pe() .and. (present(units))) &
if (is_root_pe() .and. (present(IO_handles))) &
call MOM_error(NOTE,"MOM_restart: MOM run restarted using : "//trim(filepath))
else
if (present(units)) &
if (present(IO_handles)) &
call MOM_error(WARNING,"MOM_restart: Unable to find restart file : "//trim(filepath))
endif

Expand Down
15 changes: 8 additions & 7 deletions src/initialization/MOM_coord_initialization.F90
Original file line number Diff line number Diff line change
Expand Up @@ -8,8 +8,9 @@ module MOM_coord_initialization
use MOM_error_handler, only : MOM_mesg, MOM_error, FATAL, WARNING, is_root_pe
use MOM_error_handler, only : callTree_enter, callTree_leave, callTree_waypoint
use MOM_file_parser, only : get_param, read_param, log_param, param_file_type, log_version
use MOM_io, only : MOM_read_data, close_file, create_file, fieldtype, file_exists
use MOM_io, only : MOM_write_field, vardesc, var_desc, SINGLE_FILE, MULTIPLE
use MOM_io, only : close_file, create_file, file_type, fieldtype, file_exists
use MOM_io, only : MOM_read_data, MOM_write_field, vardesc, var_desc
use MOM_io, only : SINGLE_FILE, MULTIPLE
use MOM_string_functions, only : slasher, uppercase
use MOM_unit_scaling, only : unit_scale_type
use MOM_variables, only : thermo_var_ptrs
Expand Down Expand Up @@ -517,19 +518,19 @@ subroutine write_vertgrid_file(GV, US, param_file, directory)
character(len=240) :: filepath
type(vardesc) :: vars(2)
type(fieldtype) :: fields(2)
integer :: unit
type(file_type) :: IO_handle ! The I/O handle of the fileset

filepath = trim(directory) // trim("Vertical_coordinate")

vars(1) = var_desc("R","kilogram meter-3","Target Potential Density",'1','L','1')
vars(2) = var_desc("g","meter second-2","Reduced gravity",'1','L','1')

call create_file(unit, trim(filepath), vars, 2, fields, SINGLE_FILE, GV=GV)
call create_file(IO_handle, trim(filepath), vars, 2, fields, SINGLE_FILE, GV=GV)

call MOM_write_field(unit, fields(1), GV%Rlay, scale=US%R_to_kg_m3)
call MOM_write_field(unit, fields(2), GV%g_prime, scale=US%L_T_to_m_s**2*US%m_to_Z)
call MOM_write_field(IO_handle, fields(1), GV%Rlay, scale=US%R_to_kg_m3)
call MOM_write_field(IO_handle, fields(2), GV%g_prime, scale=US%L_T_to_m_s**2*US%m_to_Z)

call close_file(unit)
call close_file(IO_handle)

end subroutine write_vertgrid_file

Expand Down
Loading

0 comments on commit 21c2696

Please sign in to comment.