Skip to content

Commit

Permalink
+Pass optional args to update_ice_dynamics_trans
Browse files Browse the repository at this point in the history
  Made use of the cycle arguments in update_ice_dynamics_trans, passing them on
to SIS_multi_dyn_trans.  Also joined numerous short continuation lines.  In the
existing MOM6-examples test cases and if the new optional arguments are not
used, the answers are bitwise identical.
  • Loading branch information
Hallberg-NOAA committed Feb 19, 2019
1 parent 5d5257c commit aacd3ad
Showing 1 changed file with 42 additions and 60 deletions.
102 changes: 42 additions & 60 deletions src/ice_model.F90
Original file line number Diff line number Diff line change
Expand Up @@ -237,12 +237,10 @@ subroutine update_ice_slow_thermo(Ice)
enddo ; enddo

if (Ice%sCS%redo_fast_update) then
call redo_update_ice_model_fast(sIST, Ice%sCS%sOSS, Ice%sCS%Rad, &
FIA, Ice%sCS%TSF, Ice%sCS%optics_CSp, Ice%sCS%Time_step_slow, &
Ice%sCS%fast_thermo_CSp, sG, sIG)
call redo_update_ice_model_fast(sIST, Ice%sCS%sOSS, Ice%sCS%Rad, FIA, Ice%sCS%TSF, &
Ice%sCS%optics_CSp, Ice%sCS%Time_step_slow, Ice%sCS%fast_thermo_CSp, sG, sIG)

call find_excess_fluxes(FIA, Ice%sCS%TSF, Ice%sCS%XSF, sIST%part_size, &
sG, sIG)
call find_excess_fluxes(FIA, Ice%sCS%TSF, Ice%sCS%XSF, sIST%part_size, sG, sIG)
endif

call convert_frost_to_snow(FIA, sG, sIG)
Expand Down Expand Up @@ -275,17 +273,15 @@ subroutine update_ice_slow_thermo(Ice)
call IOF_chksum("Before slow_thermodynamics", Ice%sCS%IOF, sG)
endif

call slow_thermodynamics(sIST, dt_slow, Ice%sCS%slow_thermo_CSp, &
Ice%sCS%OSS, FIA, Ice%sCS%XSF, Ice%sCS%IOF, &
sG, sIG)
call slow_thermodynamics(sIST, dt_slow, Ice%sCS%slow_thermo_CSp, Ice%sCS%OSS, FIA, &
Ice%sCS%XSF, Ice%sCS%IOF, sG, sIG)
if (Ice%sCS%debug) then
call Ice_public_type_chksum("Before set_ocean_top_fluxes", Ice, check_slow=.true.)
call IOF_chksum("Before set_ocean_top_fluxes", Ice%sCS%IOF, sG)
call IST_chksum("Before set_ocean_top_fluxes", sIST, sG, sIG)
endif
! Set up the thermodynamic fluxes in the externally visible structure Ice.
call set_ocean_top_fluxes(Ice, sIST, Ice%sCS%IOF, FIA, Ice%sCS%OSS, &
sG, sIG, Ice%sCS)
call set_ocean_top_fluxes(Ice, sIST, Ice%sCS%IOF, FIA, Ice%sCS%OSS, sG, sIG, Ice%sCS)

call mpp_clock_end(ice_clock_slow) ; call mpp_clock_end(iceClock)

Expand All @@ -296,40 +292,41 @@ end subroutine update_ice_slow_thermo
subroutine update_ice_dynamics_trans(Ice, time_step, start_cycle, end_cycle, cycle_length)
type(ice_data_type), intent(inout) :: Ice !< The publicly visible ice data type.
type(time_type), optional, intent(in) :: time_step !< The amount of time to cover in this update.
logical, optional, intent(in) :: start_cycle !< This indicates whether this call is to be treated
!! as the first call to update_ice_dynamics_trans
logical, optional, intent(in) :: start_cycle !< This indicates whether this call is to be
!! treated as the first call to update_ice_dynamics_trans
!! in a time-stepping cycle; missing is like true.
logical, optional, intent(in) :: end_cycle !< This indicates whether this call is to be treated
!! as the last call to update_ice_dynamics_trans
logical, optional, intent(in) :: end_cycle !< This indicates whether this call is to be
!! treated as the last call to update_ice_dynamics_trans
!! in a time-stepping cycle; missing is like true.
real, optional, intent(in) :: cycle_length !< The duration of a coupled time stepping cycle [s].
real, optional, intent(in) :: cycle_length !< The duration of a coupled time stepping cycle [s].

