Skip to content

Commit

Permalink
Merge branch 'dev/gfdl' into nonBous_interface_filter
Browse files Browse the repository at this point in the history
  • Loading branch information
marshallward authored Aug 15, 2023
2 parents 9697c15 + c803904 commit 6ef0f80
Show file tree
Hide file tree
Showing 70 changed files with 3,526 additions and 2,034 deletions.
13 changes: 12 additions & 1 deletion config_src/drivers/FMS_cap/MOM_surface_forcing_gfdl.F90
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ module MOM_surface_forcing_gfdl
!! from MOM_domains) to indicate the staggering of
!! the winds that are being provided in calls to
!! update_ocean_model.
logical :: use_temperature !< If true, temp and saln used as state variables
logical :: use_temperature !< If true, temp and saln used as state variables.
real :: wind_stress_multiplier !< A multiplier applied to incoming wind stress [nondim].

real :: Rho0 !< Boussinesq reference density [R ~> kg m-3]
Expand Down Expand Up @@ -175,6 +175,7 @@ module MOM_surface_forcing_gfdl
real, pointer, dimension(:,:) :: t_flux =>NULL() !< sensible heat flux [W m-2]
real, pointer, dimension(:,:) :: q_flux =>NULL() !< specific humidity flux [kg m-2 s-1]
real, pointer, dimension(:,:) :: salt_flux =>NULL() !< salt flux [kg m-2 s-1]
real, pointer, dimension(:,:) :: excess_salt =>NULL() !< salt left behind by brine rejection [kg m-2 s-1]
real, pointer, dimension(:,:) :: lw_flux =>NULL() !< long wave radiation [W m-2]
real, pointer, dimension(:,:) :: sw_flux_vis_dir =>NULL() !< direct visible sw radiation [W m-2]
real, pointer, dimension(:,:) :: sw_flux_vis_dif =>NULL() !< diffuse visible sw radiation [W m-2]
Expand Down Expand Up @@ -304,6 +305,8 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G,
call safe_alloc_ptr(fluxes%heat_added,isd,ied,jsd,jed)
call safe_alloc_ptr(fluxes%salt_flux_added,isd,ied,jsd,jed)

if (associated(IOB%excess_salt)) call safe_alloc_ptr(fluxes%salt_left_behind,isd,ied,jsd,jed)

do j=js-2,je+2 ; do i=is-2,ie+2
fluxes%TKE_tidal(i,j) = CS%TKE_tidal(i,j)
fluxes%ustar_tidal(i,j) = CS%ustar_tidal(i,j)
Expand Down Expand Up @@ -576,6 +579,11 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G,
call check_mask_val_consistency(IOB%salt_flux(i-i0,j-j0), G%mask2dT(i,j), i, j, 'salt_flux', G)
enddo ; enddo
endif
if (associated(IOB%excess_salt)) then
do j=js,je ; do i=is,ie
fluxes%salt_left_behind(i,j) = G%mask2dT(i,j)*(kg_m2_s_conversion*IOB%excess_salt(i-i0,j-j0))
enddo ; enddo
endif

!#CTRL# if (associated(CS%ctrl_forcing_CSp)) then
!#CTRL# do j=js,je ; do i=is,ie
Expand Down Expand Up @@ -1729,6 +1737,9 @@ subroutine ice_ocn_bnd_type_chksum(id, timestep, iobt)
if (associated(iobt%mass_berg)) then
chks = field_chksum( iobt%mass_berg ) ; if (root) write(outunit,100) 'iobt%mass_berg ', chks
endif
if (associated(iobt%excess_salt)) then
chks = field_chksum( iobt%excess_salt ) ; if (root) write(outunit,100) 'iobt%excess_salt ', chks
endif
100 FORMAT(" CHECKSUM::",A20," = ",Z20)

