Skip to content

Commit

Permalink
+Created iceberg_forces and iceberg_fluxes
Browse files Browse the repository at this point in the history
  Split add_berg_flux_to_shelf into two new subroutines, iceberg_forces and
iceberg_fluxes, that work on updating the mech_forcing and forcing types,
respectively.  All answers are bitwise identical.
  • Loading branch information
Hallberg-NOAA committed May 3, 2018
1 parent 7b17fe7 commit 327df24
Show file tree
Hide file tree
Showing 2 changed files with 43 additions and 19 deletions.
14 changes: 9 additions & 5 deletions config_src/coupled_driver/ocean_model_MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ module ocean_model_mod
use MOM_get_input, only : Get_MOM_Input, directories
use MOM_grid, only : ocean_grid_type
use MOM_io, only : close_file, file_exists, read_data, write_version_number
use MOM_marine_ice, only : add_berg_flux_to_shelf, marine_ice_init, marine_ice_CS
use MOM_marine_ice, only : iceberg_forces, iceberg_fluxes, marine_ice_init, marine_ice_CS
use MOM_restart, only : MOM_restart_CS, save_restart
use MOM_string_functions, only : uppercase
use MOM_surface_forcing, only : surface_forcing_init, convert_IOB_to_fluxes
Expand Down Expand Up @@ -523,8 +523,10 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, &
call shelf_calc_flux(OS%sfc_state, OS%forces, OS%fluxes, OS%Time, dt_coupling, OS%Ice_shelf_CSp)
endif
if (OS%icebergs_alter_ocean) then
call add_berg_flux_to_shelf(OS%grid, OS%forces, OS%fluxes, OS%use_ice_shelf, &
OS%sfc_state, dt_coupling, OS%marine_ice_CSp)
call iceberg_forces(OS%grid, OS%forces, OS%use_ice_shelf, &
OS%sfc_state, dt_coupling, OS%marine_ice_CSp)
call iceberg_fluxes(OS%grid, OS%fluxes, OS%use_ice_shelf, &
OS%sfc_state, dt_coupling, OS%marine_ice_CSp)
endif

! Fields that exist in both the forcing and mech_forcing types must be copied.
Expand All @@ -546,8 +548,10 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, &
call shelf_calc_flux(OS%sfc_state, OS%forces, OS%flux_tmp, OS%Time, dt_coupling, OS%Ice_shelf_CSp)
endif
if (OS%icebergs_alter_ocean) then
call add_berg_flux_to_shelf(OS%grid, OS%forces, OS%flux_tmp, OS%use_ice_shelf, &
OS%sfc_state, dt_coupling, OS%marine_ice_CSp)
call iceberg_forces(OS%grid, OS%forces, OS%use_ice_shelf, &
OS%sfc_state, dt_coupling, OS%marine_ice_CSp)
call iceberg_fluxes(OS%grid, OS%flux_tmp, OS%use_ice_shelf, &
OS%sfc_state, dt_coupling, OS%marine_ice_CSp)
endif

call forcing_accumulate(OS%flux_tmp, OS%forces, OS%fluxes, dt_coupling, OS%grid, weight)
Expand Down
48 changes: 34 additions & 14 deletions src/ice_shelf/MOM_marine_ice.F90
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ module MOM_marine_ice

#include <MOM_memory.h>

public add_berg_flux_to_shelf, marine_ice_init
public iceberg_forces, iceberg_fluxes, marine_ice_init

