Skip to content

Commit

Permalink
Flux through static ice-shelf to icebergs/new diagnostics (NOAA-GFDL#622
Browse files Browse the repository at this point in the history
)

* Added option to convert flux through static ice front into icebergs

Added variables for the accumulated iceberg mass and heat flux due to
calving from ice shelves (flux through the static ice front). These
will be passed to the coupler and SIS2/iceberg module to initialize
bergs. Also fixed the ice-shelf SMB override and reorganized
ice-shelf post data calls so that they do not strictly have to be
called at multiples of the ice velocity time step.

* Added ice-shelf scalar diagnostics

Added ice-shelf scalar diagnostics related to volume-above-floatation
and surface/basal mass balance. Had to modify ice-shelf diag mediator
to allow scalar diagnostics.

* Fixed units for volume-above-floatation and Cp_ice. Renamed volume-above-floatation variable from 'vab' to 'vaf'

* Fixed write_ice_shelf_energy call within subroutine solo_step_ice_shelf so that it is passing the correct arguments

* Fixed syntax of calving units

* Fixed units for ice shelf calving and scalar diagnostics
  • Loading branch information
alex-huth authored and Wendazhang33 committed Jun 3, 2024
1 parent 8e49554 commit 1c722fa
Show file tree
Hide file tree
Showing 6 changed files with 541 additions and 55 deletions.
47 changes: 43 additions & 4 deletions config_src/drivers/FMS_cap/ocean_model_MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -55,6 +55,7 @@ module ocean_model_mod
use MOM_ice_shelf, only : initialize_ice_shelf, shelf_calc_flux, ice_shelf_CS
use MOM_ice_shelf, only : initialize_ice_shelf_fluxes, initialize_ice_shelf_forces
use MOM_ice_shelf, only : add_shelf_forces, ice_shelf_end, ice_shelf_save_restart
use MOM_ice_shelf, only : ice_sheet_calving_to_ocean_sfc
use MOM_wave_interface, only: wave_parameters_CS, MOM_wave_interface_init
use MOM_wave_interface, only: Update_Surface_Waves
use iso_fortran_env, only : int64
Expand Down Expand Up @@ -121,7 +122,10 @@ module ocean_model_mod
!! formation in the ocean.
melt_potential => NULL(), & !< Instantaneous heat used to melt sea ice [J m-2].
OBLD => NULL(), & !< Ocean boundary layer depth [m].
area => NULL() !< cell area of the ocean surface [m2].
area => NULL(), & !< cell area of the ocean surface [m2].
calving => NULL(), &!< The mass per unit area of the ice shelf to convert to
!! bergs [kg m-2].
calving_hflx => NULL() !< Calving heat flux [W m-2].
type(coupler_2d_bc_type) :: fields !< A structure that may contain named
!! arrays of tracer-related surface fields.
integer :: avg_kount !< A count of contributions to running
Expand Down Expand Up @@ -157,6 +161,8 @@ module ocean_model_mod
!! ocean dynamics and forcing fluxes.
real :: press_to_z !< A conversion factor between pressure and ocean depth,
!! usually 1/(rho_0*g) [Z T2 R-1 L-2 ~> m Pa-1].
logical :: calve_ice_shelf_bergs = .false. !< If true, bergs are initialized according to
!! ice shelf flux through the ice front
real :: C_p !< The heat capacity of seawater [J degC-1 kg-1].
logical :: offline_tracer_mode = .false. !< If false, use the model in prognostic mode
!! with the barotropic and baroclinic dynamics, thermodynamics,
Expand Down Expand Up @@ -221,7 +227,7 @@ module ocean_model_mod
!! This subroutine initializes both the ocean state and the ocean surface type.
!! Because of the way that indices and domains are handled, Ocean_sfc must have
!! been used in a previous call to initialize_ocean_type.
subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, wind_stagger, gas_fields_ocn)
subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, wind_stagger, gas_fields_ocn, calve_ice_shelf_bergs)
type(ocean_public_type), target, &
intent(inout) :: Ocean_sfc !< A structure containing various publicly
!! visible ocean surface properties after initialization,
Expand All @@ -239,6 +245,8 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, wind_stagger, gas
!! in the calculation of additional gas or other
!! tracer fluxes, and can be used to spawn related
!! internal variables in the ice model.
logical, optional, intent(in) :: calve_ice_shelf_bergs !< If true, track ice shelf flux through a
!! static ice shelf, so that it can be converted into icebergs
! Local variables
real :: Rho0 ! The Boussinesq ocean density [R ~> kg m-3]
real :: G_Earth ! The gravitational acceleration [L2 Z-1 T-2 ~> m s-2]
Expand All @@ -247,6 +255,7 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, wind_stagger, gas
!! min(HFrz, OBLD), where OBLD is the boundary layer depth.
!! If HFrz <= 0 (default), melt potential will not be computed.
logical :: use_melt_pot !< If true, allocate melt_potential array
logical :: point_calving ! Equals calve_ice_shelf_bergs if calve_ice_shelf_bergs is present

