Skip to content

Commit

Permalink
Merge 5c54e98 into 237194d
Browse files Browse the repository at this point in the history
  • Loading branch information
marshallward authored Jan 18, 2023
2 parents 237194d + 5c54e98 commit 7fba2ea
Show file tree
Hide file tree
Showing 11 changed files with 2,829 additions and 174 deletions.
4 changes: 2 additions & 2 deletions config_src/infra/FMS2/MOM_io_infra.F90
Original file line number Diff line number Diff line change
Expand Up @@ -509,8 +509,8 @@ subroutine open_ASCII_file(unit, file, action, threading, fileset)
! This checks if open() failed but did not raise a runtime error.
inquire(unit, opened=is_open)
if (.not. is_open) &
call MOM_error(FATAL, 'open_ASCII_file: File ' // trim(filename) // &
' failed to open.')
call MOM_error(FATAL, &
'open_ASCII_file: File "' // trim(filename) // '" failed to open.')

! NOTE: There are two possible mpp_write_meta functions in FMS1:
! - call mpp_write_meta( unit, 'filename', cval=mpp_file(unit)%name)
Expand Down
13 changes: 7 additions & 6 deletions src/ALE/MOM_hybgen_regrid.F90
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,8 @@ module MOM_hybgen_regrid
use MOM_EOS, only : EOS_type, calculate_density
use MOM_error_handler, only : MOM_mesg, MOM_error, FATAL, WARNING, assert
use MOM_file_parser, only : get_param, param_file_type, log_param
use MOM_io, only : close_file, create_file, file_type, fieldtype, file_exists
use MOM_io, only : create_MOM_file, file_exists
use MOM_io, only : MOM_infra_file, MOM_field
use MOM_io, only : MOM_read_data, MOM_write_field, vardesc, var_desc, SINGLE_FILE
use MOM_string_functions, only : slasher
use MOM_unit_scaling, only : unit_scale_type
Expand Down Expand Up @@ -210,20 +211,20 @@ subroutine write_Hybgen_coord_file(GV, CS, filepath)
character(len=*), intent(in) :: filepath !< The full path to the file to write
! Local variables
type(vardesc) :: vars(3)
type(fieldtype) :: fields(3)
type(file_type) :: IO_handle ! The I/O handle of the fileset
type(MOM_field) :: fields(3)
type(MOM_infra_file) :: IO_handle ! The I/O handle of the fileset

vars(1) = var_desc("dp0", "meter", "Deep z-level minimum thicknesses for Hybgen", '1', 'L', '1')
vars(2) = var_desc("ds0", "meter", "Shallow z-level minimum thicknesses for Hybgen", '1', 'L', '1')
vars(3) = var_desc("Rho_tgt", "kg m-3", "Target coordinate potential densities for Hybgen", '1', 'L', '1')
call create_file(IO_handle, trim(filepath), vars, 3, fields, SINGLE_FILE, GV=GV)
call create_MOM_file(IO_handle, trim(filepath), vars, 3, fields, &
SINGLE_FILE, GV=GV)

call MOM_write_field(IO_handle, fields(1), CS%dp0k, scale=CS%coord_scale)
call MOM_write_field(IO_handle, fields(2), CS%ds0k, scale=CS%coord_scale)
call MOM_write_field(IO_handle, fields(3), CS%target_density, scale=CS%Rho_coord_scale)

call close_file(IO_handle)

call IO_handle%close()
end subroutine write_Hybgen_coord_file

!> This subroutine deallocates memory in the control structure for the hybgen module
Expand Down
14 changes: 8 additions & 6 deletions src/ALE/MOM_regridding.F90
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,9 @@ module MOM_regridding
use MOM_error_handler, only : MOM_error, FATAL, WARNING, assert
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, fieldtype, SINGLE_FILE
use MOM_io, only : create_file, MOM_write_field, close_file, file_type
use MOM_io, only : vardesc, var_desc, SINGLE_FILE
use MOM_io, only : MOM_infra_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
use MOM_variables, only : ocean_grid_type, thermo_var_ptrs
Expand Down Expand Up @@ -2212,8 +2213,8 @@ subroutine write_regrid_file( CS, GV, filepath )
character(len=*), intent(in) :: filepath !< The full path to the file to write

type(vardesc) :: vars(2)
type(fieldtype) :: fields(2)
type(file_type) :: IO_handle ! The I/O handle of the fileset
type(MOM_field) :: fields(2)
type(MOM_infra_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 All @@ -2231,10 +2232,11 @@ subroutine write_regrid_file( CS, GV, filepath )
vars(2) = var_desc('ds_interface', getCoordinateUnits( CS ), &
'Layer Center Coordinate Separation', '1', 'i', '1')

call create_file(IO_handle, trim(filepath), vars, 2, fields, SINGLE_FILE, GV=GV)
call create_MOM_file(IO_handle, trim(filepath), vars, 2, fields, &
SINGLE_FILE, GV=GV)
call MOM_write_field(IO_handle, fields(1), ds)
call MOM_write_field(IO_handle, fields(2), dsi)
call close_file(IO_handle)
call IO_handle%close()

end subroutine write_regrid_file

Expand Down
72 changes: 35 additions & 37 deletions src/diagnostics/MOM_sum_output.F90
Original file line number Diff line number Diff line change
Expand Up @@ -13,8 +13,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, file_type, fieldtype, flush_file, reopen_file, close_file
use MOM_io, only : file_exists, slasher, vardesc, var_desc, write_field, MOM_write_field
use MOM_io, only : create_MOM_file, reopen_MOM_file
use MOM_io, only : MOM_infra_file, MOM_netcdf_file, MOM_field
use MOM_io, only : file_exists, slasher, vardesc, var_desc, MOM_write_field
use MOM_io, only : field_size, read_variable, read_attribute, open_ASCII_file, stdout
use MOM_io, only : axis_info, set_axis_info, delete_axis_info, get_filename_appendix
use MOM_io, only : attribute_info, set_attribute_info, delete_attribute_info
Expand Down Expand Up @@ -125,9 +126,9 @@ 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.
type(file_type) :: fileenergy_nc !< The file handle for the netCDF version of the energy file.
type(MOM_netcdf_file) :: 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_) :: &
type(MOM_field), dimension(NUM_FIELDS+MAX_FIELDS_) :: &
fields !< fieldtype variables for the output fields.
character(len=200) :: energyfile !< The name of the energy file with path.
end type sum_output_CS
Expand Down Expand Up @@ -603,13 +604,11 @@ subroutine write_energy(u, v, h, tv, day, n, G, GV, US, CS, tracer_CSp, dt_forci

energypath_nc = trim(CS%energyfile) // ".nc"
if (day > CS%Start_time) then
call reopen_file(CS%fileenergy_nc, trim(energypath_nc), vars, &
num_nc_fields, CS%fields, SINGLE_FILE, CS%timeunit, &
G=G, GV=GV)
call reopen_MOM_file(CS%fileenergy_nc, trim(energypath_nc), vars, &
num_nc_fields, CS%fields, SINGLE_FILE, CS%timeunit, G=G, GV=GV)
else
call create_file(CS%fileenergy_nc, trim(energypath_nc), vars, &
num_nc_fields, CS%fields, SINGLE_FILE, CS%timeunit, &
G=G, GV=GV)
call create_MOM_file(CS%fileenergy_nc, trim(energypath_nc), vars, &
num_nc_fields, CS%fields, SINGLE_FILE, CS%timeunit, G=G, GV=GV)
endif
endif

Expand Down Expand Up @@ -863,35 +862,35 @@ subroutine write_energy(u, v, h, tv, day, n, G, GV, US, CS, tracer_CSp, dt_forci
endif
endif

call write_field(CS%fileenergy_nc, CS%fields(1), real(CS%ntrunc), reday)
call write_field(CS%fileenergy_nc, CS%fields(2), toten, reday)
call write_field(CS%fileenergy_nc, CS%fields(3), PE, reday)
call write_field(CS%fileenergy_nc, CS%fields(4), KE, reday)
call write_field(CS%fileenergy_nc, CS%fields(5), H_0APE, reday)
call write_field(CS%fileenergy_nc, CS%fields(6), mass_lay, reday)

call write_field(CS%fileenergy_nc, CS%fields(7), mass_tot, reday)
call write_field(CS%fileenergy_nc, CS%fields(8), mass_chg, reday)
call write_field(CS%fileenergy_nc, CS%fields(9), mass_anom, reday)
call write_field(CS%fileenergy_nc, CS%fields(10), max_CFL(1), reday)
call write_field(CS%fileenergy_nc, CS%fields(11), max_CFL(2), reday)
call CS%fileenergy_nc%write_field(CS%fields(1), real(CS%ntrunc), reday)
call CS%fileenergy_nc%write_field(CS%fields(2), toten, reday)
call CS%fileenergy_nc%write_field(CS%fields(3), PE, reday)
call CS%fileenergy_nc%write_field(CS%fields(4), KE, reday)
call CS%fileenergy_nc%write_field(CS%fields(5), H_0APE, reday)
call CS%fileenergy_nc%write_field(CS%fields(6), mass_lay, reday)

call CS%fileenergy_nc%write_field(CS%fields(7), mass_tot, reday)
call CS%fileenergy_nc%write_field(CS%fields(8), mass_chg, reday)
call CS%fileenergy_nc%write_field(CS%fields(9), mass_anom, reday)
call CS%fileenergy_nc%write_field(CS%fields(10), max_CFL(1), reday)
call CS%fileenergy_nc%write_field(CS%fields(11), max_CFL(2), reday)
if (CS%use_temperature) then
call write_field(CS%fileenergy_nc, CS%fields(12), 0.001*Salt, reday)
call write_field(CS%fileenergy_nc, CS%fields(13), 0.001*salt_chg, reday)
call write_field(CS%fileenergy_nc, CS%fields(14), 0.001*salt_anom, reday)
call write_field(CS%fileenergy_nc, CS%fields(15), Heat, reday)
call write_field(CS%fileenergy_nc, CS%fields(16), heat_chg, reday)
call write_field(CS%fileenergy_nc, CS%fields(17), heat_anom, reday)
call CS%fileenergy_nc%write_field(CS%fields(12), 0.001*Salt, reday)
call CS%fileenergy_nc%write_field(CS%fields(13), 0.001*salt_chg, reday)
call CS%fileenergy_nc%write_field(CS%fields(14), 0.001*salt_anom, reday)
call CS%fileenergy_nc%write_field(CS%fields(15), Heat, reday)
call CS%fileenergy_nc%write_field(CS%fields(16), heat_chg, reday)
call CS%fileenergy_nc%write_field(CS%fields(17), heat_anom, reday)
do m=1,nTr_stocks
call write_field(CS%fileenergy_nc, CS%fields(17+m), Tr_stocks(m), reday)
call CS%fileenergy_nc%write_field(CS%fields(17+m), Tr_stocks(m), reday)
enddo
else
do m=1,nTr_stocks
call write_field(CS%fileenergy_nc, CS%fields(11+m), Tr_stocks(m), reday)
call CS%fileenergy_nc%write_field(CS%fields(11+m), Tr_stocks(m), reday)
enddo
endif

call flush_file(CS%fileenergy_nc)
call CS%fileenergy_nc%flush()

if (is_NaN(En_mass)) then
call MOM_error(FATAL, "write_energy : NaNs in total model energy forced model termination.")
Expand Down Expand Up @@ -1233,13 +1232,13 @@ subroutine write_depth_list(G, US, DL, filename)
! Local variables
type(vardesc), dimension(:), allocatable :: &
vars ! Types that described the staggering and metadata for the fields
type(fieldtype), dimension(:), allocatable :: &
type(MOM_field), dimension(:), allocatable :: &
fields ! Types with metadata about the variables that will be written
type(axis_info), dimension(:), allocatable :: &
extra_axes ! Descriptors for extra axes that might be used
type(attribute_info), dimension(:), allocatable :: &
global_atts ! Global attributes and their values
type(file_type) :: IO_handle ! The I/O handle of the fileset
type(MOM_netcdf_file) :: IO_handle ! The I/O handle of the fileset
character(len=16) :: depth_chksum, area_chksum

! All ranks are required to compute the global checksum
Expand All @@ -1259,17 +1258,16 @@ subroutine write_depth_list(G, US, DL, filename)
call set_attribute_info(global_atts(1), depth_chksum_attr, depth_chksum)
call set_attribute_info(global_atts(2), area_chksum_attr, area_chksum)

call create_file(IO_handle, filename, vars, 3, fields, SINGLE_FILE, extra_axes=extra_axes, &
global_atts=global_atts)
call create_MOM_file(IO_handle, filename, vars, 3, fields, SINGLE_FILE, &
extra_axes=extra_axes, global_atts=global_atts)
call MOM_write_field(IO_handle, fields(1), DL%depth, scale=US%Z_to_m)
call MOM_write_field(IO_handle, fields(2), DL%area, scale=US%L_to_m**2)
call MOM_write_field(IO_handle, fields(3), DL%vol_below, scale=US%Z_to_m*US%L_to_m**2)

call delete_axis_info(extra_axes)
call delete_attribute_info(global_atts)
deallocate(vars, extra_axes, fields, global_atts)
call close_file(IO_handle)

call IO_handle%close()
end subroutine write_depth_list

!> This subroutine reads in the depth list from the specified file
Expand Down
Loading

0 comments on commit 7fba2ea

Please sign in to comment.