call coupler_type_write_chksums(iobt%fluxes, outunit, 'iobt%')
Expand Down
26 changes: 9 additions & 17 deletions config_src/drivers/FMS_cap/ocean_model_MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,8 @@ module ocean_model_mod
use MOM, only : initialize_MOM, step_MOM, MOM_control_struct, MOM_end
use MOM, only : extract_surface_state, allocate_surface_state, finish_MOM_initialization
use MOM, only : get_MOM_state_elements, MOM_state_is_synchronized
use MOM, only : get_ocean_stocks, step_offline, save_MOM6_internal_state
use MOM, only : get_ocean_stocks, step_offline
use MOM, only : save_MOM_restart
use MOM_coms, only : field_chksum
use MOM_constants, only : CELSIUS_KELVIN_OFFSET, hlf
use MOM_coupler_types, only : coupler_1d_bc_type, coupler_2d_bc_type
Expand All @@ -37,7 +38,6 @@ module ocean_model_mod
use MOM_grid, only : ocean_grid_type
use MOM_io, only : write_version_number, stdout_if_root
use MOM_marine_ice, only : iceberg_forces, iceberg_fluxes, marine_ice_init, marine_ice_CS
use MOM_restart, only : MOM_restart_CS, save_restart
use MOM_string_functions, only : uppercase
use MOM_surface_forcing_gfdl, only : surface_forcing_init, convert_IOB_to_fluxes
use MOM_surface_forcing_gfdl, only : convert_IOB_to_forces, ice_ocn_bnd_type_chksum
Expand Down Expand Up @@ -209,9 +209,6 @@ module ocean_model_mod
Waves => NULL() !< A pointer to the surface wave control structure
type(surface_forcing_CS), pointer :: &
forcing_CSp => NULL() !< A pointer to the MOM forcing control structure
type(MOM_restart_CS), pointer :: &
restart_CSp => NULL() !< A pointer set to the restart control structure
!! that will be used for MOM restart files.
type(diag_ctrl), pointer :: &
diag => NULL() !< A pointer to the diagnostic regulatory structure
end type ocean_state_type
Expand Down Expand Up @@ -279,7 +276,7 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, wind_stagger, gas
! initialization of ice shelf parameters and arrays.

call initialize_MOM(OS%Time, Time_init, param_file, OS%dirs, OS%MOM_CSp, &
OS%restart_CSp, Time_in, offline_tracer_mode=OS%offline_tracer_mode, &
Time_in, offline_tracer_mode=OS%offline_tracer_mode, &
diag_ptr=OS%diag, count_calls=.true., ice_shelf_CSp=OS%ice_shelf_CSp, &
waves_CSp=OS%Waves)
call get_MOM_state_elements(OS%MOM_CSp, G=OS%grid, GV=OS%GV, US=OS%US, C_p=OS%C_p, &
Expand Down Expand Up @@ -572,7 +569,7 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, time_start_upda
endif

if ((OS%nstep==0) .and. (OS%nstep_thermo==0)) then ! This is the first call to update_ocean_model.
call finish_MOM_initialization(OS%Time, OS%dirs, OS%MOM_CSp, OS%restart_CSp)
call finish_MOM_initialization(OS%Time, OS%dirs, OS%MOM_CSp)
endif

Time_thermo_start = OS%Time
Expand Down Expand Up @@ -693,24 +690,22 @@ subroutine ocean_model_restart(OS, timestamp)
"restart files can only be created after the buoyancy forcing is applied.")

