Skip to content

Commit

Permalink
Pass melt potential (o2x_Fioo_q) via mct driver
Browse files Browse the repository at this point in the history
  • Loading branch information
gustavo-marques committed Jul 30, 2018
1 parent 02d9be2 commit a840dc0
Show file tree
Hide file tree
Showing 4 changed files with 45 additions and 16 deletions.
30 changes: 18 additions & 12 deletions config_src/mct_driver/MOM_ocean_model.F90
Original file line number Diff line number Diff line change
Expand Up @@ -139,7 +139,8 @@ module MOM_ocean_model
!! i.e. dzt(1) + eta_t + patm/rho0/grav (m)
frazil =>NULL(), & !< Accumulated heating (in Joules/m^2) from frazil
!! formation in the ocean.
area => NULL() !< cell area of the ocean surface, in m2.
melt_potential => NULL(), & !< Accumulated heat used to melt sea ice (in W/m^2)
area => NULL() !< cell area of the ocean surface, in m2.
type(coupler_2d_bc_type) :: fields !< A structure that may contain an
!! array of named tracer-related fields.
integer :: avg_kount !< Used for accumulating averages of this type.
Expand Down Expand Up @@ -337,8 +338,8 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, gas_fields_ocn, i

! Consider using a run-time flag to determine whether to do the diagnostic
! vertical integrals, since the related 3-d sums are not negligible in cost.
call allocate_surface_state(OS%sfc_state, OS%grid, use_temperature, &
do_integrals=.true., gas_fields_ocn=gas_fields_ocn)
call allocate_surface_state(OS%sfc_state, OS%grid, use_temperature, do_integrals=.true., &
gas_fields_ocn=gas_fields_ocn, use_meltpot=.true.)

