Skip to content

Commit

Permalink
Initialization of point-particle bergs due to ice shelf calving
Browse files Browse the repository at this point in the history
-This commit is the SIS2 contribution in converting the MOM6 ice-shelf
 calving flux into new icebergs (this flux is routed through the
 several model components as follows:
 MOM6 --> coupler --> SIS2 --> icebergs)
-The ice-shelf calving flux is added to FIA%calving through the new
 subroutine unpack_ocean_ice_boundary_calved_shelf_bergs; this is
 the ice-shelf equivalent to the existing subroutine
 unpack_land_ice_boundary, which adds the frozen discharge from land
 to  FIA%calving.
-Both styles of calving can occur in the same run (e.g. frozen
 discharge from Greenland and ice-shelf calving from
 Antarctica), as long as both calving fluxes are not non-zero in the
 same cell.
  • Loading branch information
alex-huth authored and marshallward committed Jul 1, 2024
1 parent 3dfbfc1 commit 2c49005
Show file tree
Hide file tree
Showing 2 changed files with 49 additions and 2 deletions.
7 changes: 5 additions & 2 deletions src/ice_boundary_types.F90
Original file line number Diff line number Diff line change
Expand Up @@ -35,8 +35,11 @@ module ice_boundary_types
t => NULL(), & !< The ocean's surface temperature [Kelvin].
s => NULL(), & !< The ocean's surface salinity [gSalt kg-1].
frazil => NULL(), & !< The frazil heat rejected by the ocean [J m-2].
sea_level => NULL() !< The sea level after adjustment for any surface
!! pressure that the ocean allows to be expressed [m].
sea_level => NULL(), & !< The sea level after adjustment for any surface
!! pressure that the ocean allows to be expressed [m].
calving => NULL(), & !< The mass flux per unit area of the ice shelf to convert to
!!bergs [RZ_T ~> kg m-2 s-1].
calving_hflx => NULL() !< Calving heat flux [Q R Z T-1 ~> W m-2].
real, dimension(:,:,:), pointer :: data =>NULL() !< S collective field for "named" fields above
integer :: stagger = BGRID_NE !< A flag indicating how the velocities are staggered.
integer :: xtype !< A flag indicating the exchange type, which may be set to
Expand Down
44 changes: 44 additions & 0 deletions src/ice_model.F90
Original file line number Diff line number Diff line change
Expand Up @@ -127,6 +127,7 @@ module ice_model_mod
public :: lnd_ice_bnd_type_chksum, ice_data_type_chksum
public :: update_ice_atm_deposition_flux
public :: unpack_ocean_ice_boundary, unpack_ocn_ice_bdry, exchange_slow_to_fast_ice, set_ice_surface_fields
public :: unpack_ocean_ice_boundary_calved_shelf_bergs
public :: ice_model_fast_cleanup, unpack_land_ice_boundary
public :: exchange_fast_to_slow_ice, update_ice_model_slow
public :: update_ice_slow_thermo, update_ice_dynamics_trans
Expand Down Expand Up @@ -417,6 +418,49 @@ subroutine unpack_land_ice_boundary(Ice, LIB)

end subroutine unpack_land_ice_boundary

!> unpack_ocean_ice_boundary_calved_shelf_bergs converts the calving information in a publicly visible
!! ocean_ice_boundary_type into an internally visible fast_ice_avg_type variable.
subroutine unpack_ocean_ice_boundary_calved_shelf_bergs(Ice, OIB)
type(ice_data_type), intent(inout) :: Ice !< The publicly visible ice data type.
type(ocean_ice_boundary_type), intent(in) :: OIB !< The ocean ice boundary type that is being unpacked.

type(fast_ice_avg_type), pointer :: FIA => NULL()
type(SIS_hor_grid_type), pointer :: G => NULL()
type(unit_scale_type), pointer :: US => NULL()

integer :: i, j, k, m, n, i2, j2, k2, isc, iec, jsc, jec, i_off, j_off

if (.not.associated(Ice%fCS)) call SIS_error(FATAL, &
"The pointer to Ice%fCS must be associated in unpack_ocean_ice_boundary_calved_shelf_bergs.")
if (.not.associated(Ice%fCS%FIA)) call SIS_error(FATAL, &
"The pointer to Ice%fCS%FIA must be associated in unpack_ocean_ice_boundary_calved_shelf_berg.")
if (.not.associated(Ice%fCS%G)) call SIS_error(FATAL, &
"The pointer to Ice%fCS%G must be associated in unpack_ocean_ice_boundary_calved_shelf_berg.")

FIA => Ice%fCS%FIA ; G => Ice%fCS%G
US => Ice%fCS%US

isc = G%isc ; iec = G%iec ; jsc = G%jsc ; jec = G%jec

! Store calving flux from ice shelves to the sea ice or ocean.
i_off = LBOUND(OIB%calving,1) - G%isc ; j_off = LBOUND(OIB%calving,2) - G%jsc
!$OMP parallel do default(none) shared(isc,iec,jsc,jec,FIA,OIB,i_off,j_off,G,US) &
!$OMP private(i2,j2)
do j=jsc,jec ; do i=isc,iec ; if (G%mask2dT(i,j) > 0.0) then
i2 = i+i_off ; j2 = j+j_off
if (OIB%calving(i2,j2)>0.0) then
if (FIA%calving(i,j)>0.0) call SIS_error(FATAL,"Overlap in calving from snow discharge and ice shelf!")
FIA%calving(i,j) = US%kg_m2s_to_RZ_T*OIB%calving(i2,j2)
FIA%calving_hflx(i,j) = US%W_m2_to_QRZ_T*OIB%calving_hflx(i2,j2)
endif
endif ; enddo ; enddo

if (Ice%fCS%debug) then
call FIA_chksum("End of unpack_ocean_ice_boundary_calved_shelf_berg", FIA, G, Ice%fCS%US)
endif

end subroutine unpack_ocean_ice_boundary_calved_shelf_bergs

!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
!> This subroutine copies information (mostly fluxes and the updated temperatures)
!! from the fast part of the sea-ice to the slow part of the sea ice.
Expand Down

0 comments on commit 2c49005

Please sign in to comment.