if (BTEST(OS%Restart_control,1)) then
call save_restart(OS%dirs%restart_output_dir, OS%Time, OS%grid, &
OS%restart_CSp, .true., GV=OS%GV)
call save_MOM_restart(OS%MOM_CSp, OS%dirs%restart_output_dir, OS%Time, &
OS%grid, time_stamped=.true., GV=OS%GV)
call forcing_save_restart(OS%forcing_CSp, OS%grid, OS%Time, &
OS%dirs%restart_output_dir, .true.)
if (OS%use_ice_shelf) then
call ice_shelf_save_restart(OS%Ice_shelf_CSp, OS%Time, OS%dirs%restart_output_dir, .true.)
endif
call save_MOM6_internal_state(OS%MOM_CSp, OS%dirs%restart_output_dir, OS%Time, .true.)
endif
if (BTEST(OS%Restart_control,0)) then
call save_restart(OS%dirs%restart_output_dir, OS%Time, OS%grid, &
OS%restart_CSp, GV=OS%GV)
call save_MOM_restart(OS%MOM_CSp, OS%dirs%restart_output_dir, OS%Time, &
OS%grid, GV=OS%GV)
call forcing_save_restart(OS%forcing_CSp, OS%grid, OS%Time, &
OS%dirs%restart_output_dir)
if (OS%use_ice_shelf) then
call ice_shelf_save_restart(OS%Ice_shelf_CSp, OS%Time, OS%dirs%restart_output_dir)
endif
call save_MOM6_internal_state(OS%MOM_CSp, OS%dirs%restart_output_dir, OS%Time)
endif

end subroutine ocean_model_restart
Expand Down Expand Up @@ -758,16 +753,13 @@ subroutine ocean_model_save_restart(OS, Time, directory, filename_suffix)
if (present(directory)) then ; restart_dir = directory
else ; restart_dir = OS%dirs%restart_output_dir ; endif

call save_restart(restart_dir, Time, OS%grid, OS%restart_CSp, GV=OS%GV)
call save_MOM_restart(OS%MOM_CSp, restart_dir, Time, OS%grid, GV=OS%GV)

call forcing_save_restart(OS%forcing_CSp, OS%grid, Time, restart_dir)

if (OS%use_ice_shelf) then
call ice_shelf_save_restart(OS%Ice_shelf_CSp, OS%Time, OS%dirs%restart_output_dir)
endif

call save_MOM6_internal_state(OS%MOM_CSp, OS%dirs%restart_output_dir, OS%Time)

end subroutine ocean_model_save_restart

!> Initialize the public ocean type
Expand Down
28 changes: 11 additions & 17 deletions config_src/drivers/mct_cap/mom_ocean_model_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,8 @@ module MOM_ocean_model_mct
use MOM, only : initialize_MOM, step_MOM, MOM_control_struct, MOM_end
use MOM, only : extract_surface_state, allocate_surface_state, finish_MOM_initialization
use MOM, only : get_MOM_state_elements, MOM_state_is_synchronized
use MOM, only : get_ocean_stocks, step_offline, save_MOM6_internal_state
use MOM, only : get_ocean_stocks, step_offline
use MOM, only : save_MOM_restart
use MOM_coms, only : field_chksum
use MOM_constants, only : CELSIUS_KELVIN_OFFSET, hlf
use MOM_diag_mediator, only : diag_ctrl, enable_averages, disable_averaging
Expand All @@ -34,7 +35,6 @@ module MOM_ocean_model_mct
use MOM_grid, only : ocean_grid_type
use MOM_io, only : close_file, file_exists, read_data, write_version_number
use MOM_marine_ice, only : iceberg_forces, iceberg_fluxes, marine_ice_init, marine_ice_CS
use MOM_restart, only : MOM_restart_CS, save_restart
use MOM_string_functions, only : uppercase
use MOM_surface_forcing_mct, only : surface_forcing_init, convert_IOB_to_fluxes
use MOM_surface_forcing_mct, only : convert_IOB_to_forces, ice_ocn_bnd_type_chksum
Expand Down Expand Up @@ -207,9 +207,6 @@ module MOM_ocean_model_mct
Waves => NULL() !< A pointer to the surface wave control structure
type(surface_forcing_CS), pointer :: &
forcing_CSp => NULL() !< A pointer to the MOM forcing control structure
type(MOM_restart_CS), pointer :: &
restart_CSp => NULL() !< A pointer set to the restart control structure
!! that will be used for MOM restart files.
type(diag_ctrl), pointer :: &
diag => NULL() !< A pointer to the diagnostic regulatory structure
end type ocean_state_type
Expand Down Expand Up @@ -271,7 +268,7 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, gas_fields_ocn, i