! These pointers are used to simplify the code below.
type(ice_grid_type), pointer :: sIG => NULL()
type(SIS_hor_grid_type), pointer :: sG => NULL()
type(ice_state_type), pointer :: sIST => NULL()
type(fast_ice_avg_type), pointer :: FIA => NULL()
real :: dt_slow ! The time step over which to advance the model.
logical :: do_multi_trans
logical :: do_multi_trans, cycle_start

if (.not.associated(Ice%sCS)) call SIS_error(FATAL, &
"The pointer to Ice%sCS must be associated in update_ice_dynamics_trans.")

sIST => Ice%sCS%IST ; sIG => Ice%sCS%IG ; sG => Ice%sCS%G ; FIA => Ice%sCS%FIA
dt_slow = time_type_to_real(Ice%sCS%Time_step_slow)
if (present(time_step)) dt_slow = time_type_to_real(time_step)
cycle_start = .true. ; if (present(start_cycle)) cycle_start = start_cycle

call mpp_clock_begin(iceClock) ; call mpp_clock_begin(ice_clock_slow)

! Do halo updates on the forcing fields, as necessary. This must occur before
! the call to SIS_dynamics_trans, because update_icebergs does its own halo
! updates, and slow_thermodynamics only works on the computational domain.
call pass_vector(FIA%WindStr_x, FIA%WindStr_y, &
sG%Domain, stagger=AGRID, complete=.false.)
call pass_vector(FIA%WindStr_ocn_x, FIA%WindStr_ocn_y, &
sG%Domain, stagger=AGRID)
call pass_var(FIA%ice_cover, sG%Domain, complete=.false.)
call pass_var(FIA%ice_free, sG%Domain, complete=.true.)
if (cycle_start) then
call pass_vector(FIA%WindStr_x, FIA%WindStr_y, sG%Domain, stagger=AGRID, complete=.false.)
call pass_vector(FIA%WindStr_ocn_x, FIA%WindStr_ocn_y, sG%Domain, stagger=AGRID)
call pass_var(FIA%ice_cover, sG%Domain, complete=.false.)
call pass_var(FIA%ice_free, sG%Domain, complete=.true.)
endif
if (sIST%valid_IST) then
call pass_var(sIST%part_size, sG%Domain)
call pass_var(sIST%mH_ice, sG%Domain, complete=.false.)
Expand All @@ -345,19 +342,18 @@ subroutine update_ice_dynamics_trans(Ice, time_step, start_cycle, end_cycle, cyc
do_multi_trans = (present(start_cycle) .or. present(end_cycle) .or. present(cycle_length))

if (Ice%sCS%specified_ice) then ! There is no ice dynamics or transport.
call specified_ice_dynamics(sIST, Ice%sCS%OSS, FIA, Ice%sCS%IOF, &
dt_slow, Ice%sCS%specified_ice_CSp, sG, sIG)
call specified_ice_dynamics(sIST, Ice%sCS%OSS, FIA, Ice%sCS%IOF, dt_slow, &
Ice%sCS%specified_ice_CSp, sG, sIG)
elseif (do_multi_trans) then
call SIS_multi_dyn_trans(sIST, Ice%sCS%OSS, FIA, Ice%sCS%IOF, &
dt_slow, Ice%sCS%dyn_trans_CSp, Ice%icebergs, sG, &
sIG, Ice%sCS%SIS_tracer_flow_CSp)
call SIS_multi_dyn_trans(sIST, Ice%sCS%OSS, FIA, Ice%sCS%IOF, dt_slow, Ice%sCS%dyn_trans_CSp, &
Ice%icebergs, sG, sIG, Ice%sCS%SIS_tracer_flow_CSp, &
start_cycle, end_cycle, cycle_length)
elseif (Ice%sCS%slab_ice) then ! Use a very old slab ice model.
call slab_ice_dyn_trans(sIST, Ice%sCS%OSS, FIA, Ice%sCS%IOF, dt_slow, &
Ice%sCS%dyn_trans_CSp, sG, sIG, Ice%sCS%SIS_tracer_flow_CSp)
call slab_ice_dyn_trans(sIST, Ice%sCS%OSS, FIA, Ice%sCS%IOF, dt_slow, Ice%sCS%dyn_trans_CSp, &
sG, sIG, Ice%sCS%SIS_tracer_flow_CSp)
else ! This is the typical branch used by SIS2.
call SIS_dynamics_trans(sIST, Ice%sCS%OSS, FIA, Ice%sCS%IOF, &
dt_slow, Ice%sCS%dyn_trans_CSp, Ice%icebergs, sG, &
sIG, Ice%sCS%SIS_tracer_flow_CSp)
call SIS_dynamics_trans(sIST, Ice%sCS%OSS, FIA, Ice%sCS%IOF, dt_slow, Ice%sCS%dyn_trans_CSp, &
Ice%icebergs, sG, sIG, Ice%sCS%SIS_tracer_flow_CSp)
endif

! Set up the stresses and surface pressure in the externally visible structure Ice.
Expand Down Expand Up @@ -391,16 +387,13 @@ subroutine ice_model_fast_cleanup(Ice)
"The pointer to Ice%fCS must be associated in ice_model_fast_cleanup.")

