Skip to content

Commit

Permalink
Add a ridging control structure.
Browse files Browse the repository at this point in the history
  • Loading branch information
kshedstrom committed Dec 13, 2021
1 parent ae2b2e3 commit e55a3eb
Show file tree
Hide file tree
Showing 5 changed files with 33 additions and 43 deletions.
11 changes: 0 additions & 11 deletions src/SIS_dyn_bgrid.F90
Original file line number Diff line number Diff line change
Expand Up @@ -634,17 +634,6 @@ subroutine SIS_B_dynamics(ci, misp, mice, ui, vi, uo, vo, &
if (CS%id_vi>0) call post_SIS_data(CS%id_vi, vi, CS%diag)
endif

! ! Compute the deformation rate for ridging
! if (do_ridging) then
! do j=jsc,jec ; do i=isc,iec ; if (ice_present(i,j)) then
! del2 = (strn11(i,j)*strn11(i,j) + strn22(i,j)*strn22(i,j)) * (1+EC2I) + &
! 4.0*EC2I*strn12(i,j)*strn12(i,j) + 2.0*strn11(i,j)*strn22(i,j)*(1-EC2I) ! H&D eqn 9
! rdg_rate(i,j) = ridge_rate(del2, (strn11(i,j)+strn22(i,j)))
! else
! rdg_rate(i,j) = 0.0
! endif ; enddo ; enddo
! endif

end subroutine SIS_B_dynamics

!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
Expand Down
4 changes: 2 additions & 2 deletions src/SIS_dyn_trans.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2284,10 +2284,10 @@ subroutine SIS_dyn_trans_init(Time, G, US, IG, param_file, diag, CS, output_dir,
call SIS_B_dyn_init(CS%Time, G, US, param_file, CS%diag, CS%SIS_B_dyn_CSp)
endif
if (CS%merged_cont) then
call SIS_transport_init(CS%Time, G, US, param_file, CS%diag, CS%SIS_transport_CSp, &
call SIS_transport_init(CS%Time, G, IG, US, param_file, CS%diag, CS%SIS_transport_CSp, &
continuity_CSp=CS%continuity_CSp, cover_trans_CSp=CS%cover_trans_CSp)
else
call SIS_transport_init(CS%Time, G, US, param_file, CS%diag, CS%SIS_transport_CSp, &
call SIS_transport_init(CS%Time, G, IG, US, param_file, CS%diag, CS%SIS_transport_CSp, &
continuity_CSp=CS%continuity_CSp)
endif

Expand Down
14 changes: 9 additions & 5 deletions src/SIS_transport.F90
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ module SIS_transport
use SIS_tracer_registry, only : check_SIS_tracer_bounds
use SIS_types, only : ice_state_type
use ice_grid, only : ice_grid_type
use ice_ridging_mod, only : ice_ridging, ice_ridging_CS
use ice_ridging_mod, only : ice_ridging_init, ice_ridging, ice_ridging_CS

implicit none ; private

Expand Down Expand Up @@ -65,6 +65,8 @@ module SIS_transport
!< The control structure for the SIS tracer advection module
type(SIS_tracer_advect_CS), pointer :: SIS_thick_adv_CSp => NULL()
!< The control structure for the SIS thickness advection module
type(ice_ridging_CS), pointer :: ice_ridging_CSp => NULL()
!< Pointer to the control structure for the ice ridging

!>@{ Diagnostic IDs
integer :: id_ix_trans = -1, id_iy_trans = -1, id_xprt = -1, id_rdgr = -1
Expand Down Expand Up @@ -262,7 +264,7 @@ subroutine finish_ice_transport(CAS, IST, TrReg, G, US, IG, dt, CS, rdg_rate)

if (CS%do_ridging) then
! Compress the ice using the ridging scheme taken from the CICE-Icepack module
call ice_ridging(IST, G, IG, CAS%m_ice, CAS%m_snow, CAS%m_pond, TrReg, ice_ridging_CS, US, &
call ice_ridging(IST, G, IG, CAS%m_ice, CAS%m_snow, CAS%m_pond, TrReg, CS%ice_ridging_CSp, US, &
dt, rdg_rate=IST%rdg_rate, rdg_height=IST%rdg_height)
! Clean up any residuals
call compress_ice(IST%part_size, IST%mH_ice, IST%mH_snow, IST%mH_pond, TrReg, G, US, IG, CS, CAS)
Expand Down Expand Up @@ -1123,11 +1125,12 @@ end subroutine get_total_enthalpy

!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
!> SIS_transport_init initializes the ice transport and sets parameters.
subroutine SIS_transport_init(Time, G, US, param_file, diag, CS, continuity_CSp, cover_trans_CSp)
subroutine SIS_transport_init(Time, G, IG, US, param_file, diag, CS, continuity_CSp, cover_trans_CSp)
type(time_type), target, intent(in) :: Time !< The sea-ice model's clock,
!! set with the current model time.
type(SIS_hor_grid_type), intent(in) :: G !< The horizontal grid type
type(unit_scale_type), intent(in) :: US !< A structure with unit conversion factors
type(ice_grid_type), intent(in) :: IG !< The sea-ice specific grid type
type(unit_scale_type), intent(in) :: US !< A structure with unit conversion factors
type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
type(SIS_diag_ctrl), target, intent(inout) :: diag !< A structure that is used to regulate diagnostic output
type(SIS_transport_CS), pointer :: CS !< The control structure for this module
Expand Down Expand Up @@ -1175,7 +1178,6 @@ subroutine SIS_transport_init(Time, G, US, param_file, diag, CS, continuity_CSp,
"in categories with less than this coverage to be discarded.", &
units="nondim", default=-1.0)


call get_param(param_file, mdl, "CHECK_ICE_TRANSPORT_CONSERVATION", CS%check_conservation, &
"If true, use add multiple diagnostics of ice and snow "//&
"mass conservation in the sea-ice transport code. This "//&
Expand Down Expand Up @@ -1218,6 +1220,8 @@ subroutine SIS_transport_init(Time, G, US, param_file, diag, CS, continuity_CSp,
call SIS_continuity_init(Time, G, US, param_file, diag, CS%continuity_CSp, &
CS_cvr=cover_trans_CSp)
call SIS_tracer_advect_init(Time, G, param_file, diag, CS%SIS_tr_adv_CSp)
if (CS%do_ridging) &
call ice_ridging_init(G, IG, param_file, CS%ice_ridging_CSp, US)

if (present(continuity_CSp)) continuity_CSp => CS%continuity_CSp

Expand Down
3 changes: 0 additions & 3 deletions src/ice_model.F90
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,6 @@ module ice_model_mod
use ice_type_mod, only : ice_type_slow_reg_restarts, ice_type_fast_reg_restarts
use ice_type_mod, only : Ice_public_type_chksum, Ice_public_type_bounds_check
use ice_type_mod, only : ice_model_restart, ice_stock_pe, ice_data_type_chksum
use ice_ridging_mod, only : ice_ridging_init, ice_ridging_CS

use SIS_ctrl_types, only : SIS_slow_CS, SIS_fast_CS
use SIS_ctrl_types, only : ice_diagnostics_init, ice_diags_fast_init
Expand Down Expand Up @@ -2137,8 +2136,6 @@ subroutine ice_model_init(Ice, Time_Init, Time, Time_step_fast, Time_step_slow,
massless_val=massless_ice_salin, nonnegative=.true.)
endif

call ice_ridging_init(sG, sIG, sIST%TrReg, param_file, ice_ridging_CS, US)

! Register any tracers that will be handled via tracer flow control for
! restarts and advection.
call SIS_call_tracer_register(sG, sIG, param_file, Ice%sCS%SIS_tracer_flow_CSp, &
Expand Down
44 changes: 22 additions & 22 deletions src/ice_ridge.F90
Original file line number Diff line number Diff line change
Expand Up @@ -43,36 +43,36 @@ module ice_ridging_mod

type, public :: ice_ridging_CS ; private
logical :: &
new_rdg_partic = .true., & !< .true. = new participation, .false. = Thorndike et al 75
new_rdg_redist = .true. !< .true. = new redistribution, .false. = Hibler 80
real (kind=dbl_kind) :: mu_rdg = 3.0 !< e-folding scale of ridged ice, new_rdg_partic (m^0.5)
new_rdg_partic = .false., & !< .true. = new participation, .false. = Thorndike et al 75
new_rdg_redist = .false. !< .true. = new redistribution, .false. = Hibler 80
real (kind=dbl_kind) :: mu_rdg = 3.0 !< e-folding scale of ridged ice, new_rdg_partic (m^0.5)
end type ice_ridging_CS

contains

subroutine ice_ridging_init(G, IG, TrReg, PF, CS, US)
type(SIS_hor_grid_type), intent(inout) :: G !< G The ocean's grid structure.
type(ice_grid_type), intent(inout) :: IG !< The sea-ice-specific grid structure.
type(SIS_tracer_registry_type), pointer :: TrReg ! TrReg - The registry of registered SIS ice and snow tracers.
type(param_file_type), intent(in) :: PF !< A structure to parse for run-time parameters
type(ice_ridging_CS), intent(in) :: CS !< The ridging control structure.
type(unit_scale_type), intent(in) :: US !< A structure with unit conversion factors.
subroutine ice_ridging_init(G, IG, PF, CS, US)
type(SIS_hor_grid_type), intent(in) :: G !< G The ocean's grid structure.
type(ice_grid_type), intent(in) :: IG !< The sea-ice-specific grid structure.
type(param_file_type), intent(in) :: PF !< A structure to parse for run-time parameters
type(ice_ridging_CS), pointer :: CS !< The ridging control structure.
type(unit_scale_type), intent(in) :: US !< A structure with unit conversion factors.

integer (kind=int_kind) :: ntrcr, ncat, nilyr, nslyr, nblyr, nfsd, n_iso, n_aero
integer (kind=int_kind) :: nt_Tsfc, nt_sice, nt_qice, nt_alvl, nt_vlvl, nt_qsno
character(len=40) :: mdl = "ice_ridging_init" ! This module's name.

! call get_param(PF, mdl, "NEW_RIDGE_PARTICIPATION", CS%new_rdg_partic, &
! "Participation function used in ridging, .false. for Thorndike et al. 1975 "//&
! ".true. for Lipscomb et al. 2007", default=.true.)
! call get_param(PF, mdl, "NEW_RIDGE_REDISTRIBUTION", CS%new_rdg_redist, &
! "Redistribution function used in ridging, .false. for Hibler 1980 "//&
! ".true. for Lipscomb et al. 2007", default=.true.)
! if (CS%new_rdg_partic) then
! call get_param(PF, mdl, "RIDGE_MU", CS%mu_rdg, &
! "E-folding scale of ridge ice from Lipscomb et al. 2007", &
! units="m^0.5", default=3.0)
! endif
if (.not.associated(CS)) allocate(CS)
call get_param(PF, mdl, "NEW_RIDGE_PARTICIPATION", CS%new_rdg_partic, &
"Participation function used in ridging, .false. for Thorndike et al. 1975 "//&
".true. for Lipscomb et al. 2007", default=.false.)
call get_param(PF, mdl, "NEW_RIDGE_REDISTRIBUTION", CS%new_rdg_redist, &
"Redistribution function used in ridging, .false. for Hibler 1980 "//&
".true. for Lipscomb et al. 2007", default=.false.)
if (CS%new_rdg_partic) then
call get_param(PF, mdl, "RIDGE_MU", CS%mu_rdg, &
"E-folding scale of ridge ice from Lipscomb et al. 2007", &
units="m^0.5", default=3.0)
endif

ncat=IG%CatIce ! The number of sea-ice thickness categories
nilyr=IG%NkIce ! The number of ice layers per category
Expand Down Expand Up @@ -115,7 +115,7 @@ subroutine ice_ridging(IST, G, IG, mca_ice, mca_snow, mca_pond, TrReg, CS, US, d
real, dimension(SZI_(G),SZJ_(G),SZCAT_(IG)), intent(inout) :: mca_pond !< mass of pond water?
type(SIS_tracer_registry_type), pointer :: TrReg !< TrReg - The registry of registered SIS ice and
!! snow tracers.
type(ice_ridging_CS), intent(in) :: CS !< The ridging control structure.
type(ice_ridging_CS), intent(in) :: CS !< The ridging control structure.
type(unit_scale_type), intent(in) :: US !< A structure with unit conversion factors.
real (kind=dbl_kind), intent(in) :: dt !< The amount of time over which the ice dynamics are to be.
!! advanced in seconds.
Expand Down

0 comments on commit e55a3eb

Please sign in to comment.