OS%Time = Time_in
call initialize_MOM(OS%Time, Time_init, param_file, OS%dirs, OS%MOM_CSp, &
OS%restart_CSp, Time_in, offline_tracer_mode=OS%offline_tracer_mode, &
Time_in, offline_tracer_mode=OS%offline_tracer_mode, &
input_restart_file=input_restart_file, &
diag_ptr=OS%diag, count_calls=.true., waves_CSp=OS%Waves)
call get_MOM_state_elements(OS%MOM_CSp, G=OS%grid, GV=OS%GV, US=OS%US, C_p=OS%C_p, &
Expand Down Expand Up @@ -575,7 +572,7 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, &
endif

if (OS%nstep==0) then
call finish_MOM_initialization(OS%Time, OS%dirs, OS%MOM_CSp, OS%restart_CSp)
call finish_MOM_initialization(OS%Time, OS%dirs, OS%MOM_CSp)
endif

call disable_averaging(OS%diag)
Expand Down Expand Up @@ -689,35 +686,32 @@ subroutine ocean_model_restart(OS, timestamp, restartname)
"restart files can only be created after the buoyancy forcing is applied.")

if (present(restartname)) then
call save_restart(OS%dirs%restart_output_dir, OS%Time, OS%grid, &
OS%restart_CSp, GV=OS%GV, filename=restartname)
call save_MOM_restart(OS%MOM_CSp, OS%dirs%restart_output_dir, OS%Time, &
OS%grid, GV=OS%GV, filename=restartname)
call forcing_save_restart(OS%forcing_CSp, OS%grid, OS%Time, &
OS%dirs%restart_output_dir) ! Is this needed?
if (OS%use_ice_shelf) then
call ice_shelf_save_restart(OS%Ice_shelf_CSp, OS%Time, &
OS%dirs%restart_output_dir)
endif
call save_MOM6_internal_state(OS%MOM_CSp, OS%dirs%restart_output_dir, OS%Time)
else
if (BTEST(OS%Restart_control,1)) then
call save_restart(OS%dirs%restart_output_dir, OS%Time, OS%grid, &
OS%restart_CSp, .true., GV=OS%GV)
call save_MOM_restart(OS%MOM_CSp, OS%dirs%restart_output_dir, OS%Time, &
OS%grid, time_stamped=.true., GV=OS%GV)
call forcing_save_restart(OS%forcing_CSp, OS%grid, OS%Time, &
OS%dirs%restart_output_dir, .true.)
if (OS%use_ice_shelf) then
call ice_shelf_save_restart(OS%Ice_shelf_CSp, OS%Time, OS%dirs%restart_output_dir, .true.)
endif
call save_MOM6_internal_state(OS%MOM_CSp, OS%dirs%restart_output_dir, OS%Time, .true.)
endif
if (BTEST(OS%Restart_control,0)) then
call save_restart(OS%dirs%restart_output_dir, OS%Time, OS%grid, &
OS%restart_CSp, GV=OS%GV)
call save_MOM_restart(OS%MOM_CSp, OS%dirs%restart_output_dir, OS%Time, &
OS%grid, GV=OS%GV)
call forcing_save_restart(OS%forcing_CSp, OS%grid, OS%Time, &
OS%dirs%restart_output_dir)
if (OS%use_ice_shelf) then
call ice_shelf_save_restart(OS%Ice_shelf_CSp, OS%Time, OS%dirs%restart_output_dir)
endif
call save_MOM6_internal_state(OS%MOM_CSp, OS%dirs%restart_output_dir, OS%Time)
endif
endif

Expand Down Expand Up @@ -768,7 +762,7 @@ subroutine ocean_model_save_restart(OS, Time, directory, filename_suffix)
if (present(directory)) then ; restart_dir = directory
else ; restart_dir = OS%dirs%restart_output_dir ; endif

