Skip to content

Commit

Permalink
Merge branch 'Hallberg-NOAA-ice_shelf_fix' into dev/gfdl
Browse files Browse the repository at this point in the history
  • Loading branch information
adcroft committed Jan 4, 2021
2 parents 353cc63 + 464f39e commit aebed92
Show file tree
Hide file tree
Showing 5 changed files with 281 additions and 242 deletions.
24 changes: 9 additions & 15 deletions config_src/coupled_driver/ocean_model_MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,6 @@ module ocean_model_mod
use MOM_verticalGrid, only : verticalGrid_type
use MOM_ice_shelf, only : initialize_ice_shelf, shelf_calc_flux, ice_shelf_CS
use MOM_ice_shelf, only : add_shelf_forces, ice_shelf_end, ice_shelf_save_restart
use MOM_IS_diag_mediator, only : diag_IS_ctrl => diag_ctrl, diag_mediator_IS_end=>diag_mediator_end
use coupler_types_mod, only : coupler_1d_bc_type, coupler_2d_bc_type
use coupler_types_mod, only : coupler_type_spawn, coupler_type_write_chksums
use coupler_types_mod, only : coupler_type_initialized, coupler_type_copy_data
Expand Down Expand Up @@ -182,13 +181,13 @@ module ocean_model_mod
!! processes before time stepping the dynamics.

type(directories) :: dirs !< A structure containing several relevant directory paths.
type(mech_forcing), pointer :: forces => NULL() !< A structure with the driving mechanical surface forces
type(forcing), pointer :: fluxes => NULL() !< A structure containing pointers to
type(mech_forcing) :: forces !< A structure with the driving mechanical surface forces
type(forcing) :: fluxes !< A structure containing pointers to
!! the thermodynamic ocean forcing fields.
type(forcing), pointer :: flux_tmp => NULL() !< A secondary structure containing pointers to the
type(forcing) :: flux_tmp !< A secondary structure containing pointers to the
!! ocean forcing fields for when multiple coupled
!! timesteps are taken per thermodynamic step.
type(surface), pointer :: sfc_state => NULL() !< A structure containing pointers to
type(surface) :: sfc_state !< A structure containing pointers to
!! the ocean surface state fields.
type(ocean_grid_type), pointer :: &
grid => NULL() !< A pointer to a grid structure containing metrics
Expand Down Expand Up @@ -217,9 +216,6 @@ module ocean_model_mod
!! that will be used for MOM restart files.
type(diag_ctrl), pointer :: &
diag => NULL() !< A pointer to the diagnostic regulatory structure
type(diag_IS_ctrl), pointer :: &
diag_IS => NULL() !< A pointer to the diagnostic regulatory structure
!! for the ice shelf module.
end type ocean_state_type

contains
Expand Down Expand Up @@ -273,9 +269,9 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, wind_stagger, gas
endif
allocate(OS)

allocate(OS%fluxes)
allocate(OS%forces)
allocate(OS%flux_tmp)
! allocate(OS%fluxes)
! allocate(OS%forces)
! allocate(OS%flux_tmp)

OS%is_ocean_pe = Ocean_sfc%is_ocean_pe
if (.not.OS%is_ocean_pe) return
Expand Down Expand Up @@ -365,7 +361,7 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, wind_stagger, gas
use_melt_pot=.false.
endif

allocate(OS%sfc_state)
!allocate(OS%sfc_state)
call allocate_surface_state(OS%sfc_state, OS%grid, use_temperature, do_integrals=.true., &
gas_fields_ocn=gas_fields_ocn, use_meltpot=use_melt_pot)

Expand All @@ -379,7 +375,7 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, wind_stagger, gas

if (OS%use_ice_shelf) then
call initialize_ice_shelf(param_file, OS%grid, OS%Time, OS%ice_shelf_CSp, &
OS%diag_IS, OS%forces, OS%fluxes)
OS%diag, OS%forces, OS%fluxes)
endif
if (OS%icebergs_alter_ocean) then
call marine_ice_init(OS%Time, OS%grid, param_file, OS%diag, OS%marine_ice_CSp)
Expand Down Expand Up @@ -728,8 +724,6 @@ subroutine ocean_model_end(Ocean_sfc, Ocean_state, Time)