call surface_forcing_init(Time_in, OS%grid, param_file, OS%diag, &
OS%forcing_CSp, OS%restore_salinity, OS%restore_temp)
Expand Down Expand Up @@ -706,20 +707,22 @@ subroutine initialize_ocean_public_type(input_domain, Ocean_sfc, diag, maskmap,
endif
call mpp_get_compute_domain(Ocean_sfc%Domain, isc, iec, jsc, jec)

allocate ( Ocean_sfc%t_surf (isc:iec,jsc:jec), &
Ocean_sfc%s_surf (isc:iec,jsc:jec), &
Ocean_sfc%u_surf (isc:iec,jsc:jec), &
Ocean_sfc%v_surf (isc:iec,jsc:jec), &
Ocean_sfc%sea_lev(isc:iec,jsc:jec), &
Ocean_sfc%area (isc:iec,jsc:jec), &
Ocean_sfc%frazil (isc:iec,jsc:jec))
allocate (Ocean_sfc%t_surf (isc:iec,jsc:jec), &
Ocean_sfc%s_surf (isc:iec,jsc:jec), &
Ocean_sfc%u_surf (isc:iec,jsc:jec), &
Ocean_sfc%v_surf (isc:iec,jsc:jec), &
Ocean_sfc%sea_lev(isc:iec,jsc:jec), &
Ocean_sfc%area (isc:iec,jsc:jec), &
Ocean_sfc%melt_potential(isc:iec,jsc:jec), &
Ocean_sfc%frazil (isc:iec,jsc:jec))

Ocean_sfc%t_surf = 0.0 ! time averaged sst (Kelvin) passed to atmosphere/ice model
Ocean_sfc%s_surf = 0.0 ! time averaged sss (psu) passed to atmosphere/ice models
Ocean_sfc%u_surf = 0.0 ! time averaged u-current (m/sec) passed to atmosphere/ice models
Ocean_sfc%v_surf = 0.0 ! time averaged v-current (m/sec) passed to atmosphere/ice models
Ocean_sfc%sea_lev = 0.0 ! time averaged thickness of top model grid cell (m) plus patm/rho0/grav
Ocean_sfc%frazil = 0.0 ! time accumulated frazil (J/m^2) passed to ice model
Ocean_sfc%melt_potential = 0.0 ! time accumulated melt potential (W/m^2) passed to ice model
Ocean_sfc%area = 0.0
Ocean_sfc%axes = diag%axesT1%handles !diag axes to be used by coupler tracer flux diagnostics

Expand Down Expand Up @@ -783,11 +786,13 @@ subroutine convert_state_to_ocean_type(state, Ocean_sfc, G, patm, press_to_z)

do j=jsc_bnd,jec_bnd ; do i=isc_bnd,iec_bnd
Ocean_sfc%sea_lev(i,j) = state%sea_lev(i+i0,j+j0)
Ocean_sfc%area(i,j) = G%areaT(i+i0,j+j0)
if (present(patm)) &
Ocean_sfc%sea_lev(i,j) = Ocean_sfc%sea_lev(i,j) + patm(i,j) * press_to_z
if (associated(state%frazil)) &
if (associated(state%frazil)) &
Ocean_sfc%frazil(i,j) = state%frazil(i+i0,j+j0)
Ocean_sfc%area(i,j) = G%areaT(i+i0,j+j0)
if (allocated(state%melt_potential)) &
Ocean_sfc%melt_potential(i,j) = state%melt_potential(i+i0,j+j0)
enddo ; enddo

if (Ocean_sfc%stagger == AGRID) then
Expand Down Expand Up @@ -1012,6 +1017,7 @@ subroutine ocean_public_type_chksum(id, timestep, ocn)
write(outunit,100) 'ocean%v_surf ',mpp_chksum(ocn%v_surf )
write(outunit,100) 'ocean%sea_lev ',mpp_chksum(ocn%sea_lev)
write(outunit,100) 'ocean%frazil ',mpp_chksum(ocn%frazil )
write(outunit,100) 'ocean%melt_potential ',mpp_chksum(ocn%melt_potential)

call coupler_type_write_chksums(ocn%fields, outunit, 'ocean%')
100 FORMAT(" CHECKSUM::",A20," = ",Z20)
Expand Down
18 changes: 17 additions & 1 deletion config_src/mct_driver/ocn_cap_methods.F90
Original file line number Diff line number Diff line change
Expand Up @@ -141,18 +141,26 @@ end subroutine ocn_import
!=======================================================================

!> Maps outgoing ocean data to MCT attribute vector real array
subroutine ocn_export(ind, ocn_public, grid, o2x)
subroutine ocn_export(ind, ocn_public, grid, o2x, dt_int, ncouple_per_day)
type(cpl_indices_type), intent(inout) :: ind !< Structure with coupler indices and vectors
type(ocean_public_type), intent(in) :: ocn_public !< Ocean surface state
type(ocean_grid_type), intent(in) :: grid !< Ocean model grid
real(kind=8), intent(inout) :: o2x(:,:) !< MCT outgoing bugger
real(kind=8), intent(in) :: dt_int !< Amount of time over which to advance the
!! ocean (ocean_coupling_time_step), in sec
integer, intent(in) :: ncouple_per_day !< Number of ocean coupling calls per day

! Local variables
real, dimension(grid%isd:grid%ied,grid%jsd:grid%jed) :: ssh !< Local copy of sea_lev with updated halo
integer :: i, j, n, ig, jg !< Grid indices
real :: slp_L, slp_R, slp_C, slope, u_min, u_max
real :: I_time_int !< The inverse of coupling time interval in s-1.

!-----------------------------------------------------------------------

! Use Adcroft's rule of reciprocals; it does the right thing here.
I_time_int = 0.0 ; if (dt_int > 0.0) I_time_int = 1.0 / dt_int

! Copy from ocn_public to o2x. ocn_public uses global indexing with no halos.
! The mask comes from "grid" that uses the usual MOM domain that has halos
! and does not use global indexing.
Expand All @@ -168,6 +176,14 @@ subroutine ocn_export(ind, ocn_public, grid, o2x)
o2x(ind%o2x_So_s, n) = ocn_public%s_surf(ig,jg) * grid%mask2dT(i,j)
o2x(ind%o2x_So_u, n) = ocn_public%u_surf(ig,jg) * grid%mask2dT(i,j)
o2x(ind%o2x_So_v, n) = ocn_public%v_surf(ig,jg) * grid%mask2dT(i,j)
! ocean melt and freeze potential (o2x_Fioo_q), W m-2
if (ocn_public%frazil(ig,jg) > 0.0) then
! Frazil: change from J/m^2 to W/m^2
o2x(ind%o2x_Fioo_q, n) = ocn_public%frazil(ig,jg) * grid%mask2dT(i,j) * I_time_int
else
! Melt_potential already is in W/m^2 (ncouple_per_day is unitless)
o2x(ind%o2x_Fioo_q, n) = -ocn_public%melt_potential(ig,jg) * grid%mask2dT(i,j) * ncouple_per_day
endif
! Make a copy of ssh in order to do a halo update. We use the usual MOM domain
! in order to update halos. i.e. does not use global indexing.
ssh(i,j) = ocn_public%sea_lev(ig,jg)
Expand Down
11 changes: 9 additions & 2 deletions config_src/mct_driver/ocn_comp_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -423,6 +423,10 @@ subroutine ocn_run_mct( EClock, cdata_o, x2o_o, o2x_o)
integer :: shrlogunit ! original log file unit
integer :: shrloglev ! original log level
logical, save :: firstCall = .true.
real (kind=8), parameter :: seconds_in_day = 86400.0 !< number of seconds in one day
integer :: ocn_cpl_dt !< one ocn coupling interval in seconds. (to be received from cesm)
real (kind=8) :: mom_cpl_dt !< one ocn coupling interval in seconds. (internal)
integer :: ncouple_per_day !< number of ocean coupled call in one day (non-dim)

! reset shr logging to ocn log file:
if (is_root_pe()) then
Expand All @@ -441,6 +445,10 @@ subroutine ocn_run_mct( EClock, cdata_o, x2o_o, o2x_o)
call ESMF_TimeIntervalGet(ocn_cpl_interval, yy=year, mm=month, d=day, s=seconds, sn=seconds_n, sd=seconds_d, rc=rc)
coupling_timestep = set_time(seconds, days=day, err_msg=err_msg)

call seq_timemgr_EClockGetData(EClock, dtime=ocn_cpl_dt)
ncouple_per_day = seconds_in_day / ocn_cpl_dt
mom_cpl_dt = seconds_in_day / ncouple_per_day

! The following if-block is to correct monthly mean outputs:
! With this change, MOM6 starts at the same date as the other components, and runs for the same
! duration as other components, unlike POP, which would have one missing interval due to ocean
Expand Down Expand Up @@ -502,7 +510,7 @@ subroutine ocn_run_mct( EClock, cdata_o, x2o_o, o2x_o)
call update_ocean_model(ice_ocean_boundary, glb%ocn_state, glb%ocn_public, time_start, coupling_timestep)

! Return export state to driver
call ocn_export(glb%ind, glb%ocn_public, glb%grid, o2x_o%rattr)
call ocn_export(glb%ind, glb%ocn_public, glb%grid, o2x_o%rattr, mom_cpl_dt, ncouple_per_day)

!--- write out intermediate restart file when needed.
! Check alarms for flag to write restart at end of day
Expand Down Expand Up @@ -806,6 +814,5 @@ end subroutine ocean_model_init_sfc
!! Boundary layer depth
!! CO2
!! DMS
!! o2x_Fioo_q !< Heat flux?

end module ocn_comp_mct
2 changes: 1 addition & 1 deletion config_src/mct_driver/ocn_cpl_indices.F90
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ module ocn_cpl_indices
integer :: o2x_So_dhdx !< Zonal slope in the sea surface height
integer :: o2x_So_dhdy !< Meridional lope in the sea surface height
integer :: o2x_So_bldepth !< Boundary layer depth (m)
integer :: o2x_Fioo_q !< Heat flux?
integer :: o2x_Fioo_q !< Ocean melt and freeze potential (W/m2)
integer :: o2x_Faoo_fco2_ocn !< CO2 flux
integer :: o2x_Faoo_fdms_ocn !< DMS flux

Expand Down

0 comments on commit a840dc0

Please sign in to comment.