Skip to content

Commit

Permalink
+Added optional gas_flux args to ice_model_init
Browse files Browse the repository at this point in the history
  Added optional arguments gas_flux and gas_fields_ocn arguments of type
coupler_1d_bc_type to several SIS2 initialization routines, including
ice_model_init.  If these are present, they are used to spawn the types used to
describe additional gas or tracer fluxes and fields at the same time as other
SIS2 arrays are allocated.  There is a new version of the coupler that makes use
of these new arguments, but because they are optional, older versions of the
coupler will work also.  All answers are bitwise identical.
  • Loading branch information
Hallberg-NOAA committed Jul 31, 2017
1 parent e2497e6 commit 9020bf1
Show file tree
Hide file tree
Showing 3 changed files with 105 additions and 36 deletions.
77 changes: 59 additions & 18 deletions src/SIS_types.F90
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ module SIS_types
use fms_io_mod, only : register_restart_field, restart_file_type
use fms_io_mod, only : restore_state, query_initialized
use time_manager_mod, only : time_type, time_type_to_real
use coupler_types_mod, only : coupler_2d_bc_type, coupler_3d_bc_type
use coupler_types_mod, only : coupler_1d_bc_type, coupler_2d_bc_type, coupler_3d_bc_type
use coupler_types_mod, only : coupler_type_spawn, coupler_type_copy_data
use coupler_types_mod, only : coupler_type_redistribute_data
use SIS_hor_grid, only : SIS_hor_grid_type
Expand Down Expand Up @@ -729,16 +729,20 @@ end subroutine ice_state_read_alt_restarts

!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
!> alloc_fast_ice_avg allocates and zeros out the arrays in a fast_ice_avg_type.
subroutine alloc_fast_ice_avg(FIA, HI, IG, interp_fluxes)
subroutine alloc_fast_ice_avg(FIA, HI, IG, interp_fluxes, gas_fluxes)
type(fast_ice_avg_type), pointer :: FIA
type(hor_index_type), intent(in) :: HI
type(ice_grid_type), intent(in) :: IG
logical, intent(in) :: interp_fluxes

integer :: isd, ied, jsd, jed, CatIce
type(coupler_1d_bc_type), &
optional, intent(in) :: gas_fluxes !< If present, this type describes the
!! additional gas or other tracer fluxes between the
!! ocean, ice, and atmosphere.
integer :: isc, iec, jsc, jec, isd, ied, jsd, jed, CatIce

if (.not.associated(FIA)) allocate(FIA)
CatIce = IG%CatIce
isc = HI%isc ; iec = HI%iec ; jsc = HI%jsc ; jec = HI%jec
isd = HI%isd ; ied = HI%ied ; jsd = HI%jsd ; jed = HI%jed

FIA%avg_count = 0
Expand Down Expand Up @@ -783,17 +787,27 @@ subroutine alloc_fast_ice_avg(FIA, HI, IG, interp_fluxes)
allocate(FIA%flux_sw_dn(isd:ied, jsd:jed, NBANDS)) ; FIA%flux_sw_dn(:,:,:) = 0.0
allocate(FIA%sw_abs_ocn(isd:ied, jsd:jed, CatIce)) ; FIA%sw_abs_ocn(:,:,:) = 0.0

if (present(gas_fluxes)) &
call coupler_type_spawn(gas_fluxes, FIA%tr_flux, (/isd, isc, iec, ied/), &
(/jsd, jsc, jec, jed/), (/0, CatIce/))

end subroutine alloc_fast_ice_avg

!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
!> alloc_total_sfc_flux allocates and zeros out the arrays in a total_sfc_flux_type.
subroutine alloc_total_sfc_flux(TSF, HI)
type(total_sfc_flux_type), pointer :: TSF
type(hor_index_type), intent(in) :: HI
subroutine alloc_total_sfc_flux(TSF, HI, gas_fluxes)
type(total_sfc_flux_type), pointer :: TSF !< The total surface flux type being allocated
type(hor_index_type), intent(in) :: HI !< The hor_index_type with information about the
!! array extents to be allocated.
type(coupler_1d_bc_type), &
optional, intent(in) :: gas_fluxes !< If present, this type describes the
!! additional gas or other tracer fluxes between the
!! ocean, ice, and atmosphere.