call save_restart(restart_dir, Time, OS%grid, OS%restart_CSp, GV=OS%GV)
call save_MOM_restart(OS%MOM_CSp, restart_dir, Time, OS%grid, GV=OS%GV)

call forcing_save_restart(OS%forcing_CSp, OS%grid, Time, restart_dir)

Expand Down
36 changes: 13 additions & 23 deletions config_src/drivers/nuopc_cap/mom_ocean_model_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,8 @@ module MOM_ocean_model_nuopc
use MOM, only : initialize_MOM, step_MOM, MOM_control_struct, MOM_end
use MOM, only : extract_surface_state, allocate_surface_state, finish_MOM_initialization
use MOM, only : get_MOM_state_elements, MOM_state_is_synchronized
use MOM, only : get_ocean_stocks, step_offline, save_MOM6_internal_state
use MOM, only : get_ocean_stocks, step_offline
use MOM, only : save_MOM_restart
use MOM_coms, only : field_chksum
use MOM_constants, only : CELSIUS_KELVIN_OFFSET, hlf
use MOM_diag_mediator, only : diag_ctrl, enable_averages, disable_averaging
Expand All @@ -34,7 +35,6 @@ module MOM_ocean_model_nuopc
use MOM_grid, only : ocean_grid_type
use MOM_io, only : close_file, file_exists, read_data, write_version_number
use MOM_marine_ice, only : iceberg_forces, iceberg_fluxes, marine_ice_init, marine_ice_CS
use MOM_restart, only : MOM_restart_CS, save_restart
use MOM_string_functions, only : uppercase
use MOM_time_manager, only : time_type, get_time, set_time, operator(>)
use MOM_time_manager, only : operator(+), operator(-), operator(*), operator(/)
Expand Down Expand Up @@ -214,9 +214,6 @@ module MOM_ocean_model_nuopc
Waves => NULL() !< A pointer to the surface wave control structure
type(surface_forcing_CS), pointer :: &
forcing_CSp => NULL() !< A pointer to the MOM forcing control structure
type(MOM_restart_CS), pointer :: &
restart_CSp => NULL() !< A pointer set to the restart control structure
!! that will be used for MOM restart files.
type(diag_ctrl), pointer :: &
diag => NULL() !< A pointer to the diagnostic regulatory structure
end type ocean_state_type
Expand Down Expand Up @@ -281,7 +278,7 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, gas_fields_ocn, i