! This include declares and sets the variable "version".
# include "version_variable.h"
Expand Down Expand Up @@ -274,11 +283,11 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, wind_stagger, gas
OS%Time = Time_in ; OS%Time_dyn = Time_in
! Call initialize MOM with an optional Ice Shelf CS which, if present triggers
! initialization of ice shelf parameters and arrays.

point_calving=.false.; if (present(calve_ice_shelf_bergs)) point_calving=calve_ice_shelf_bergs
call initialize_MOM(OS%Time, Time_init, param_file, OS%dirs, OS%MOM_CSp, &
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)
waves_CSp=OS%Waves, calve_ice_shelf_bergs=point_calving)
call get_MOM_state_elements(OS%MOM_CSp, G=OS%grid, GV=OS%GV, US=OS%US, C_p=OS%C_p, &
C_p_scaled=OS%fluxes%C_p, use_temp=use_temperature)

Expand Down Expand Up @@ -406,6 +415,13 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, wind_stagger, gas

endif

if (present(calve_ice_shelf_bergs)) then
if (calve_ice_shelf_bergs) then
call convert_shelf_state_to_ocean_type(Ocean_sfc, OS%Ice_shelf_CSp, OS%US)
OS%calve_ice_shelf_bergs=.true.
endif
endif

call close_param_file(param_file)
call diag_mediator_close_registration(OS%diag)

Expand Down Expand Up @@ -668,6 +684,7 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, time_start_upda
! call convert_state_to_ocean_type(OS%sfc_state, Ocean_sfc, OS%grid, OS%US, &
! OS%fluxes%p_surf_full, OS%press_to_z)
call convert_state_to_ocean_type(OS%sfc_state, Ocean_sfc, OS%grid, OS%US)
if (OS%calve_ice_shelf_bergs) call convert_shelf_state_to_ocean_type(Ocean_sfc,OS%Ice_shelf_CSp, OS%US)
Time1 = OS%Time ; if (do_dyn) Time1 = OS%Time_dyn
call coupler_type_send_data(Ocean_sfc%fields, Time1)