integer :: isd, ied, jsd, jed
integer :: isc, iec, jsc, jec, isd, ied, jsd, jed

if (.not.associated(TSF)) allocate(TSF)
isc = HI%isc ; iec = HI%iec ; jsc = HI%jsc ; jec = HI%jec
isd = HI%isd ; ied = HI%ied ; jsd = HI%jsd ; jed = HI%jed

allocate(TSF%flux_u(isd:ied, jsd:jed)) ; TSF%flux_u(:,:) = 0.0
Expand All @@ -805,6 +819,9 @@ subroutine alloc_total_sfc_flux(TSF, HI)
allocate(TSF%evap(isd:ied, jsd:jed)) ; TSF%evap(:,:) = 0.0
allocate(TSF%lprec(isd:ied, jsd:jed)) ; TSF%lprec(:,:) = 0.0
allocate(TSF%fprec(isd:ied, jsd:jed)) ; TSF%fprec(:,:) = 0.0
if (present(gas_fluxes)) &
call coupler_type_spawn(gas_fluxes, TSF%tr_flux, (/isd, isc, iec, ied/), &
(/jsd, jsc, jec, jed/))

end subroutine alloc_total_sfc_flux

Expand Down Expand Up @@ -917,10 +934,21 @@ end subroutine alloc_ice_ocean_flux

!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
!> alloc_ocean_sfc_state allocates and zeros out the arrays in an ocean_sfc_state_type.
subroutine alloc_ocean_sfc_state(OSS, HI, Cgrid_dyn)
type(ocean_sfc_state_type), pointer :: OSS
type(hor_index_type), intent(in) :: HI
logical, intent(in) :: Cgrid_dyn
subroutine alloc_ocean_sfc_state(OSS, HI, Cgrid_dyn, gas_fields_ocn)
type(ocean_sfc_state_type), pointer :: OSS !< The ocean_sfc_state_type being allocated
type(hor_index_type), intent(in) :: HI !< The hor_index_type with information about the
!! array extents to be allocated.
logical, intent(in) :: Cgrid_dyn !< A variable indicating whether the ice
!! ice dynamics are calculated on a C-grid (true)
!! or on a B-grid (false).
type(coupler_1d_bc_type), &
optional, intent(in) :: gas_fields_ocn !< If present, this type describes the
!! ocean and surface-ice fields that will participate
!! in the calculation of additional gas or other
!! tracer fluxes.
integer :: isc, iec, jsc, jec, isd, ied, jsd, jed
isc = HI%isc ; iec = HI%iec ; jsc = HI%jsc ; jec = HI%jec
isd = HI%isd ; ied = HI%ied ; jsd = HI%jsd ; jed = HI%jed

if (.not.associated(OSS)) allocate(OSS)

Expand All @@ -942,19 +970,30 @@ subroutine alloc_ocean_sfc_state(OSS, HI, Cgrid_dyn)

OSS%Cgrid_dyn = Cgrid_dyn

if (present(gas_fields_ocn)) &
call coupler_type_spawn(gas_fields_ocn, OSS%tr_fields, (/isd, isc, iec, ied/), &
(/jsd, jsc, jec, jed/))

end subroutine alloc_ocean_sfc_state


!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
!> alloc_simple_ocean_sfc_state allocates and zeros out the arrays in a
!! simple_OSS_type.
subroutine alloc_simple_OSS(OSS, HI)
type(simple_OSS_type), pointer :: OSS
type(hor_index_type), intent(in) :: HI