!> Control structure for MOM_marine_ice
type, public :: marine_ice_CS ; private
Expand All @@ -41,24 +41,19 @@ module MOM_marine_ice
!> add_berg_flux_to_shelf adds rigidity and ice-area coverage due to icebergs
!! to the forces type fields, and adds ice-areal coverage and modifies various
!! thermodynamic fluxes due to the presence of icebergs.
subroutine add_berg_flux_to_shelf(G, forces, fluxes, use_ice_shelf, sfc_state, &
subroutine iceberg_forces(G, forces, use_ice_shelf, sfc_state, &
time_step, CS)
type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure
type(mech_forcing), intent(inout) :: forces !< A structure with the driving mechanical forces
type(forcing), intent(inout) :: fluxes !< A structure with pointers to themodynamic,
!! tracer and mass exchange forcing fields
type(surface), intent(inout) :: sfc_state !< A structure containing fields that
!! describe the surface state of the ocean.
logical, intent(in) :: use_ice_shelf !< If true, this configuration uses ice shelves.
real, intent(in) :: time_step !< The coupling time step, in s.
type(marine_ice_CS), pointer :: CS !< Pointer to the control structure for MOM_marine_ice

real :: fraz ! refreezing rate in kg m-2 s-1
real :: I_dt_LHF ! The inverse of the timestep times the latent heat of fusion, in kg J-1 s-1.
real :: kv_rho_ice ! The viscosity of ice divided by its density, in m5 kg-1 s-1.
integer :: i, j, is, ie, js, je, isd, ied, jsd, jed
integer :: i, j, is, ie, js, je
is = G%isc ; ie = G%iec ; js = G%jsc ; je = G%jec
isd = G%isd ; jsd = G%jsd ; ied = G%ied ; jed = G%jed
!This routine adds iceberg data to the ice shelf data (if ice shelf is used)
!which can then be used to change the top of ocean boundary condition used in
!the ocean model. This routine is taken from the add_shelf_flux subroutine
Expand All @@ -71,10 +66,6 @@ subroutine add_berg_flux_to_shelf(G, forces, fluxes, use_ice_shelf, sfc_state, &
if (.not.(associated(forces%frac_shelf_u) .and. associated(forces%frac_shelf_v) .and. &
associated(forces%rigidity_ice_u) .and. associated(forces%rigidity_ice_v)) ) return

if (.not.(associated(fluxes%area_berg) .and. associated(fluxes%ustar_berg) .and. &
associated(fluxes%mass_berg) ) ) return
if (.not.(associated(fluxes%frac_shelf_h) .and. associated(fluxes%ustar_shelf)) ) return

! This section sets or augments the values of fields in forces.
if (.not. use_ice_shelf) then
forces%frac_shelf_u(:,:) = 0.0 ; forces%frac_shelf_v(:,:) = 0.0
Expand Down Expand Up @@ -104,7 +95,36 @@ subroutine add_berg_flux_to_shelf(G, forces, fluxes, use_ice_shelf, sfc_state, &
!### This halo update may be unnecessary. Test it. -RWH
call pass_vector(forces%frac_shelf_u, forces%frac_shelf_v, G%domain, TO_ALL, CGRID_NE)

! The remaining code sets or augments the values of fields in fluxes.
end subroutine iceberg_forces

!> iceberg_fluxes adds ice-area-coverage and modifies various
!! thermodynamic fluxes due to the presence of icebergs.
subroutine iceberg_fluxes(G, fluxes, use_ice_shelf, sfc_state, &
time_step, CS)
type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure
type(forcing), intent(inout) :: fluxes !< A structure with pointers to themodynamic,
!! tracer and mass exchange forcing fields
type(surface), intent(inout) :: sfc_state !< A structure containing fields that
!! describe the surface state of the ocean.
logical, intent(in) :: use_ice_shelf !< If true, this configuration uses ice shelves.
real, intent(in) :: time_step !< The coupling time step, in s.
type(marine_ice_CS), pointer :: CS !< Pointer to the control structure for MOM_marine_ice

real :: fraz ! refreezing rate in kg m-2 s-1
real :: I_dt_LHF ! The inverse of the timestep times the latent heat of fusion, in kg J-1 s-1.
integer :: i, j, is, ie, js, je, isd, ied, jsd, jed
is = G%isc ; ie = G%iec ; js = G%jsc ; je = G%jec
isd = G%isd ; jsd = G%jsd ; ied = G%ied ; jed = G%jed
!This routine adds iceberg data to the ice shelf data (if ice shelf is used)
!which can then be used to change the top of ocean boundary condition used in
!the ocean model. This routine is taken from the add_shelf_flux subroutine
!within the ice shelf model.

if (.not.associated(CS)) return
if (.not.(associated(fluxes%area_berg) .and. associated(fluxes%ustar_berg) .and. &
associated(fluxes%mass_berg) ) ) return
if (.not.(associated(fluxes%frac_shelf_h) .and. associated(fluxes%ustar_shelf)) ) return


if (.not.(associated(fluxes%area_berg) .and. associated(fluxes%ustar_berg) .and. &
associated(fluxes%mass_berg) ) ) return
Expand Down Expand Up @@ -148,7 +168,7 @@ subroutine add_berg_flux_to_shelf(G, forces, fluxes, use_ice_shelf, sfc_state, &
enddo ; enddo
endif

end subroutine add_berg_flux_to_shelf
end subroutine iceberg_fluxes

!> Initialize control structure for MOM_marine_ice
subroutine marine_ice_init(Time, G, param_file, diag, CS)
Expand Down

0 comments on commit 327df24

Please sign in to comment.