Expand Down Expand Up @@ -789,6 +806,8 @@ subroutine initialize_ocean_public_type(input_domain, Ocean_sfc, diag, gas_field
Ocean_sfc%u_surf (isc:iec,jsc:jec), &
Ocean_sfc%v_surf (isc:iec,jsc:jec), &
Ocean_sfc%sea_lev(isc:iec,jsc:jec), &
Ocean_sfc%calving(isc:iec,jsc:jec), &
Ocean_sfc%calving_hflx(isc:iec,jsc:jec), &
Ocean_sfc%area (isc:iec,jsc:jec), &
Ocean_sfc%melt_potential(isc:iec,jsc:jec), &
Ocean_sfc%OBLD (isc:iec,jsc:jec), &
Expand All @@ -799,6 +818,8 @@ subroutine initialize_ocean_public_type(input_domain, Ocean_sfc, diag, gas_field
Ocean_sfc%u_surf(:,:) = 0.0 ! time averaged u-current (m/sec) passed to atmosphere/ice models
Ocean_sfc%v_surf(:,:) = 0.0 ! time averaged v-current (m/sec) passed to atmosphere/ice models
Ocean_sfc%sea_lev(:,:) = 0.0 ! time averaged thickness of top model grid cell (m) plus patm/rho0/grav
Ocean_sfc%calving(:,:) = 0.0 ! time accumulated ice sheet calving (kg m-2) passed to ice model
Ocean_sfc%calving_hflx(:,:) = 0.0 ! time accumulated ice sheet calving heat flux (W m-2) passed to ice model
Ocean_sfc%frazil(:,:) = 0.0 ! time accumulated frazil (J/m^2) passed to ice model
Ocean_sfc%melt_potential(:,:) = 0.0 ! time accumulated melt potential (J/m^2) passed to ice model
Ocean_sfc%OBLD(:,:) = 0.0 ! ocean boundary layer depth (m)
Expand Down Expand Up @@ -932,6 +953,24 @@ subroutine convert_state_to_ocean_type(sfc_state, Ocean_sfc, G, US, patm, press_

end subroutine convert_state_to_ocean_type

!> Converts the ice-shelf-to-ocean calving and calving_hflx variables from the ice-shelf state (ISS) type
!! to the ocean public type
subroutine convert_shelf_state_to_ocean_type(Ocean_sfc, CS, US)
type(ocean_public_type), &
target, intent(inout) :: Ocean_sfc !< A structure containing various publicly
!! visible ocean surface fields, whose elements
!! have their data set here.
type(ice_shelf_CS), pointer :: CS !< A pointer to the ice shelf control structure
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
integer :: isc_bnd, iec_bnd, jsc_bnd, jec_bnd, i, j

call get_domain_extent(Ocean_sfc%Domain, isc_bnd, iec_bnd, jsc_bnd, jec_bnd)

call ice_sheet_calving_to_ocean_sfc(CS,US,Ocean_sfc%calving(isc_bnd:iec_bnd,jsc_bnd:jec_bnd),&
Ocean_sfc%calving_hflx(isc_bnd:iec_bnd,jsc_bnd:jec_bnd))

end subroutine convert_shelf_state_to_ocean_type

!> This subroutine extracts the surface properties from the ocean's internal
!! state and stores them in the ocean type returned to the calling ice model.
!! It has to be separate from the ocean_initialization call because the coupler
Expand Down
15 changes: 12 additions & 3 deletions src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2007,7 +2007,8 @@ end subroutine step_offline
!! initializing the ocean state variables, and initializing subsidiary modules
subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, &
Time_in, offline_tracer_mode, input_restart_file, diag_ptr, &
count_calls, tracer_flow_CSp, ice_shelf_CSp, waves_CSp, ensemble_num)
count_calls, tracer_flow_CSp, ice_shelf_CSp, waves_CSp, ensemble_num, &
calve_ice_shelf_bergs)
type(time_type), target, intent(inout) :: Time !< model time, set in this routine
type(time_type), intent(in) :: Time_init !< The start time for the coupled model's calendar
type(param_file_type), intent(out) :: param_file !< structure indicating parameter file to parse
Expand All @@ -2030,6 +2031,8 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, &
optional, pointer :: Waves_CSp !< An optional pointer to a wave property CS
integer, optional :: ensemble_num !< Ensemble index provided by the cap (instead of FMS
!! ensemble manager)
logical, optional :: calve_ice_shelf_bergs !< If true, will add point iceberg calving variables to the ice
!! shelf restart
! local variables
type(ocean_grid_type), pointer :: G => NULL() ! A pointer to the metric grid use for the run
type(ocean_grid_type), pointer :: G_in => NULL() ! Pointer to the input grid
Expand All @@ -2043,6 +2046,7 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, &
type(MOM_restart_CS), pointer :: restart_CSp => NULL()
character(len=4), parameter :: vers_num = 'v2.0'
integer :: turns ! Number of grid quarter-turns
logical :: point_calving

! Initial state on the input index map
real, allocatable :: u_in(:,:,:) ! Initial zonal velocities [L T-1 ~> m s-1]
Expand Down Expand Up @@ -2903,6 +2907,10 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, &
! Consider removing this later?
G%ke = GV%ke

if (use_ice_shelf) then
point_calving=.false.; if (present(calve_ice_shelf_bergs)) point_calving=calve_ice_shelf_bergs
endif

if (CS%rotate_index) then
G_in%ke = GV%ke

Expand All @@ -2928,7 +2936,7 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, &
! 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, &
Time_init, dirs%output_directory)
Time_init, dirs%output_directory, calve_ice_shelf_bergs=point_calving)
allocate(frac_shelf_in(G_in%isd:G_in%ied, G_in%jsd:G_in%jed), source=0.0)
allocate(mass_shelf_in(G_in%isd:G_in%ied, G_in%jsd:G_in%jed), source=0.0)
allocate(CS%frac_shelf_h(isd:ied, jsd:jed), source=0.0)
Expand Down Expand Up @@ -2987,7 +2995,8 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, &
deallocate(frac_shelf_in,mass_shelf_in)
else
if (use_ice_shelf) then
call initialize_ice_shelf(param_file, G, Time, ice_shelf_CSp, diag_ptr, Time_init, dirs%output_directory)
call initialize_ice_shelf(param_file, G, Time, ice_shelf_CSp, diag_ptr, Time_init, &
dirs%output_directory, calve_ice_shelf_bergs=point_calving)
allocate(CS%frac_shelf_h(isd:ied, jsd:jed), source=0.0)
allocate(CS%mass_shelf(isd:ied, jsd:jed), source=0.0)
call ice_shelf_query(ice_shelf_CSp,G,CS%frac_shelf_h, CS%mass_shelf)
Expand Down
Loading

0 comments on commit 1c722fa

Please sign in to comment.