integer :: isd, ied, jsd, jed
subroutine alloc_simple_OSS(OSS, HI, gas_fields_ocn)
type(simple_OSS_type), pointer :: OSS !< The simple_OSS_type being allocated
type(hor_index_type), intent(in) :: HI !< The hor_index_type with information about the
!! array extents to be allocated.
type(coupler_1d_bc_type), &
optional, intent(in) :: gas_fields_ocn !< If present, this type describes the
!! ocean and surface-ice fields that will participate
!! in the calculation of additional gas or other
!! tracer fluxes.

integer :: isc, iec, jsc, jec, isd, ied, jsd, jed

if (.not.associated(OSS)) allocate(OSS)
isc = HI%isc ; iec = HI%iec ; jsc = HI%jsc ; jec = HI%jec
isd = HI%isd ; ied = HI%ied ; jsd = HI%jsd ; jed = HI%jed

allocate(OSS%s_surf(isd:ied, jsd:jed)) ; OSS%s_surf(:,:) = 0.0
Expand All @@ -965,10 +1004,12 @@ subroutine alloc_simple_OSS(OSS, HI)
allocate(OSS%v_ocn_A(isd:ied, jsd:jed)) ; OSS%v_ocn_A(:,:) = 0.0
allocate(OSS%u_ice_A(isd:ied, jsd:jed)) ; OSS%u_ice_A(:,:) = 0.0
allocate(OSS%v_ice_A(isd:ied, jsd:jed)) ; OSS%v_ice_A(:,:) = 0.0
if (present(gas_fields_ocn)) &
call coupler_type_spawn(gas_fields_ocn, OSS%tr_fields, (/isd, isc, iec, ied/), &
(/jsd, jsc, jec, jed/))

end subroutine alloc_simple_OSS


!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
!> copy_IST_to_IST copies the computational domain of one ice state type into
!! the computational domain of another ice_state_type. Both must use the same
Expand Down
31 changes: 21 additions & 10 deletions src/ice_model.F90
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,7 @@ module ice_model_mod
use MOM_time_manager, only : set_date, set_time, operator(+), operator(-)
use MOM_time_manager, only : operator(>), operator(*), operator(/), operator(/=)

use coupler_types_mod, only : coupler_2d_bc_type, coupler_3d_bc_type
use coupler_types_mod, only : coupler_1d_bc_type, coupler_2d_bc_type, coupler_3d_bc_type
use coupler_types_mod, only : coupler_type_spawn, coupler_type_initialized
use coupler_types_mod, only : coupler_type_rescale_data, coupler_type_copy_data
use fms_mod, only : file_exist, clock_flag_default
Expand Down Expand Up @@ -1607,7 +1607,7 @@ end subroutine add_diurnal_sw
!> ice_model_init - initializes ice model data, parameters and diagnostics. It
!! might operate on the fast ice processors, the slow ice processors or both.
subroutine ice_model_init(Ice, Time_Init, Time, Time_step_fast, Time_step_slow, &
Verona_coupler, Concurrent_ice )
Verona_coupler, Concurrent_ice, gas_fluxes, gas_fields_ocn )