call ocean_model_save_restart(Ocean_state, Time)
call diag_mediator_end(Time, Ocean_state%diag)
if (Ocean_state%use_ice_shelf) &
call diag_mediator_IS_end(Time, Ocean_state%diag_IS)
call MOM_end(Ocean_state%MOM_CSp)
if (Ocean_state%use_ice_shelf) call ice_shelf_end(Ocean_state%Ice_shelf_CSp)
end subroutine ocean_model_end
Expand Down
45 changes: 19 additions & 26 deletions config_src/solo_driver/MOM_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,6 @@ program MOM_main
use MOM_cpu_clock, only : CLOCK_COMPONENT
use MOM_diag_mediator, only : enable_averaging, disable_averaging, diag_mediator_end
use MOM_diag_mediator, only : diag_ctrl, diag_mediator_close_registration
use MOM_IS_diag_mediator, only : diag_IS_ctrl=>diag_ctrl, diag_mediator_IS_end=>diag_mediator_end
use MOM, only : initialize_MOM, step_MOM, MOM_control_struct, MOM_end
use MOM, only : extract_surface_state, finish_MOM_initialization
use MOM, only : get_MOM_state_elements, MOM_state_is_synchronized
Expand Down Expand Up @@ -71,6 +70,7 @@ program MOM_main

use MOM_ice_shelf, only : initialize_ice_shelf, ice_shelf_end, ice_shelf_CS
use MOM_ice_shelf, only : shelf_calc_flux, add_shelf_forces, ice_shelf_save_restart
use MOM_ice_shelf, only : initialize_ice_shelf_fluxes, initialize_ice_shelf_forces

use MOM_wave_interface, only: wave_parameters_CS, MOM_wave_interface_init
use MOM_wave_interface, only: MOM_wave_interface_init_lite, Update_Surface_Waves
Expand All @@ -80,13 +80,12 @@ program MOM_main
#include <MOM_memory.h>

! A structure with the driving mechanical surface forces
type(mech_forcing), pointer :: forces => NULL()
type(mech_forcing) :: forces
! A structure containing pointers to the thermodynamic forcing fields
! at the ocean surface.
type(forcing), pointer :: fluxes => NULL()

type(forcing) :: fluxes
! A structure containing pointers to the ocean surface state fields.
type(surface), pointer :: sfc_state => NULL()
type(surface) :: sfc_state

! A pointer to a structure containing metrics and related information.
type(ocean_grid_type), pointer :: grid => NULL()
Expand Down Expand Up @@ -200,8 +199,6 @@ program MOM_main
!! that will be used for MOM restart files.
type(diag_ctrl), pointer :: &
diag => NULL() !< A pointer to the diagnostic regulatory structure
type(diag_IS_ctrl), pointer :: &
diag_IS => NULL() !< A pointer to the diagnostic regulatory structure
!-----------------------------------------------------------------------

character(len=4), parameter :: vers_num = 'v2.0'
Expand All @@ -221,7 +218,7 @@ program MOM_main

call MOM_infra_init() ; call io_infra_init()

allocate(forces,fluxes,sfc_state)
!allocate(forces,fluxes,sfc_state)

! Initialize the ensemble manager. If there are no settings for ensemble_size
! in input.nml(ensemble.nml), these should not do anything. In coupled
Expand Down Expand Up @@ -307,32 +304,29 @@ program MOM_main
Time = Start_time
endif

! Read paths and filenames from namelist and store in "dirs".
! Also open the parsed input parameter file(s) and setup param_file.
call get_MOM_input(param_file, dirs)

call get_param(param_file, mod_name, "ICE_SHELF", use_ice_shelf, &
"If true, enables the ice shelf model.", default=.false.)
if (use_ice_shelf) then
! These arrays are not initialized in most solo cases, but are needed
! when using an ice shelf
call initialize_ice_shelf(param_file, grid, Time, ice_shelf_CSp, &
diag_IS, forces, fluxes, sfc_state)
endif
call close_param_file(param_file)

! Call initialize MOM with an optional Ice Shelf CS which, if present triggers
! initialization of ice shelf parameters and arrays.
if (sum(date) >= 0) then
call initialize_MOM(Time, Start_time, param_file, dirs, MOM_CSp, restart_CSp, &
segment_start_time, offline_tracer_mode=offline_tracer_mode, &
diag_ptr=diag, tracer_flow_CSp=tracer_flow_CSp,ice_shelf_CSp=ice_shelf_CSp)
diag_ptr=diag, tracer_flow_CSp=tracer_flow_CSp, ice_shelf_CSp=ice_shelf_CSp)
else
call initialize_MOM(Time, Start_time, param_file, dirs, MOM_CSp, restart_CSp, &
offline_tracer_mode=offline_tracer_mode, diag_ptr=diag, &
tracer_flow_CSp=tracer_flow_CSp,ice_shelf_CSp=ice_shelf_CSp)
tracer_flow_CSp=tracer_flow_CSp, ice_shelf_CSp=ice_shelf_CSp)
endif