! average fluxes from update_ice_model_fast
call avg_top_quantities(Ice%fCS%FIA, Ice%fCS%Rad, Ice%fCS%IST, &
Ice%fCS%G, Ice%fCS%IG)
call avg_top_quantities(Ice%fCS%FIA, Ice%fCS%Rad, Ice%fCS%IST, Ice%fCS%G, Ice%fCS%IG)

call total_top_quantities(Ice%fCS%FIA, Ice%fCS%TSF, Ice%fCS%IST%part_size, &
Ice%fCS%G, Ice%fCS%IG)
call total_top_quantities(Ice%fCS%FIA, Ice%fCS%TSF, Ice%fCS%IST%part_size, Ice%fCS%G, Ice%fCS%IG)

if (allocated(Ice%fCS%IST%t_surf)) &
Ice%fCS%IST%t_surf(:,:,1:) = Ice%fCS%Rad%T_skin(:,:,:) + T_0degC
call infill_array(Ice%fCS%IST, Ice%fCS%sOSS%T_fr_ocn, Ice%fCS%Rad%T_skin, &
Ice%fCS%G, Ice%fCS%IG)
call infill_array(Ice%fCS%IST, Ice%fCS%sOSS%T_fr_ocn, Ice%fCS%Rad%T_skin, Ice%fCS%G, Ice%fCS%IG)

end subroutine ice_model_fast_cleanup

Expand Down Expand Up @@ -507,20 +500,17 @@ subroutine exchange_fast_to_slow_ice(Ice)
"associated (although perhaps not with each other) in exchange_fast_to_slow_ice.")

if (.not.associated(Ice%fCS%FIA, Ice%sCS%FIA)) then
call copy_FIA_to_FIA(Ice%fCS%FIA, Ice%sCS%FIA, Ice%fCS%G%HI, Ice%sCS%G%HI, &
Ice%sCS%IG)
call copy_FIA_to_FIA(Ice%fCS%FIA, Ice%sCS%FIA, Ice%fCS%G%HI, Ice%sCS%G%HI, Ice%sCS%IG)
endif