OS%Time = Time_in
call initialize_MOM(OS%Time, Time_init, param_file, OS%dirs, OS%MOM_CSp, &
OS%restart_CSp, Time_in, offline_tracer_mode=OS%offline_tracer_mode, &
Time_in, offline_tracer_mode=OS%offline_tracer_mode, &
input_restart_file=input_restart_file, &
diag_ptr=OS%diag, count_calls=.true., waves_CSp=OS%Waves)
call get_MOM_state_elements(OS%MOM_CSp, G=OS%grid, GV=OS%GV, US=OS%US, C_p=OS%C_p, &
Expand Down Expand Up @@ -407,7 +404,7 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, gas_fields_ocn, i

! MOM_wave_interface_init is called regardless of the value of USE_WAVES because
! it also initializes statistical waves.
call MOM_wave_interface_init(OS%Time, OS%grid, OS%GV, OS%US, param_file, OS%Waves, OS%diag, OS%restart_CSp)
call MOM_wave_interface_init(OS%Time, OS%grid, OS%GV, OS%US, param_file, OS%Waves, OS%diag)

if (associated(OS%grid%Domain%maskmap)) then
call initialize_ocean_public_type(OS%grid%Domain%mpp_domain, Ocean_sfc, &
Expand Down Expand Up @@ -608,7 +605,7 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, &
endif

if (OS%nstep==0) then
call finish_MOM_initialization(OS%Time, OS%dirs, OS%MOM_CSp, OS%restart_CSp)
call finish_MOM_initialization(OS%Time, OS%dirs, OS%MOM_CSp)
endif

call disable_averaging(OS%diag)
Expand Down Expand Up @@ -730,36 +727,32 @@ subroutine ocean_model_restart(OS, timestamp, restartname, stoch_restartname, nu
"restart files can only be created after the buoyancy forcing is applied.")

if (present(restartname)) then
call save_restart(OS%dirs%restart_output_dir, OS%Time, OS%grid, &
OS%restart_CSp, GV=OS%GV, filename=restartname, num_rest_files=num_rest_files)
call save_MOM_restart(OS%MOM_CSp, OS%dirs%restart_output_dir, OS%Time, &
OS%grid, GV=OS%GV, filename=restartname, num_rest_files=num_rest_files)
call forcing_save_restart(OS%forcing_CSp, OS%grid, OS%Time, &
OS%dirs%restart_output_dir) ! Is this needed?
if (OS%use_ice_shelf) then
call ice_shelf_save_restart(OS%Ice_shelf_CSp, OS%Time, &
OS%dirs%restart_output_dir)
endif

call save_MOM6_internal_state(OS%MOM_CSp, OS%dirs%restart_output_dir, OS%Time)
else
if (BTEST(OS%Restart_control,1)) then
call save_restart(OS%dirs%restart_output_dir, OS%Time, OS%grid, &
OS%restart_CSp, .true., GV=OS%GV)
call save_MOM_restart(OS%MOM_CSp, OS%dirs%restart_output_dir, OS%Time, &
OS%grid, time_stamped=.true., GV=OS%GV)
call forcing_save_restart(OS%forcing_CSp, OS%grid, OS%Time, &
OS%dirs%restart_output_dir, .true.)
OS%dirs%restart_output_dir, time_stamped=.true.)
if (OS%use_ice_shelf) then
call ice_shelf_save_restart(OS%Ice_shelf_CSp, OS%Time, OS%dirs%restart_output_dir, .true.)
endif
call save_MOM6_internal_state(OS%MOM_CSp, OS%dirs%restart_output_dir, OS%Time, .true.)
endif
if (BTEST(OS%Restart_control,0)) then
call save_restart(OS%dirs%restart_output_dir, OS%Time, OS%grid, &
OS%restart_CSp, GV=OS%GV)
call save_MOM_restart(OS%MOM_CSp, OS%dirs%restart_output_dir, OS%Time, &
OS%grid, GV=OS%GV)
call forcing_save_restart(OS%forcing_CSp, OS%grid, OS%Time, &
OS%dirs%restart_output_dir)
if (OS%use_ice_shelf) then
call ice_shelf_save_restart(OS%Ice_shelf_CSp, OS%Time, OS%dirs%restart_output_dir)
endif
call save_MOM6_internal_state(OS%MOM_CSp, OS%dirs%restart_output_dir, OS%Time)
endif
endif
if (present(stoch_restartname)) then
Expand Down Expand Up @@ -814,16 +807,13 @@ subroutine ocean_model_save_restart(OS, Time, directory, filename_suffix)
if (present(directory)) then ; restart_dir = directory
else ; restart_dir = OS%dirs%restart_output_dir ; endif

call save_restart(restart_dir, Time, OS%grid, OS%restart_CSp, GV=OS%GV)
call save_MOM_restart(OS%MOM_CSp, restart_dir, Time, OS%grid, GV=OS%GV)

call forcing_save_restart(OS%forcing_CSp, OS%grid, Time, restart_dir)

if (OS%use_ice_shelf) then
call ice_shelf_save_restart(OS%Ice_shelf_CSp, OS%Time, OS%dirs%restart_output_dir)
endif

call save_MOM6_internal_start(OS%MOM_CSp, OS%dirs%restart_output_dir, OS%Time)

end subroutine ocean_model_save_restart

!> Initialize the public ocean type
Expand Down
Loading

0 comments on commit 6ef0f80

Please sign in to comment.