call get_MOM_state_elements(MOM_CSp, G=grid, GV=GV, US=US, C_p_scaled=fluxes%C_p)
Master_Time = Time
use_ice_shelf = associated(ice_shelf_CSp)

if (use_ice_shelf) then
! These arrays are not initialized in most solo cases, but are needed
! when using an ice shelf
call initialize_ice_shelf_fluxes(ice_shelf_CSp, grid, US, fluxes)
call initialize_ice_shelf_forces(ice_shelf_CSp, grid, US, forces)
endif


call callTree_waypoint("done initialize_MOM")

Expand Down Expand Up @@ -665,14 +659,13 @@ program MOM_main
endif

call callTree_waypoint("End MOM_main")
if (use_ice_shelf) call ice_shelf_end(ice_shelf_CSp)
call diag_mediator_end(Time, diag, end_diag_manager=.true.)
if (use_ice_shelf) call diag_mediator_IS_end(Time, diag_IS)
if (cpu_steps > 0) call write_cputime(Time, ns-1, write_CPU_CSp, call_end=.true.)
call cpu_clock_end(termClock)

call io_infra_end ; call MOM_infra_end

call MOM_end(MOM_CSp)
if (use_ice_shelf) call ice_shelf_end(ice_shelf_CSp)

end program MOM_main
11 changes: 8 additions & 3 deletions src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -141,7 +141,7 @@ module MOM
use MOM_offline_main, only : offline_fw_fluxes_into_ocean, offline_fw_fluxes_out_ocean
use MOM_offline_main, only : offline_advection_layer, offline_transport_end
use MOM_ALE, only : ale_offline_tracer_final, ALE_main_offline
use MOM_ice_shelf, only : ice_shelf_CS, ice_shelf_query
use MOM_ice_shelf, only : ice_shelf_CS, ice_shelf_query, initialize_ice_shelf

implicit none ; private

Expand Down Expand Up @@ -2037,7 +2037,8 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, restart_CSp, &

use_ice_shelf=.false.
if (present(ice_shelf_CSp)) then
if (associated(ice_shelf_CSp)) use_ice_shelf=.true.
call get_param(param_file, "MOM", "ICE_SHELF", use_ice_shelf, &
"If true, enables the ice shelf model.", default=.false.)
endif

CS%ensemble_ocean=.false.
Expand Down Expand Up @@ -2381,6 +2382,10 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, restart_CSp, &
endif

if (use_ice_shelf) then
! These arrays are not initialized in most solo cases, but are needed
! when using an ice shelf. Passing the ice shelf diagnostics CS from MOM
! for legacy reasons. The actual ice shelf diag CS is internal to the ice shelf
call initialize_ice_shelf(param_file, G_in, Time, ice_shelf_CSp, diag_ptr)
allocate(frac_shelf_in(G_in%isd:G_in%ied, G_in%jsd:G_in%jed))
frac_shelf_in(:,:) = 0.0
allocate(CS%frac_shelf_h(isd:ied, jsd:jed))
Expand Down Expand Up @@ -2431,10 +2436,10 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, restart_CSp, &
deallocate(frac_shelf_in)
else
if (use_ice_shelf) then
call initialize_ice_shelf(param_file, G, Time, ice_shelf_CSp, diag_ptr)
allocate(CS%frac_shelf_h(isd:ied, jsd:jed))
CS%frac_shelf_h(:,:) = 0.0
call ice_shelf_query(ice_shelf_CSp,G,CS%frac_shelf_h)

call MOM_initialize_state(CS%u, CS%v, CS%h, CS%tv, Time, G, GV, US, &
param_file, dirs, restart_CSp, CS%ALE_CSp, CS%tracer_Reg, &
CS%sponge_CSp, CS%ALE_sponge_CSp, CS%OBC, Time_in, &
Expand Down
Loading

0 comments on commit aebed92

Please sign in to comment.