type(ice_data_type), intent(inout) :: Ice !< The ice data type that is being initialized.
type(time_type) , intent(in) :: Time_Init !< The starting time of the model integration
Expand All @@ -1625,6 +1625,17 @@ subroutine ice_model_init(Ice, Time_Init, Time, Time_step_fast, Time_step_slow,
!! settings appropriate for running the atmosphere and
!! slow ice simultaneously, including embedding the
!! slow sea-ice time stepping in the ocean model.
type(coupler_1d_bc_type), &
optional, intent(in) :: gas_fluxes !< If present, this type describes the
!! additional gas or other tracer fluxes between the
!! ocean, ice, and atmosphere, and can be used to
!! spawn related internal variables in the ice model.
type(coupler_1d_bc_type), &
optional, intent(in) :: gas_fields_ocn !< If present, this type describes the
!! ocean and surface-ice fields that will participate
!! in the calculation of additional gas or other
!! tracer fluxes, and can be used to spawn related
!! internal variables in the ice model.

! This include declares and sets the variable "version".
#include "version_variable.h"
Expand Down Expand Up @@ -2076,19 +2087,19 @@ subroutine ice_model_init(Ice, Time_Init, Time, Time_step_fast, Time_step_slow,
call alloc_IST_arrays(sHI, sIG, sIST, omit_tsurf=Eulerian_tsurf)
call ice_state_register_restarts(sIST, sG, sIG, Ice%Ice_restart, restart_file)

call alloc_ocean_sfc_state(Ice%sCS%OSS, sHI, sIST%Cgrid_dyn)
call alloc_ocean_sfc_state(Ice%sCS%OSS, sHI, sIST%Cgrid_dyn, gas_fields_ocn)
Ice%sCS%OSS%kmelt = kmelt

call alloc_simple_OSS(Ice%sCS%sOSS, sHI)
call alloc_simple_OSS(Ice%sCS%sOSS, sHI, gas_fields_ocn)

call alloc_ice_ocean_flux(Ice%sCS%IOF, sHI, do_iceberg_fields=Ice%sCS%do_icebergs)
Ice%sCS%IOF%slp2ocean = slp2ocean
Ice%sCS%IOF%flux_uv_stagger = Ice%flux_uv_stagger
call alloc_fast_ice_avg(Ice%sCS%FIA, sHI, sIG, interp_fluxes)
call alloc_fast_ice_avg(Ice%sCS%FIA, sHI, sIG, interp_fluxes, gas_fluxes)

if (Ice%sCS%redo_fast_update) then
call alloc_total_sfc_flux(Ice%sCS%TSF, sHI)
call alloc_total_sfc_flux(Ice%sCS%XSF, sHI)
call alloc_total_sfc_flux(Ice%sCS%TSF, sHI, gas_fluxes)
call alloc_total_sfc_flux(Ice%sCS%XSF, sHI, gas_fluxes)
call alloc_ice_rad(Ice%sCS%Rad, sHI, sIG)
endif

Expand Down Expand Up @@ -2223,11 +2234,11 @@ subroutine ice_model_init(Ice, Time_Init, Time, Time_step_fast, Time_step_slow,
omit_velocities=.true., omit_tsurf=Eulerian_tsurf)
endif
if (.not.single_IST) then
call alloc_fast_ice_avg(Ice%fCS%FIA, fHI, Ice%fCS%IG, interp_fluxes)
call alloc_fast_ice_avg(Ice%fCS%FIA, fHI, Ice%fCS%IG, interp_fluxes, gas_fluxes)

call alloc_simple_OSS(Ice%fCS%sOSS, fHI)
call alloc_simple_OSS(Ice%fCS%sOSS, fHI, gas_fields_ocn)
endif
call alloc_total_sfc_flux(Ice%fCS%TSF, fHI)
call alloc_total_sfc_flux(Ice%fCS%TSF, fHI, gas_fluxes)
Ice%fCS%FIA%atmos_winds = atmos_winds

call ice_rad_register_restarts(fGD%mpp_domain, fHI, Ice%fCS%IG, param_file, &
Expand Down
33 changes: 25 additions & 8 deletions src/ice_type.F90
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,8 @@ module ice_type_mod
use fms_io_mod, only: save_restart, restore_state, query_initialized
use fms_io_mod, only: register_restart_field, restart_file_type
use time_manager_mod, only: time_type, time_type_to_real
use coupler_types_mod,only: coupler_2d_bc_type, coupler_3d_bc_type, coupler_type_write_chksums
use coupler_types_mod,only: coupler_1d_bc_type, coupler_2d_bc_type, coupler_3d_bc_type
use coupler_types_mod,only: coupler_type_spawn, coupler_type_write_chksums

use SIS_hor_grid, only : SIS_hor_grid_type
use ice_grid, only : ice_grid_type
Expand Down Expand Up @@ -156,13 +157,17 @@ module ice_type_mod
! ice restart files. !
!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
subroutine ice_type_slow_reg_restarts(domain, CatIce, param_file, Ice, &
Ice_restart, restart_file)
Ice_restart, restart_file, gas_fluxes)
type(domain2d), intent(in) :: domain
integer, intent(in) :: CatIce
type(param_file_type), intent(in) :: param_file
type(ice_data_type), intent(inout) :: Ice
type(restart_file_type), pointer :: Ice_restart
character(len=*), intent(in) :: restart_file
type(coupler_1d_bc_type), &
optional, intent(in) :: gas_fluxes !< If present, this type describes the
!! additional gas or other tracer fluxes between the
!! ocean, ice, and atmosphere.

! This subroutine allocates the externally visible ice_data_type's arrays and
! registers the appopriate ones for inclusion in the restart file.
Expand Down Expand Up @@ -202,6 +207,10 @@ subroutine ice_type_slow_reg_restarts(domain, CatIce, param_file, Ice, &
allocate(Ice%mass_berg(isc:iec, jsc:jec)) ; Ice%mass_berg(:,:) = 0.0
endif ; endif

if (present(gas_fluxes)) &
call coupler_type_spawn(gas_fluxes, Ice%ocean_fluxes, (/isc,isc,iec,iec/), &
(/jsc,jsc,jec,jec/), suffix = '_ice')

! These are used by the ocean model, and need to be in the slow PE restarts.
if (associated(Ice_restart)) then
idr = register_restart_field(Ice_restart, restart_file, 'flux_u', Ice%flux_u, domain=domain)
Expand Down Expand Up @@ -229,19 +238,23 @@ subroutine ice_type_slow_reg_restarts(domain, CatIce, param_file, Ice, &
end subroutine ice_type_slow_reg_restarts

!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
! ice_type_slow_reg_restarts - allocate the arrays in the ice_data_type !
! that are predominantly associated with the fast processors, and register !
! any variables in the ice data type that need to be included in the fast !
! ice restart files. !
!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
!> ice_type_fast_reg_restarts allocates the arrays in the ice_data_type that are
!! predominantly associated with the fast processors, and registers any
!! variables in the ice data type that need to be included in the fast
!! ice restart files.
subroutine ice_type_fast_reg_restarts(domain, CatIce, param_file, Ice, &
Ice_restart, restart_file)
Ice_restart, restart_file, gas_fields_ocn)
type(domain2d), intent(in) :: domain
integer, intent(in) :: CatIce
type(param_file_type), intent(in) :: param_file
type(ice_data_type), intent(inout) :: Ice
type(restart_file_type), pointer :: Ice_restart
character(len=*), intent(in) :: restart_file
type(coupler_1d_bc_type), &
optional, intent(in) :: gas_fields_ocn !< If present, this type describes the
!! ocean and surface-ice fields that will participate
!! in the calculation of additional gas or other
!! tracer fluxes.

! This subroutine allocates the externally visible ice_data_type's arrays and
! registers the appopriate ones for inclusion in the restart file.
Expand All @@ -268,6 +281,10 @@ subroutine ice_type_fast_reg_restarts(domain, CatIce, param_file, Ice, &
allocate(Ice%albedo_vis_dif(isc:iec, jsc:jec, km)) ; Ice%albedo_vis_dif(:,:,:) = 0.0
allocate(Ice%albedo_nir_dif(isc:iec, jsc:jec, km)) ; Ice%albedo_nir_dif(:,:,:) = 0.0

if (present(gas_fields_ocn)) &
call coupler_type_spawn(gas_fields_ocn, Ice%ocean_fields, (/isc,isc,iec,iec/), &
(/jsc,jsc,jec,jec/), (/1, km/), suffix = '_ice')

! Now register some of these arrays to be read from the restart files.
! These are used by the atmospheric model, and need to be in the fast PE restarts.
if (associated(Ice_restart)) then
Expand Down

0 comments on commit 9020bf1

Please sign in to comment.