Skip to content

Commit

Permalink
Merge branch 'dev/esmg' of github.com:ESMG/MOM6 into OBC_patches
Browse files Browse the repository at this point in the history
  • Loading branch information
MJHarrison-GFDL committed Aug 22, 2019
2 parents ceab18a + 4af643c commit 6c687e9
Show file tree
Hide file tree
Showing 25 changed files with 2,240 additions and 1,991 deletions.

Large diffs are not rendered by default.

Large diffs are not rendered by default.

25 changes: 10 additions & 15 deletions config_src/mct_driver/ocn_cap_methods.F90
Original file line number Diff line number Diff line change
@@ -1,13 +1,13 @@
module ocn_cap_methods

use ESMF, only: ESMF_clock, ESMF_time, ESMF_ClockGet, ESMF_TimeGet
use MOM_ocean_model, only: ocean_public_type, ocean_state_type
use MOM_surface_forcing, only: ice_ocean_boundary_type
use MOM_grid, only: ocean_grid_type
use MOM_domains, only: pass_var
use MOM_error_handler, only: is_root_pe
use mpp_domains_mod, only: mpp_get_compute_domain
use ocn_cpl_indices, only: cpl_indices_type
use ESMF, only: ESMF_clock, ESMF_time, ESMF_ClockGet, ESMF_TimeGet
use MOM_ocean_model_mct, only: ocean_public_type, ocean_state_type
use MOM_surface_forcing_mct, only: ice_ocean_boundary_type
use MOM_grid, only: ocean_grid_type
use MOM_domains, only: pass_var
use MOM_error_handler, only: is_root_pe
use mpp_domains_mod, only: mpp_get_compute_domain
use ocn_cpl_indices, only: cpl_indices_type