if (redo_fast_update) then
if (.not.associated(Ice%fCS%TSF, Ice%sCS%TSF)) &
call copy_TSF_to_TSF(Ice%fCS%TSF, Ice%sCS%TSF, Ice%fCS%G%HI, Ice%sCS%G%HI)
if (.not.associated(Ice%fCS%Rad, Ice%sCS%Rad)) &
call copy_Rad_to_Rad(Ice%fCS%Rad, Ice%sCS%Rad, Ice%fCS%G%HI, &
Ice%sCS%G%HI, Ice%fCS%IG)
call copy_Rad_to_Rad(Ice%fCS%Rad, Ice%sCS%Rad, Ice%fCS%G%HI, Ice%sCS%G%HI, Ice%fCS%IG)
else
if (.not.associated(Ice%fCS%IST, Ice%sCS%IST)) &
call copy_IST_to_IST(Ice%fCS%IST, Ice%sCS%IST, Ice%fCS%G%HI, Ice%sCS%G%HI, &
Ice%fCS%IG)
call copy_IST_to_IST(Ice%fCS%IST, Ice%sCS%IST, Ice%fCS%G%HI, Ice%sCS%G%HI, Ice%fCS%IG)
endif
elseif (Ice%xtype == REDIST) then
if (.not.associated(Ice%fCS) .and. .not.associated(Ice%sCS)) call SIS_error(FATAL, &
Expand All @@ -535,36 +525,28 @@ subroutine exchange_fast_to_slow_ice(Ice)
if (redo_fast_update) then
call redistribute_TSF_to_TSF(Ice%fCS%TSF, Ice%sCS%TSF, Ice%fast_domain, &
Ice%slow_domain, Ice%sCS%G%HI)
call redistribute_Rad_to_Rad(Ice%fCS%Rad, Ice%sCS%Rad, Ice%fast_domain, &
Ice%slow_domain)
call redistribute_Rad_to_Rad(Ice%fCS%Rad, Ice%sCS%Rad, Ice%fast_domain, Ice%slow_domain)
else
if (.not.associated(Ice%fCS%IST, Ice%sCS%IST)) &
call redistribute_IST_to_IST(Ice%fCS%IST, Ice%sCS%IST, Ice%fast_domain, &
Ice%slow_domain)
call redistribute_IST_to_IST(Ice%fCS%IST, Ice%sCS%IST, Ice%fast_domain, Ice%slow_domain)
endif
elseif (associated(Ice%fCS)) then
call redistribute_FIA_to_FIA(Ice%fCS%FIA, FIA_null, Ice%fast_domain, &
Ice%slow_domain)
call redistribute_FIA_to_FIA(Ice%fCS%FIA, FIA_null, Ice%fast_domain, Ice%slow_domain)
if (redo_fast_update) then
call redistribute_TSF_to_TSF(Ice%fCS%TSF, TSF_null, Ice%fast_domain, &
Ice%slow_domain)
call redistribute_Rad_to_Rad(Ice%fCS%Rad, Rad_null, Ice%fast_domain, &
Ice%slow_domain)
call redistribute_TSF_to_TSF(Ice%fCS%TSF, TSF_null, Ice%fast_domain, Ice%slow_domain)
call redistribute_Rad_to_Rad(Ice%fCS%Rad, Rad_null, Ice%fast_domain, Ice%slow_domain)
else
call redistribute_IST_to_IST(Ice%fCS%IST, IST_null, Ice%fast_domain, &
Ice%slow_domain)
call redistribute_IST_to_IST(Ice%fCS%IST, IST_null, Ice%fast_domain, Ice%slow_domain)
endif
elseif (associated(Ice%sCS)) then
call redistribute_FIA_to_FIA(FIA_null, Ice%sCS%FIA, Ice%fast_domain, &
Ice%slow_domain, Ice%sCS%G, Ice%sCS%IG)
if (redo_fast_update) then
call redistribute_TSF_to_TSF(TSF_null, Ice%sCS%TSF, Ice%fast_domain, &
Ice%slow_domain, Ice%sCS%G%HI)
call redistribute_Rad_to_Rad(Rad_null, Ice%sCS%Rad, Ice%fast_domain, &
Ice%slow_domain)
call redistribute_Rad_to_Rad(Rad_null, Ice%sCS%Rad, Ice%fast_domain, Ice%slow_domain)
else
call redistribute_IST_to_IST(IST_null, Ice%sCS%IST, Ice%fast_domain, &
Ice%slow_domain)
call redistribute_IST_to_IST(IST_null, Ice%sCS%IST, Ice%fast_domain, Ice%slow_domain)
endif
else
call SIS_error(FATAL, "Either the pointer to Ice%sCS or the pointer to "//&
Expand Down

0 comments on commit aacd3ad

Please sign in to comment.