implicit none
private
Expand Down Expand Up @@ -71,9 +71,6 @@ subroutine ocn_import(x2o, ind, grid, ice_ocean_boundary, ocean_public, logunit,
! sensible heat flux (W/m2)
ice_ocean_boundary%t_flux(i,j) = x2o(ind%x2o_Foxx_sen,k)

! latent heat flux (W/m^2)
ice_ocean_boundary%latent_flux(i,j) = x2o(ind%x2o_Foxx_lat,k)

! snow&ice melt heat flux (W/m^2)
ice_ocean_boundary%seaice_melt_heat(i,j) = x2o(ind%x2o_Fioi_melth,k)

Expand All @@ -89,8 +86,8 @@ subroutine ocn_import(x2o, ind, grid, ice_ocean_boundary, ocean_public, logunit,
! surface pressure
ice_ocean_boundary%p(i,j) = x2o(ind%x2o_Sa_pslv,k) * GRID%mask2dT(i,j)

! salt flux (minus sign needed here -GMM)
ice_ocean_boundary%salt_flux(i,j) = -x2o(ind%x2o_Fioi_salt,k) * GRID%mask2dT(i,j)
! salt flux
ice_ocean_boundary%salt_flux(i,j) = x2o(ind%x2o_Fioi_salt,k) * GRID%mask2dT(i,j)

! 1) visible, direct shortwave (W/m2)
! 2) visible, diffuse shortwave (W/m2)
Expand Down Expand Up @@ -127,8 +124,6 @@ subroutine ocn_import(x2o, ind, grid, ice_ocean_boundary, ocean_public, logunit,
day,secs,j,i,ice_ocean_boundary%seaice_melt_heat(i,j)
write(logunit,F01)'import: day, secs, j, i, seaice_melt = ',&
day,secs,j,i,ice_ocean_boundary%seaice_melt(i,j)
write(logunit,F01)'import: day, secs, j, i, latent_flux = ',&
day,secs,j,i,ice_ocean_boundary%latent_flux(i,j)
write(logunit,F01)'import: day, secs, j, i, runoff = ',&
day,secs,j,i,ice_ocean_boundary%rofl_flux(i,j) + ice_ocean_boundary%rofi_flux(i,j)
write(logunit,F01)'import: day, secs, j, i, psurf = ',&
Expand Down
67 changes: 61 additions & 6 deletions config_src/mct_driver/ocn_comp_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -24,8 +24,6 @@ module ocn_comp_mct
shr_file_getLogUnit, shr_file_getLogLevel, &
shr_file_setLogUnit, shr_file_setLogLevel

use MOM_surface_forcing, only: IOB_allocate, ice_ocean_boundary_type

! MOM6 modules
use MOM, only: extract_surface_state
use MOM_variables, only: surface
Expand All @@ -46,10 +44,10 @@ module ocn_comp_mct
use mpp_domains_mod, only: mpp_get_compute_domain

! Previously inlined - now in separate modules
use MOM_ocean_model, only: ocean_public_type, ocean_state_type
use MOM_ocean_model, only: ocean_model_init , update_ocean_model, ocean_model_end
use MOM_ocean_model, only: convert_state_to_ocean_type
use MOM_surface_forcing, only: surface_forcing_CS, forcing_save_restart
use MOM_ocean_model_mct, only: ocean_public_type, ocean_state_type
use MOM_ocean_model_mct, only: ocean_model_init , update_ocean_model, ocean_model_end
use MOM_ocean_model_mct, only: convert_state_to_ocean_type
use MOM_surface_forcing_mct, only: surface_forcing_CS, forcing_save_restart, ice_ocean_boundary_type
use ocn_cap_methods, only: ocn_import, ocn_export

! FMS modules
Expand Down Expand Up @@ -813,4 +811,61 @@ end subroutine ocean_model_init_sfc
!! CO2
!! DMS

!> Allocates ice-ocean boundary type containers and sets to 0.
subroutine IOB_allocate(IOB, isc, iec, jsc, jec)
type(ice_ocean_boundary_type), intent(inout) :: IOB !< An ice-ocean boundary type with fluxes to drive
integer, intent(in) :: isc, iec, jsc, jec !< The ocean's local grid size

allocate ( IOB% rofl_flux (isc:iec,jsc:jec), &
IOB% rofi_flux (isc:iec,jsc:jec), &
IOB% u_flux (isc:iec,jsc:jec), &
IOB% v_flux (isc:iec,jsc:jec), &
IOB% t_flux (isc:iec,jsc:jec), &
IOB% seaice_melt_heat (isc:iec,jsc:jec),&
IOB% seaice_melt (isc:iec,jsc:jec), &
IOB% q_flux (isc:iec,jsc:jec), &
IOB% salt_flux (isc:iec,jsc:jec), &
IOB% lw_flux (isc:iec,jsc:jec), &
IOB% sw_flux_vis_dir (isc:iec,jsc:jec), &
IOB% sw_flux_vis_dif (isc:iec,jsc:jec), &
IOB% sw_flux_nir_dir (isc:iec,jsc:jec), &
IOB% sw_flux_nir_dif (isc:iec,jsc:jec), &
IOB% lprec (isc:iec,jsc:jec), &
IOB% fprec (isc:iec,jsc:jec), &
IOB% ustar_berg (isc:iec,jsc:jec), &
IOB% area_berg (isc:iec,jsc:jec), &
IOB% mass_berg (isc:iec,jsc:jec), &
IOB% calving (isc:iec,jsc:jec), &
IOB% runoff_hflx (isc:iec,jsc:jec), &
IOB% calving_hflx (isc:iec,jsc:jec), &
IOB% mi (isc:iec,jsc:jec), &
IOB% p (isc:iec,jsc:jec))

IOB%rofl_flux = 0.0
IOB%rofi_flux = 0.0
IOB%u_flux = 0.0
IOB%v_flux = 0.0
IOB%t_flux = 0.0
IOB%seaice_melt_heat = 0.0
IOB%seaice_melt = 0.0
IOB%q_flux = 0.0
IOB%salt_flux = 0.0
IOB%lw_flux = 0.0
IOB%sw_flux_vis_dir = 0.0
IOB%sw_flux_vis_dif = 0.0
IOB%sw_flux_nir_dir = 0.0
IOB%sw_flux_nir_dif = 0.0
IOB%lprec = 0.0
IOB%fprec = 0.0
IOB%ustar_berg = 0.0
IOB%area_berg = 0.0
IOB%mass_berg = 0.0
IOB%calving = 0.0
IOB%runoff_hflx = 0.0
IOB%calving_hflx = 0.0
IOB%mi = 0.0
IOB%p = 0.0

end subroutine IOB_allocate

end module ocn_comp_mct
Loading

0 comments on commit 6c687e9

Please sign in to comment.